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

source: branches/DEV_r1837_MLF/NEMO/OPA_SRC/DIA/diahsb.F90 @ 2112

Last change on this file since 2112 was 2112, checked in by mlelod, 14 years ago

ticket: #663 introduce dia_hsb_init routine (called by opa_init)

File size: 12.1 KB
Line 
1MODULE diahsb
2   !!======================================================================
3   !!                       ***  MODULE  diahsb  ***
4   !! Ocean diagnostics: Heat salt and volume budgets
5   !!======================================================================
6   !! History :  NEMO 3.3  !  2010-09  (M. Leclair)  Original code
7   !!----------------------------------------------------------------------
8   !! * Modules used
9   USE oce             ! ocean dynamics and tracers
10   USE dom_oce         ! ocean space and time domain
11   USE phycst          ! physical constants
12   USE sbc_oce         ! surface thermohaline fluxes
13   USE in_out_manager  ! I/O manager
14   USE domvvl          ! vertical scale factors
15   USE traqsr          ! penetrative solar radiation
16   USE lib_mpp         ! distributed memory computing library
17   USE trabbc          ! bottom boundary condition
18   USE bdy_par         ! (for lk_bdy)
19   USE obc_par         ! (for lk_obc)
20
21   IMPLICIT NONE
22   PRIVATE
23
24   !! * Routine accessibility
25   PUBLIC dia_hsb        ! routine called by step.F90
26   PUBLIC dia_hsb_init   ! routine called by opa.F90
27
28   !! * Module variables
29   INTEGER              ::   num                 !
30   REAL(dp)                  ::   surf_tot  , vol_tot               !
31   REAL(dp)                  ::   frc_t     , frc_s     , frc_v     ! global forcing trends
32   REAL(dp)             ::   fact1                  ! conversion factors
33   REAL(dp)             ::   fact21   , fact22            !     -         -
34   REAL(dp)                      ::   fact31   , fact32            !     -         -
35   REAL(dp), DIMENSION(:,:)  , ALLOCATABLE ::   surf    , ssh_ini      !
36   REAL(dp), DIMENSION(:,:,:), ALLOCATABLE ::   hc_loc_ini, sc_loc_ini, e3t_ini   !
37
38   !! * Substitutions
39#  include "domzgr_substitute.h90"
40#  include "vectopt_loop_substitute.h90"
41
42   !!----------------------------------------------------------------------
43   !! NEMO/OPA 3.3 , LOCEAN-IPSL (2010)
44   !! $Id: trasbc.F90 2091 2010-09-14 20:29:38Z mlelod $
45   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
46   !!----------------------------------------------------------------------
47
48CONTAINS
49
50   SUBROUTINE dia_hsb( kt )
51      !!---------------------------------------------------------------------------
52      !!                  ***  ROUTINE dia_hsb  ***
53      !!     
54      !! ** Purpose: Compute the ocean global heat content, salt content and volume
55      !!             non conservation
56      !!
57      !! ** Method : - Compute the deviation of heat content, salt content and volume
58      !!        at the current time step from their values at nit000
59      !!      - Compute the contribution of forcing and remove it from these
60      !!                deviations
61      !! ** Action : Write the results in the 'heat_salt_volume_budgets.txt' ASCII file
62      !!---------------------------------------------------------------------------
63      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
64      !!
65      INTEGER   ::   jk              ! dummy loop indice
66      REAL(dp)  ::   zdiff_hc   , zdiff_sc     ! heat and salt content variations
67      REAL(dp)  ::   zdiff_v1   , zdiff_v2     ! volume variation
68      REAL(dp)  ::   z1_rau0                ! local scalars
69      REAL(dp)  ::   zdeltat          !    -     -
70      REAL(dp)  ::   z_frc_trd_t , z_frc_trd_s   !    -     -
71      REAL(dp)  ::   z_frc_trd_v           !    -     -
72      !!---------------------------------------------------------------------------
73
74      ! ------------------------- !
75      ! 1 - Trends due to forcing !
76      ! ------------------------- !
77      z1_rau0 = 1.e0 / rau0
78      z_frc_trd_v = z1_rau0 * SUM(    - emp(:,:) * surf(:,:) )     ! volume fluxes
79      z_frc_trd_t =           SUM( sbc_hc_n(:,:) * surf(:,:) )     ! heat fluxes
80      z_frc_trd_s =           SUM( sbc_sc_n(:,:) * surf(:,:) )     ! salt fluxes
81      ! Add penetrative solar radiation
82      IF( ln_traqsr ) z_frc_trd_t = z_frc_trd_t + ro0cpr * SUM( qsr     (:,:) * surf(:,:) )
83      ! Add geothermal heat flux
84      IF( lk_trabbc ) z_frc_trd_t = z_frc_trd_t + ro0cpr * SUM( qgh_trd0(:,:) * surf(:,:) )
85      IF( lk_mpp ) THEN
86         CALL mpp_sum( z_frc_trd_v )
87         CALL mpp_sum( z_frc_trd_t )
88      ENDIF
89      frc_v = frc_v + z_frc_trd_v * rdt
90      frc_t = frc_t + z_frc_trd_t * rdt
91      frc_s = frc_s + z_frc_trd_s * rdt
92
93      ! ----------------------- !
94      ! 2 -  Content variations !
95      ! ----------------------- !
96      zdiff_v2 = 0.d0
97      zdiff_hc = 0.d0
98      zdiff_sc = 0.d0
99      ! volume variation (calculated with ssh)
100      zdiff_v1 = SUM( surf(:,:) * tmask(:,:,1) * ( sshn(:,:) - ssh_ini(:,:) ) )
101      DO jk = 1, jpkm1
102         ! volume variation (calculated with scale factors)
103         zdiff_v2 = zdiff_v2 + SUM( surf(:,:) * tmask(:,:,jk)   &
104            &                       * ( fse3t_n(:,:,jk)         &
105            &                           - e3t_ini(:,:,jk) ) )
106         ! heat content variation
107         zdiff_hc = zdiff_hc + SUM( surf(:,:) * tmask(:,:,jk)          &
108            &                       * ( fse3t_n(:,:,jk) * tn(:,:,jk)   &
109            &                           - hc_loc_ini(:,:,jk) ) )
110         ! salt content variation
111         zdiff_sc = zdiff_sc + SUM( surf(:,:) * tmask(:,:,jk)          &
112            &                       * ( fse3t_n(:,:,jk) * sn(:,:,jk)   &
113            &                           - sc_loc_ini(:,:,jk) ) )
114      ENDDO
115
116      IF( lk_mpp ) THEN
117         CALL mpp_sum( zdiff_hc )
118         CALL mpp_sum( zdiff_sc )
119         CALL mpp_sum( zdiff_v1 )
120         CALL mpp_sum( zdiff_v2 )
121      ENDIF
122
123      ! Substract forcing from heat content, salt content and volume variations
124      zdiff_v1 = zdiff_v1 - frc_v
125      zdiff_v2 = zdiff_v2 - frc_v
126      zdiff_hc = zdiff_hc - frc_t
127      zdiff_sc = zdiff_sc - frc_s
128     
129      ! ----------------------- !
130      ! 3 - Diagnostics writing !
131      ! ----------------------- !
132      zdeltat  = 1.e0 / ( ( kt - nit000 + 1 ) * rdt )
133      WRITE(num , 9020) kt , zdiff_hc / vol_tot , zdiff_hc * fact1  * zdeltat,                                &
134         &                   zdiff_sc / vol_tot , zdiff_sc * fact21 * zdeltat, zdiff_sc * fact22 * zdeltat,   &
135         &                   zdiff_v1           , zdiff_v1 * fact31 * zdeltat, zdiff_v1 * fact32 * zdeltat,   &
136         &                   zdiff_v2           , zdiff_v2 * fact31 * zdeltat, zdiff_v2 * fact32 * zdeltat
137
138      IF ( kt == nitend ) CLOSE( num )
139
1409020  FORMAT(I5,11D15.7)
141
142   END SUBROUTINE dia_hsb
143
144
145   SUBROUTINE dia_hsb_init
146      !!---------------------------------------------------------------------------
147      !!                  ***  ROUTINE dia_hsb  ***
148      !!     
149      !! ** Purpose: Initialization for the heat salt volume budgets
150      !!
151      !! ** Method : Compute initial heat content, salt content and volume
152      !!
153      !! ** Action : - Compute initial heat content, salt content and volume
154      !!             - Initialize forcing trends
155      !!             - Compute coefficients for conversion
156      !!---------------------------------------------------------------------------
157      CHARACTER (len=32) ::   s_name        ! output file name
158      INTEGER      ::   jk      ! dummy loop indice
159      INTEGER      ::   ierror              ! local integer
160      !!---------------------------------------------------------------------------
161
162      ! ------------------- !
163      ! 1 - Allocate memory !
164      ! ------------------- !
165      ALLOCATE( hc_loc_ini(jpi,jpj,jpk), STAT=ierror )
166      IF( ierror > 0 ) THEN
167         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN
168      ENDIF
169      ALLOCATE( sc_loc_ini(jpi,jpj,jpk), STAT=ierror )
170      IF( ierror > 0 ) THEN
171         CALL ctl_stop( 'dia_hsb: unable to allocate sc_loc_ini' )   ;   RETURN
172      ENDIF
173      ALLOCATE( e3t_ini(jpi,jpj,jpk)   , STAT=ierror )
174      IF( ierror > 0 ) THEN
175         CALL ctl_stop( 'dia_hsb: unable to allocate e3t_ini' )      ;   RETURN
176      ENDIF
177      ALLOCATE( surf(jpi,jpj)          , STAT=ierror )
178      IF( ierror > 0 ) THEN
179         CALL ctl_stop( 'dia_hsb: unable to allocate surf' )         ;   RETURN
180      ENDIF
181      ALLOCATE( ssh_ini(jpi,jpj)       , STAT=ierror )
182      IF( ierror > 0 ) THEN
183         CALL ctl_stop( 'dia_hsb: unable to allocate ssh_ini' )      ;   RETURN
184      ENDIF
185
186      ! ----------------------------------------------- !
187      ! 2 - Time independant variables and file opening !
188      ! ----------------------------------------------- !
189      WRITE(numout,*) "dia_hsb: heat salt volume budgets activated"
190      WRITE(numout,*) "~~~~~~~  output written in the 'heat_salt_volume_budgets.txt' ASCII file"
191      IF( lk_obc .OR. lk_bdy) THEN
192         CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )         
193      ENDIF
194      s_name    = 'heat_salt_volume_budgets.txt'                         ! name of output file
195      surf(:,:) = e1t(:,:) * e2t(:,:) * tmask(:,:,1) * tmask_i(:,:)      ! masked surface grid cell area
196      surf_tot  = SUM( surf(:,:) )                                       ! total ocean surface area
197      vol_tot   = 0.d0                                                   ! total ocean volume
198      DO jk = 1, jpkm1
199         vol_tot  = vol_tot + SUM( surf(:,:) * tmask(:,:,jk)     &
200            &                      * fse3t_n(:,:,jk)         )
201      ENDDO
202      IF( lk_mpp ) THEN
203         CALL mpp_sum( vol_tot )
204         CALL mpp_sum( surf_tot )
205      ENDIF
206
207      CALL ctl_opn( num , s_name , 'UNKNOWN' , 'FORMATTED' , 'SEQUENTIAL' , 1 , numout , lwp , 1 )
208      !                   12345678901234567890123456789012345678901234567890123456789012345678901234567890 -> 80
209      WRITE( num, 9010 ) "kt   |     heat content budget     |            salt content budget             ",   &
210         !                                                   123456789012345678901234567890123456789012345 -> 45
211         &                                                  "|            volume budget (ssh)             ",   &
212         !                                                   678901234567890123456789012345678901234567890 -> 45
213         &                                                  "|            volume budget (e3t)             "
214      WRITE( num, 9010 ) "     |      [C]         [W/m2]     |     [psu]        [mmm/s]          [SV]     ",   &
215         &                                                  "|     [m3]         [mmm/s]          [SV]     ",   &
216         &                                                  "|     [m3]         [mmm/s]          [SV]     "
217
218      ! --------------- !
219      ! 3 - Conversions ! (factors will be multiplied by duration afterwards)
220      ! --------------- !
221
222      ! heat content variation   =>   equivalent heat flux:
223      fact1  = rau0 * rcp / surf_tot                                         ! [C*m3]   ->  [W/m2]
224      ! salt content variation   =>   equivalent EMP and equivalent "flow":
225      fact21 = 1.e3  / ( soce * surf_tot )                                   ! [psu*m3] ->  [mm/s]
226      fact22 = 1.e-6 / soce                                                  ! [psu*m3] ->  [Sv]
227      ! volume variation         =>   equivalent EMP and equivalent "flow":
228      fact31 = 1.e3  / surf_tot                                              ! [m3]     ->  [mm/s]
229      fact32 = 1.e-6                                                         ! [m3]     ->  [SV]
230
231      ! ---------------------------------- !
232      ! 4 - initial conservation variables !
233      ! ---------------------------------- !
234      ssh_ini(:,:) = sshn(:,:)                               ! initial ssh
235      DO jk = 1, jpk
236         e3t_ini   (:,:,jk) = fse3t_n(:,:,jk)                ! initial vertical scale factors
237         hc_loc_ini(:,:,jk) = tn(:,:,jk) * fse3t_n(:,:,jk)   ! initial heat content
238         sc_loc_ini(:,:,jk) = sn(:,:,jk) * fse3t_n(:,:,jk)   ! initial salt content
239      END DO
240      frc_v = 0.d0                                           ! volume       trend due to forcing
241      frc_t = 0.d0                                           ! heat content   -    -   -    -   
242      frc_s = 0.d0                                           ! salt content   -    -   -    -         
243      !
2449010  FORMAT(A80,A45,A45)
245      !
246   END SUBROUTINE dia_hsb_init
247
248   !!======================================================================
249END MODULE diahsb
Note: See TracBrowser for help on using the repository browser.