MODULE ice #if defined key_lim3 !!---------------------------------------------------------------------- !! 'key_lim3' : LIM3 sea-ice model !!---------------------------------------------------------------------- !! History : !! 2.0 ! 03-08 (C. Ethe) F90: Free form and module !! 3.0 ! 08-03 (M. Vancoppenolle) : LIM3 ! !!---------------------------------------------------------------------- !! LIM 3.0, UCL-LOCEAN-IPSL (2005) !! $ Id: $ !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt !!---------------------------------------------------------------------- !! * Modules used USE par_ice ! LIM sea-ice parameters IMPLICIT NONE PRIVATE !! !!====================================================================== !! *** MODULE ice *** !! !! ************** !! * L I M 3.0 * !! ************** !! !! ''in ice we trust'' !! !! This module contains the sea ice !! diagnostics variables of ice defined !! in memory !! !!====================================================================== !! !! LIM3 by the use of sweat, agile fingers and sometimes brain juice, !! was developed in Louvain-la-Neuve by : !! !! * Martin Vancoppenolle (UCL-ASTR, Belgium) !! * Sylvain Bouillon (UCL-ASTR, Belgium) !! * Miguel Angel Morales Maqueda (POL, UK) !! !! Based on extremely valuable earlier work by !! !! * Thierry Fichefet !! * Hugues Goosse !! !! The following persons also contributed to the code in various ways !! !! * Gurvan Madec, Claude Talandier, Christian Ethe !! and Rachid Benshila (LOCEAN-IPSL, France) !! * Xavier Fettweis (UCL-ASTR), Ralph Timmermann (AWI, Germany) !! * Bill Lipscomb (LANL), Cecilia Bitz (UWa) !! and Elisabeth Hunke (LANL), USA. !! !! (c) UCL-ASTR, 2005-2008 !! !! For more info, the interested user is kindly invited to consult the !! following references !! For model description and validation : !! * Vancoppenolle et al., Ocean Modelling, 2008a. !! * Vancoppenolle et al., Ocean Modelling, 2008b. !! !! For a specific description of EVP : !! * Bouillon et al., in prep for 2008. !! !! Or the reference manual, that should be available by 2009 !! !!====================================================================== !! | !! ***************************************** | !! * * | !! ************ I C E S T A T E V A R I A B L E S **************** | !! * * | !! ***************************************** | !! | !! Introduction : | !! -------------- | !! | !! Every ice-covered grid cell is characterized by a series of state | !! variables. To account for unresolved spatial variability in ice | !! thickness, the ice cover in divided in ice thickness categories. | !! | !! Sea ice state variables depend on the ice thickness category | !! | !! Those variables are divided into two groups | !! * Extensive (or global) variables. | !! These are the variables that are transported by all means | !! * Intensive (or equivalent) variables. | !! These are the variables that are either physically more | !! meaningful and/or used in ice thermodynamics | !! | !! Routines in limvar.F90 perform conversions | !! - lim_var_glo2eqv : from global to equivalent variables | !! - lim_var_eqv2glo : from equivalent to global variables | !! | !! For various purposes, the sea ice state variables have sometimes | !! to be aggregated over all ice thickness categories. This operation | !! is done in : | !! - lim_var_agg | !! | !! in icestp.F90, the routines that compute the changes in the ice | !! state variables are called | !! - lim_dyn : ice dynamics | !! - lim_trp : ice transport | !! - lim_itd_me : mechanical redistribution (ridging and rafting) | !! - lim_thd : ice halo-thermodynamics | !! - lim_itd_th : thermodynamic changes in ice thickness distribution | !! and creation of new ice | !! | !! See the associated routines for more information | !! | !! List of ice state variables : | !! ----------------------------- | !! | !!-------------|-------------|---------------------------------|-------| !! name in | name in | meaning | units | !! 2D routines | 1D routines | | | !!-------------|-------------|---------------------------------|-------| !! | !! ******************************************************************* | !! *** Dynamical variables (prognostic) *** | !! ******************************************************************* | !! | !! u_ice | - | Comp. U of the ice velocity | m/s | !! v_ice | - | Comp. V of the ice velocity | m/s | !! | !! ******************************************************************* | !! *** Category dependent state variables (prognostic) *** | !! ******************************************************************* | !! | !! ** Global variables | !! | !!-------------|-------------|---------------------------------|-------| !! a_i | a_i_b | Ice concentration | | !! v_i | - | Ice volume per unit area | m | !! v_s | - | Snow volume per unit area | m | !! smv_i | - | Sea ice salt content | ppt.m | !! oa_i ! - ! Sea ice areal age content | day | !! e_i ! - ! Ice enthalpy | 10^9 J| !! - ! q_i_b ! Ice enthalpy per unit vol. | J/m3 | !! e_s ! - ! Snow enthalpy | 10^9 J| !! - ! q_s_b ! Snow enthalpy per unit vol. | J/m3 | !! | !!-------------|-------------|---------------------------------|-------| !! | !! ** Equivalent variables | !! | !!-------------|-------------|---------------------------------|-------| !! | !! ht_i | ht_i_b | Ice thickness | m | !! ht_s ! ht_s_b | Snow depth | m | !! sm_i ! sm_i_b | Sea ice bulk salinity ! ppt | !! s_i ! s_i_b | Sea ice salinity profile ! ppt | !! o_i ! - | Sea ice Age ! days | !! t_i ! t_i_b | Sea ice temperature ! K | !! t_s ! t_s_b | Snow temperature ! K | !! t_su ! t_su_b | Sea ice surface temperature ! K | !! | !! notes: the ice model only sees a bulk (i.e., vertically averaged) | !! salinity, except in thermodynamic computations, for which | !! the salinity profile is computed as a function of bulk | !! salinity | !! | !! the sea ice surface temperature is not associated to any | !! heat content. Therefore, it is not a state variable and | !! does not have to be advected. Nevertheless, it has to be | !! computed to determine whether the ice is melting or not | !! | !! ******************************************************************* | !! *** Category-summed state variables (diagnostic) *** | !! ******************************************************************* | !! at_i | at_i_b | Total ice concentration | | !! vt_i | - | Total ice vol. per unit area | m | !! vt_s | - | Total snow vol. per unit ar. | m | !! smt_i | - | Mean sea ice salinity | ppt | !! tm_i | - | Mean sea ice temperature | K | !! ot_i ! - ! Sea ice areal age content | day | !! et_i ! - ! Total ice enthalpy | 10^9 J| !! et_s ! - ! Total snow enthalpy | 10^9 J| !! bv_i ! - ! Mean relative brine volume | ??? | !! | !! | !!===================================================================== LOGICAL, PUBLIC :: & con_i = .false. ! switch for conservation test !!-------------------------------------------------------------------------- !! * Share Module variables !!-------------------------------------------------------------------------- INTEGER , PUBLIC :: & !!: ** ice-dynamic namelist (namicedyn) ** nbiter = 1 , & !: number of sub-time steps for relaxation nbitdr = 250 , & !: maximum number of iterations for relaxation nevp = 400 , & !: number of iterations for subcycling nlay_i = 5 !: number of layers in the ice REAL(wp), PUBLIC :: & !!: ** ice-dynamic namelist (namicedyn) ** epsd = 1.0e-20, & !: tolerance parameter for dynamic alpha = 0.5 , & !: coefficient for semi-implicit coriolis dm = 0.6e+03, & !: diffusion constant for dynamics om = 0.5 , & !: relaxation constant resl = 5.0e-05, & !: maximum value for the residual of relaxation cw = 5.0e-03, & !: drag coefficient for oceanic stress angvg = 0.0 , & !: turning angle for oceanic stress pstar = 1.0e+04, & !: determines ice strength (N/M), Hibler JPO79 c_rhg = 20.0 , & !: determines changes in ice strength etamn = 0.0e+07, & !: minimun value for viscosity : has to be 0 creepl = 2.0e-08, & !: creep limit : has to be under 1.0e-9 ecc = 2.0 , & !: eccentricity of the elliptical yield curve ahi0 = 350.e0 , & !: sea-ice hor. eddy diffusivity coeff. (m2/s) telast = 2880.0 , & !: timescale for elastic waves (s) !SB alphaevp = 1.0 , & !: coeficient of the internal stresses !SB unit_fac = 1.0e9 !: conversion factor for ice / snow enthalpy REAL(wp), PUBLIC :: & !!: ** ice-salinity namelist (namicesal) ** s_i_max = 20.0 , & !: maximum ice salinity (ppt) s_i_min = 0.1 , & !: minimum ice salinity (ppt) s_i_0 = 3.5 , & !: 1st sal. value for the computation of sal .prof. !: (ppt) s_i_1 = 4.5 , & !: 2nd sal. value for the computation of sal .prof. !: (ppt) sal_G = 5.00 , & !: restoring salinity for gravity drainage !: (ppt) sal_F = 2.50 , & !: restoring salinity for flushing !: (ppt) time_G = 1.728e+06,&!: restoring time constant for gravity drainage !: (= 20 days, in s) time_F = 8.640e+05,&!: restoring time constant for gravity drainage !: (= 10 days, in s) bulk_sal = 4.0 !: bulk salinity (ppt) in case of constant salinity INTEGER , PUBLIC :: & !!: ** ice-salinity namelist (namicesal) ** num_sal = 1 , & !: salinity configuration used in the model !: 1 - s constant in space and time !: 2 - prognostic salinity (s(z,t)) !: 3 - salinity profile, constant in time !: 4 - salinity variations affect only ice ! thermodynamics sal_prof = 1 , & !: salinity profile or not thcon_i_swi = 1 !: thermal conductivity of Untersteiner (1964) (1) or !: Pringle et al (2007) (2) REAL(wp), PUBLIC :: & !!: ** ice-mechanical redistribution namelist (namiceitdme) Cs = 0.25 , & !!: fraction of shearing energy contributing to ridging Cf = 17.0 , & !!: ratio of ridging work to PE loss fsnowrdg = 0.5 , & !!: fractional snow loss to the ocean during ridging fsnowrft = 0.5 , & !!: fractional snow loss to the ocean during ridging Gstar = 0.15 , & !!: fractional area of young ice contributing to ridging astar = 0.05 , & !!: equivalent of G* for an exponential participation function Hstar = 100.0 , & !!: thickness that determines the maximal thickness of ridged !!: ice hparmeter = 0.75, & !!: threshold thickness (m) for rafting / ridging Craft = 5.0 , & !!: coefficient for smoothness of the hyperbolic tangent in rafting ridge_por = 0.0 , & !!: initial porosity of ridges (0.3 regular value) sal_max_ridge = 15.0, & !!: maximum ridged ice salinity (ppt) betas = 1.0 , & !:: coef. for partitioning of snowfall between leads and sea ice kappa_i = 1.0 , & !!: coefficient for the extinction of radiation !!: Grenfell et al. (2006) (m-1) nconv_i_thd = 50 , & !!: maximal number of iterations for heat diffusion maxer_i_thd = 1.0e-4 !!: maximal tolerated error (C) for heat diffusion INTEGER , PUBLIC :: & !!: ** ice-mechanical redistribution namelist (namiceitdme) ridge_scheme_swi = 0, & !!: scheme used for ice ridging raftswi = 1, & !!: rafting of ice or not partfun_swi = 1, & !!: participation function Thorndike et al. JGR75 (0) !!: or Lipscomb et al. JGR07 (1) transfun_swi = 0, & !!: transfer function of Hibler, MWR80 (0) !!: or Lipscomb et al., 2007 (1) brinstren_swi = 0 !!: use brine volume to diminish ice strength REAL(wp), PUBLIC :: & !: usecc2 , & !: = 1.0 / ( ecc * ecc ) rhoco , & !: = rau0 * cw sangvg, cangvg , & !: sin and cos of the turning angle for ocean stress pstarh !: pstar / 2.0 REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: u_oce, v_oce , & !: surface ocean velocity used in ice dynamics ahiu , ahiv , & !: hor. diffusivity coeff. at ocean U- and V-points (m2/s) pahu , pahv , & !: ice hor. eddy diffusivity coef. at ocean U- and V-points ust2s, hicol , & !: friction velocity, ice collection thickness accreted in leads strength , & !: ice strength strp1, strp2 , & !: strength at previous time steps stress1_i , & !: first stress tensor element stress2_i , & !: second stress tensor element stress12_i , & !: diagonal stress tensor element delta_i , & !: Delta factor for the ice rheology (see Flato and Hibler 95) [s-1] -> limrhg.F90 divu_i , & !: Divergence of the velocity field [s-1] -> limrhg.F90 shear_i !: Shear of the velocity field [s-1] -> limrhg.F90 REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: firic , & !: IR flux over the ice (only used for outputs) fcsic , & !: Sensible heat flux over the ice (only used for outputs) fleic , & !: Latent heat flux over the ice (only used for outputs) qlatic , & !: latent flux rdvosif, & !: Variation of volume at surface (only used for outputs) rdvobif, & !: Variation of ice volume at the bottom ice (only used for outputs) fdvolif, & !: Total variation of ice volume (only used for outputs) rdvonif, & !: Lateral Variation of ice volume (only used for outputs) sist , & !: Average Sea-Ice Surface Temperature (Kelvin ??? degree ??? I don't know) t_bo , & !: Sea-Ice bottom temperature (Kelvin) hicifp , & !: Ice production/melting !obsolete... can be removed frld , & !: Leads fraction = 1-a/totalarea REFERS TO LEAD FRACTION everywhere !: except in the OUTPUTS!!!! pfrld , & !: Leads fraction at previous time phicif , & !: Old ice thickness fbif , & !: Heat flux at the ice base rdmsnif, & !: Variation of snow mass rdmicif, & !: Variation of ice mass qldif , & !: heat balance of the lead (or of the open ocean) qcmif , & !: Energy needed to bring the ocean surface layer until its freezing fdtcn , & !: net downward heat flux from the ice to the ocean qdtcn , & !: energy from the ice to the ocean fstric , & !: transmitted solar radiation under ice fscmbq , & !: associated with lead chipotage with solar flux ffltbif, & !: Array linked with the max heat contained in brine pockets (?) fsbbq , & !: Also linked with the solar flux below the ice (?) qfvbq , & !: Array used to store energy in case of toral lateral ablation (?) dmgwi , & !: Variation of the mass of snow ice fsalt_res, & !: Residual salt flux due to correction of ice thickness fsbri , & !: Salt flux due to brine rejection fsalt_rpo, & !: Salt flux associated with porous ridged ice formation fheat_rpo, & !: Heat flux associated with porous ridged ice formation fhbri , & !: heat flux due to brine rejection fmmec , & !: Mass flux due to snow loss during compression fseqv , & !: Equivalent salt flux due to ice growth/melt fheat_res, & !: Residual heat flux due to correction of ice thickness fhmec !: Heat flux due to snow loss during compression REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: albege , & !: Albedo of the snow or ice (only for outputs) albecn , & !: Albedo of the ocean (only for outputs) tauc !: Cloud optical depth ! temporary arrays for dummy version of the code REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: dh_i_surf2D, dh_i_bott2D, fstbif, fsup2D, focea2D, q_s INTEGER, PUBLIC, DIMENSION(jpi, jpj, jpl) :: & !:: patho_case ! number of the pathological case (if any, of course) !!-------------------------------------------------------------------------- !! * Ice global state variables !!-------------------------------------------------------------------------- !! Variables defined for each ice category REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) :: & !: ht_i , & !: Ice thickness (m) a_i , & !: Ice fractional areas (concentration) v_i , & !: Ice volume per unit area (m) v_s , & !: Snow volume per unit area(m) ht_s , & !: Snow thickness (m) t_su , & !: Sea-Ice Surface Temperature (K) sm_i , & !: Sea-Ice Bulk salinity (ppt) smv_i , & !: Sea-Ice Bulk salinity times volume per area (ppt.m) !: this is an extensive variable that has to be transported o_i , & !: Sea-Ice Age (days) ov_i , & !: Sea-Ice Age times volume per area (days.m) oa_i !: Sea-Ice Age times ice area (days) !! Variables summed over all categories, or associated to !! all the ice in a single grid cell REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: u_ice, v_ice, & !: two components of the ice velocity (m/s) tio_u, tio_v, & !: two components of the ice-ocean stress (N/m2) vt_i , & !: ice total volume per unit area (m) vt_s , & !: snow total volume per unit area (m) at_i , & !: ice total fractional area (ice concentration) ato_i , & !: total open water fractional area (1-at_i) et_i , & !: total ice heat content et_s , & !: total snow heat content ot_i , & !: mean age over all categories tm_i , & !: mean ice temperature over all categories bv_i , & !: brine volume averaged over all categories smt_i !: mean sea ice salinity averaged over all categories REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpm) :: & !: at_i_typ , & !: total area contained in each ice type vt_i_typ !: total volume contained in each ice type REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpsmax) :: & !: scal0 !: ??? REAL(wp), PUBLIC, DIMENSION(jpi,jpj,nlay_s,jpl) :: & !: t_s, & !: Snow temperatures (K) e_s REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) :: & !: ! go to trash e_i_cat REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jkmax,jpl) :: & !: t_i, & !: Ice temperatures [ Kelvins ] e_i, & !: Ice thermal contents [ Joules*10^9 ] s_i !: Ice salinities REAL(wp), DIMENSION(jpi,jpj,0:jpkmax+1) :: & !: reslum !: Relative absorption of solar radiation in each ocean level !!-------------------------------------------------------------------------- !! * Moments for advection !!-------------------------------------------------------------------------- REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: sxopw, syopw, sxxopw, syyopw, sxyopw !: open water in sea ice REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) :: & !: sxice, syice, sxxice, syyice, sxyice, & !: ice thickness moments for advection sxsn, sysn, sxxsn, syysn, sxysn, & !: snow thickness sxa, sya, sxxa, syya, sxya, & !: lead fraction sxc0, syc0, sxxc0, syyc0, sxyc0, & !: snow thermal content sxsal, sysal, sxxsal, syysal, sxysal, & !: ice salinity sxage, syage, sxxage, syyage, sxyage !: ice age REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jkmax,jpl) :: & !: sxe , sye , sxxe , syye , sxye !: ice layers heat content !!-------------------------------------------------------------------------- !! * Old values of global variables !!-------------------------------------------------------------------------- REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) :: & !: old_v_s, old_v_i, & !: snow and ice volumes old_a_i, old_smv_i, old_oa_i REAL(wp), PUBLIC, DIMENSION(jpi,jpj,nlay_s,jpl) :: & !: old_e_s !: snow heat content REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jkmax,jpl) :: & !: old_e_i !: ice temperatures REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: ice velocity (gv6 and gv7) old_u_ice, old_v_ice !!-------------------------------------------------------------------------- !! * Increment of global variables !!-------------------------------------------------------------------------- ! thd refers to changes induced by thermodynamics ! trp '' '' '' advection (transport of ice) REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) :: & !: d_a_i_thd , d_a_i_trp , & !: icefractions d_v_s_thd , d_v_s_trp, & !: snow volume d_v_i_thd , d_v_i_trp, & !: ice volume d_smv_i_thd, d_smv_i_trp, & d_sm_i_fl , d_sm_i_gd , & d_sm_i_se , d_sm_i_si , d_sm_i_la , & d_oa_i_thd , d_oa_i_trp, s_i_newice REAL(wp), PUBLIC, DIMENSION(jpi,jpj,nlay_s,jpl) :: & !: d_e_s_thd, d_e_s_trp REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jkmax,jpl) :: & !: d_e_i_thd, d_e_i_trp REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: ice velocity d_u_ice_dyn, d_v_ice_dyn !!-------------------------------------------------------------------------- !! * Ice thickness distribution variables !!-------------------------------------------------------------------------- ! REMOVE INTEGER, PUBLIC, DIMENSION(jpl) :: & !: ice_types !: Vector making the connection between types and categories INTEGER, PUBLIC, DIMENSION(jpm,2) :: & !: ice_cat_bounds !: Matrix containing the integer upper and !: lower boundaries of ice thickness categories ! REMOVE INTEGER, PUBLIC, DIMENSION(jpm) :: & !: ice_ncat_types !: Vector containing the number of thickness categories in each ice type REAL(wp), PUBLIC, DIMENSION(0:jpl) :: & !: hi_max !: Boundary of ice thickness categories in thickness space REAL(wp), PUBLIC, DIMENSION(jpl) :: & !: hi_mean !: Mean ice thickness in catgories ! REMOVE REAL(wp), PUBLIC, DIMENSION(0:jpl,jpm) :: & !: hi_max_typ !: Boundary of ice thickness categories !:in thickness space (same but specific for each ice type) !!-------------------------------------------------------------------------- !! * Ice Run !!-------------------------------------------------------------------------- !! Namelist namicerun read in iceini LOGICAL , PUBLIC :: & !!! ** init namelist (namicerun) ** ln_limdyn = .TRUE., & !: flag for ice dynamics (T) or not (F) ln_nicep = .TRUE. !: flag for sea-ice points output (T) or not (F) REAL(wp), PUBLIC :: & !: hsndif = 0.e0 , & !: computation of temp. in snow (0) or not (9999) hicdif = 0.e0 , & !: computation of temp. in ice (0) or not (9999) cai = 1.40e-3 , & !: atmospheric drag over sea ice cao = 1.00e-3 !: atmospheric drag over ocean REAL(wp), PUBLIC, DIMENSION(2) :: & !: acrit = (/ 1.e-06 , 1.e-06 /) !: minimum fraction for leads in ! ! north and south hemisphere !!-------------------------------------------------------------------------- !! * Ice diagnostics !!-------------------------------------------------------------------------- !! Check if everything down here is necessary REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & !: volume of ice formed in the leads v_newice REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) :: & !: thermodynamic growth rates dv_dt_thd, & izero, fstroc, fhbricat REAL(wp), PUBLIC, DIMENSION(jpi,jpj) :: & diag_sni_gr, & ! snow ice growth diag_lat_gr, & ! lateral ice growth diag_bot_gr, & ! bottom ice growth diag_dyn_gr, & ! dynamical ice growth diag_bot_me, & ! vertical bottom melt diag_sur_me ! vertical surface melt INTEGER , PUBLIC :: jiindx, jjindx !: indexes of the debugging point #else !!---------------------------------------------------------------------- !! Default option Empty module NO LIM sea-ice model !!---------------------------------------------------------------------- #endif !!====================================================================== END MODULE ice