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/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limdiahsb.F90 @ 6746

Last change on this file since 6746 was 6746, checked in by clem, 8 years ago

landfast ice parameterization + update from trunk + removing useless dom_ice.F90 and limmsh.F90 and limwri_dimg.h90

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