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

source: branches/2012/dev_r3385_NOCS04_HAMF/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90 @ 3396

Last change on this file since 3396 was 3396, checked in by acc, 12 years ago

Branch: dev_r3385_NOCS04_HAMF; #665. Stage 1 of 2012 development: porting of changes on old development branch (2011/DEV_r1837_mass_heat_salt_fluxes) into new branch. Corrected a few errors on the way. This branch now compiles but is incomplete. Still missing LIM3 changes which must reside on a certain persons laptop somewhere

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