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/2013/dev_r4028_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2013/dev_r4028_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limdiahsb.F90 @ 4635

Last change on this file since 4635 was 4634, checked in by clem, 10 years ago

major changes in heat budget

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