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.
ice_2.F90 in branches/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/LIM_SRC_2 – NEMO

source: branches/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/LIM_SRC_2/ice_2.F90 @ 5058

Last change on this file since 5058 was 5058, checked in by clem, 9 years ago

LIM3: add a namelist parameter to change the shape of ice thickness categories

  • Property svn:keywords set to Id
File size: 14.7 KB
RevLine 
[821]1MODULE ice_2
[3]2   !!======================================================================
3   !!                        ***  MODULE ice  ***
4   !! Sea Ice physics:  diagnostics variables of ice defined in memory
5   !!=====================================================================
[2715]6   !! History :  2.0  ! 2003-08  (C. Ethe)  F90: Free form and module
7   !!            3.3  ! 2009-05  (G.Garric) addition of the lim2_evp cas
8   !!            4.0  ! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation
[888]9   !!----------------------------------------------------------------------
[821]10#if defined key_lim2
[3]11   !!----------------------------------------------------------------------
[821]12   !!   'key_lim2' :                                  LIM 2.0 sea-ice model
[3]13   !!----------------------------------------------------------------------
[2715]14   USE par_ice_2      ! LIM sea-ice parameters
[3]15
16   IMPLICIT NONE
[12]17   PRIVATE
[2528]18   
[2715]19   PUBLIC    ice_alloc_2  !  Called in iceini_2.F90
20
[3625]21   INTEGER , PUBLIC ::   numit        !: ice iteration index
22   REAL(wp), PUBLIC ::   rdt_ice      !: ice time step
[3]23
[4147]24   !                                                   !!* namicerun read in iceini  *
25   CHARACTER(len=32)     , PUBLIC ::   cn_icerst_in     !: suffix of ice restart name (input)
26   CHARACTER(len=32)     , PUBLIC ::   cn_icerst_out    !: suffix of ice restart name (output)
27   LOGICAL               , PUBLIC ::   ln_limdyn        !: flag for ice dynamics (T) or not (F)
28   LOGICAL               , PUBLIC ::   ln_limdmp        !: Ice damping
29   REAL(wp)              , PUBLIC ::   hsndif           !: snow temp. computation (0) or not (9999)
30   REAL(wp)              , PUBLIC ::   hicdif           !: ice  temp. computation (0) or not (9999)
31   REAL(wp), DIMENSION(2), PUBLIC ::   acrit            !: minimum lead fraction in the 2 hemisphere
32   !
33   LOGICAL               , PUBLIC ::   ln_nicep      = .TRUE.     !: flag grid points output (T) or not (F)
34   !                                !!* ice-dynamic namelist (namicedyn) *
35   INTEGER , PUBLIC ::   nbiter      !: number of sub-time steps for relaxation
36   INTEGER , PUBLIC ::   nbitdr      !: maximum number of iterations for relaxation
37   INTEGER , PUBLIC ::   nevp        !: number of EVP subcycling iterations
38   INTEGER , PUBLIC ::   telast      !: timescale for EVP elastic waves
39   REAL(wp), PUBLIC ::   epsd        !: tolerance parameter for dynamic
40   REAL(wp), PUBLIC ::   alpha       !: coefficient for semi-implicit coriolis
41   REAL(wp), PUBLIC ::   dm          !: diffusion constant for dynamics
42   REAL(wp), PUBLIC ::   om          !: relaxation constant
43   REAL(wp), PUBLIC ::   resl        !: maximum value for the residual of relaxation
44   REAL(wp), PUBLIC ::   cw          !: drag coefficient for oceanic stress
45   REAL(wp), PUBLIC ::   angvg       !: turning angle for oceanic stress
46   REAL(wp), PUBLIC ::   pstar       !: first bulk-rheology parameter
47   REAL(wp), PUBLIC ::   c_rhg       !: second bulk-rhelogy parameter
48   REAL(wp), PUBLIC ::   etamn       !: minimun value for viscosity
49   REAL(wp), PUBLIC ::   creepl      !: creep limit
50   REAL(wp), PUBLIC ::   ecc         !: eccentricity of the elliptical yield curve
51   REAL(wp), PUBLIC ::   ahi0        !: sea-ice hor. eddy diffusivity coeff. (m2/s)
52   REAL(wp), PUBLIC ::   alphaevp    !: coefficient for the solution of EVP int. stresses
[3]53
[2528]54   REAL(wp), PUBLIC ::   usecc2                !:  = 1.0 / ( ecc * ecc )
55   REAL(wp), PUBLIC ::   rhoco                 !: = rau0 * cw
56   REAL(wp), PUBLIC ::   sangvg, cangvg        !: sin and cos of the turning angle for ocean stress
57   REAL(wp), PUBLIC ::   pstarh                !: pstar / 2.0
[3]58
[5058]59   !                                !!** switch for presence of ice or not
60   REAL(wp), PUBLIC ::   rswitch
61
[2715]62   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ahiu , ahiv   !: hor. diffusivity coeff. at ocean U- and V-points (m2/s)
63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   pahu , pahv   !: ice hor. eddy diffusivity coef. at ocean U- and V-points
64   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ust2s         !: friction velocity
[2528]65
66   !!* Ice Rheology
[4306]67
68   LOGICAL , PUBLIC::  ltrcdm2dc_ice = .FALSE.              !: In case of Diurnal Cycle short wave, compute a Daily Mean short waves flux
69
[2528]70# if defined key_lim2_vp
71   !                                                      !!* VP rheology *
72   LOGICAL , PUBLIC ::   lk_lim2_vp = .TRUE.               !: Visco-Plactic reology flag
73   !
[2715]74   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hsnm , hicm   !: mean snow and ice thicknesses
[2528]75   !
76# else
77   !                                                      !!* EVP rheology *
78   LOGICAL , PUBLIC::   lk_lim2_vp = .FALSE.               !: Visco-Plactic reology flag
79   !
[2715]80   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress1_i     !: first stress tensor element       
81   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress2_i     !: second stress tensor element
82   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress12_i    !: diagonal stress tensor element
83   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   delta_i       !: rheology delta factor (see Flato and Hibler 95) [s-1]
84   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   divu_i        !: Divergence of the velocity field [s-1] -> limrhg.F90
85   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   shear_i       !: Shear of the velocity field [s-1] -> limrhg.F90
86   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   at_i          !: ice fraction
[2528]87   !
88   REAL(wp), PUBLIC, DIMENSION(:,:)    , POINTER :: vt_s ,vt_i    !: mean snow and ice thicknesses
[2715]89   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:), TARGET  :: hsnm , hicm   !: target vt_s,vt_i pointers
[2528]90#endif
[3]91
[2715]92   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rdvosif       !: ice volume change at ice surface (only used for outputs)
93   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rdvobif       !: ice volume change at ice bottom  (only used for outputs)
94   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fdvolif       !: Total   ice volume change (only used for outputs)
95   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rdvonif       !: Lateral ice volume change (only used for outputs)
96   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sist          !: Sea-Ice Surface Temperature [Kelvin]
97   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tfu           !: Freezing/Melting point temperature of sea water at SSS
98   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hicif         !: Ice thickness
99   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hsnif         !: Snow thickness
100   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hicifp        !: Ice production/melting
101   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   frld          !: Leads fraction = 1-a/totalarea
102   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   phicif        !: ice thickness  at previous time
103   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   pfrld         !: Leads fraction at previous time 
104   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qstoif        !: Energy stored in the brine pockets
105   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fbif          !: Heat flux at the ice base
[3625]106   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rdm_snw       !: Variation of snow mass over 1 time step           [Kg/m2]
107   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rdq_snw       !: Heat content associated with rdm_snw              [J/m2]
108   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rdm_ice       !: Variation of ice  mass over 1 time step           [Kg/m2]
109   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rdq_ice       !: Heat content associated with rdm_ice              [J/m2]
[2715]110   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qldif         !: heat balance of the lead (or of the open ocean)
111   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qcmif         !: Energy needed to freeze the ocean surface layer
112   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fdtcn         !: net downward heat flux from the ice to the ocean
113   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qdtcn         !: energy from the ice to the ocean point (at a factor 2)
114   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   thcm          !: part of the solar energy used in the lead heat budget
[4306]115   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fstric_daymean!: Solar flux transmitted trough the ice, for day mean of qsr ( PISCES, with dirunal cycle )
[2715]116   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fstric        !: Solar flux transmitted trough the ice
117   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ffltbif       !: linked with the max heat contained in brine pockets (?)
118   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fscmbq        !: Linked with the solar flux below the ice (?)
119   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fsbbq         !: Also linked with the solar flux below the ice (?)
120   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qfvbq         !: used to store energy in case of toral lateral ablation (?)
121   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   dmgwi         !: Variation of the mass of snow ice
122   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_ice, v_ice  !: two components of the ice   velocity at I-point (m/s)
123   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_oce, v_oce  !: two components of the ocean velocity at I-point (m/s)
[3]124
[2715]125   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tbif  !: Temperature inside the ice/snow layer
[3]126
[888]127   !!* moment used in the advection scheme
[2715]128   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sxice, syice, sxxice, syyice, sxyice   !: for ice  volume
129   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sxsn,  sysn,  sxxsn,  syysn,  sxysn    !: for snow volume                 
130   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sxa,   sya,   sxxa,   syya,   sxya     !: for ice cover area               
131   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sxc0,  syc0,  sxxc0,  syyc0,  sxyc0    !: for heat content of snow         
132   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sxc1,  syc1,  sxxc1,  syyc1,  sxyc1    !: for heat content of 1st ice layer
133   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sxc2,  syc2,  sxxc2,  syyc2,  sxyc2    !: for heat content of 2nd ice layer
134   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sxst,  syst,  sxxst,  syyst,  sxyst    !: for heat content of brine pockets
135   !!----------------------------------------------------------------------
136   CONTAINS
[3]137
[2715]138   INTEGER FUNCTION ice_alloc_2()
139      !!-----------------------------------------------------------------
140      !!               *** FUNCTION ice_alloc_2 ***
141      !!-----------------------------------------------------------------
142      USE lib_mpp, ONLY:   ctl_warn   ! MPP library
143      INTEGER :: ierr(9)              ! Local variables
144      !!-----------------------------------------------------------------
145      ierr(:) = 0
146      !
147      ALLOCATE( ahiu(jpi,jpj) , pahu(jpi,jpj) ,                      &
148         &      ahiv(jpi,jpj) , pahv(jpi,jpj) , ust2s(jpi,jpj) , STAT=ierr(1) )
149         !
150      !* Ice Rheology
151#if defined key_lim2_vp
152      ALLOCATE( hsnm(jpi,jpj) , hicm(jpi,jpj) , STAT=ierr(2) )
[3]153#else
[2715]154      ALLOCATE( stress1_i (jpi,jpj) , delta_i(jpi,jpj) , at_i(jpi,jpj) ,     &
155                stress2_i (jpi,jpj) , divu_i (jpi,jpj) , hsnm(jpi,jpj) ,     &
156                stress12_i(jpi,jpj) , shear_i(jpi,jpj) , hicm(jpi,jpj) , STAT=ierr(2) )
157#endif
158      ALLOCATE( rdvosif(jpi,jpj) , rdvobif(jpi,jpj) ,                      &
159         &      fdvolif(jpi,jpj) , rdvonif(jpi,jpj) ,                      &
160         &      sist   (jpi,jpj) , tfu    (jpi,jpj) , hicif(jpi,jpj) ,     &
161         &      hsnif  (jpi,jpj) , hicifp (jpi,jpj) , frld (jpi,jpj) , STAT=ierr(3) )
162
163      ALLOCATE(phicif(jpi,jpj) , pfrld  (jpi,jpj) , qstoif (jpi,jpj) ,     &
[3625]164         &     fbif  (jpi,jpj) , rdm_snw(jpi,jpj) , rdq_snw(jpi,jpj) ,     &
165         &                       rdm_ice(jpi,jpj) , rdq_ice(jpi,jpj) ,     &
[2715]166         &     qldif (jpi,jpj) , qcmif  (jpi,jpj) , fdtcn  (jpi,jpj) ,     &
167         &     qdtcn (jpi,jpj) , thcm   (jpi,jpj)                    , STAT=ierr(4) )
168
169      ALLOCATE(fstric(jpi,jpj) , ffltbif(jpi,jpj) , fscmbq(jpi,jpj) ,     &
170         &     fsbbq (jpi,jpj) , qfvbq  (jpi,jpj) , dmgwi (jpi,jpj) ,     &
171         &     u_ice (jpi,jpj) , v_ice  (jpi,jpj) ,                       &
172         &     u_oce (jpi,jpj) , v_oce  (jpi,jpj) ,                       &
173         &     tbif  (jpi,jpj,jplayersp1)                           , STAT=ierr(5))
174
[4306]175      IF( ltrcdm2dc_ice ) ALLOCATE(fstric_daymean(jpi,jpj), STAT=ierr(6) )
176
[2715]177      !* moment used in the advection scheme
178      ALLOCATE(sxice (jpi,jpj) , syice (jpi,jpj) , sxxice(jpi,jpj) ,     &
179         &     syyice(jpi,jpj) , sxyice(jpi,jpj) ,                       &
180         &     sxsn  (jpi,jpj) , sysn  (jpi,jpj) , sxxsn (jpi,jpj) ,     &
181         &     syysn (jpi,jpj) , sxysn (jpi,jpj)                   , STAT=ierr(6) )
182      ALLOCATE(sxa   (jpi,jpj) , sya   (jpi,jpj) , sxxa  (jpi,jpj) ,     &
183         &     syya  (jpi,jpj) , sxya  (jpi,jpj) ,                       & 
184         &     sxc0  (jpi,jpj) , syc0  (jpi,jpj) , sxxc0 (jpi,jpj) ,     &
185         &     syyc0 (jpi,jpj) , sxyc0 (jpi,jpj)                   , STAT=ierr(7))
186      ALLOCATE(sxc1  (jpi,jpj) , syc1  (jpi,jpj) , sxxc1 (jpi,jpj) ,     &
187         &     syyc1 (jpi,jpj) , sxyc1 (jpi,jpj) ,                       &
188         &     sxc2  (jpi,jpj) , syc2  (jpi,jpj) , sxxc2 (jpi,jpj) ,     &
189         &     syyc2 (jpi,jpj) , sxyc2 (jpi,jpj)                   , STAT=ierr(8))
190      ALLOCATE(sxst  (jpi,jpj) , syst  (jpi,jpj) , sxxst (jpi,jpj) ,     &
191         &     syyst (jpi,jpj) , sxyst (jpi,jpj)                   , STAT=ierr(9))
192         !
193      ice_alloc_2 = MAXVAL( ierr )
194      !
195      IF( ice_alloc_2 /= 0 )   CALL ctl_warn('ice_alloc_2: failed to allocate arrays')
196      !
197   END FUNCTION ice_alloc_2
198
199#else
[3]200   !!----------------------------------------------------------------------
[821]201   !!   Default option         Empty module        NO LIM 2.0 sea-ice model
[3]202   !!----------------------------------------------------------------------
[4306]203   LOGICAL , PUBLIC::  ltrcdm2dc_ice = .FALSE.              !: In case of Diurnal Cycle short wave, compute a Daily Mean short waves flux
[3]204#endif
[2715]205   !!-----------------------------------------------------------------
[2528]206   !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010)
207   !! $Id$
208   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[3]209   !!======================================================================
[821]210END MODULE ice_2
Note: See TracBrowser for help on using the repository browser.