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.
icedia.F90 in NEMO/trunk/src/ICE – NEMO

source: NEMO/trunk/src/ICE/icedia.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 15.2 KB
Line 
1MODULE icedia
2   !!======================================================================
3   !!                       ***  MODULE icedia  ***
4   !!  Sea-Ice:   global budgets
5   !!======================================================================
6   !! History :  3.4  !  2012-10  (C. Rousset)       original code
7   !!            4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
8   !!----------------------------------------------------------------------
9#if defined key_si3
10   !!----------------------------------------------------------------------
11   !!   'key_si3'                                       SI3 sea-ice model
12   !!----------------------------------------------------------------------
13   !!    ice_dia      : diagnostic of the sea-ice global heat content, salt content and volume conservation
14   !!    ice_dia_init : initialization of budget calculation
15   !!    ice_dia_rst  : read/write budgets restart
16   !!----------------------------------------------------------------------
17   USE dom_oce        ! ocean domain
18   USE phycst         ! physical constant
19   USE daymod         ! model calendar
20   USE sbc_oce , ONLY : sfx, nn_fsbc   ! surface boundary condition: ocean fields
21   USE ice            ! sea-ice: variables
22   USE icerst         ! sea-ice: restart
23   !
24   USE in_out_manager ! I/O manager
25   USE iom            ! I/O manager library
26   USE lib_mpp        ! MPP library
27   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
28   USE timing         ! Timing
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   ice_dia        ! called by icestp.F90
34   PUBLIC   ice_dia_init   ! called in icestp.F90
35
36   REAL(wp), SAVE ::   z1_e1e2  ! inverse of the ocean area
37   REAL(wp), DIMENSION(:,:), ALLOCATABLE ::   vol_loc_ini, sal_loc_ini, tem_loc_ini                    ! initial volume, salt and heat contents
38   REAL(wp)                              ::   frc_sal, frc_voltop, frc_volbot, frc_temtop, frc_tembot  ! global forcing trends
39   
40   !!----------------------------------------------------------------------
41   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
42   !! $Id$
43   !! Software governed by the CeCILL license (see ./LICENSE)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   INTEGER FUNCTION ice_dia_alloc()
48      !!---------------------------------------------------------------------!
49      !!                ***  ROUTINE ice_dia_alloc ***
50      !!---------------------------------------------------------------------!
51      ALLOCATE( vol_loc_ini(jpi,jpj), sal_loc_ini(jpi,jpj), tem_loc_ini(jpi,jpj), STAT=ice_dia_alloc )
52
53      CALL mpp_sum ( 'icedia', ice_dia_alloc )
54      IF( ice_dia_alloc /= 0 )   CALL ctl_stop( 'STOP',  'ice_dia_alloc: failed to allocate arrays'  )
55      !
56   END FUNCTION ice_dia_alloc
57
58   SUBROUTINE ice_dia( kt )
59      !!---------------------------------------------------------------------------
60      !!                  ***  ROUTINE ice_dia  ***
61      !!     
62      !! ** Purpose:   Compute the sea-ice global heat content, salt content
63      !!             and volume conservation
64      !!---------------------------------------------------------------------------
65      INTEGER, INTENT(in) ::   kt   ! ocean time step
66      !!
67      REAL(wp)   ::   zbg_ivol, zbg_item, zbg_area, zbg_isal
68      REAL(wp)   ::   zbg_svol, zbg_stem
69      REAL(wp)   ::   z_frc_voltop, z_frc_temtop, z_frc_sal
70      REAL(wp)   ::   z_frc_volbot, z_frc_tembot 
71      REAL(wp)   ::   zdiff_vol, zdiff_sal, zdiff_tem 
72      !!---------------------------------------------------------------------------
73      IF( ln_timing )   CALL timing_start('ice_dia')
74
75      IF( kt == nit000 .AND. lwp ) THEN
76         WRITE(numout,*)
77         WRITE(numout,*)'icedia: output ice diagnostics (integrated over the domain)'
78         WRITE(numout,*)'~~~~~~'
79      ENDIF
80
81      IF( kt == nit000 ) THEN
82         z1_e1e2 = 1._wp / glob_sum( 'icedia', e1e2t(:,:) )
83      ENDIF
84     
85      ! ----------------------- !
86      ! 1 -  Contents           !
87      ! ----------------------- !
88      IF(  iom_use('ibgvol_tot' ) .OR. iom_use('sbgvol_tot' ) .OR. iom_use('ibgarea_tot') .OR. &
89         & iom_use('ibgsalt_tot') .OR. iom_use('ibgheat_tot') .OR. iom_use('sbgheat_tot') ) THEN
90
91         zbg_ivol = glob_sum( 'icedia', vt_i(:,:) * e1e2t(:,:) ) * 1.e-9  ! ice volume (km3)
92         zbg_svol = glob_sum( 'icedia', vt_s(:,:) * e1e2t(:,:) ) * 1.e-9  ! snow volume (km3)
93         zbg_area = glob_sum( 'icedia', at_i(:,:) * e1e2t(:,:) ) * 1.e-6  ! area (km2)
94         zbg_isal = glob_sum( 'icedia', st_i(:,:) * e1e2t(:,:) ) * 1.e-9  ! salt content (pss*km3)
95         zbg_item = glob_sum( 'icedia', et_i(:,:) * e1e2t(:,:) ) * 1.e-20 ! heat content (1.e20 J)
96         zbg_stem = glob_sum( 'icedia', et_s(:,:) * e1e2t(:,:) ) * 1.e-20 ! heat content (1.e20 J)
97
98         CALL iom_put( 'ibgvol_tot'  , zbg_ivol ) 
99         CALL iom_put( 'sbgvol_tot'  , zbg_svol ) 
100         CALL iom_put( 'ibgarea_tot' , zbg_area ) 
101         CALL iom_put( 'ibgsalt_tot' , zbg_isal ) 
102         CALL iom_put( 'ibgheat_tot' , zbg_item ) 
103         CALL iom_put( 'sbgheat_tot' , zbg_stem ) 
104 
105      ENDIF
106
107      ! ---------------------------!
108      ! 2 - Trends due to forcing  !
109      ! ---------------------------!
110      ! they must be kept outside an IF(iom_use) because of the call to dia_rst below
111      z_frc_volbot = r1_rau0 * glob_sum( 'icedia', -( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) ) * 1.e-9   ! freshwater flux ice/snow-ocean
112      z_frc_voltop = r1_rau0 * glob_sum( 'icedia', -( wfx_sub(:,:) + wfx_spr(:,:) )                    * e1e2t(:,:) ) * 1.e-9   ! freshwater flux ice/snow-atm
113      z_frc_sal    = r1_rau0 * glob_sum( 'icedia', -      sfx(:,:)                                     * e1e2t(:,:) ) * 1.e-9   ! salt fluxes ice/snow-ocean
114      z_frc_tembot =           glob_sum( 'icedia',  qt_oce_ai(:,:)                                     * e1e2t(:,:) ) * 1.e-20  ! heat on top of ocean (and below ice)
115      z_frc_temtop =           glob_sum( 'icedia',  qt_atm_oi(:,:)                                     * e1e2t(:,:) ) * 1.e-20  ! heat on top of ice-coean
116      !
117      frc_voltop  = frc_voltop  + z_frc_voltop  * rdt_ice ! km3
118      frc_volbot  = frc_volbot  + z_frc_volbot  * rdt_ice ! km3
119      frc_sal     = frc_sal     + z_frc_sal     * rdt_ice ! km3*pss
120      frc_temtop  = frc_temtop  + z_frc_temtop  * rdt_ice ! 1.e20 J
121      frc_tembot  = frc_tembot  + z_frc_tembot  * rdt_ice ! 1.e20 J
122
123      CALL iom_put( 'ibgfrcvoltop' , frc_voltop )   ! vol  forcing ice/snw-atm          (km3 equivalent ocean water)
124      CALL iom_put( 'ibgfrcvolbot' , frc_volbot )   ! vol  forcing ice/snw-ocean        (km3 equivalent ocean water)
125      CALL iom_put( 'ibgfrcsal'    , frc_sal    )   ! sal - forcing                     (psu*km3 equivalent ocean water)   
126      CALL iom_put( 'ibgfrctemtop' , frc_temtop )   ! heat on top of ice/snw/ocean      (1.e20 J)   
127      CALL iom_put( 'ibgfrctembot' , frc_tembot )   ! heat on top of ocean(below ice)   (1.e20 J)   
128
129      IF(  iom_use('ibgfrchfxtop') .OR. iom_use('ibgfrchfxbot') ) THEN
130         CALL iom_put( 'ibgfrchfxtop' , frc_temtop * z1_e1e2 * 1.e-20 * kt*rdt ) ! heat on top of ice/snw/ocean      (W/m2)
131         CALL iom_put( 'ibgfrchfxbot' , frc_tembot * z1_e1e2 * 1.e-20 * kt*rdt ) ! heat on top of ocean(below ice)   (W/m2)
132      ENDIF
133     
134      ! ---------------------------------- !
135      ! 3 -  Content variations and drifts !
136      ! ---------------------------------- !
137      IF(  iom_use('ibgvolume') .OR. iom_use('ibgsaltco') .OR. iom_use('ibgheatco') .OR. iom_use('ibgheatfx') ) THEN
138           
139         zdiff_vol = r1_rau0 * glob_sum( 'icedia', ( rhoi*vt_i(:,:) + rhos*vt_s(:,:) - vol_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9   ! freshwater trend (km3)
140         zdiff_sal = r1_rau0 * glob_sum( 'icedia', ( rhoi*st_i(:,:)                  - sal_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9   ! salt content trend (km3*pss)
141         zdiff_tem =           glob_sum( 'icedia', ( et_i(:,:) + et_s(:,:)           - tem_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-20  ! heat content trend (1.e20 J)
142         !                               + SUM( qevap_ice * a_i_b, dim=3 )       !! clem: I think this term should not be there (but needs a check)
143         
144         zdiff_vol = zdiff_vol - ( frc_voltop + frc_volbot )
145         zdiff_sal = zdiff_sal - frc_sal
146         zdiff_tem = zdiff_tem - ( frc_tembot - frc_temtop )
147         
148         CALL iom_put( 'ibgvolume' , zdiff_vol )   ! ice/snow volume  drift            (km3 equivalent ocean water)         
149         CALL iom_put( 'ibgsaltco' , zdiff_sal )   ! ice salt content drift            (psu*km3 equivalent ocean water)
150         CALL iom_put( 'ibgheatco' , zdiff_tem )   ! ice/snow heat content drift       (1.e20 J)
151         !
152      ENDIF
153     
154      IF( lrst_ice )   CALL ice_dia_rst( 'WRITE', kt_ice )
155      !
156      IF( ln_timing )   CALL timing_stop('ice_dia')
157      !
158   END SUBROUTINE ice_dia
159
160
161   SUBROUTINE ice_dia_init
162      !!---------------------------------------------------------------------------
163      !!                  ***  ROUTINE ice_dia_init  ***
164      !!     
165      !! ** Purpose: Initialization for the heat salt volume budgets
166      !!
167      !! ** Method : Compute initial heat content, salt content and volume
168      !!
169      !! ** Action : - Compute initial heat content, salt content and volume
170      !!             - Initialize forcing trends
171      !!             - Compute coefficients for conversion
172      !!---------------------------------------------------------------------------
173      INTEGER            ::   ios, ierror   ! local integer
174      !!
175      NAMELIST/namdia/ ln_icediachk, rn_icechk_cel, rn_icechk_glo, ln_icediahsb, ln_icectl, iiceprt, jiceprt 
176      !!----------------------------------------------------------------------
177      !
178      READ  ( numnam_ice_ref, namdia, IOSTAT = ios, ERR = 901)
179901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdia in reference namelist' )
180      READ  ( numnam_ice_cfg, namdia, IOSTAT = ios, ERR = 902 )
181902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namdia in configuration namelist' )
182      IF(lwm) WRITE ( numoni, namdia )
183      !
184      IF(lwp) THEN                  ! control print
185         WRITE(numout,*)
186         WRITE(numout,*) 'ice_dia_init: ice diagnostics'
187         WRITE(numout,*) ' ~~~~~~~~~~~'
188         WRITE(numout,*) '   Namelist namdia:'
189         WRITE(numout,*) '      Diagnose online heat/mass/salt conservation ln_icediachk  = ', ln_icediachk
190         WRITE(numout,*) '         threshold for conservation (gridcell)    rn_icechk_cel = ', rn_icechk_cel
191         WRITE(numout,*) '         threshold for conservation (global)      rn_icechk_glo = ', rn_icechk_glo
192         WRITE(numout,*) '      Output          heat/mass/salt budget       ln_icediahsb  = ', ln_icediahsb
193         WRITE(numout,*) '      control prints for a given grid point       ln_icectl     = ', ln_icectl
194         WRITE(numout,*) '         chosen grid point position          (iiceprt,jiceprt)  = (', iiceprt,',', jiceprt,')'
195      ENDIF
196      !     
197      IF( ln_icediahsb ) THEN
198         IF( ice_dia_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'ice_dia_init : unable to allocate arrays' )   ! allocate tke arrays
199         CALL ice_dia_rst( 'READ' )   ! read or initialize all required files
200      ENDIF
201      !
202   END SUBROUTINE ice_dia_init
203
204
205   SUBROUTINE ice_dia_rst( cdrw, kt )
206      !!---------------------------------------------------------------------
207      !!                   ***  ROUTINE icedia_rst  ***
208      !!                     
209      !! ** Purpose :   Read or write DIA file in restart file
210      !!
211      !! ** Method  :   use of IOM library
212      !!----------------------------------------------------------------------
213      CHARACTER(len=*) , INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag
214      INTEGER, OPTIONAL, INTENT(in) ::   kt     ! ice time-step
215      !
216      INTEGER  ::   iter    ! local integer
217      REAL(wp) ::   ziter   ! local scalar
218      !!----------------------------------------------------------------------
219      !
220      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise
221         IF( ln_rstart ) THEN                   !* Read the restart file
222            !
223            CALL iom_get( numrir, 'kt_ice' , ziter )
224            IF(lwp) WRITE(numout,*)
225            IF(lwp) WRITE(numout,*) 'ice_dia_rst read at time step = ', ziter
226            IF(lwp) WRITE(numout,*) '~~~~~~~~~~'
227            CALL iom_get( numrir, 'frc_voltop' , frc_voltop  )
228            CALL iom_get( numrir, 'frc_volbot' , frc_volbot  )
229            CALL iom_get( numrir, 'frc_temtop' , frc_temtop  )
230            CALL iom_get( numrir, 'frc_tembot' , frc_tembot  )
231            CALL iom_get( numrir, 'frc_sal'    , frc_sal     )
232            CALL iom_get( numrir, jpdom_autoglo, 'vol_loc_ini', vol_loc_ini )
233            CALL iom_get( numrir, jpdom_autoglo, 'tem_loc_ini', tem_loc_ini )
234            CALL iom_get( numrir, jpdom_autoglo, 'sal_loc_ini', sal_loc_ini )
235         ELSE
236            IF(lwp) WRITE(numout,*)
237            IF(lwp) WRITE(numout,*) ' ice_dia at initial state '
238            IF(lwp) WRITE(numout,*) '~~~~~~~'
239            ! set trends to 0
240            frc_voltop  = 0._wp                                         
241            frc_volbot  = 0._wp                                         
242            frc_temtop  = 0._wp                                                 
243            frc_tembot  = 0._wp                                                 
244            frc_sal     = 0._wp                                                 
245            ! record initial ice volume, salt and temp
246            vol_loc_ini(:,:) = rhoi * vt_i(:,:) + rhos * vt_s(:,:)  ! ice/snow volume (kg/m2)
247            tem_loc_ini(:,:) = et_i(:,:) + et_s(:,:)                ! ice/snow heat content (J)
248            sal_loc_ini(:,:) = rhoi * st_i(:,:)                     ! ice salt content (pss*kg/m2)
249         ENDIF
250         !
251      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file
252         !                                   ! -------------------
253         iter = kt + nn_fsbc - 1   ! ice restarts are written at kt == nitrst - nn_fsbc + 1
254         !
255         IF( iter == nitrst ) THEN
256            IF(lwp) WRITE(numout,*)
257            IF(lwp) WRITE(numout,*) 'ice_dia_rst write at time step = ', kt
258            IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
259         ENDIF
260         !
261         ! Write in numriw (if iter == nitrst)
262         ! ------------------
263         CALL iom_rstput( iter, nitrst, numriw, 'frc_voltop' , frc_voltop  )
264         CALL iom_rstput( iter, nitrst, numriw, 'frc_volbot' , frc_volbot  )
265         CALL iom_rstput( iter, nitrst, numriw, 'frc_temtop' , frc_temtop  )
266         CALL iom_rstput( iter, nitrst, numriw, 'frc_tembot' , frc_tembot  )
267         CALL iom_rstput( iter, nitrst, numriw, 'frc_sal'    , frc_sal     )
268         CALL iom_rstput( iter, nitrst, numriw, 'vol_loc_ini', vol_loc_ini )
269         CALL iom_rstput( iter, nitrst, numriw, 'tem_loc_ini', tem_loc_ini )
270         CALL iom_rstput( iter, nitrst, numriw, 'sal_loc_ini', sal_loc_ini )
271         !
272      ENDIF
273      !
274   END SUBROUTINE ice_dia_rst
275 
276#else
277   !!----------------------------------------------------------------------
278   !!   Default option :         Empty module         NO SI3 sea-ice model
279   !!----------------------------------------------------------------------
280#endif
281
282   !!======================================================================
283END MODULE icedia
Note: See TracBrowser for help on using the repository browser.