1 | MODULE diahsb |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE diahsb *** |
---|
4 | !! Ocean diagnostics: Heat, salt and volume budgets |
---|
5 | !!====================================================================== |
---|
6 | !! History : 3.3 ! 2010-09 (M. Leclair) Original code |
---|
7 | !! ! 2012-10 (C. Rousset) add iom_put |
---|
8 | !!---------------------------------------------------------------------- |
---|
9 | |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | !! dia_hsb : Diagnose the conservation of ocean heat and salt contents, and volume |
---|
12 | !! dia_hsb_rst : Read or write DIA file in restart file |
---|
13 | !! dia_hsb_init : Initialization of the conservation diagnostic |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | USE oce ! ocean dynamics and tracers |
---|
16 | USE dom_oce ! ocean space and time domain |
---|
17 | USE phycst ! physical constants |
---|
18 | USE sbc_oce ! surface thermohaline fluxes |
---|
19 | USE sbcrnf ! river runoff |
---|
20 | USE isf ! ice shelves |
---|
21 | USE domvvl ! vertical scale factors |
---|
22 | USE traqsr ! penetrative solar radiation |
---|
23 | USE trabbc ! bottom boundary condition |
---|
24 | USE trabbc ! bottom boundary condition |
---|
25 | USE restart ! ocean restart |
---|
26 | USE bdy_oce , ONLY : ln_bdy |
---|
27 | ! |
---|
28 | USE iom ! I/O manager |
---|
29 | USE in_out_manager ! I/O manager |
---|
30 | USE lib_fortran ! glob_sum |
---|
31 | USE lib_mpp ! distributed memory computing library |
---|
32 | USE timing ! preformance summary |
---|
33 | |
---|
34 | IMPLICIT NONE |
---|
35 | PRIVATE |
---|
36 | |
---|
37 | PUBLIC dia_hsb ! routine called by step.F90 |
---|
38 | PUBLIC dia_hsb_init ! routine called by nemogcm.F90 |
---|
39 | |
---|
40 | LOGICAL, PUBLIC :: ln_diahsb !: check the heat and salt budgets |
---|
41 | |
---|
42 | REAL(wp) :: surf_tot ! ocean surface |
---|
43 | REAL(wp) :: frc_t, frc_s, frc_v ! global forcing trends |
---|
44 | REAL(wp) :: frc_wn_t, frc_wn_s ! global forcing trends |
---|
45 | ! |
---|
46 | REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: surf |
---|
47 | REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: surf_ini , ssh_ini ! |
---|
48 | REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: ssh_hc_loc_ini, ssh_sc_loc_ini ! |
---|
49 | REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: hc_loc_ini, sc_loc_ini, e3t_ini ! |
---|
50 | |
---|
51 | !! * Substitutions |
---|
52 | # include "vectopt_loop_substitute.h90" |
---|
53 | !!---------------------------------------------------------------------- |
---|
54 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
55 | !! $Id$ |
---|
56 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
57 | !!---------------------------------------------------------------------- |
---|
58 | CONTAINS |
---|
59 | |
---|
60 | SUBROUTINE dia_hsb( kt ) |
---|
61 | !!--------------------------------------------------------------------------- |
---|
62 | !! *** ROUTINE dia_hsb *** |
---|
63 | !! |
---|
64 | !! ** Purpose: Compute the ocean global heat content, salt content and volume conservation |
---|
65 | !! |
---|
66 | !! ** Method : - Compute the deviation of heat content, salt content and volume |
---|
67 | !! at the current time step from their values at nit000 |
---|
68 | !! - Compute the contribution of forcing and remove it from these deviations |
---|
69 | !! |
---|
70 | !!--------------------------------------------------------------------------- |
---|
71 | INTEGER, INTENT(in) :: kt ! ocean time-step index |
---|
72 | ! |
---|
73 | INTEGER :: ji, jj, jk ! dummy loop indice |
---|
74 | REAL(wp) :: zdiff_hc , zdiff_sc ! heat and salt content variations |
---|
75 | REAL(wp) :: zdiff_hc1 , zdiff_sc1 ! - - - - |
---|
76 | REAL(wp) :: zdiff_v1 , zdiff_v2 ! volume variation |
---|
77 | REAL(wp) :: zerr_hc1 , zerr_sc1 ! heat and salt content misfit |
---|
78 | REAL(wp) :: zvol_tot ! volume |
---|
79 | REAL(wp) :: z_frc_trd_t , z_frc_trd_s ! - - |
---|
80 | REAL(wp) :: z_frc_trd_v ! - - |
---|
81 | REAL(wp) :: z_wn_trd_t , z_wn_trd_s ! - - |
---|
82 | REAL(wp) :: z_ssh_hc , z_ssh_sc ! - - |
---|
83 | REAL(wp), DIMENSION(jpi,jpj) :: z2d0, z2d1 ! 2D workspace |
---|
84 | REAL(wp), DIMENSION(jpi,jpj,jpkm1) :: zwrk ! 3D workspace |
---|
85 | !!--------------------------------------------------------------------------- |
---|
86 | IF( ln_timing ) CALL timing_start('dia_hsb') |
---|
87 | ! |
---|
88 | tsn(:,:,:,1) = tsn(:,:,:,1) * tmask(:,:,:) ; tsb(:,:,:,1) = tsb(:,:,:,1) * tmask(:,:,:) ; |
---|
89 | tsn(:,:,:,2) = tsn(:,:,:,2) * tmask(:,:,:) ; tsb(:,:,:,2) = tsb(:,:,:,2) * tmask(:,:,:) ; |
---|
90 | ! ------------------------- ! |
---|
91 | ! 1 - Trends due to forcing ! |
---|
92 | ! ------------------------- ! |
---|
93 | z_frc_trd_v = r1_rau0 * glob_sum( 'diahsb', - ( emp(:,:) - rnf(:,:) + fwfisf_cav(:,:) + fwfisf_par(:,:) ) * surf(:,:) ) ! volume fluxes |
---|
94 | z_frc_trd_t = glob_sum( 'diahsb', sbc_tsc(:,:,jp_tem) * surf(:,:) ) ! heat fluxes |
---|
95 | z_frc_trd_s = glob_sum( 'diahsb', sbc_tsc(:,:,jp_sal) * surf(:,:) ) ! salt fluxes |
---|
96 | ! ! Add runoff heat & salt input |
---|
97 | IF( ln_rnf ) z_frc_trd_t = z_frc_trd_t + glob_sum( 'diahsb', rnf_tsc(:,:,jp_tem) * surf(:,:) ) |
---|
98 | IF( ln_rnf_sal) z_frc_trd_s = z_frc_trd_s + glob_sum( 'diahsb', rnf_tsc(:,:,jp_sal) * surf(:,:) ) |
---|
99 | ! ! Add ice shelf heat & salt input |
---|
100 | IF( ln_isf ) z_frc_trd_t = z_frc_trd_t & |
---|
101 | & + glob_sum( 'diahsb', ( risf_cav_tsc(:,:,jp_tem) + risf_par_tsc(:,:,jp_tem) ) * surf(:,:) ) |
---|
102 | ! ! Add penetrative solar radiation |
---|
103 | IF( ln_traqsr ) z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( 'diahsb', qsr (:,:) * surf(:,:) ) |
---|
104 | ! ! Add geothermal heat flux |
---|
105 | IF( ln_trabbc ) z_frc_trd_t = z_frc_trd_t + glob_sum( 'diahsb', qgh_trd0(:,:) * surf(:,:) ) |
---|
106 | ! |
---|
107 | IF( ln_linssh ) THEN |
---|
108 | IF( ln_isfcav ) THEN |
---|
109 | DO ji=1,jpi |
---|
110 | DO jj=1,jpj |
---|
111 | z2d0(ji,jj) = surf(ji,jj) * wn(ji,jj,mikt(ji,jj)) * tsb(ji,jj,mikt(ji,jj),jp_tem) |
---|
112 | z2d1(ji,jj) = surf(ji,jj) * wn(ji,jj,mikt(ji,jj)) * tsb(ji,jj,mikt(ji,jj),jp_sal) |
---|
113 | END DO |
---|
114 | END DO |
---|
115 | ELSE |
---|
116 | z2d0(:,:) = surf(:,:) * wn(:,:,1) * tsb(:,:,1,jp_tem) |
---|
117 | z2d1(:,:) = surf(:,:) * wn(:,:,1) * tsb(:,:,1,jp_sal) |
---|
118 | END IF |
---|
119 | z_wn_trd_t = - glob_sum( 'diahsb', z2d0 ) |
---|
120 | z_wn_trd_s = - glob_sum( 'diahsb', z2d1 ) |
---|
121 | ENDIF |
---|
122 | |
---|
123 | frc_v = frc_v + z_frc_trd_v * rdt |
---|
124 | frc_t = frc_t + z_frc_trd_t * rdt |
---|
125 | frc_s = frc_s + z_frc_trd_s * rdt |
---|
126 | ! ! Advection flux through fixed surface (z=0) |
---|
127 | IF( ln_linssh ) THEN |
---|
128 | frc_wn_t = frc_wn_t + z_wn_trd_t * rdt |
---|
129 | frc_wn_s = frc_wn_s + z_wn_trd_s * rdt |
---|
130 | ENDIF |
---|
131 | |
---|
132 | ! ------------------------ ! |
---|
133 | ! 2 - Content variations ! |
---|
134 | ! ------------------------ ! |
---|
135 | ! glob_sum_full is needed because you keep the full interior domain to compute the sum (iscpl) |
---|
136 | |
---|
137 | ! ! volume variation (calculated with ssh) |
---|
138 | zdiff_v1 = glob_sum_full( 'diahsb', surf(:,:)*sshn(:,:) - surf_ini(:,:)*ssh_ini(:,:) ) |
---|
139 | |
---|
140 | ! ! heat & salt content variation (associated with ssh) |
---|
141 | IF( ln_linssh ) THEN ! linear free surface case |
---|
142 | IF( ln_isfcav ) THEN ! ISF case |
---|
143 | DO ji = 1, jpi |
---|
144 | DO jj = 1, jpj |
---|
145 | z2d0(ji,jj) = surf(ji,jj) * ( tsn(ji,jj,mikt(ji,jj),jp_tem) * sshn(ji,jj) - ssh_hc_loc_ini(ji,jj) ) |
---|
146 | z2d1(ji,jj) = surf(ji,jj) * ( tsn(ji,jj,mikt(ji,jj),jp_sal) * sshn(ji,jj) - ssh_sc_loc_ini(ji,jj) ) |
---|
147 | END DO |
---|
148 | END DO |
---|
149 | ELSE ! no under ice-shelf seas |
---|
150 | z2d0(:,:) = surf(:,:) * ( tsn(:,:,1,jp_tem) * sshn(:,:) - ssh_hc_loc_ini(:,:) ) |
---|
151 | z2d1(:,:) = surf(:,:) * ( tsn(:,:,1,jp_sal) * sshn(:,:) - ssh_sc_loc_ini(:,:) ) |
---|
152 | END IF |
---|
153 | z_ssh_hc = glob_sum_full( 'diahsb', z2d0 ) |
---|
154 | z_ssh_sc = glob_sum_full( 'diahsb', z2d1 ) |
---|
155 | ENDIF |
---|
156 | ! |
---|
157 | DO jk = 1, jpkm1 ! volume variation (calculated with scale factors) |
---|
158 | zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk) - surf_ini(:,:)*e3t_ini(:,:,jk) ) * tmask(:,:,jk) |
---|
159 | END DO |
---|
160 | zdiff_v2 = glob_sum_full( 'diahsb', zwrk(:,:,:) ) |
---|
161 | DO jk = 1, jpkm1 ! heat content variation |
---|
162 | zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk)*tsn(:,:,jk,jp_tem) - surf_ini(:,:)*hc_loc_ini(:,:,jk) ) * tmask(:,:,jk) |
---|
163 | END DO |
---|
164 | zdiff_hc = glob_sum_full( 'diahsb', zwrk(:,:,:) ) |
---|
165 | DO jk = 1, jpkm1 ! salt content variation |
---|
166 | zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk)*tsn(:,:,jk,jp_sal) - surf_ini(:,:)*sc_loc_ini(:,:,jk) ) * tmask(:,:,jk) |
---|
167 | END DO |
---|
168 | zdiff_sc = glob_sum_full( 'diahsb', zwrk(:,:,:) ) |
---|
169 | |
---|
170 | ! ------------------------ ! |
---|
171 | ! 3 - Drifts ! |
---|
172 | ! ------------------------ ! |
---|
173 | zdiff_v1 = zdiff_v1 - frc_v |
---|
174 | IF( .NOT.ln_linssh ) zdiff_v2 = zdiff_v2 - frc_v |
---|
175 | zdiff_hc = zdiff_hc - frc_t |
---|
176 | zdiff_sc = zdiff_sc - frc_s |
---|
177 | IF( ln_linssh ) THEN |
---|
178 | zdiff_hc1 = zdiff_hc + z_ssh_hc |
---|
179 | zdiff_sc1 = zdiff_sc + z_ssh_sc |
---|
180 | zerr_hc1 = z_ssh_hc - frc_wn_t |
---|
181 | zerr_sc1 = z_ssh_sc - frc_wn_s |
---|
182 | ENDIF |
---|
183 | |
---|
184 | ! ----------------------- ! |
---|
185 | ! 4 - Diagnostics writing ! |
---|
186 | ! ----------------------- ! |
---|
187 | DO jk = 1, jpkm1 ! total ocean volume (calculated with scale factors) |
---|
188 | zwrk(:,:,jk) = surf(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) |
---|
189 | END DO |
---|
190 | zvol_tot = glob_sum_full( 'diahsb', zwrk(:,:,:) ) |
---|
191 | |
---|
192 | !!gm to be added ? |
---|
193 | ! IF( ln_linssh ) THEN ! fixed volume, add the ssh contribution |
---|
194 | ! zvol_tot = zvol_tot + glob_sum( 'diahsb', surf(:,:) * sshn(:,:) ) |
---|
195 | ! ENDIF |
---|
196 | !!gm end |
---|
197 | |
---|
198 | CALL iom_put( 'bgfrcvol' , frc_v * 1.e-9 ) ! vol - surface forcing (km3) |
---|
199 | CALL iom_put( 'bgfrctem' , frc_t * rau0 * rcp * 1.e-20 ) ! hc - surface forcing (1.e20 J) |
---|
200 | CALL iom_put( 'bgfrchfx' , frc_t * rau0 * rcp / & ! hc - surface forcing (W/m2) |
---|
201 | & ( surf_tot * kt * rdt ) ) |
---|
202 | CALL iom_put( 'bgfrcsal' , frc_s * 1.e-9 ) ! sc - surface forcing (psu*km3) |
---|
203 | |
---|
204 | IF( .NOT. ln_linssh ) THEN |
---|
205 | CALL iom_put( 'bgtemper' , zdiff_hc / zvol_tot ) ! Temperature drift (C) |
---|
206 | CALL iom_put( 'bgsaline' , zdiff_sc / zvol_tot ) ! Salinity drift (PSU) |
---|
207 | CALL iom_put( 'bgheatco' , zdiff_hc * 1.e-20 * rau0 * rcp ) ! Heat content drift (1.e20 J) |
---|
208 | CALL iom_put( 'bgheatfx' , zdiff_hc * rau0 * rcp / & ! Heat flux drift (W/m2) |
---|
209 | & ( surf_tot * kt * rdt ) ) |
---|
210 | CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9 ) ! Salt content drift (psu*km3) |
---|
211 | CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9 ) ! volume ssh drift (km3) |
---|
212 | CALL iom_put( 'bgvole3t' , zdiff_v2 * 1.e-9 ) ! volume e3t drift (km3) |
---|
213 | ! |
---|
214 | IF( kt == nitend .AND. lwp ) THEN |
---|
215 | WRITE(numout,*) |
---|
216 | WRITE(numout,*) 'dia_hsb : last time step hsb diagnostics: at it= ', kt,' date= ', ndastp |
---|
217 | WRITE(numout,*) '~~~~~~~' |
---|
218 | WRITE(numout,*) ' Temperature drift = ', zdiff_hc / zvol_tot, ' C' |
---|
219 | WRITE(numout,*) ' Salinity drift = ', zdiff_sc / zvol_tot, ' PSU' |
---|
220 | WRITE(numout,*) ' volume ssh drift = ', zdiff_v1 * 1.e-9 , ' km^3' |
---|
221 | WRITE(numout,*) ' volume e3t drift = ', zdiff_v2 * 1.e-9 , ' km^3' |
---|
222 | ENDIF |
---|
223 | ! |
---|
224 | ELSE |
---|
225 | CALL iom_put( 'bgtemper' , zdiff_hc1 / zvol_tot) ! Heat content drift (C) |
---|
226 | CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot) ! Salt content drift (PSU) |
---|
227 | CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp ) ! Heat content drift (1.e20 J) |
---|
228 | CALL iom_put( 'bgheatfx' , zdiff_hc1 * rau0 * rcp / & ! Heat flux drift (W/m2) |
---|
229 | & ( surf_tot * kt * rdt ) ) |
---|
230 | CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9 ) ! Salt content drift (psu*km3) |
---|
231 | CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9 ) ! volume ssh drift (km3) |
---|
232 | CALL iom_put( 'bgmistem' , zerr_hc1 / zvol_tot ) ! hc - error due to free surface (C) |
---|
233 | CALL iom_put( 'bgmissal' , zerr_sc1 / zvol_tot ) ! sc - error due to free surface (psu) |
---|
234 | ENDIF |
---|
235 | ! |
---|
236 | IF( lrst_oce ) CALL dia_hsb_rst( kt, 'WRITE' ) |
---|
237 | ! |
---|
238 | IF( ln_timing ) CALL timing_stop('dia_hsb') |
---|
239 | ! |
---|
240 | END SUBROUTINE dia_hsb |
---|
241 | |
---|
242 | |
---|
243 | SUBROUTINE dia_hsb_rst( kt, cdrw ) |
---|
244 | !!--------------------------------------------------------------------- |
---|
245 | !! *** ROUTINE dia_hsb_rst *** |
---|
246 | !! |
---|
247 | !! ** Purpose : Read or write DIA file in restart file |
---|
248 | !! |
---|
249 | !! ** Method : use of IOM library |
---|
250 | !!---------------------------------------------------------------------- |
---|
251 | INTEGER , INTENT(in) :: kt ! ocean time-step |
---|
252 | CHARACTER(len=*), INTENT(in) :: cdrw ! "READ"/"WRITE" flag |
---|
253 | ! |
---|
254 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
255 | !!---------------------------------------------------------------------- |
---|
256 | ! |
---|
257 | IF( TRIM(cdrw) == 'READ' ) THEN ! Read/initialise |
---|
258 | IF( ln_rstart ) THEN !* Read the restart file |
---|
259 | ! |
---|
260 | IF(lwp) WRITE(numout,*) |
---|
261 | IF(lwp) WRITE(numout,*) ' dia_hsb_rst : read hsb restart at it= ', kt,' date= ', ndastp |
---|
262 | IF(lwp) WRITE(numout,*) |
---|
263 | CALL iom_get( numror, 'frc_v', frc_v, ldxios = lrxios ) |
---|
264 | CALL iom_get( numror, 'frc_t', frc_t, ldxios = lrxios ) |
---|
265 | CALL iom_get( numror, 'frc_s', frc_s, ldxios = lrxios ) |
---|
266 | IF( ln_linssh ) THEN |
---|
267 | CALL iom_get( numror, 'frc_wn_t', frc_wn_t, ldxios = lrxios ) |
---|
268 | CALL iom_get( numror, 'frc_wn_s', frc_wn_s, ldxios = lrxios ) |
---|
269 | ENDIF |
---|
270 | CALL iom_get( numror, jpdom_autoglo, 'surf_ini' , surf_ini , ldxios = lrxios ) ! ice sheet coupling |
---|
271 | CALL iom_get( numror, jpdom_autoglo, 'ssh_ini' , ssh_ini , ldxios = lrxios ) |
---|
272 | CALL iom_get( numror, jpdom_autoglo, 'e3t_ini' , e3t_ini , ldxios = lrxios ) |
---|
273 | CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini, ldxios = lrxios ) |
---|
274 | CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini, ldxios = lrxios ) |
---|
275 | IF( ln_linssh ) THEN |
---|
276 | CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini, ldxios = lrxios ) |
---|
277 | CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini, ldxios = lrxios ) |
---|
278 | ENDIF |
---|
279 | ELSE |
---|
280 | IF(lwp) WRITE(numout,*) |
---|
281 | IF(lwp) WRITE(numout,*) ' dia_hsb_rst : initialise hsb at initial state ' |
---|
282 | IF(lwp) WRITE(numout,*) |
---|
283 | surf_ini(:,:) = e1e2t(:,:) * tmask_i(:,:) ! initial ocean surface |
---|
284 | ssh_ini(:,:) = sshn(:,:) ! initial ssh |
---|
285 | DO jk = 1, jpk |
---|
286 | ! if ice sheet/oceqn coupling, need to mask ini variables here (mask could change at the next NEMO instance). |
---|
287 | e3t_ini (:,:,jk) = e3t_n(:,:,jk) * tmask(:,:,jk) ! initial vertical scale factors |
---|
288 | hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * e3t_n(:,:,jk) * tmask(:,:,jk) ! initial heat content |
---|
289 | sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * e3t_n(:,:,jk) * tmask(:,:,jk) ! initial salt content |
---|
290 | END DO |
---|
291 | frc_v = 0._wp ! volume trend due to forcing |
---|
292 | frc_t = 0._wp ! heat content - - - - |
---|
293 | frc_s = 0._wp ! salt content - - - - |
---|
294 | IF( ln_linssh ) THEN |
---|
295 | IF( ln_isfcav ) THEN |
---|
296 | DO ji = 1, jpi |
---|
297 | DO jj = 1, jpj |
---|
298 | ssh_hc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) * sshn(ji,jj) ! initial heat content in ssh |
---|
299 | ssh_sc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) * sshn(ji,jj) ! initial salt content in ssh |
---|
300 | END DO |
---|
301 | END DO |
---|
302 | ELSE |
---|
303 | ssh_hc_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:) ! initial heat content in ssh |
---|
304 | ssh_sc_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:) ! initial salt content in ssh |
---|
305 | END IF |
---|
306 | frc_wn_t = 0._wp ! initial heat content misfit due to free surface |
---|
307 | frc_wn_s = 0._wp ! initial salt content misfit due to free surface |
---|
308 | ENDIF |
---|
309 | ENDIF |
---|
310 | ! |
---|
311 | ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN ! Create restart file |
---|
312 | ! ! ------------------- |
---|
313 | IF(lwp) WRITE(numout,*) |
---|
314 | IF(lwp) WRITE(numout,*) ' dia_hsb_rst : write restart at it= ', kt,' date= ', ndastp |
---|
315 | IF(lwp) WRITE(numout,*) |
---|
316 | ! |
---|
317 | IF( lwxios ) CALL iom_swap( cwxios_context ) |
---|
318 | CALL iom_rstput( kt, nitrst, numrow, 'frc_v', frc_v, ldxios = lwxios ) |
---|
319 | CALL iom_rstput( kt, nitrst, numrow, 'frc_t', frc_t, ldxios = lwxios ) |
---|
320 | CALL iom_rstput( kt, nitrst, numrow, 'frc_s', frc_s, ldxios = lwxios ) |
---|
321 | IF( ln_linssh ) THEN |
---|
322 | CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_t', frc_wn_t, ldxios = lwxios ) |
---|
323 | CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s, ldxios = lwxios ) |
---|
324 | ENDIF |
---|
325 | CALL iom_rstput( kt, nitrst, numrow, 'surf_ini' , surf_ini , ldxios = lwxios ) ! ice sheet coupling |
---|
326 | CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini' , ssh_ini , ldxios = lwxios ) |
---|
327 | CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini' , e3t_ini , ldxios = lwxios ) |
---|
328 | CALL iom_rstput( kt, nitrst, numrow, 'hc_loc_ini', hc_loc_ini, ldxios = lwxios ) |
---|
329 | CALL iom_rstput( kt, nitrst, numrow, 'sc_loc_ini', sc_loc_ini, ldxios = lwxios ) |
---|
330 | IF( ln_linssh ) THEN |
---|
331 | CALL iom_rstput( kt, nitrst, numrow, 'ssh_hc_loc_ini', ssh_hc_loc_ini, ldxios = lwxios ) |
---|
332 | CALL iom_rstput( kt, nitrst, numrow, 'ssh_sc_loc_ini', ssh_sc_loc_ini, ldxios = lwxios ) |
---|
333 | ENDIF |
---|
334 | IF( lwxios ) CALL iom_swap( cxios_context ) |
---|
335 | ! |
---|
336 | ENDIF |
---|
337 | ! |
---|
338 | END SUBROUTINE dia_hsb_rst |
---|
339 | |
---|
340 | |
---|
341 | SUBROUTINE dia_hsb_init |
---|
342 | !!--------------------------------------------------------------------------- |
---|
343 | !! *** ROUTINE dia_hsb *** |
---|
344 | !! |
---|
345 | !! ** Purpose: Initialization for the heat salt volume budgets |
---|
346 | !! |
---|
347 | !! ** Method : Compute initial heat content, salt content and volume |
---|
348 | !! |
---|
349 | !! ** Action : - Compute initial heat content, salt content and volume |
---|
350 | !! - Initialize forcing trends |
---|
351 | !! - Compute coefficients for conversion |
---|
352 | !!--------------------------------------------------------------------------- |
---|
353 | INTEGER :: ierror, ios ! local integer |
---|
354 | !! |
---|
355 | NAMELIST/namhsb/ ln_diahsb |
---|
356 | !!---------------------------------------------------------------------- |
---|
357 | ! |
---|
358 | IF(lwp) THEN |
---|
359 | WRITE(numout,*) |
---|
360 | WRITE(numout,*) 'dia_hsb_init : heat and salt budgets diagnostics' |
---|
361 | WRITE(numout,*) '~~~~~~~~~~~~ ' |
---|
362 | ENDIF |
---|
363 | REWIND( numnam_ref ) ! Namelist namhsb in reference namelist |
---|
364 | READ ( numnam_ref, namhsb, IOSTAT = ios, ERR = 901) |
---|
365 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namhsb in reference namelist', lwp ) |
---|
366 | REWIND( numnam_cfg ) ! Namelist namhsb in configuration namelist |
---|
367 | READ ( numnam_cfg, namhsb, IOSTAT = ios, ERR = 902 ) |
---|
368 | 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namhsb in configuration namelist', lwp ) |
---|
369 | IF(lwm) WRITE( numond, namhsb ) |
---|
370 | |
---|
371 | IF(lwp) THEN |
---|
372 | WRITE(numout,*) ' Namelist namhsb :' |
---|
373 | WRITE(numout,*) ' check the heat and salt budgets (T) or not (F) ln_diahsb = ', ln_diahsb |
---|
374 | ENDIF |
---|
375 | ! |
---|
376 | IF( .NOT. ln_diahsb ) RETURN |
---|
377 | |
---|
378 | IF(lwxios) THEN |
---|
379 | ! define variables in restart file when writing with XIOS |
---|
380 | CALL iom_set_rstw_var_active('frc_v') |
---|
381 | CALL iom_set_rstw_var_active('frc_t') |
---|
382 | CALL iom_set_rstw_var_active('frc_s') |
---|
383 | CALL iom_set_rstw_var_active('surf_ini') |
---|
384 | CALL iom_set_rstw_var_active('ssh_ini') |
---|
385 | CALL iom_set_rstw_var_active('e3t_ini') |
---|
386 | CALL iom_set_rstw_var_active('hc_loc_ini') |
---|
387 | CALL iom_set_rstw_var_active('sc_loc_ini') |
---|
388 | IF( ln_linssh ) THEN |
---|
389 | CALL iom_set_rstw_var_active('ssh_hc_loc_ini') |
---|
390 | CALL iom_set_rstw_var_active('ssh_sc_loc_ini') |
---|
391 | CALL iom_set_rstw_var_active('frc_wn_t') |
---|
392 | CALL iom_set_rstw_var_active('frc_wn_s') |
---|
393 | ENDIF |
---|
394 | ENDIF |
---|
395 | ! ------------------- ! |
---|
396 | ! 1 - Allocate memory ! |
---|
397 | ! ------------------- ! |
---|
398 | ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), surf_ini(jpi,jpj), & |
---|
399 | & e3t_ini(jpi,jpj,jpk), surf(jpi,jpj), ssh_ini(jpi,jpj), STAT=ierror ) |
---|
400 | IF( ierror > 0 ) THEN |
---|
401 | CALL ctl_stop( 'dia_hsb_init: unable to allocate hc_loc_ini' ) ; RETURN |
---|
402 | ENDIF |
---|
403 | |
---|
404 | IF( ln_linssh ) ALLOCATE( ssh_hc_loc_ini(jpi,jpj), ssh_sc_loc_ini(jpi,jpj),STAT=ierror ) |
---|
405 | IF( ierror > 0 ) THEN |
---|
406 | CALL ctl_stop( 'dia_hsb: unable to allocate ssh_hc_loc_ini' ) ; RETURN |
---|
407 | ENDIF |
---|
408 | |
---|
409 | ! ----------------------------------------------- ! |
---|
410 | ! 2 - Time independant variables and file opening ! |
---|
411 | ! ----------------------------------------------- ! |
---|
412 | surf(:,:) = e1e2t(:,:) * tmask_i(:,:) ! masked surface grid cell area |
---|
413 | surf_tot = glob_sum( 'diahsb', surf(:,:) ) ! total ocean surface area |
---|
414 | |
---|
415 | IF( ln_bdy ) CALL ctl_warn( 'dia_hsb_init: heat/salt budget does not consider open boundary fluxes' ) |
---|
416 | ! |
---|
417 | ! ---------------------------------- ! |
---|
418 | ! 4 - initial conservation variables ! |
---|
419 | ! ---------------------------------- ! |
---|
420 | CALL dia_hsb_rst( nit000, 'READ' ) !* read or initialize all required files |
---|
421 | ! |
---|
422 | END SUBROUTINE dia_hsb_init |
---|
423 | |
---|
424 | !!====================================================================== |
---|
425 | END MODULE diahsb |
---|