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.
limdiahsb.F90 in branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/LIM_SRC_3/limdiahsb.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 9 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • Property svn:keywords set to Id
File size: 17.3 KB
Line 
1MODULE limdiahsb
2   !!======================================================================
3   !!                       ***  MODULE limdia_hsb   ***
4   !!  LIM-3 sea ice model :   diagnostics of ice model
5   !!======================================================================
6   !! History :  3.4  ! 2012-10  (C. Rousset)  original code
7   !!----------------------------------------------------------------------
8#if defined key_lim3
9   !!----------------------------------------------------------------------
10   !!   'key_lim3'                                       LIM3 sea-ice model
11   !!----------------------------------------------------------------------
12   !!   lim_dia_hsb        : computation and output of the time evolution of keys variables
13   !!   lim_dia_hsb_init   : initialization and namelist read
14   !!----------------------------------------------------------------------
15   USE ice             ! LIM-3: sea-ice variable
16   USE dom_ice         ! LIM-3: sea-ice domain
17   USE dom_oce         ! ocean domain
18   USE sbc_oce         ! surface boundary condition: ocean fields
19   USE sbc_ice         ! Surface boundary condition: sea-ice fields
20   USE daymod          ! model calendar
21   USE phycst          ! physical constant
22   USE in_out_manager  ! I/O manager
23   USE lib_mpp         ! MPP library
24   USE timing          ! preformance summary
25   USE iom             ! I/O manager
26   USE lib_fortran     ! glob_sum
27   USE limrst          ! ice restart
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   lim_diahsb        ! routine called by ice_step.F90
33
34   real(wp) ::   frc_sal, frc_vol   ! global forcing trends
35   real(wp) ::   bg_grme            ! global ice growth+melt trends
36
37   !! * Substitutions
38#  include "vectopt_loop_substitute.h90"
39
40   !!----------------------------------------------------------------------
41   !! NEMO/OPA 3.4 , NEMO Consortium (2012)
42   !! $Id$
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48   SUBROUTINE lim_diahsb
49      !!---------------------------------------------------------------------------
50      !!                  ***  ROUTINE lim_diahsb  ***
51      !!     
52      !! ** Purpose: Compute the ice global heat content, salt content and volume conservation
53      !!
54      !!---------------------------------------------------------------------------
55      !!
56      real(wp)   ::   zbg_ivo, zbg_svo, zbg_are, zbg_sal ,zbg_tem ,zbg_ihc ,zbg_shc
57      real(wp)   ::   zbg_sfx, zbg_sfx_bri, zbg_sfx_bog, zbg_sfx_bom, zbg_sfx_sum, zbg_sfx_sni,   &
58      &               zbg_sfx_opw, zbg_sfx_res, zbg_sfx_dyn 
59      real(wp)   ::   zbg_vfx, zbg_vfx_bog, zbg_vfx_opw, zbg_vfx_sni, zbg_vfx_dyn
60      real(wp)   ::   zbg_vfx_bom, zbg_vfx_sum, zbg_vfx_res, zbg_vfx_spr, zbg_vfx_snw, zbg_vfx_sub 
61      real(wp)   ::   zbg_hfx_dhc, zbg_hfx_spr
62      real(wp)   ::   zbg_hfx_res, zbg_hfx_sub, zbg_hfx_dyn, zbg_hfx_thd, zbg_hfx_snw, zbg_hfx_out, zbg_hfx_in   
63      real(wp)   ::   zbg_hfx_sum, zbg_hfx_bom, zbg_hfx_bog, zbg_hfx_dif, zbg_hfx_opw
64      real(wp)   ::   z_frc_vol, z_frc_sal, z_bg_grme 
65      real(wp)   ::   z1_area                     !    -     -
66      REAL(wp)   ::   ztmp
67      !!---------------------------------------------------------------------------
68      IF( nn_timing == 1 )   CALL timing_start('lim_diahsb')
69
70      IF( numit == nstart ) CALL lim_diahsb_init 
71
72      ! 1/area
73      z1_area = 1._wp / MAX( glob_sum( e1e2t(:,:) * tmask(:,:,1) ), epsi06 )
74
75      rswitch = MAX( 0._wp , SIGN( 1._wp , glob_sum( e1e2t(:,:) * tmask(:,:,1) ) - epsi06 ) )
76      ! ----------------------- !
77      ! 1 -  Content variations !
78      ! ----------------------- !
79      zbg_ivo = glob_sum( vt_i(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! volume ice
80      zbg_svo = glob_sum( vt_s(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! volume snow
81      zbg_are = glob_sum( at_i(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! area
82      zbg_sal = glob_sum( SUM( smv_i(:,:,:), dim=3 ) * e1e2t(:,:) * tmask(:,:,1) )       ! mean salt content
83      zbg_tem = glob_sum( ( tm_i(:,:) - rt0 ) * vt_i(:,:) * e1e2t(:,:) * tmask(:,:,1) )  ! mean temp content
84
85      !zbg_ihc = glob_sum( et_i(:,:) * e1e2t(:,:) * tmask(:,:,1) ) / MAX( zbg_ivo,epsi06 ) ! ice heat content
86      !zbg_shc = glob_sum( et_s(:,:) * e1e2t(:,:) * tmask(:,:,1) ) / MAX( zbg_svo,epsi06 ) ! snow heat content
87
88      ! Volume
89      ztmp = rswitch * z1_area * r1_rau0 * rday
90      zbg_vfx     = ztmp * glob_sum(     emp(:,:) * e1e2t(:,:) * tmask(:,:,1) )
91      zbg_vfx_bog = ztmp * glob_sum( wfx_bog(:,:) * e1e2t(:,:) * tmask(:,:,1) )
92      zbg_vfx_opw = ztmp * glob_sum( wfx_opw(:,:) * e1e2t(:,:) * tmask(:,:,1) )
93      zbg_vfx_sni = ztmp * glob_sum( wfx_sni(:,:) * e1e2t(:,:) * tmask(:,:,1) )
94      zbg_vfx_dyn = ztmp * glob_sum( wfx_dyn(:,:) * e1e2t(:,:) * tmask(:,:,1) )
95      zbg_vfx_bom = ztmp * glob_sum( wfx_bom(:,:) * e1e2t(:,:) * tmask(:,:,1) )
96      zbg_vfx_sum = ztmp * glob_sum( wfx_sum(:,:) * e1e2t(:,:) * tmask(:,:,1) )
97      zbg_vfx_res = ztmp * glob_sum( wfx_res(:,:) * e1e2t(:,:) * tmask(:,:,1) )
98      zbg_vfx_spr = ztmp * glob_sum( wfx_spr(:,:) * e1e2t(:,:) * tmask(:,:,1) )
99      zbg_vfx_snw = ztmp * glob_sum( wfx_snw(:,:) * e1e2t(:,:) * tmask(:,:,1) )
100      zbg_vfx_sub = ztmp * glob_sum( wfx_sub(:,:) * e1e2t(:,:) * tmask(:,:,1) )
101
102      ! Salt
103      zbg_sfx     = ztmp * glob_sum(     sfx(:,:) * e1e2t(:,:) * tmask(:,:,1) )
104      zbg_sfx_bri = ztmp * glob_sum( sfx_bri(:,:) * e1e2t(:,:) * tmask(:,:,1) )
105      zbg_sfx_res = ztmp * glob_sum( sfx_res(:,:) * e1e2t(:,:) * tmask(:,:,1) )
106      zbg_sfx_dyn = ztmp * glob_sum( sfx_dyn(:,:) * e1e2t(:,:) * tmask(:,:,1) )
107
108      zbg_sfx_bog = ztmp * glob_sum( sfx_bog(:,:) * e1e2t(:,:) * tmask(:,:,1) )
109      zbg_sfx_opw = ztmp * glob_sum( sfx_opw(:,:) * e1e2t(:,:) * tmask(:,:,1) )
110      zbg_sfx_sni = ztmp * glob_sum( sfx_sni(:,:) * e1e2t(:,:) * tmask(:,:,1) )
111      zbg_sfx_bom = ztmp * glob_sum( sfx_bom(:,:) * e1e2t(:,:) * tmask(:,:,1) )
112      zbg_sfx_sum = ztmp * glob_sum( sfx_sum(:,:) * e1e2t(:,:) * tmask(:,:,1) )
113
114      ! Heat budget
115      zbg_ihc      = glob_sum( et_i(:,:) * e1e2t(:,:) ) * 1.e-20  ! ice heat content  [1.e20 J]
116      zbg_shc      = glob_sum( et_s(:,:) * e1e2t(:,:) ) * 1.e-20  ! snow heat content [1.e20 J]
117      zbg_hfx_dhc  = glob_sum( diag_heat(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
118      zbg_hfx_spr  = glob_sum( hfx_spr(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
119
120      zbg_hfx_thd  = glob_sum( hfx_thd(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
121      zbg_hfx_dyn  = glob_sum( hfx_dyn(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
122      zbg_hfx_res  = glob_sum( hfx_res(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
123      zbg_hfx_sub  = glob_sum( hfx_sub(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
124      zbg_hfx_snw  = glob_sum( hfx_snw(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
125      zbg_hfx_sum  = glob_sum( hfx_sum(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
126      zbg_hfx_bom  = glob_sum( hfx_bom(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
127      zbg_hfx_bog  = glob_sum( hfx_bog(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
128      zbg_hfx_dif  = glob_sum( hfx_dif(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
129      zbg_hfx_opw  = glob_sum( hfx_opw(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
130      zbg_hfx_out  = glob_sum( hfx_out(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
131      zbg_hfx_in   = glob_sum(  hfx_in(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! [in W]
132   
133      ! --------------------------------------------- !
134      ! 2 - Trends due to forcing and ice growth/melt !
135      ! --------------------------------------------- !
136      z_frc_vol = r1_rau0 * glob_sum( - emp(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! volume fluxes
137      z_frc_sal = r1_rau0 * glob_sum(   sfx(:,:) * e1e2t(:,:) * tmask(:,:,1) ) ! salt fluxes
138      z_bg_grme = glob_sum( - ( wfx_bog(:,:) + wfx_opw(:,:) + wfx_sni(:,:) + wfx_dyn(:,:) + &
139                          &     wfx_bom(:,:) + wfx_sum(:,:) + wfx_res(:,:) + wfx_snw(:,:) + &
140                          &     wfx_sub(:,:) ) * e1e2t(:,:) * tmask(:,:,1) ) ! volume fluxes
141      !
142      frc_vol  = frc_vol  + z_frc_vol  * rdt_ice
143      frc_sal  = frc_sal  + z_frc_sal  * rdt_ice
144      bg_grme  = bg_grme  + z_bg_grme  * rdt_ice
145     
146      ! difference
147      !frc_vol = zbg_ivo - frc_vol
148      !frc_sal = zbg_sal - frc_sal
149     
150      ! ----------------------- !
151      ! 3 - Diagnostics writing !
152      ! ----------------------- !
153      rswitch = MAX( 0._wp , SIGN( 1._wp , zbg_ivo - epsi06 ) )
154      !
155      IF( iom_use('ibgvoltot') )   &
156      CALL iom_put( 'ibgvoltot' , zbg_ivo * rhoic * r1_rau0 * 1.e-9        )   ! ice volume (km3 equivalent liquid)         
157      IF( iom_use('sbgvoltot') )   &
158      CALL iom_put( 'sbgvoltot' , zbg_svo * rhosn * r1_rau0 * 1.e-9        )   ! snw volume (km3 equivalent liquid)       
159      IF( iom_use('ibgarea') )   &
160      CALL iom_put( 'ibgarea'   , zbg_are * 1.e-6                          )   ! ice area   (km2)
161      IF( iom_use('ibgsaline') )   &
162      CALL iom_put( 'ibgsaline' , rswitch * zbg_sal / MAX( zbg_ivo, epsi06 ) )   ! ice saline (psu)
163      IF( iom_use('ibgtemper') )   &
164      CALL iom_put( 'ibgtemper' , rswitch * zbg_tem / MAX( zbg_ivo, epsi06 ) )   ! ice temper (C)
165      CALL iom_put( 'ibgheatco' , zbg_ihc                                  )   ! ice heat content (1.e20 J)       
166      CALL iom_put( 'sbgheatco' , zbg_shc                                  )   ! snw heat content (1.e20 J)
167      IF( iom_use('ibgsaltco') )   &
168      CALL iom_put( 'ibgsaltco' , zbg_sal * rhoic * r1_rau0 * 1.e-9        )   ! ice salt content (psu*km3 equivalent liquid)       
169
170      CALL iom_put( 'ibgvfx'    , zbg_vfx                                  )   ! volume flux emp (m/day liquid)
171      CALL iom_put( 'ibgvfxbog' , zbg_vfx_bog                              )   ! volume flux bottom growth     -(m/day equivalent liquid)
172      CALL iom_put( 'ibgvfxopw' , zbg_vfx_opw                              )   ! volume flux open water growth -
173      CALL iom_put( 'ibgvfxsni' , zbg_vfx_sni                              )   ! volume flux snow ice growth   -
174      CALL iom_put( 'ibgvfxdyn' , zbg_vfx_dyn                              )   ! volume flux dynamic growth    -
175      CALL iom_put( 'ibgvfxbom' , zbg_vfx_bom                              )   ! volume flux bottom melt       -
176      CALL iom_put( 'ibgvfxsum' , zbg_vfx_sum                              )   ! volume flux surface melt      -
177      CALL iom_put( 'ibgvfxres' , zbg_vfx_res                              )   ! volume flux resultant         -
178      CALL iom_put( 'ibgvfxspr' , zbg_vfx_spr                              )   ! volume flux from snow precip         -
179      CALL iom_put( 'ibgvfxsnw' , zbg_vfx_snw                              )   ! volume flux from snow melt         -
180      CALL iom_put( 'ibgvfxsub' , zbg_vfx_sub                              )   ! volume flux from sublimation         -
181         
182      CALL iom_put( 'ibgsfx'    , zbg_sfx                                  )   ! salt flux         -(psu*m/day equivalent liquid)       
183      CALL iom_put( 'ibgsfxbri' , zbg_sfx_bri                              )   ! salt flux brines  -     
184      CALL iom_put( 'ibgsfxdyn' , zbg_sfx_dyn                              )   ! salt flux dynamic -   
185      CALL iom_put( 'ibgsfxres' , zbg_sfx_res                              )   ! salt flux result  -   
186      CALL iom_put( 'ibgsfxbog' , zbg_sfx_bog                              )   ! salt flux bottom growth   
187      CALL iom_put( 'ibgsfxopw' , zbg_sfx_opw                              )   ! salt flux open water growth -
188      CALL iom_put( 'ibgsfxsni' , zbg_sfx_sni                              )   ! salt flux snow ice growth   -
189      CALL iom_put( 'ibgsfxbom' , zbg_sfx_bom                              )   ! salt flux bottom melt       -
190      CALL iom_put( 'ibgsfxsum' , zbg_sfx_sum                              )   ! salt flux surface melt      -
191
192      CALL iom_put( 'ibghfxdhc' , zbg_hfx_dhc                              )   ! Heat content variation in snow and ice [W]
193      CALL iom_put( 'ibghfxspr' , zbg_hfx_spr                              )   ! Heat content of snow precip [W]
194
195      CALL iom_put( 'ibghfxres' , zbg_hfx_res                              )   !
196      CALL iom_put( 'ibghfxsub' , zbg_hfx_sub                              )   !
197      CALL iom_put( 'ibghfxdyn' , zbg_hfx_dyn                              )   !
198      CALL iom_put( 'ibghfxthd' , zbg_hfx_thd                              )   !
199      CALL iom_put( 'ibghfxsnw' , zbg_hfx_snw                              )   !
200      CALL iom_put( 'ibghfxsum' , zbg_hfx_sum                              )   !
201      CALL iom_put( 'ibghfxbom' , zbg_hfx_bom                              )   !
202      CALL iom_put( 'ibghfxbog' , zbg_hfx_bog                              )   !
203      CALL iom_put( 'ibghfxdif' , zbg_hfx_dif                              )   !
204      CALL iom_put( 'ibghfxopw' , zbg_hfx_opw                              )   !
205      CALL iom_put( 'ibghfxout' , zbg_hfx_out                              )   !
206      CALL iom_put( 'ibghfxin'  , zbg_hfx_in                               )   !
207
208      CALL iom_put( 'ibgfrcvol' , frc_vol * 1.e-9                          )   ! vol - forcing     (km3 equivalent liquid)
209      CALL iom_put( 'ibgfrcsfx' , frc_sal * 1.e-9                          )   ! sal - forcing     (psu*km3 equivalent liquid)   
210      IF( iom_use('ibgvolgrm') )   &
211      CALL iom_put( 'ibgvolgrm' , bg_grme * r1_rau0 * 1.e-9                )   ! vol growth + melt (km3 equivalent liquid)         
212
213      !
214      IF( lrst_ice )   CALL lim_diahsb_rst( numit, 'WRITE' )
215      !
216      IF( nn_timing == 1 )   CALL timing_stop('lim_diahsb')
217!
218   END SUBROUTINE lim_diahsb
219
220
221   SUBROUTINE lim_diahsb_init
222      !!---------------------------------------------------------------------------
223      !!                  ***  ROUTINE lim_diahsb_init  ***
224      !!     
225      !! ** Purpose: Initialization for the heat salt volume budgets
226      !!
227      !! ** Method : Compute initial heat content, salt content and volume
228      !!
229      !! ** Action : - Compute initial heat content, salt content and volume
230      !!             - Initialize forcing trends
231      !!             - Compute coefficients for conversion
232      !!---------------------------------------------------------------------------
233      INTEGER            ::   jk       ! dummy loop indice
234      INTEGER            ::   ierror   ! local integer
235      !!
236      !!NAMELIST/namicehsb/ blabla
237      !!----------------------------------------------------------------------
238      !
239      !!REWIND ( numnam_ice )              ! Read Namelist namicehsb
240      !!READ   ( numnam_ice, namicehsb )
241      !
242      IF(lwp) THEN                   ! Control print
243         WRITE(numout,*)
244         WRITE(numout,*) 'lim_diahsb_init : check the heat and salt budgets'
245         WRITE(numout,*) '~~~~~~~~~~~~'
246      ENDIF
247      !
248      CALL lim_diahsb_rst( nstart, 'READ' )  !* read or initialize all required files
249      !
250   END SUBROUTINE lim_diahsb_init
251
252   SUBROUTINE lim_diahsb_rst( kt, cdrw )
253     !!---------------------------------------------------------------------
254     !!                   ***  ROUTINE limdia_rst  ***
255     !!                     
256     !! ** Purpose :   Read or write DIA file in restart file
257     !!
258     !! ** Method  :   use of IOM library
259     !!----------------------------------------------------------------------
260     INTEGER         , INTENT(in) ::   kt     ! ice time-step
261     CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag
262     !
263     INTEGER ::   id1, id2, id3   ! local integers
264     !!----------------------------------------------------------------------
265     !
266     IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise
267        IF( ln_rstart ) THEN                   !* Read the restart file
268           !id1 = iom_varid( numrir, 'frc_vol'  , ldstop = .TRUE. )
269           !
270           IF(lwp) WRITE(numout,*) '~~~~~~~'
271           IF(lwp) WRITE(numout,*) ' lim_diahsb_rst at it= ', kt,' date= ', ndastp
272           IF(lwp) WRITE(numout,*) '~~~~~~~'
273           CALL iom_get( numrir, 'frc_vol', frc_vol )
274           CALL iom_get( numrir, 'frc_sal', frc_sal )
275           CALL iom_get( numrir, 'bg_grme', bg_grme )
276        ELSE
277           IF(lwp) WRITE(numout,*) '~~~~~~~'
278           IF(lwp) WRITE(numout,*) ' lim_diahsb at initial state '
279           IF(lwp) WRITE(numout,*) '~~~~~~~'
280           frc_vol  = 0._wp                                         
281           frc_sal  = 0._wp                                                 
282           bg_grme  = 0._wp                                       
283       ENDIF
284
285     ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file
286        !                                   ! -------------------
287        IF(lwp) WRITE(numout,*) '~~~~~~~'
288        IF(lwp) WRITE(numout,*) ' lim_diahsb_rst at it= ', kt,' date= ', ndastp
289        IF(lwp) WRITE(numout,*) '~~~~~~~'
290        CALL iom_rstput( kt, nitrst, numriw, 'frc_vol'   , frc_vol     )
291        CALL iom_rstput( kt, nitrst, numriw, 'frc_sal'   , frc_sal     )
292        CALL iom_rstput( kt, nitrst, numriw, 'bg_grme'   , bg_grme     )
293        !
294     ENDIF
295     !
296   END SUBROUTINE lim_diahsb_rst
297 
298#else
299   !!----------------------------------------------------------------------
300   !!   Default option :         Empty module          NO LIM sea-ice model
301   !!----------------------------------------------------------------------
302CONTAINS
303   SUBROUTINE lim_diahsb          ! Empty routine
304   END SUBROUTINE lim_diahsb
305#endif
306   !!======================================================================
307END MODULE limdiahsb
Note: See TracBrowser for help on using the repository browser.