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

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 13 years ago

update licence of all NEMO files...

  • Property svn:keywords set to Id
File size: 13.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   LOGICAL , PUBLIC ::   ln_diahsb  = .FALSE.   !: check the heat and salt budgets
29
30   !! * Module variables
31   INTEGER                                 ::   numhsb                           !
32   REAL(dp)                                ::   surf_tot   , vol_tot             !
33   REAL(dp)                                ::   frc_t      , frc_s     , frc_v   ! global forcing trends
34   REAL(dp)                                ::   fact1                            ! conversion factors
35   REAL(dp)                                ::   fact21    , fact22               !     -         -
36   REAL(dp)                                ::   fact31    , fact32               !     -         -
37   REAL(dp), DIMENSION(:,:)  , ALLOCATABLE ::   surf      , ssh_ini              !
38   REAL(dp), DIMENSION(:,:,:), ALLOCATABLE ::   hc_loc_ini, sc_loc_ini, e3t_ini  !
39
40   !! * Substitutions
41#  include "domzgr_substitute.h90"
42#  include "vectopt_loop_substitute.h90"
43
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
46   !! $Id$
47   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49
50CONTAINS
51
52   SUBROUTINE dia_hsb( kt )
53      !!---------------------------------------------------------------------------
54      !!                  ***  ROUTINE dia_hsb  ***
55      !!     
56      !! ** Purpose: Compute the ocean global heat content, salt content and volume
57      !!             non conservation
58      !!
59      !! ** Method : - Compute the deviation of heat content, salt content and volume
60      !!        at the current time step from their values at nit000
61      !!      - Compute the contribution of forcing and remove it from these
62      !!                deviations
63      !! ** Action : Write the results in the 'heat_salt_volume_budgets.txt' ASCII file
64      !!---------------------------------------------------------------------------
65      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
66      !!
67      INTEGER    ::   jk                          ! dummy loop indice
68      REAL(dp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations
69      REAL(dp)   ::   zdiff_v1    , zdiff_v2      ! volume variation
70      REAL(dp)   ::   z1_rau0                     ! local scalars
71      REAL(dp)   ::   zdeltat                     !    -     -
72      REAL(dp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     -
73      REAL(dp)   ::   z_frc_trd_v                 !    -     -
74      !!---------------------------------------------------------------------------
75
76      ! ------------------------- !
77      ! 1 - Trends due to forcing !
78      ! ------------------------- !
79      z1_rau0 = 1.e0 / rau0
80      z_frc_trd_v = z1_rau0 * SUM( - ( emp(:,:) - rnf(:,:) ) * surf(:,:) )     ! volume fluxes
81      z_frc_trd_t =           SUM( sbc_tsc(:,:,jp_tem) * surf(:,:) )     ! heat fluxes
82      z_frc_trd_s =           SUM( sbc_tsc(:,:,jp_sal) * surf(:,:) )     ! salt fluxes
83      ! Add penetrative solar radiation
84      IF( ln_traqsr ) z_frc_trd_t = z_frc_trd_t + ro0cpr * SUM( qsr     (:,:) * surf(:,:) )
85#if defined key_trabbc
86      ! Add geothermal heat flux
87      IF( lk_trabbc ) z_frc_trd_t = z_frc_trd_t + ro0cpr * SUM( qgh_trd0(:,:) * surf(:,:) )
88#endif
89      IF( lk_mpp ) THEN
90         CALL mpp_sum( z_frc_trd_v )
91         CALL mpp_sum( z_frc_trd_t )
92      ENDIF
93      frc_v = frc_v + z_frc_trd_v * rdt
94      frc_t = frc_t + z_frc_trd_t * rdt
95      frc_s = frc_s + z_frc_trd_s * rdt
96
97      ! ----------------------- !
98      ! 2 -  Content variations !
99      ! ----------------------- !
100      zdiff_v2 = 0.d0
101      zdiff_hc = 0.d0
102      zdiff_sc = 0.d0
103      ! volume variation (calculated with ssh)
104      zdiff_v1 = SUM( surf(:,:) * tmask(:,:,1) * ( sshn(:,:) - ssh_ini(:,:) ) )
105      DO jk = 1, jpkm1
106         ! volume variation (calculated with scale factors)
107         zdiff_v2 = zdiff_v2 + SUM( surf(:,:) * tmask(:,:,jk)   &
108            &                       * ( fse3t_n(:,:,jk)         &
109            &                           - e3t_ini(:,:,jk) ) )
110         ! heat content variation
111         zdiff_hc = zdiff_hc + SUM( surf(:,:) * tmask(:,:,jk)          &
112            &                       * ( fse3t_n(:,:,jk) * tn(:,:,jk)   &
113            &                           - hc_loc_ini(:,:,jk) ) )
114         ! salt content variation
115         zdiff_sc = zdiff_sc + SUM( surf(:,:) * tmask(:,:,jk)          &
116            &                       * ( fse3t_n(:,:,jk) * sn(:,:,jk)   &
117            &                           - sc_loc_ini(:,:,jk) ) )
118      ENDDO
119
120      IF( lk_mpp ) THEN
121         CALL mpp_sum( zdiff_hc )
122         CALL mpp_sum( zdiff_sc )
123         CALL mpp_sum( zdiff_v1 )
124         CALL mpp_sum( zdiff_v2 )
125      ENDIF
126
127      ! Substract forcing from heat content, salt content and volume variations
128      zdiff_v1 = zdiff_v1 - frc_v
129      zdiff_v2 = zdiff_v2 - frc_v
130      zdiff_hc = zdiff_hc - frc_t
131      zdiff_sc = zdiff_sc - frc_s
132     
133      ! ----------------------- !
134      ! 3 - Diagnostics writing !
135      ! ----------------------- !
136      zdeltat  = 1.e0 / ( ( kt - nit000 + 1 ) * rdt )
137      WRITE(numhsb , 9020) kt , zdiff_hc / vol_tot , zdiff_hc * fact1  * zdeltat,                                &
138         &                      zdiff_sc / vol_tot , zdiff_sc * fact21 * zdeltat, zdiff_sc * fact22 * zdeltat,   &
139         &                      zdiff_v1           , zdiff_v1 * fact31 * zdeltat, zdiff_v1 * fact32 * zdeltat,   &
140         &                      zdiff_v2           , zdiff_v2 * fact31 * zdeltat, zdiff_v2 * fact32 * zdeltat
141
142      IF ( kt == nitend ) CLOSE( numhsb )
143
1449020  FORMAT(I5,11D15.7)
145
146   END SUBROUTINE dia_hsb
147
148   SUBROUTINE dia_hsb_init
149      !!---------------------------------------------------------------------------
150      !!                  ***  ROUTINE dia_hsb  ***
151      !!     
152      !! ** Purpose: Initialization for the heat salt volume budgets
153      !!
154      !! ** Method : Compute initial heat content, salt content and volume
155      !!
156      !! ** Action : - Compute initial heat content, salt content and volume
157      !!             - Initialize forcing trends
158      !!             - Compute coefficients for conversion
159      !!---------------------------------------------------------------------------
160      CHARACTER (len=32) ::   cl_name  ! output file name
161      INTEGER            ::   jk       ! dummy loop indice
162      INTEGER            ::   ierror   ! local integer
163
164      NAMELIST/namhsb/ ln_diahsb
165      !!----------------------------------------------------------------------
166
167      REWIND ( numnam )              ! Read Namelist namhsb
168      READ   ( numnam, namhsb )
169
170      IF(lwp) THEN                   ! Control print
171         WRITE(numout,*)
172         WRITE(numout,*) 'dia_hsb_init : check the heat and salt budgets'
173         WRITE(numout,*) '~~~~~~~~~~~~'
174         WRITE(numout,*) '   Namelist namhsb : set hsb parameters'
175         WRITE(numout,*) '      Switch for hsb diagnostic (T) or not (F)  ln_diahsb  = ', ln_diahsb
176      ENDIF
177      !!---------------------------------------------------------------------------
178
179      IF( .NOT. ln_diahsb )   RETURN
180
181      ! ------------------- !
182      ! 1 - Allocate memory !
183      ! ------------------- !
184      ALLOCATE( hc_loc_ini(jpi,jpj,jpk), STAT=ierror )
185      IF( ierror > 0 ) THEN
186         CALL ctl_stop( 'dia_hsb: unable to allocate hc_loc_ini' )   ;   RETURN
187      ENDIF
188      ALLOCATE( sc_loc_ini(jpi,jpj,jpk), STAT=ierror )
189      IF( ierror > 0 ) THEN
190         CALL ctl_stop( 'dia_hsb: unable to allocate sc_loc_ini' )   ;   RETURN
191      ENDIF
192      ALLOCATE( e3t_ini(jpi,jpj,jpk)   , STAT=ierror )
193      IF( ierror > 0 ) THEN
194         CALL ctl_stop( 'dia_hsb: unable to allocate e3t_ini' )      ;   RETURN
195      ENDIF
196      ALLOCATE( surf(jpi,jpj)          , STAT=ierror )
197      IF( ierror > 0 ) THEN
198         CALL ctl_stop( 'dia_hsb: unable to allocate surf' )         ;   RETURN
199      ENDIF
200      ALLOCATE( ssh_ini(jpi,jpj)       , STAT=ierror )
201      IF( ierror > 0 ) THEN
202         CALL ctl_stop( 'dia_hsb: unable to allocate ssh_ini' )      ;   RETURN
203      ENDIF
204
205      ! ----------------------------------------------- !
206      ! 2 - Time independant variables and file opening !
207      ! ----------------------------------------------- !
208      WRITE(numout,*) "dia_hsb: heat salt volume budgets activated"
209      WRITE(numout,*) "~~~~~~~  output written in the 'heat_salt_volume_budgets.txt' ASCII file"
210      IF( lk_obc .OR. lk_bdy) THEN
211         CALL ctl_warn( 'dia_hsb does not take open boundary fluxes into account' )         
212      ENDIF
213      cl_name    = 'heat_salt_volume_budgets.txt'                         ! name of output file
214      surf(:,:) = e1t(:,:) * e2t(:,:) * tmask(:,:,1) * tmask_i(:,:)      ! masked surface grid cell area
215      surf_tot  = SUM( surf(:,:) )                                       ! total ocean surface area
216      vol_tot   = 0.d0                                                   ! total ocean volume
217      DO jk = 1, jpkm1
218         vol_tot  = vol_tot + SUM( surf(:,:) * tmask(:,:,jk)     &
219            &                      * fse3t_n(:,:,jk)         )
220      ENDDO
221      IF( lk_mpp ) THEN
222         CALL mpp_sum( vol_tot )
223         CALL mpp_sum( surf_tot )
224      ENDIF
225
226      CALL ctl_opn( numhsb , cl_name , 'UNKNOWN' , 'FORMATTED' , 'SEQUENTIAL' , 1 , numout , lwp , 1 )
227      !                   12345678901234567890123456789012345678901234567890123456789012345678901234567890 -> 80
228      WRITE( numhsb, 9010 ) "kt   |     heat content budget     |            salt content budget             ",   &
229         !                                                   123456789012345678901234567890123456789012345 -> 45
230         &                                                  "|            volume budget (ssh)             ",   &
231         !                                                   678901234567890123456789012345678901234567890 -> 45
232         &                                                  "|            volume budget (e3t)             "
233      WRITE( numhsb, 9010 ) "     |      [C]         [W/m2]     |     [psu]        [mmm/s]          [SV]     ",   &
234         &                                                  "|     [m3]         [mmm/s]          [SV]     ",   &
235         &                                                  "|     [m3]         [mmm/s]          [SV]     "
236
237      ! --------------- !
238      ! 3 - Conversions ! (factors will be multiplied by duration afterwards)
239      ! --------------- !
240
241      ! heat content variation   =>   equivalent heat flux:
242      fact1  = rau0 * rcp / surf_tot                                         ! [C*m3]   ->  [W/m2]
243      ! salt content variation   =>   equivalent EMP and equivalent "flow":
244      fact21 = 1.e3  / ( soce * surf_tot )                                   ! [psu*m3] ->  [mm/s]
245      fact22 = 1.e-6 / soce                                                  ! [psu*m3] ->  [Sv]
246      ! volume variation         =>   equivalent EMP and equivalent "flow":
247      fact31 = 1.e3  / surf_tot                                              ! [m3]     ->  [mm/s]
248      fact32 = 1.e-6                                                         ! [m3]     ->  [SV]
249
250      ! ---------------------------------- !
251      ! 4 - initial conservation variables !
252      ! ---------------------------------- !
253      ssh_ini(:,:) = sshn(:,:)                               ! initial ssh
254      DO jk = 1, jpk
255         e3t_ini   (:,:,jk) = fse3t_n(:,:,jk)                ! initial vertical scale factors
256         hc_loc_ini(:,:,jk) = tn(:,:,jk) * fse3t_n(:,:,jk)   ! initial heat content
257         sc_loc_ini(:,:,jk) = sn(:,:,jk) * fse3t_n(:,:,jk)   ! initial salt content
258      END DO
259      frc_v = 0.d0                                           ! volume       trend due to forcing
260      frc_t = 0.d0                                           ! heat content   -    -   -    -   
261      frc_s = 0.d0                                           ! salt content   -    -   -    -         
262      !
2639010  FORMAT(A80,A45,A45)
264      !
265   END SUBROUTINE dia_hsb_init
266
267   !!======================================================================
268END MODULE diahsb
Note: See TracBrowser for help on using the repository browser.