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

source: branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 @ 7910

Last change on this file since 7910 was 7910, checked in by timgraham, 7 years ago

All wrk_alloc removed

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