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 trunk/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 @ 7698

Last change on this file since 7698 was 7698, checked in by mocavero, 7 years ago

update trunk with OpenMP parallelization

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