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 branches/UKMO/test_moci_test_suite_namelist_read/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/UKMO/test_moci_test_suite_namelist_read/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 @ 9383

Last change on this file since 9383 was 9383, checked in by andmirek, 6 years ago

#2050 fixes and changes

File size: 21.2 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 bdy_par         ! (for lk_bdy)
26   USE restart         ! ocean restart
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   USE wrk_nemo        ! work arrays
34   USE iom_def, ONLY : lxios_read
35   USE iom_def, ONLY : lwxios
36
37   IMPLICIT NONE
38   PRIVATE
39
40   PUBLIC   dia_hsb        ! routine called by step.F90
41   PUBLIC   dia_hsb_init   ! routine called by nemogcm.F90
42   PUBLIC   dia_hsb_rst    ! routine called by step.F90
43   PRIVATE  hsb_namelist
44
45   LOGICAL, PUBLIC ::   ln_diahsb   !: check the heat and salt budgets
46
47   REAL(wp) ::   surf_tot              ! ocean surface
48   REAL(wp) ::   frc_t, frc_s, frc_v   ! global forcing trends
49   REAL(wp) ::   frc_wn_t, frc_wn_s    ! global forcing trends
50   !
51   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   surf          , ssh_ini          !
52   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE ::   ssh_hc_loc_ini, ssh_sc_loc_ini   !
53   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   hc_loc_ini, sc_loc_ini, e3t_ini  !
54
55   !! * Substitutions
56#  include "domzgr_substitute.h90"
57#  include "vectopt_loop_substitute.h90"
58   !!----------------------------------------------------------------------
59   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
60   !! $Id$
61   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
62   !!----------------------------------------------------------------------
63CONTAINS
64
65   SUBROUTINE dia_hsb( kt )
66      !!---------------------------------------------------------------------------
67      !!                  ***  ROUTINE dia_hsb  ***
68      !!     
69      !! ** Purpose: Compute the ocean global heat content, salt content and volume conservation
70      !!
71      !! ** Method : - Compute the deviation of heat content, salt content and volume
72      !!             at the current time step from their values at nit000
73      !!             - Compute the contribution of forcing and remove it from these deviations
74      !!
75      !!---------------------------------------------------------------------------
76      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
77      !
78      INTEGER    ::   ji, jj, jk                  ! dummy loop indice
79      REAL(wp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations
80      REAL(wp)   ::   zdiff_hc1   , zdiff_sc1     !  -         -     -        -
81      REAL(wp)   ::   zdiff_v1    , zdiff_v2      ! volume variation
82      REAL(wp)   ::   zerr_hc1    , zerr_sc1      ! heat and salt content misfit
83      REAL(wp)   ::   zvol_tot                    ! volume
84      REAL(wp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     -
85      REAL(wp)   ::   z_frc_trd_v                 !    -     -
86      REAL(wp)   ::   z_wn_trd_t , z_wn_trd_s     !    -     -
87      REAL(wp)   ::   z_ssh_hc , z_ssh_sc         !    -     -
88      REAL(wp), DIMENSION(:,:), POINTER ::   z2d0, z2d1
89      !!---------------------------------------------------------------------------
90      IF( nn_timing == 1 )   CALL timing_start('dia_hsb')     
91      CALL wrk_alloc( jpi,jpj,   z2d0, z2d1 )
92      !
93      tsn(:,:,:,1) = tsn(:,:,:,1) * tmask(:,:,:) ; tsb(:,:,:,1) = tsb(:,:,:,1) * tmask(:,:,:) ;
94      tsn(:,:,:,2) = tsn(:,:,:,2) * tmask(:,:,:) ; tsb(:,:,:,2) = tsb(:,:,:,2) * tmask(:,:,:) ;
95      ! ------------------------- !
96      ! 1 - Trends due to forcing !
97      ! ------------------------- !
98      z_frc_trd_v = r1_rau0 * glob_sum( - ( emp(:,:) - rnf(:,:) + fwfisf(:,:) ) * surf(:,:) ) ! volume fluxes
99      z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * surf(:,:) )                               ! heat fluxes
100      z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * surf(:,:) )                               ! salt fluxes
101      ! Add runoff    heat & salt input
102      IF( ln_rnf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( rnf_tsc(:,:,jp_tem) * surf(:,:) )
103      IF( ln_rnf_sal)   z_frc_trd_s = z_frc_trd_s + glob_sum( rnf_tsc(:,:,jp_sal) * surf(:,:) )
104      ! Add ice shelf heat & salt input
105      IF( nn_isf .GE. 1 )  THEN
106          z_frc_trd_t = z_frc_trd_t + glob_sum( risf_tsc(:,:,jp_tem) * surf(:,:) )
107          z_frc_trd_s = z_frc_trd_s + glob_sum( risf_tsc(:,:,jp_sal) * surf(:,:) )
108      ENDIF
109
110      ! Add penetrative solar radiation
111      IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( qsr     (:,:) * surf(:,:) )
112      ! Add geothermal heat flux
113      IF( ln_trabbc )   z_frc_trd_t = z_frc_trd_t +               glob_sum( qgh_trd0(:,:) * surf(:,:) )
114      !
115      IF( .NOT. lk_vvl ) THEN
116         IF ( ln_isfcav ) THEN
117            DO ji=1,jpi
118               DO jj=1,jpj
119                  z2d0(ji,jj) = surf(ji,jj) * wn(ji,jj,mikt(ji,jj)) * tsb(ji,jj,mikt(ji,jj),jp_tem)
120                  z2d1(ji,jj) = surf(ji,jj) * wn(ji,jj,mikt(ji,jj)) * tsb(ji,jj,mikt(ji,jj),jp_sal)
121               ENDDO
122            ENDDO
123         ELSE
124            z2d0(:,:) = surf(:,:) * wn(:,:,1) * tsb(:,:,1,jp_tem)
125            z2d1(:,:) = surf(:,:) * wn(:,:,1) * tsb(:,:,1,jp_sal)
126         END IF
127         z_wn_trd_t = - glob_sum( z2d0 ) 
128         z_wn_trd_s = - glob_sum( z2d1 )
129      ENDIF
130
131      frc_v = frc_v + z_frc_trd_v * rdt
132      frc_t = frc_t + z_frc_trd_t * rdt
133      frc_s = frc_s + z_frc_trd_s * rdt
134      !                                          ! Advection flux through fixed surface (z=0)
135      IF( .NOT. lk_vvl ) THEN
136         frc_wn_t = frc_wn_t + z_wn_trd_t * rdt
137         frc_wn_s = frc_wn_s + z_wn_trd_s * rdt
138      ENDIF
139
140      ! ------------------------ !
141      ! 2 -  Content variations !
142      ! ------------------------ !
143      zdiff_v2 = 0._wp
144      zdiff_hc = 0._wp
145      zdiff_sc = 0._wp
146
147      ! volume variation (calculated with ssh)
148      zdiff_v1 = glob_sum( surf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) )
149
150      ! heat & salt content variation (associated with ssh)
151      IF( .NOT. lk_vvl ) THEN
152         IF ( ln_isfcav ) THEN
153            DO ji = 1, jpi
154               DO jj = 1, jpj
155                  z2d0(ji,jj) = surf(ji,jj) * ( tsn(ji,jj,mikt(ji,jj),jp_tem) * sshn(ji,jj) - ssh_hc_loc_ini(ji,jj) ) 
156                  z2d1(ji,jj) = surf(ji,jj) * ( tsn(ji,jj,mikt(ji,jj),jp_sal) * sshn(ji,jj) - ssh_sc_loc_ini(ji,jj) ) 
157               END DO
158            END DO
159         ELSE
160            z2d0(:,:) = surf(:,:) * ( tsn(:,:,1,jp_tem) * sshn(:,:) - ssh_hc_loc_ini(:,:) ) 
161            z2d1(:,:) = surf(:,:) * ( tsn(:,:,1,jp_sal) * sshn(:,:) - ssh_sc_loc_ini(:,:) ) 
162         END IF
163         z_ssh_hc = glob_sum( z2d0 ) 
164         z_ssh_sc = glob_sum( z2d1 ) 
165      ENDIF
166
167      DO jk = 1, jpkm1
168         ! volume variation (calculated with scale factors)
169         zdiff_v2 = zdiff_v2 + glob_sum( surf(:,:) * tmask(:,:,jk) &
170            &                           * ( fse3t_n(:,:,jk) - e3t_ini(:,:,jk) ) )
171         ! heat content variation
172         zdiff_hc = zdiff_hc + glob_sum(  surf(:,:) * tmask(:,:,jk) & 
173            &                           * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) - hc_loc_ini(:,:,jk) ) )
174         ! salt content variation
175         zdiff_sc = zdiff_sc + glob_sum(  surf(:,:) * tmask(:,:,jk)   &
176            &                           * ( fse3t_n(:,:,jk) * tsn(:,:,jk,jp_sal) - sc_loc_ini(:,:,jk) ) )
177      ENDDO
178
179      ! Substract forcing from heat content, salt content and volume variations
180      zdiff_v1 = zdiff_v1 - frc_v
181      IF( lk_vvl )   zdiff_v2 = zdiff_v2 - frc_v
182      zdiff_hc = zdiff_hc - frc_t
183      zdiff_sc = zdiff_sc - frc_s
184      IF( .NOT. lk_vvl ) THEN
185         zdiff_hc1 = zdiff_hc + z_ssh_hc 
186         zdiff_sc1 = zdiff_sc + z_ssh_sc
187         zerr_hc1  = z_ssh_hc - frc_wn_t
188         zerr_sc1  = z_ssh_sc - frc_wn_s
189      ENDIF
190
191      ! ----------------------- !
192      ! 3 - Diagnostics writing !
193      ! ----------------------- !
194      zvol_tot = 0._wp                    ! total ocean volume (calculated with scale factors)
195      DO jk = 1, jpkm1
196         zvol_tot  = zvol_tot + glob_sum( surf(:,:) * tmask(:,:,jk) * fse3t_n(:,:,jk) )
197      END DO
198
199!!gm to be added ?
200!      IF( .NOT. lk_vvl ) THEN            ! fixed volume, add the ssh contribution
201!        zvol_tot = zvol_tot + glob_sum( surf(:,:) * sshn(:,:) )
202!      ENDIF
203!!gm end
204
205      IF( lk_vvl ) THEN
206        CALL iom_put( 'bgtemper' , zdiff_hc / zvol_tot )              ! Temperature variation (C)
207        CALL iom_put( 'bgsaline' , zdiff_sc / zvol_tot )              ! Salinity    variation (psu)
208        CALL iom_put( 'bgheatco' , zdiff_hc * 1.e-20 * rau0 * rcp )   ! Heat content variation (1.e20 J)
209        CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9    )              ! Salt content variation (psu*km3)
210        CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh variation (km3) 
211        CALL iom_put( 'bgvole3t' , zdiff_v2 * 1.e-9    )              ! volume e3t variation (km3) 
212        CALL iom_put( 'bgfrcvol' , frc_v    * 1.e-9    )              ! vol - surface forcing (km3)
213        CALL iom_put( 'bgfrctem' , frc_t / zvol_tot    )              ! hc  - surface forcing (C)
214        CALL iom_put( 'bgfrcsal' , frc_s / zvol_tot    )              ! sc  - surface forcing (psu)
215      ELSE
216        CALL iom_put( 'bgtemper' , zdiff_hc1 / zvol_tot)              ! Heat content variation (C)
217        CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot)              ! Salt content variation (psu)
218        CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp )  ! Heat content variation (1.e20 J)
219        CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9    )             ! Salt content variation (psu*km3)
220        CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh variation (km3) 
221        CALL iom_put( 'bgfrcvol' , frc_v    * 1.e-9    )              ! vol - surface forcing (km3)
222        CALL iom_put( 'bgfrctem' , frc_t / zvol_tot    )              ! hc  - surface forcing (C)
223        CALL iom_put( 'bgfrcsal' , frc_s / zvol_tot    )              ! sc  - surface forcing (psu)
224        CALL iom_put( 'bgmistem' , zerr_hc1 / zvol_tot )              ! hc  - error due to free surface (C)
225        CALL iom_put( 'bgmissal' , zerr_sc1 / zvol_tot )              ! sc  - error due to free surface (psu)
226      ENDIF
227      !
228      IF( lrst_oce )   CALL dia_hsb_rst( kt, 'WRITE' )
229
230      CALL wrk_dealloc( jpi,jpj,   z2d0, z2d1 )
231
232      IF( nn_timing == 1 )   CALL timing_stop('dia_hsb')
233      !
234   END SUBROUTINE dia_hsb
235
236
237   SUBROUTINE dia_hsb_rst( kt, cdrw )
238     !!---------------------------------------------------------------------
239     !!                   ***  ROUTINE limdia_rst  ***
240     !!                     
241     !! ** Purpose :   Read or write DIA file in restart file
242     !!
243     !! ** Method  :   use of IOM library
244     !!----------------------------------------------------------------------
245     INTEGER         , INTENT(in) ::   kt     ! ocean time-step
246     CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag
247     !
248     INTEGER ::   ji, jj, jk   ! dummy loop indices
249     INTEGER ::   id1          ! local integers
250     !!----------------------------------------------------------------------
251     !
252     IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise
253        IF( ln_rstart ) THEN                   !* Read the restart file
254           !id1 = iom_varid( numror, 'frc_vol'  , ldstop = .FALSE. )
255           !
256           IF(lwp) WRITE(numout,*) '~~~~~~~'
257           IF(lwp) WRITE(numout,*) ' dia_hsb_rst at it= ', kt,' date= ', ndastp
258           IF(lwp) WRITE(numout,*) '~~~~~~~'
259           CALL iom_get( numror, 'frc_v', frc_v, lrxios = lxios_read  )
260           CALL iom_get( numror, 'frc_t', frc_t, lrxios = lxios_read )
261           CALL iom_get( numror, 'frc_s', frc_s, lrxios = lxios_read )
262           IF( .NOT. lk_vvl ) THEN
263              CALL iom_get( numror, 'frc_wn_t', frc_wn_t, lrxios = lxios_read )
264              CALL iom_get( numror, 'frc_wn_s', frc_wn_s, lrxios = lxios_read )
265           ENDIF
266           CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini, lrxios = lxios_read )
267           CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini, lrxios = lxios_read )
268           CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini, lrxios = lxios_read )
269           CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini, lrxios = lxios_read )
270           IF( .NOT. lk_vvl ) THEN
271              CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini, lrxios = lxios_read )
272              CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini, lrxios = lxios_read )
273           ENDIF
274       ELSE
275          IF(lwp) WRITE(numout,*) '~~~~~~~'
276          IF(lwp) WRITE(numout,*) ' dia_hsb at initial state '
277          IF(lwp) WRITE(numout,*) '~~~~~~~'
278          ssh_ini(:,:) = sshn(:,:)                                       ! initial ssh
279          DO jk = 1, jpk
280             e3t_ini   (:,:,jk) = fse3t_n(:,:,jk)                        ! initial vertical scale factors
281             hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * fse3t_n(:,:,jk)   ! initial heat content
282             sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * fse3t_n(:,:,jk)   ! initial salt content
283          END DO
284          frc_v = 0._wp                                           ! volume       trend due to forcing
285          frc_t = 0._wp                                           ! heat content   -    -   -    -   
286          frc_s = 0._wp                                           ! salt content   -    -   -    -       
287          IF( .NOT. lk_vvl ) THEN
288             IF ( ln_isfcav ) THEN
289                DO ji=1,jpi
290                   DO jj=1,jpj
291                      ssh_hc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) * sshn(ji,jj)   ! initial heat content in ssh
292                      ssh_sc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) * sshn(ji,jj)   ! initial salt content in ssh
293                   ENDDO
294                ENDDO
295             ELSE
296                ssh_hc_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh
297                ssh_sc_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh
298             END IF
299             frc_wn_t = 0._wp                                       ! initial heat content misfit due to free surface
300             frc_wn_s = 0._wp                                       ! initial salt content misfit due to free surface
301          ENDIF
302       ENDIF
303
304     ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file
305        !                                   ! -------------------
306        IF(lwp) WRITE(numout,*) '~~~~~~~'
307        IF(lwp) WRITE(numout,*) ' dia_hsb_rst at it= ', kt,' date= ', ndastp
308        IF(lwp) WRITE(numout,*) '~~~~~~~'
309        IF( lwxios ) CALL iom_swap(      wxios_context          )
310        CALL iom_rstput( kt, nitrst, numrow, 'frc_v'   , frc_v, lxios = lwxios)
311        CALL iom_rstput( kt, nitrst, numrow, 'frc_t'   , frc_t, lxios = lwxios)
312        CALL iom_rstput( kt, nitrst, numrow, 'frc_s'   , frc_s, lxios = lwxios)
313        IF( .NOT. lk_vvl ) THEN
314           CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_t', frc_wn_t, lxios = lwxios)
315           CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s, lxios = lwxios )
316        ENDIF
317        CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini', ssh_ini, lxios = lwxios)
318        CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini', e3t_ini, lxios = lwxios)
319        CALL iom_rstput( kt, nitrst, numrow, 'hc_loc_ini', hc_loc_ini, lxios = lwxios)
320        CALL iom_rstput( kt, nitrst, numrow, 'sc_loc_ini', sc_loc_ini, lxios = lwxios)
321        IF( .NOT. lk_vvl ) THEN
322           CALL iom_rstput( kt, nitrst, numrow, 'ssh_hc_loc_ini', ssh_hc_loc_ini, lxios = lwxios )
323           CALL iom_rstput( kt, nitrst, numrow, 'ssh_sc_loc_ini', ssh_sc_loc_ini, lxios = lwxios )
324        ENDIF
325        !
326        IF( lwxios ) CALL iom_swap(      cxios_context          )
327     ENDIF
328     !
329   END SUBROUTINE dia_hsb_rst
330
331
332   SUBROUTINE dia_hsb_init
333      !!---------------------------------------------------------------------------
334      !!                  ***  ROUTINE dia_hsb  ***
335      !!     
336      !! ** Purpose: Initialization for the heat salt volume budgets
337      !!
338      !! ** Method : Compute initial heat content, salt content and volume
339      !!
340      !! ** Action : - Compute initial heat content, salt content and volume
341      !!             - Initialize forcing trends
342      !!             - Compute coefficients for conversion
343      !!---------------------------------------------------------------------------
344      INTEGER ::   jk       ! dummy loop indice
345      INTEGER ::   ierror   ! local integer
346      INTEGER ::   ios
347      !
348      NAMELIST/namhsb/ ln_diahsb
349      !!----------------------------------------------------------------------
350
351      IF(lwp) THEN
352         WRITE(numout,*)
353         WRITE(numout,*) 'dia_hsb_init : check the heat and salt budgets'
354         WRITE(numout,*) '~~~~~~~~ '
355      ENDIF
356      IF(lwm) THEN
357         REWIND( numnam_ref )              ! Namelist namhsb in reference namelist
358         READ  ( numnam_ref, namhsb, IOSTAT = ios, ERR = 901)
359901      CONTINUE
360      ENDIF
361      call mpp_bcast(ios)
362      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namhsb in reference namelist', lwp )
363      IF(lwm) THEN
364         REWIND( numnam_cfg )              ! Namelist namhsb in configuration namelist
365         READ  ( numnam_cfg, namhsb, IOSTAT = ios, ERR = 902 )
366902      CONTINUE
367      ENDIF
368      call mpp_bcast(ios)
369      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namhsb in configuration namelist', lwp )
370
371      IF(lwm) WRITE ( numond, namhsb )
372
373      CALL hsb_namelist()
374      !
375      IF(lwp) THEN                   ! Control print
376         WRITE(numout,*)
377         WRITE(numout,*) 'dia_hsb_init : check the heat and salt budgets'
378         WRITE(numout,*) '~~~~~~~~~~~~'
379         WRITE(numout,*) '   Namelist namhsb : set hsb parameters'
380         WRITE(numout,*) '      Switch for hsb diagnostic (T) or not (F)  ln_diahsb  = ', ln_diahsb
381         WRITE(numout,*)
382      ENDIF
383
384      IF( .NOT. ln_diahsb )   RETURN
385         !      IF( .NOT. lk_mpp_rep ) &
386         !        CALL ctl_stop (' Your global mpp_sum if performed in single precision - 64 bits -', &
387         !             &         ' whereas the global sum to be precise must be done in double precision ',&
388         !             &         ' please add key_mpp_rep')
389
390      ! ------------------- !
391      ! 1 - Allocate memory !
392      ! ------------------- !
393      ALLOCATE( hc_loc_ini(jpi,jpj,jpk), sc_loc_ini(jpi,jpj,jpk), &
394         &      e3t_ini(jpi,jpj,jpk), surf(jpi,jpj),  ssh_ini(jpi,jpj), STAT=ierror )
395      IF( ierror > 0 ) THEN
396         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN
397      ENDIF
398
399      IF(.NOT. lk_vvl ) ALLOCATE( ssh_hc_loc_ini(jpi,jpj), ssh_sc_loc_ini(jpi,jpj),STAT=ierror )
400      IF( ierror > 0 ) THEN
401         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN
402      ENDIF
403
404      ! ----------------------------------------------- !
405      ! 2 - Time independant variables and file opening !
406      ! ----------------------------------------------- !
407      IF(lwp) WRITE(numout,*) "dia_hsb: heat salt volume budgets activated"
408      IF(lwp) WRITE(numout,*) '~~~~~~~'
409      surf(:,:) = e1t(:,:) * e2t(:,:) * tmask_i(:,:)      ! masked surface grid cell area
410      surf_tot  = glob_sum( surf(:,:) )                                       ! total ocean surface area
411
412      IF( lk_bdy ) CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )         
413      !
414      ! ---------------------------------- !
415      ! 4 - initial conservation variables !
416      ! ---------------------------------- !
417      CALL dia_hsb_rst( nit000, 'READ' )  !* read or initialize all required files
418      !
419   END SUBROUTINE dia_hsb_init
420
421   SUBROUTINE hsb_namelist()
422     !!---------------------------------------------------------------------
423     !!                   ***  ROUTINE hsb_namelist  ***
424     !!                     
425     !! ** Purpose :   Broadcast namelist variables read by procesor lwm
426     !!
427     !! ** Method  :   use lib_mpp
428     !!----------------------------------------------------------------------
429#if defined key_mpp_mpi
430      CALL mpp_bcast(ln_diahsb)
431#endif
432   END SUBROUTINE hsb_namelist
433   !!======================================================================
434END MODULE diahsb
Note: See TracBrowser for help on using the repository browser.