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/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/ICE – NEMO

source: NEMO/branches/2021/dev_r14273_HPC-02_Daley_Tiling/src/ICE/icedia.F90 @ 14806

Last change on this file since 14806 was 14806, checked in by hadcv, 3 years ago

#2600: Merge in trunk changes to r14778

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