1 | MODULE diatmb |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE diaharm *** |
---|
4 | !! Harmonic analysis of tidal constituents |
---|
5 | !!====================================================================== |
---|
6 | !! History : 3.6 ! 2014 (E O'Dea) Original code |
---|
7 | !!---------------------------------------------------------------------- |
---|
8 | USE oce ! ocean dynamics and tracers variables |
---|
9 | USE dom_oce ! ocean space and time domain |
---|
10 | USE in_out_manager ! I/O units |
---|
11 | USE iom ! I/0 library |
---|
12 | USE wrk_nemo ! working arrays |
---|
13 | #if defined key_fabm |
---|
14 | USE trc, ONLY: trn |
---|
15 | USE par_fabm |
---|
16 | USE fabm, ONLY: fabm_get_interior_diagnostic_data |
---|
17 | #endif |
---|
18 | |
---|
19 | |
---|
20 | IMPLICIT NONE |
---|
21 | PRIVATE |
---|
22 | |
---|
23 | LOGICAL , PUBLIC :: ln_diatmb !: Top Middle and Bottom output |
---|
24 | PUBLIC dia_tmb_init ! routine called by nemogcm.F90 |
---|
25 | PUBLIC dia_tmb ! routine called by diawri.F90 |
---|
26 | PUBLIC dia_calctmb ! routine called by dia25h.F90 |
---|
27 | |
---|
28 | !!---------------------------------------------------------------------- |
---|
29 | !! NEMO/OPA 3.6 , NEMO Consortium (2014) |
---|
30 | !! $Id$ |
---|
31 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
32 | !!---------------------------------------------------------------------- |
---|
33 | CONTAINS |
---|
34 | |
---|
35 | SUBROUTINE dia_tmb_init |
---|
36 | !!--------------------------------------------------------------------------- |
---|
37 | !! *** ROUTINE dia_tmb_init *** |
---|
38 | !! |
---|
39 | !! ** Purpose: Initialization of tmb namelist |
---|
40 | !! |
---|
41 | !! ** Method : Read namelist |
---|
42 | !! History |
---|
43 | !! 3.6 ! 08-14 (E. O'Dea) Routine to initialize dia_tmb |
---|
44 | !!--------------------------------------------------------------------------- |
---|
45 | !! |
---|
46 | INTEGER :: ios ! Local integer output status for namelist read |
---|
47 | ! |
---|
48 | NAMELIST/nam_diatmb/ ln_diatmb |
---|
49 | !!---------------------------------------------------------------------- |
---|
50 | ! |
---|
51 | REWIND ( numnam_ref ) ! Read Namelist nam_diatmb in reference namelist : TMB diagnostics |
---|
52 | READ ( numnam_ref, nam_diatmb, IOSTAT=ios, ERR= 901 ) |
---|
53 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diatmb in reference namelist', lwp ) |
---|
54 | |
---|
55 | REWIND( numnam_cfg ) ! Namelist nam_diatmb in configuration namelist TMB diagnostics |
---|
56 | READ ( numnam_cfg, nam_diatmb, IOSTAT = ios, ERR = 902 ) |
---|
57 | 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_diatmb in configuration namelist', lwp ) |
---|
58 | IF(lwm) WRITE ( numond, nam_diatmb ) |
---|
59 | |
---|
60 | IF(lwp) THEN ! Control print |
---|
61 | WRITE(numout,*) |
---|
62 | WRITE(numout,*) 'dia_tmb_init : Output Top, Middle, Bottom Diagnostics' |
---|
63 | WRITE(numout,*) '~~~~~~~~~~~~' |
---|
64 | WRITE(numout,*) 'Namelist nam_diatmb : set tmb outputs ' |
---|
65 | WRITE(numout,*) 'Switch for TMB diagnostics (T) or not (F) ln_diatmb = ', ln_diatmb |
---|
66 | ENDIF |
---|
67 | |
---|
68 | END SUBROUTINE dia_tmb_init |
---|
69 | |
---|
70 | SUBROUTINE dia_calctmb( pinfield,pouttmb ) |
---|
71 | !!--------------------------------------------------------------------- |
---|
72 | !! *** ROUTINE dia_tmb *** |
---|
73 | !! |
---|
74 | !! ** Purpose : Find the Top, Mid and Bottom fields of water Column |
---|
75 | !! |
---|
76 | !! ** Method : |
---|
77 | !! use mbathy to find surface, mid and bottom of model levels |
---|
78 | !! |
---|
79 | !! History : |
---|
80 | !! 3.6 ! 08-14 (E. O'Dea) Routine based on dia_wri_foam |
---|
81 | !!---------------------------------------------------------------------- |
---|
82 | !! * Modules used |
---|
83 | |
---|
84 | ! Routine to map 3d field to top, middle, bottom |
---|
85 | IMPLICIT NONE |
---|
86 | |
---|
87 | |
---|
88 | ! Routine arguments |
---|
89 | REAL(wp), DIMENSION(jpi, jpj, jpk), INTENT(IN ) :: pinfield ! Input 3d field and mask |
---|
90 | REAL(wp), DIMENSION(jpi, jpj, 3 ), INTENT( OUT) :: pouttmb ! Output top, middle, bottom |
---|
91 | |
---|
92 | |
---|
93 | |
---|
94 | ! Local variables |
---|
95 | INTEGER :: ji,jj,jk ! Dummy loop indices |
---|
96 | |
---|
97 | ! Local Real |
---|
98 | REAL(wp) :: zmdi ! set masked values |
---|
99 | |
---|
100 | zmdi=1.e+20 !missing data indicator for masking |
---|
101 | |
---|
102 | ! Calculate top |
---|
103 | pouttmb(:,:,1) = pinfield(:,:,1)*tmask(:,:,1) + zmdi*(1.0-tmask(:,:,1)) |
---|
104 | |
---|
105 | ! Calculate middle |
---|
106 | DO jj = 1,jpj |
---|
107 | DO ji = 1,jpi |
---|
108 | jk = max(1,mbathy(ji,jj)/2) |
---|
109 | pouttmb(ji,jj,2) = pinfield(ji,jj,jk)*tmask(ji,jj,jk) + zmdi*(1.0-tmask(ji,jj,jk)) |
---|
110 | END DO |
---|
111 | END DO |
---|
112 | |
---|
113 | ! Calculate bottom |
---|
114 | DO jj = 1,jpj |
---|
115 | DO ji = 1,jpi |
---|
116 | jk = max(1,mbathy(ji,jj) ) |
---|
117 | pouttmb(ji,jj,3) = pinfield(ji,jj,jk)*tmask(ji,jj,jk) + zmdi*(1.0-tmask(ji,jj,jk)) |
---|
118 | END DO |
---|
119 | END DO |
---|
120 | |
---|
121 | END SUBROUTINE dia_calctmb |
---|
122 | |
---|
123 | |
---|
124 | |
---|
125 | SUBROUTINE dia_tmb |
---|
126 | !!---------------------------------------------------------------------- |
---|
127 | !! *** ROUTINE dia_tmb *** |
---|
128 | !! ** Purpose : Write diagnostics for Top, Mid and Bottom of water Column |
---|
129 | !! |
---|
130 | !! ** Method : |
---|
131 | !! use mbathy to find surface, mid and bottom of model levels |
---|
132 | !! calls calctmb to retrieve TMB values before sending to iom_put |
---|
133 | !! |
---|
134 | !! History : |
---|
135 | !! 3.6 ! 08-14 (E. O'Dea) |
---|
136 | !! |
---|
137 | !!-------------------------------------------------------------------- |
---|
138 | REAL(wp), POINTER, DIMENSION(:,:,:) :: zwtmb ! temporary workspace |
---|
139 | REAL(wp) :: zmdi ! set masked values |
---|
140 | INTEGER :: jn ! loop counter |
---|
141 | |
---|
142 | zmdi=1.e+20 !missing data indicator for maskin |
---|
143 | |
---|
144 | IF (ln_diatmb) THEN |
---|
145 | CALL wrk_alloc( jpi , jpj, 3 , zwtmb ) |
---|
146 | CALL dia_calctmb( tsn(:,:,:,jp_tem),zwtmb ) |
---|
147 | !ssh already output but here we output it masked |
---|
148 | CALL iom_put( "sshnmasked" , sshn(:,:)*tmask(:,:,1) + zmdi*(1.0 - tmask(:,:,1)) ) ! tmb Temperature |
---|
149 | CALL iom_put( "top_temp" , zwtmb(:,:,1) ) ! tmb Temperature |
---|
150 | CALL iom_put( "mid_temp" , zwtmb(:,:,2) ) ! tmb Temperature |
---|
151 | CALL iom_put( "bot_temp" , zwtmb(:,:,3) ) ! tmb Temperature |
---|
152 | ! CALL iom_put( "sotrefml" , hmld_tref(:,:) ) ! "T criterion Mixed Layer Depth |
---|
153 | |
---|
154 | CALL dia_calctmb( tsn(:,:,:,jp_sal),zwtmb ) |
---|
155 | CALL iom_put( "top_sal" , zwtmb(:,:,1) ) ! tmb Salinity |
---|
156 | CALL iom_put( "mid_sal" , zwtmb(:,:,2) ) ! tmb Salinity |
---|
157 | CALL iom_put( "bot_sal" , zwtmb(:,:,3) ) ! tmb Salinity |
---|
158 | |
---|
159 | CALL dia_calctmb( un(:,:,:),zwtmb ) |
---|
160 | CALL iom_put( "top_u" , zwtmb(:,:,1) ) ! tmb U Velocity |
---|
161 | CALL iom_put( "mid_u" , zwtmb(:,:,2) ) ! tmb U Velocity |
---|
162 | CALL iom_put( "bot_u" , zwtmb(:,:,3) ) ! tmb U Velocity |
---|
163 | !Called in dynspg_ts.F90 CALL iom_put( "baro_u" , un_b ) ! Barotropic U Velocity |
---|
164 | |
---|
165 | CALL dia_calctmb( vn(:,:,:),zwtmb ) |
---|
166 | CALL iom_put( "top_v" , zwtmb(:,:,1) ) ! tmb V Velocity |
---|
167 | CALL iom_put( "mid_v" , zwtmb(:,:,2) ) ! tmb V Velocity |
---|
168 | CALL iom_put( "bot_v" , zwtmb(:,:,3) ) ! tmb V Velocity |
---|
169 | !Called in dynspg_ts.F90 CALL iom_put( "baro_v" , vn_b ) ! Barotropic V Velocity |
---|
170 | |
---|
171 | #if defined key_fabm |
---|
172 | DO jn = 1, jp_fabm |
---|
173 | CALL dia_calctmb( trn(:,:,:,jp_fabm_m1+jn), zwtmb ) |
---|
174 | CALL iom_put( "top_"//TRIM(model%state_variables(jn)%name) , zwtmb(:,:,1) ) |
---|
175 | CALL iom_put( "mid_"//TRIM(model%state_variables(jn)%name) , zwtmb(:,:,2) ) |
---|
176 | CALL iom_put( "bot_"//TRIM(model%state_variables(jn)%name) , zwtmb(:,:,3) ) |
---|
177 | END DO |
---|
178 | DO jn = 1, jp_fabm_3d |
---|
179 | CALL dia_calctmb( fabm_get_interior_diagnostic_data(model, jn), zwtmb ) |
---|
180 | CALL iom_put( "top_"//TRIM(model%diagnostic_variables(jn)%name) , zwtmb(:,:,1) ) |
---|
181 | CALL iom_put( "mid_"//TRIM(model%diagnostic_variables(jn)%name) , zwtmb(:,:,2) ) |
---|
182 | CALL iom_put( "bot_"//TRIM(model%diagnostic_variables(jn)%name) , zwtmb(:,:,3) ) |
---|
183 | END DO |
---|
184 | #endif |
---|
185 | ELSE |
---|
186 | CALL ctl_warn('dia_tmb: tmb diagnostic is set to false you should not have seen this') |
---|
187 | ENDIF |
---|
188 | |
---|
189 | END SUBROUTINE dia_tmb |
---|
190 | !!====================================================================== |
---|
191 | END MODULE diatmb |
---|