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/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/tests/DIA_GPU/MY_SRC – NEMO

source: NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/tests/DIA_GPU/MY_SRC/diahsb.F90 @ 14792

Last change on this file since 14792 was 14792, checked in by mcastril, 3 years ago

[2021/HPC-11_mcastril_HPDAonline_DiagGPU] Add an #endif left out in the merge

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