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 branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedia.F90 @ 8506

Last change on this file since 8506 was 8505, checked in by clem, 7 years ago

changes in style - part5 - start changing init routines

File size: 15.8 KB
Line 
1MODULE icedia
2   !!======================================================================
3   !!                       ***  MODULE icedia  ***
4   !!  Sea-Ice model :   global budgets
5   !!======================================================================
6   !! History :  3.4  ! 2012-10  (C. Rousset)  original code
7   !!            4.0  ! 2017-08  (C. Rousset)  fits nemo4.0 standards
8   !!----------------------------------------------------------------------
9#if defined key_lim3
10   !!----------------------------------------------------------------------
11   !!   'key_lim3'                                       LIM3 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 ice            ! LIM-3: sea-ice variable
18   USE dom_oce        ! ocean domain
19   USE phycst         ! physical constant
20   USE daymod         ! model calendar
21   USE sbc_oce , ONLY : sfx   ! surface boundary condition: ocean fields
22   USE icerst         ! ice restart
23   !
24   USE in_out_manager ! I/O manager
25   USE lib_mpp        ! MPP library
26   USE timing         ! preformance summary
27   USE iom            ! I/O manager
28   USE lib_fortran    ! glob_sum
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), DIMENSION(:,:), ALLOCATABLE ::   vol_loc_ini, sal_loc_ini, tem_loc_ini ! initial volume, salt and heat contents
37   REAL(wp)                              ::   frc_sal, frc_voltop, frc_volbot, frc_temtop, frc_tembot  ! global forcing trends
38   
39   !! * Substitutions
40#  include "vectopt_loop_substitute.h90"
41   !!----------------------------------------------------------------------
42   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
43   !! $Id: icedia.F90 8413 2017-08-07 17:05:39Z clem $
44   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
46CONTAINS
47
48   SUBROUTINE ice_dia( kt )
49      !!---------------------------------------------------------------------------
50      !!                  ***  ROUTINE ice_dia  ***
51      !!     
52      !! ** Purpose:   Compute the sea-ice global heat content, salt content
53      !!             and volume conservation
54      !!---------------------------------------------------------------------------
55      INTEGER, INTENT(in) ::   kt   ! ocean time step
56      !!
57      REAL(wp)   ::   zbg_ivol, zbg_item, zbg_area, zbg_isal
58      REAL(wp)   ::   zbg_svol, zbg_stem
59      REAL(wp)   ::   z_frc_voltop, z_frc_temtop, z_frc_sal
60      REAL(wp)   ::   z_frc_volbot, z_frc_tembot 
61      REAL(wp)   ::   zdiff_vol, zdiff_sal, zdiff_tem 
62      !!---------------------------------------------------------------------------
63      IF( nn_timing == 1 )   CALL timing_start('ice_dia')
64
65      IF( kt == nit000 .AND. lwp ) THEN
66         WRITE(numout,*)
67         WRITE(numout,*)'icedia : outpout ice diagnostics (integrated over the domain)'
68         WRITE(numout,*)'~~~~~~'
69      ENDIF
70
71!!gm glob_sum includes a " * tmask_i ", so remove  " * tmask(:,:,1) "
72
73      ! ----------------------- !
74      ! 1 -  Contents !
75      ! ----------------------- !
76      zbg_ivol = glob_sum( vt_i(:,:) * e1e2t(:,:) ) * 1.e-9                  ! ice volume (km3)
77      zbg_svol = glob_sum( vt_s(:,:) * e1e2t(:,:) ) * 1.e-9                  ! snow volume (km3)
78      zbg_area = glob_sum( at_i(:,:) * e1e2t(:,:) ) * 1.e-6                  ! area (km2)
79      zbg_isal = glob_sum( SUM( smv_i(:,:,:), dim=3 ) * e1e2t(:,:) ) * 1.e-9 ! salt content (pss*km3)
80      zbg_item = glob_sum( et_i * e1e2t(:,:) ) * 1.e-20                      ! heat content (1.e20 J)
81      zbg_stem = glob_sum( et_s * e1e2t(:,:) ) * 1.e-20                      ! heat content (1.e20 J)
82     
83      ! ---------------------------!
84      ! 2 - Trends due to forcing  !
85      ! ---------------------------!
86      z_frc_volbot = r1_rau0 * glob_sum( - ( wfx_ice(:,:) + wfx_snw(:,:) + wfx_err_sub(:,:) ) * e1e2t(:,:) ) * 1.e-9  ! freshwater flux ice/snow-ocean
87      z_frc_voltop = r1_rau0 * glob_sum( - ( wfx_sub(:,:) + wfx_spr(:,:) ) * e1e2t(:,:) ) * 1.e-9                     ! freshwater flux ice/snow-atm
88      z_frc_sal    = r1_rau0 * glob_sum(   - sfx(:,:) * e1e2t(:,:) ) * 1.e-9                                          ! salt fluxes ice/snow-ocean
89      z_frc_tembot =           glob_sum( hfx_out(:,:) * e1e2t(:,:) ) * 1.e-20                                         ! heat on top of ocean (and below ice)
90      z_frc_temtop =           glob_sum( hfx_in (:,:) * e1e2t(:,:) ) * 1.e-20                                         ! heat on top of ice-coean
91      !
92      frc_voltop  = frc_voltop  + z_frc_voltop  * rdt_ice ! km3
93      frc_volbot  = frc_volbot  + z_frc_volbot  * rdt_ice ! km3
94      frc_sal     = frc_sal     + z_frc_sal     * rdt_ice ! km3*pss
95      frc_temtop  = frc_temtop  + z_frc_temtop  * rdt_ice ! 1.e20 J
96      frc_tembot  = frc_tembot  + z_frc_tembot  * rdt_ice ! 1.e20 J
97           
98      ! ----------------------- !
99      ! 3 -  Content variations !
100      ! ----------------------- !
101      zdiff_vol = r1_rau0 * glob_sum( ( rhoic*vt_i(:,:) + rhosn*vt_s(:,:) - vol_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! freshwater trend (km3)
102      zdiff_sal = r1_rau0 * glob_sum( ( rhoic* SUM( smv_i(:,:,:), dim=3 ) - sal_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-9 ! salt content trend (km3*pss)
103      zdiff_tem =           glob_sum( ( et_i(:,:) + et_s(:,:)             - tem_loc_ini(:,:) ) * e1e2t(:,:) ) * 1.e-20 ! heat content trend (1.e20 J)
104      !                               + SUM( qevap_ice * a_i_b, dim=3 )       !! clem: I think this term should not be there (but needs a check)
105
106      ! ----------------------- !
107      ! 4 -  Drifts             !
108      ! ----------------------- !
109      zdiff_vol = zdiff_vol - ( frc_voltop + frc_volbot )
110      zdiff_sal = zdiff_sal - frc_sal
111      zdiff_tem = zdiff_tem - ( frc_tembot - frc_temtop )
112
113      ! ----------------------- !
114      ! 5 - Diagnostics writing !
115      ! ----------------------- !
116!!gm I don't understand the division by the ocean surface (i.e. glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt )
117!!   and its multiplication bu kt ! is it really what we want ? what is this quantity ?
118!!   IF it is really what we want, compute it at kt=nit000, not 3 time by time-step !
119!!   kt*rdt  : you mean rdtice ?
120!!gm
121      !
122      IF( iom_use('ibgvolume')    )   CALL iom_put( 'ibgvolume' , zdiff_vol     )   ! ice/snow volume  drift            (km3 equivalent ocean water)         
123      IF( iom_use('ibgsaltco')    )   CALL iom_put( 'ibgsaltco' , zdiff_sal     )   ! ice salt content drift            (psu*km3 equivalent ocean water)
124      IF( iom_use('ibgheatco')    )   CALL iom_put( 'ibgheatco' , zdiff_tem     )   ! ice/snow heat content drift       (1.e20 J)
125      IF( iom_use('ibgheatfx')    )   CALL iom_put( 'ibgheatfx' ,               &   ! ice/snow heat flux drift          (W/m2)
126         &                                                     zdiff_tem /glob_sum( e1e2t(:,:) * 1.e-20 * kt*rdt ) )
127
128      IF( iom_use('ibgfrcvoltop') )   CALL iom_put( 'ibgfrcvoltop' , frc_voltop )   ! vol  forcing ice/snw-atm          (km3 equivalent ocean water)
129      IF( iom_use('ibgfrcvolbot') )   CALL iom_put( 'ibgfrcvolbot' , frc_volbot )   ! vol  forcing ice/snw-ocean        (km3 equivalent ocean water)
130      IF( iom_use('ibgfrcsal')    )   CALL iom_put( 'ibgfrcsal'    , frc_sal    )   ! sal - forcing                     (psu*km3 equivalent ocean water)   
131      IF( iom_use('ibgfrctemtop') )   CALL iom_put( 'ibgfrctemtop' , frc_temtop )   ! heat on top of ice/snw/ocean      (1.e20 J)   
132      IF( iom_use('ibgfrctembot') )   CALL iom_put( 'ibgfrctembot' , frc_tembot )   ! heat on top of ocean(below ice)   (1.e20 J)   
133      IF( iom_use('ibgfrchfxtop') )   CALL iom_put( 'ibgfrchfxtop' ,            &   ! heat on top of ice/snw/ocean      (W/m2)
134         &                                                          frc_temtop / glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt  )
135      IF( iom_use('ibgfrchfxbot') )   CALL iom_put( 'ibgfrchfxbot' ,            &   ! heat on top of ocean(below ice)   (W/m2)
136         &                                                          frc_tembot / glob_sum( e1e2t(:,:) ) * 1.e-20 * kt*rdt  )
137
138      IF( iom_use('ibgvol_tot' )  )   CALL iom_put( 'ibgvol_tot'  , zbg_ivol     )   ! ice volume                       (km3)
139      IF( iom_use('sbgvol_tot' )  )   CALL iom_put( 'sbgvol_tot'  , zbg_svol     )   ! snow volume                      (km3)
140      IF( iom_use('ibgarea_tot')  )   CALL iom_put( 'ibgarea_tot' , zbg_area     )   ! ice area                         (km2)
141      IF( iom_use('ibgsalt_tot')  )   CALL iom_put( 'ibgsalt_tot' , zbg_isal     )   ! ice salinity content             (pss*km3)
142      IF( iom_use('ibgheat_tot')  )   CALL iom_put( 'ibgheat_tot' , zbg_item     )   ! ice heat content                 (1.e20 J)
143      IF( iom_use('sbgheat_tot')  )   CALL iom_put( 'sbgheat_tot' , zbg_stem     )   ! snow heat content                (1.e20 J)
144      !
145      IF( lrst_ice )   CALL ice_dia_rst( 'WRITE', kt_ice )
146      !
147      IF( nn_timing == 1 )   CALL timing_stop('ice_dia')
148      !
149   END SUBROUTINE ice_dia
150
151
152   SUBROUTINE ice_dia_init
153      !!---------------------------------------------------------------------------
154      !!                  ***  ROUTINE ice_dia_init  ***
155      !!     
156      !! ** Purpose: Initialization for the heat salt volume budgets
157      !!
158      !! ** Method : Compute initial heat content, salt content and volume
159      !!
160      !! ** Action : - Compute initial heat content, salt content and volume
161      !!             - Initialize forcing trends
162      !!             - Compute coefficients for conversion
163      !!---------------------------------------------------------------------------
164      INTEGER            ::   ios, ierror   ! local integer
165      !!
166      NAMELIST/namicediag/ ln_limdiachk, ln_limdiahsb, ln_limctl, iiceprt, jiceprt 
167      !!----------------------------------------------------------------------
168      !
169      REWIND( numnam_ice_ref )      ! Namelist namicediag in reference namelist : Parameters for ice
170      READ  ( numnam_ice_ref, namicediag, IOSTAT = ios, ERR = 901)
171901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicediag in reference namelist', lwp )
172
173      REWIND( numnam_ice_cfg )      ! Namelist namicediag in configuration namelist : Parameters for ice
174      READ  ( numnam_ice_cfg, namicediag, IOSTAT = ios, ERR = 902 )
175902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicediag in configuration namelist', lwp )
176      IF(lwm) WRITE ( numoni, namicediag )
177      !
178      IF(lwp) THEN                  ! control print
179         WRITE(numout,*)
180         WRITE(numout,*) 'ice_dia_init: ice diagnostics'
181         WRITE(numout,*) ' ~~~~~~~~~~~'
182         WRITE(numout,*) '   Namelist namicediag : '
183         WRITE(numout,*) '      Diagnose online heat/mass/salt budget      ln_limdiachk = ', ln_limdiachk
184         WRITE(numout,*) '      Output          heat/mass/salt budget      ln_limdiahsb = ', ln_limdiahsb
185         WRITE(numout,*) '      control prints for a given grid point         ln_limctl = ', ln_limctl
186         WRITE(numout,*) '         chosen grid point position         (iiceprt,jiceprt) = (', iiceprt,',', jiceprt,')'
187      ENDIF
188      !     
189      IF( ln_limdiahsb ) THEN
190         ALLOCATE( vol_loc_ini(jpi,jpj), sal_loc_ini(jpi,jpj), tem_loc_ini(jpi,jpj), STAT=ierror )
191         IF( ierror > 0 )  THEN
192            CALL ctl_stop( 'ice_dia: unable to allocate vol_loc_ini' )
193            RETURN
194         ENDIF
195         !
196         CALL ice_dia_rst( 'READ' )  !* read or initialize all required files
197      ENDIF
198      !
199   END SUBROUTINE ice_dia_init
200
201
202   SUBROUTINE ice_dia_rst( cdrw, kt )
203      !!---------------------------------------------------------------------
204      !!                   ***  ROUTINE limdia_rst  ***
205      !!                     
206      !! ** Purpose :   Read or write DIA file in restart file
207      !!
208      !! ** Method  :   use of IOM library
209      !!----------------------------------------------------------------------
210      CHARACTER(len=*) , INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag
211      INTEGER, OPTIONAL, INTENT(in) ::   kt     ! ice time-step
212      !
213      INTEGER  ::   iter    ! local integer
214      REAL(wp) ::   ziter   ! local scalar
215      !!----------------------------------------------------------------------
216      !
217      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise
218         IF( ln_rstart ) THEN                   !* Read the restart file
219            !
220            CALL iom_get( numrir, 'kt_ice' , ziter )
221            IF(lwp) WRITE(numout,*)
222            IF(lwp) WRITE(numout,*) ' ice_dia_rst read at time step = ', ziter
223            IF(lwp) WRITE(numout,*) '~~~~~~~'
224            CALL iom_get( numrir, 'frc_voltop' , frc_voltop  )
225            CALL iom_get( numrir, 'frc_volbot' , frc_volbot  )
226            CALL iom_get( numrir, 'frc_temtop' , frc_temtop  )
227            CALL iom_get( numrir, 'frc_tembot' , frc_tembot  )
228            CALL iom_get( numrir, 'frc_sal'    , frc_sal     )
229            CALL iom_get( numrir, jpdom_autoglo, 'vol_loc_ini', vol_loc_ini )
230            CALL iom_get( numrir, jpdom_autoglo, 'tem_loc_ini', tem_loc_ini )
231            CALL iom_get( numrir, jpdom_autoglo, 'sal_loc_ini', sal_loc_ini )
232         ELSE
233            IF(lwp) WRITE(numout,*)
234            IF(lwp) WRITE(numout,*) ' ice_dia at initial state '
235            IF(lwp) WRITE(numout,*) '~~~~~~~'
236            ! set trends to 0
237            frc_voltop  = 0._wp                                         
238            frc_volbot  = 0._wp                                         
239            frc_temtop  = 0._wp                                                 
240            frc_tembot  = 0._wp                                                 
241            frc_sal     = 0._wp                                                 
242            ! record initial ice volume, salt and temp
243            vol_loc_ini(:,:) = rhoic * vt_i(:,:) + rhosn * vt_s(:,:)  ! ice/snow volume (kg/m2)
244            tem_loc_ini(:,:) = et_i(:,:) + et_s(:,:)                  ! ice/snow heat content (J)
245            sal_loc_ini(:,:) = rhoic * SUM( smv_i(:,:,:), dim=3 )     ! ice salt content (pss*kg/m2)
246         ENDIF
247         !
248      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file
249         !                                   ! -------------------
250         iter = kt + nn_fsbc - 1   ! ice restarts are written at kt == nitrst - nn_fsbc + 1
251         !
252         IF( iter == nitrst ) THEN
253            IF(lwp) WRITE(numout,*)
254            IF(lwp) WRITE(numout,*) ' ice_dia_rst write at time step = ', kt
255            IF(lwp) WRITE(numout,*) '~~~~~~~'
256         ENDIF
257         !
258         ! Write in numriw (if iter == nitrst)
259         ! ------------------
260         CALL iom_rstput( iter, nitrst, numriw, 'frc_voltop' , frc_voltop  )
261         CALL iom_rstput( iter, nitrst, numriw, 'frc_volbot' , frc_volbot  )
262         CALL iom_rstput( iter, nitrst, numriw, 'frc_temtop' , frc_temtop  )
263         CALL iom_rstput( iter, nitrst, numriw, 'frc_tembot' , frc_tembot  )
264         CALL iom_rstput( iter, nitrst, numriw, 'frc_sal'    , frc_sal     )
265         CALL iom_rstput( iter, nitrst, numriw, 'vol_loc_ini', vol_loc_ini )
266         CALL iom_rstput( iter, nitrst, numriw, 'tem_loc_ini', tem_loc_ini )
267         CALL iom_rstput( iter, nitrst, numriw, 'sal_loc_ini', sal_loc_ini )
268         !
269      ENDIF
270      !
271   END SUBROUTINE ice_dia_rst
272 
273#else
274   !!----------------------------------------------------------------------
275   !!   Default option :         Empty module          NO LIM sea-ice model
276   !!----------------------------------------------------------------------
277#endif
278
279   !!======================================================================
280END MODULE icedia
Note: See TracBrowser for help on using the repository browser.