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/trunk/src/OCE/DIA – NEMO

source: NEMO/trunk/src/OCE/DIA/diahsb.F90 @ 15234

Last change on this file since 15234 was 15062, checked in by jchanut, 3 years ago

Suppress time varying scale factors and depths declarations with key_qco and key_linssh. Remove spaces that preclude from correct replacement of some scale factor arrays during preprocessing stage (at least with Apple clang version 11.0.3, this is problem).

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