New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
diahsb.F90 in NEMO/branches/UKMO/dev_r10037_GPU/src/OCE/DIA – NEMO

source: NEMO/branches/UKMO/dev_r10037_GPU/src/OCE/DIA/diahsb.F90 @ 11467

Last change on this file since 11467 was 11467, checked in by andmirek, 5 years ago

Ticket #2197 allocate arrays at the beggining of the run

File size: 21.8 KB
Line 
1MODULE 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 sbcisf         ! 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   !!----------------------------------------------------------------------
58CONTAINS
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      USE scoce, ONLY : z2d0 => scr2D1, z2d1 => scr2D2, zwrk => scr1
72      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
73      !
74      INTEGER    ::   ji, jj, jk                  ! dummy loop indice
75      REAL(wp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations
76      REAL(wp)   ::   zdiff_hc1   , zdiff_sc1     !  -         -     -        -
77      REAL(wp)   ::   zdiff_v1    , zdiff_v2      ! volume variation
78      REAL(wp)   ::   zerr_hc1    , zerr_sc1      ! heat and salt content misfit
79      REAL(wp)   ::   zvol_tot                    ! volume
80      REAL(wp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     -
81      REAL(wp)   ::   z_frc_trd_v                 !    -     -
82      REAL(wp)   ::   z_wn_trd_t , z_wn_trd_s     !    -     -
83      REAL(wp)   ::   z_ssh_hc , z_ssh_sc         !    -     -
84      !!---------------------------------------------------------------------------
85      IF( ln_timing )   CALL timing_start('dia_hsb')     
86      !
87      tsn(:,:,:,1) = tsn(:,:,:,1) * tmask(:,:,:) ; tsb(:,:,:,1) = tsb(:,:,:,1) * tmask(:,:,:) ;
88      tsn(:,:,:,2) = tsn(:,:,:,2) * tmask(:,:,:) ; tsb(:,:,:,2) = tsb(:,:,:,2) * tmask(:,:,:) ;
89      ! ------------------------- !
90      ! 1 - Trends due to forcing !
91      ! ------------------------- !
92      z_frc_trd_v = r1_rau0 * glob_sum( - ( emp(:,:) - rnf(:,:) + fwfisf(:,:) ) * surf(:,:) )   ! volume fluxes
93      z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * surf(:,:) )                       ! heat fluxes
94      z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * surf(:,:) )                       ! salt fluxes
95      !                    !  Add runoff    heat & salt input
96      IF( ln_rnf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( rnf_tsc(:,:,jp_tem) * surf(:,:) )
97      IF( ln_rnf_sal)   z_frc_trd_s = z_frc_trd_s + glob_sum( rnf_tsc(:,:,jp_sal) * surf(:,:) )
98      !                    ! Add ice shelf heat & salt input
99      IF( ln_isf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( risf_tsc(:,:,jp_tem) * surf(:,:) )
100      !                    ! Add penetrative solar radiation
101      IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( qsr     (:,:) * surf(:,:) )
102      !                    ! Add geothermal heat flux
103      IF( ln_trabbc )   z_frc_trd_t = z_frc_trd_t +               glob_sum( qgh_trd0(:,:) * surf(:,:) )
104      !
105      IF( ln_linssh ) THEN
106         IF( ln_isfcav ) THEN
107            DO ji=1,jpi
108               DO jj=1,jpj
109                  z2d0(ji,jj) = surf(ji,jj) * wn(ji,jj,mikt(ji,jj)) * tsb(ji,jj,mikt(ji,jj),jp_tem)
110                  z2d1(ji,jj) = surf(ji,jj) * wn(ji,jj,mikt(ji,jj)) * tsb(ji,jj,mikt(ji,jj),jp_sal)
111               END DO
112            END DO
113         ELSE
114            z2d0(:,:) = surf(:,:) * wn(:,:,1) * tsb(:,:,1,jp_tem)
115            z2d1(:,:) = surf(:,:) * wn(:,:,1) * tsb(:,:,1,jp_sal)
116         END IF
117         z_wn_trd_t = - glob_sum( z2d0 ) 
118         z_wn_trd_s = - glob_sum( z2d1 )
119      ENDIF
120
121      frc_v = frc_v + z_frc_trd_v * rdt
122      frc_t = frc_t + z_frc_trd_t * rdt
123      frc_s = frc_s + z_frc_trd_s * rdt
124      !                                          ! Advection flux through fixed surface (z=0)
125      IF( ln_linssh ) THEN
126         frc_wn_t = frc_wn_t + z_wn_trd_t * rdt
127         frc_wn_s = frc_wn_s + z_wn_trd_s * rdt
128      ENDIF
129
130      ! ------------------------ !
131      ! 2 -  Content variations  !
132      ! ------------------------ !
133      ! glob_sum_full is needed because you keep the full interior domain to compute the sum (iscpl)
134
135      !                    ! volume variation (calculated with ssh)
136      zdiff_v1 = glob_sum_full( surf(:,:)*sshn(:,:) - surf_ini(:,:)*ssh_ini(:,:) )
137
138      !                    ! heat & salt content variation (associated with ssh)
139      IF( ln_linssh ) THEN       ! linear free surface case
140         IF( ln_isfcav ) THEN          ! ISF case
141            DO ji = 1, jpi
142               DO jj = 1, jpj
143                  z2d0(ji,jj) = surf(ji,jj) * ( tsn(ji,jj,mikt(ji,jj),jp_tem) * sshn(ji,jj) - ssh_hc_loc_ini(ji,jj) ) 
144                  z2d1(ji,jj) = surf(ji,jj) * ( tsn(ji,jj,mikt(ji,jj),jp_sal) * sshn(ji,jj) - ssh_sc_loc_ini(ji,jj) ) 
145               END DO
146            END DO
147         ELSE                          ! no under ice-shelf seas
148            z2d0(:,:) = surf(:,:) * ( tsn(:,:,1,jp_tem) * sshn(:,:) - ssh_hc_loc_ini(:,:) ) 
149            z2d1(:,:) = surf(:,:) * ( tsn(:,:,1,jp_sal) * sshn(:,:) - ssh_sc_loc_ini(:,:) ) 
150         END IF
151         z_ssh_hc = glob_sum_full( z2d0 ) 
152         z_ssh_sc = glob_sum_full( z2d1 ) 
153      ENDIF
154      !
155      DO jk = 1, jpkm1     ! volume variation (calculated with scale factors)
156         zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk) - surf_ini(:,:)*e3t_ini(:,:,jk) ) * tmask(:,:,jk)
157      END DO
158      zdiff_v2 = glob_sum_full( zwrk(:,:,:) )
159      DO jk = 1, jpkm1           ! heat content variation
160         zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk)*tsn(:,:,jk,jp_tem) - surf_ini(:,:)*hc_loc_ini(:,:,jk) ) * tmask(:,:,jk)
161      END DO
162      zdiff_hc = glob_sum_full( zwrk(:,:,:) )
163      DO jk = 1, jpkm1           ! salt content variation
164         zwrk(:,:,jk) = ( surf(:,:)*e3t_n(:,:,jk)*tsn(:,:,jk,jp_sal) - surf_ini(:,:)*sc_loc_ini(:,:,jk) ) * tmask(:,:,jk)
165      END DO
166      zdiff_sc = glob_sum_full( zwrk(:,:,:) )
167
168      ! ------------------------ !
169      ! 3 -  Drifts              !
170      ! ------------------------ !
171      zdiff_v1 = zdiff_v1 - frc_v
172      IF( .NOT.ln_linssh )   zdiff_v2 = zdiff_v2 - frc_v
173      zdiff_hc = zdiff_hc - frc_t
174      zdiff_sc = zdiff_sc - frc_s
175      IF( ln_linssh ) THEN
176         zdiff_hc1 = zdiff_hc + z_ssh_hc 
177         zdiff_sc1 = zdiff_sc + z_ssh_sc
178         zerr_hc1  = z_ssh_hc - frc_wn_t
179         zerr_sc1  = z_ssh_sc - frc_wn_s
180      ENDIF
181
182      ! ----------------------- !
183      ! 4 - Diagnostics writing !
184      ! ----------------------- !
185      DO jk = 1, jpkm1           ! total ocean volume (calculated with scale factors)
186         zwrk(:,:,jk) = surf(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk)
187      END DO
188      zvol_tot = glob_sum_full( zwrk(:,:,:) )
189
190!!gm to be added ?
191!      IF( ln_linssh ) THEN            ! fixed volume, add the ssh contribution
192!        zvol_tot = zvol_tot + glob_sum( surf(:,:) * sshn(:,:) )
193!      ENDIF
194!!gm end
195
196      CALL iom_put(   'bgfrcvol' , frc_v    * 1.e-9    )              ! vol - surface forcing (km3)
197      CALL iom_put(   'bgfrctem' , frc_t    * rau0 * rcp * 1.e-20 )   ! hc  - surface forcing (1.e20 J)
198      CALL iom_put(   'bgfrchfx' , frc_t    * rau0 * rcp /  &         ! hc  - surface forcing (W/m2)
199         &                       ( surf_tot * kt * rdt )        )
200      CALL iom_put(   'bgfrcsal' , frc_s    * 1.e-9    )              ! sc  - surface forcing (psu*km3)
201
202      IF( .NOT. ln_linssh ) THEN
203         CALL iom_put( 'bgtemper' , zdiff_hc / zvol_tot )              ! Temperature drift     (C)
204         CALL iom_put( 'bgsaline' , zdiff_sc / zvol_tot )              ! Salinity    drift     (PSU)
205         CALL iom_put( 'bgheatco' , zdiff_hc * 1.e-20 * rau0 * rcp )   ! Heat content drift    (1.e20 J)
206         CALL iom_put( 'bgheatfx' , zdiff_hc * rau0 * rcp /  &         ! Heat flux drift       (W/m2)
207            &                       ( surf_tot * kt * rdt )        )
208         CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9    )              ! Salt content drift    (psu*km3)
209         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh drift      (km3) 
210         CALL iom_put( 'bgvole3t' , zdiff_v2 * 1.e-9    )              ! volume e3t drift      (km3) 
211         !
212         IF( kt == nitend .AND. lwp ) THEN
213            WRITE(numout,*)
214            WRITE(numout,*) 'dia_hsb : last time step hsb diagnostics: at it= ', kt,' date= ', ndastp
215            WRITE(numout,*) '~~~~~~~'
216            WRITE(numout,*) '   Temperature drift = ', zdiff_hc / zvol_tot, ' C'
217            WRITE(numout,*) '   Salinity    drift = ', zdiff_sc / zvol_tot, ' PSU'
218            WRITE(numout,*) '   volume ssh  drift = ', zdiff_v1 * 1.e-9   , ' km^3'
219            WRITE(numout,*) '   volume e3t  drift = ', zdiff_v2 * 1.e-9   , ' km^3'
220         ENDIF
221         !
222      ELSE
223         CALL iom_put( 'bgtemper' , zdiff_hc1 / zvol_tot)              ! Heat content drift    (C)
224         CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot)              ! Salt content drift    (PSU)
225         CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp )  ! Heat content drift    (1.e20 J)
226         CALL iom_put( 'bgheatfx' , zdiff_hc1 * rau0 * rcp /  &        ! Heat flux drift       (W/m2)
227            &                       ( surf_tot * kt * rdt )         )
228         CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9    )             ! Salt content drift    (psu*km3)
229         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh drift      (km3) 
230         CALL iom_put( 'bgmistem' , zerr_hc1 / zvol_tot )              ! hc  - error due to free surface (C)
231         CALL iom_put( 'bgmissal' , zerr_sc1 / zvol_tot )              ! sc  - error due to free surface (psu)
232      ENDIF
233      !
234      IF( lrst_oce )   CALL dia_hsb_rst( kt, 'WRITE' )
235      !
236      IF( ln_timing )   CALL timing_stop('dia_hsb')
237      !
238   END SUBROUTINE dia_hsb
239
240
241   SUBROUTINE dia_hsb_rst( kt, cdrw )
242      !!---------------------------------------------------------------------
243      !!                   ***  ROUTINE dia_hsb_rst  ***
244      !!                     
245      !! ** Purpose :   Read or write DIA file in restart file
246      !!
247      !! ** Method  :   use of IOM library
248      !!----------------------------------------------------------------------
249      INTEGER         , INTENT(in) ::   kt     ! ocean time-step
250      CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag
251      !
252      INTEGER ::   ji, jj, jk   ! dummy loop indices
253      !!----------------------------------------------------------------------
254      !
255      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise
256         IF( ln_rstart ) THEN                   !* Read the restart file
257            !
258            IF(lwp) WRITE(numout,*)
259            IF(lwp) WRITE(numout,*) '   dia_hsb_rst : read hsb restart at it= ', kt,' date= ', ndastp
260            IF(lwp) WRITE(numout,*)
261            CALL iom_get( numror, 'frc_v', frc_v, ldxios = lrxios )
262            CALL iom_get( numror, 'frc_t', frc_t, ldxios = lrxios )
263            CALL iom_get( numror, 'frc_s', frc_s, ldxios = lrxios )
264            IF( ln_linssh ) THEN
265               CALL iom_get( numror, 'frc_wn_t', frc_wn_t, ldxios = lrxios )
266               CALL iom_get( numror, 'frc_wn_s', frc_wn_s, ldxios = lrxios )
267            ENDIF
268            CALL iom_get( numror, jpdom_autoglo, 'surf_ini'  , surf_ini  , ldxios = lrxios ) ! ice sheet coupling
269            CALL iom_get( numror, jpdom_autoglo, 'ssh_ini'   , ssh_ini   , ldxios = lrxios )
270            CALL iom_get( numror, jpdom_autoglo, 'e3t_ini'   , e3t_ini   , ldxios = lrxios )
271            CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini, ldxios = lrxios )
272            CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini, ldxios = lrxios )
273            IF( ln_linssh ) THEN
274               CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini, ldxios = lrxios )
275               CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini, ldxios = lrxios )
276            ENDIF
277         ELSE
278            IF(lwp) WRITE(numout,*)
279            IF(lwp) WRITE(numout,*) '   dia_hsb_rst : initialise hsb at initial state '
280            IF(lwp) WRITE(numout,*)
281            surf_ini(:,:) = e1e2t(:,:) * tmask_i(:,:)         ! initial ocean surface
282            ssh_ini(:,:) = sshn(:,:)                          ! initial ssh
283            DO jk = 1, jpk
284              ! if ice sheet/oceqn coupling, need to mask ini variables here (mask could change at the next NEMO instance).
285               e3t_ini   (:,:,jk) = e3t_n(:,:,jk)                      * tmask(:,:,jk)  ! initial vertical scale factors
286               hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * e3t_n(:,:,jk) * tmask(:,:,jk)  ! initial heat content
287               sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * e3t_n(:,:,jk) * tmask(:,:,jk)  ! initial salt content
288            END DO
289            frc_v = 0._wp                                           ! volume       trend due to forcing
290            frc_t = 0._wp                                           ! heat content   -    -   -    -   
291            frc_s = 0._wp                                           ! salt content   -    -   -    -       
292            IF( ln_linssh ) THEN
293               IF( ln_isfcav ) THEN
294                  DO ji = 1, jpi
295                     DO jj = 1, jpj
296                        ssh_hc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) * sshn(ji,jj)   ! initial heat content in ssh
297                        ssh_sc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) * sshn(ji,jj)   ! initial salt content in ssh
298                     END DO
299                   END DO
300                ELSE
301                  ssh_hc_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh
302                  ssh_sc_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh
303               END IF
304               frc_wn_t = 0._wp                                       ! initial heat content misfit due to free surface
305               frc_wn_s = 0._wp                                       ! initial salt content misfit due to free surface
306            ENDIF
307         ENDIF
308         !
309      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file
310         !                                   ! -------------------
311         IF(lwp) WRITE(numout,*)
312         IF(lwp) WRITE(numout,*) '   dia_hsb_rst : write restart at it= ', kt,' date= ', ndastp
313         IF(lwp) WRITE(numout,*)
314         !
315         IF( lwxios ) CALL iom_swap(      cwxios_context          )
316         CALL iom_rstput( kt, nitrst, numrow, 'frc_v', frc_v, ldxios = lwxios )
317         CALL iom_rstput( kt, nitrst, numrow, 'frc_t', frc_t, ldxios = lwxios )
318         CALL iom_rstput( kt, nitrst, numrow, 'frc_s', frc_s, ldxios = lwxios )
319         IF( ln_linssh ) THEN
320            CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_t', frc_wn_t, ldxios = lwxios )
321            CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s, ldxios = lwxios )
322         ENDIF
323         CALL iom_rstput( kt, nitrst, numrow, 'surf_ini'  , surf_ini  , ldxios = lwxios )      ! ice sheet coupling
324         CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini'   , ssh_ini   , ldxios = lwxios )
325         CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini'   , e3t_ini   , ldxios = lwxios )
326         CALL iom_rstput( kt, nitrst, numrow, 'hc_loc_ini', hc_loc_ini, ldxios = lwxios )
327         CALL iom_rstput( kt, nitrst, numrow, 'sc_loc_ini', sc_loc_ini, ldxios = lwxios )
328         IF( ln_linssh ) THEN
329            CALL iom_rstput( kt, nitrst, numrow, 'ssh_hc_loc_ini', ssh_hc_loc_ini, ldxios = lwxios )
330            CALL iom_rstput( kt, nitrst, numrow, 'ssh_sc_loc_ini', ssh_sc_loc_ini, ldxios = lwxios )
331         ENDIF
332         IF( lwxios ) CALL iom_swap(      cxios_context          )
333         !
334      ENDIF
335      !
336   END SUBROUTINE dia_hsb_rst
337
338
339   SUBROUTINE dia_hsb_init
340      !!---------------------------------------------------------------------------
341      !!                  ***  ROUTINE dia_hsb  ***
342      !!     
343      !! ** Purpose: Initialization for the heat salt volume budgets
344      !!
345      !! ** Method : Compute initial heat content, salt content and volume
346      !!
347      !! ** Action : - Compute initial heat content, salt content and volume
348      !!             - Initialize forcing trends
349      !!             - Compute coefficients for conversion
350      !!---------------------------------------------------------------------------
351      INTEGER ::   ierror, ios   ! local integer
352      !!
353      NAMELIST/namhsb/ ln_diahsb
354      !!----------------------------------------------------------------------
355      !
356      IF(lwp) THEN
357         WRITE(numout,*)
358         WRITE(numout,*) 'dia_hsb_init : heat and salt budgets diagnostics'
359         WRITE(numout,*) '~~~~~~~~~~~~ '
360      ENDIF
361      REWIND( numnam_ref )              ! Namelist namhsb in reference namelist
362      READ  ( numnam_ref, namhsb, IOSTAT = ios, ERR = 901)
363901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namhsb in reference namelist', lwp )
364      REWIND( numnam_cfg )              ! Namelist namhsb in configuration namelist
365      READ  ( numnam_cfg, namhsb, IOSTAT = ios, ERR = 902 )
366902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namhsb in configuration namelist', lwp )
367      IF(lwm) WRITE( numond, namhsb )
368
369      IF(lwp) THEN
370         WRITE(numout,*) '   Namelist  namhsb :'
371         WRITE(numout,*) '      check the heat and salt budgets (T) or not (F)       ln_diahsb = ', ln_diahsb
372      ENDIF
373      !
374      IF( .NOT. ln_diahsb )   RETURN
375
376      IF(lwxios) THEN
377! define variables in restart file when writing with XIOS
378        CALL iom_set_rstw_var_active('frc_v')
379        CALL iom_set_rstw_var_active('frc_t')
380        CALL iom_set_rstw_var_active('frc_s')
381        CALL iom_set_rstw_var_active('surf_ini')
382        CALL iom_set_rstw_var_active('ssh_ini')
383        CALL iom_set_rstw_var_active('e3t_ini')
384        CALL iom_set_rstw_var_active('hc_loc_ini')
385        CALL iom_set_rstw_var_active('sc_loc_ini')
386        IF( ln_linssh ) THEN
387           CALL iom_set_rstw_var_active('ssh_hc_loc_ini')
388           CALL iom_set_rstw_var_active('ssh_sc_loc_ini')
389           CALL iom_set_rstw_var_active('frc_wn_t')
390           CALL iom_set_rstw_var_active('frc_wn_s')
391        ENDIF
392      ENDIF
393      ! ------------------- !
394      ! 1 - Allocate memory !
395      ! ------------------- !
396      ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), surf_ini(jpi,jpj), &
397         &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror  )
398      IF( ierror > 0 ) THEN
399         CALL ctl_stop( 'dia_hsb_init: unable to allocate hc_loc_ini' )   ;   RETURN
400      ENDIF
401
402      IF( ln_linssh )   ALLOCATE( ssh_hc_loc_ini(jpi,jpj), ssh_sc_loc_ini(jpi,jpj),STAT=ierror )
403      IF( ierror > 0 ) THEN
404         CALL ctl_stop( 'dia_hsb: unable to allocate ssh_hc_loc_ini' )   ;   RETURN
405      ENDIF
406
407      ! ----------------------------------------------- !
408      ! 2 - Time independant variables and file opening !
409      ! ----------------------------------------------- !
410      surf(:,:) = e1e2t(:,:) * tmask_i(:,:)     ! masked surface grid cell area
411      surf_tot  = glob_sum( surf(:,:) )         ! total ocean surface area
412
413      IF( ln_bdy ) CALL ctl_warn( 'dia_hsb_init: heat/salt budget does not consider open boundary fluxes' )         
414      !
415      ! ---------------------------------- !
416      ! 4 - initial conservation variables !
417      ! ---------------------------------- !
418      CALL dia_hsb_rst( nit000, 'READ' )  !* read or initialize all required files
419      !
420   END SUBROUTINE dia_hsb_init
421
422   !!======================================================================
423END MODULE diahsb
Note: See TracBrowser for help on using the repository browser.