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

source: branches/2014/dev_r4650_UKMO2_ice_shelves/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 @ 4724

Last change on this file since 4724 was 4724, checked in by mathiot, 10 years ago

ISF branch: add comments, fix mpp and restar issues, add test to stop if incompatible options and fix mask issue in sbcice and sbcblk.

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