123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161 |
- MODULE my_variables
- IMPLICIT NONE
- ! 0. Variable declaration
- ! -----------------------
- !
- ! 0.1 Type of real (that made me struggle so bad ARGH)
- INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(12,307)
- INTEGER, PARAMETER :: wp = dp
- REAL(wp) :: rzero = 0._wp
- REAL(wp) :: rone = 1._wp
- ! 0.1 File names
- CHARACTER(LEN=99) :: cfile_analysis_ice, cfile_forecast_ice, cfile_analysis_oce, cfile_forecast_oce
- CHARACTER(LEN=99) :: cfileout_ice = "ice_out.nc"
- CHARACTER(LEN=99) :: cfileout_oce = "oce_out.nc"
- CHARACTER(LEN=99) :: cinteger, cinteger2 ! To convert integers to strings
- ! 0.2 Model variable names (e.g. a_i_htc, v_i_htc, ...)
- CHARACTER(LEN=99) :: cvarroot, cvarname
- ! 0.3 File Opening & Reading
- LOGICAL :: l_ex ! whether a file exists or not
- INTEGER :: incid_ice_an_in, incid_mask, incid_mesh, incid_oce_an_in,&
- &incid_ice_an_out, incid_oce_an_out, incid_oce_fc_in, incid_ice_fc_in
- INTEGER :: ierr, ivarid, idimid(5) ! Error log, variable id
- ! & variable dimension
- !INTEGER :: varID ! The id given by the
- ! Netcdf
- !
- ! 0.4 Geometrical data (mask, mesh, domain dimensions)
- INTEGER :: jpi, jpj ! Horizontal grid dimensions
- INTEGER :: jpk ! Vertical
- INTEGER :: jpl, nlay_i ! Number of ice categories and layers
- INTEGER :: nlay_s ! Number of snow layers
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ze1t, ze2t ! Grid edge length
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zcellarea ! The product ze1t*ze2t
- INTEGER, ALLOCATABLE, DIMENSION(:,:) :: ilandmask ! Horizontal land-sea mask
- CHARACTER(LEN=99), PARAMETER :: cmaskfile = "mask.nc"
- CHARACTER(LEN=99), PARAMETER :: cmaskvar = "tmask"
- CHARACTER(LEN=99), PARAMETER :: cmeshfile = "mesh_hgr.nc"
- CHARACTER(LEN=99), PARAMETER :: ce1tvar = "e1t"
- CHARACTER(LEN=99), PARAMETER :: ce2tvar = "e2t"
- ! 0.5 Ice variables of interest
- REAL(wp) :: ztime_counter ! iteration
- REAL(wp), DIMENSION(:), ALLOCATABLE :: hi_max
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: a_i, v_i, ht_i, v_s,&
- & oa_i, smv_i, t_su,&
- & v_i_fc, v_s_fc
- ! -Ice concentration (jpi,jpj,jpl)
- ! -Ice volume per surface unit
- ! (jpi,jpj,jpl)
- ! -In situ thickness (jpi,jpj,jpl)
- ! -Snow volume per surface unit
- ! -Ice age
- ! -Ice salinity
- ! -Surface temperature
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: at_i, snwice_mass, snwice_mass_b
- ! Total (sum over categories) of conc.
- ! Snow ice loads
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: e_i, e_s
- ! ice enthalpy (jpi,jpi,nlay_i,jpl)
- ! snow ~
- CHARACTER(LEN=99) :: csss_m = "sss_m" ! Sea surf. salinity name in restart
- CHARACTER(LEN=99) :: csn = "sn" ! Sea salinity name in restart
- CHARACTER(LEN=99) :: csst_m = "sst_m" ! Sea surf. temperature name in restart
- CHARACTER(LEN=99) :: ctn = "tn" ! Sea temperature name in restart
- CHARACTER(LEN=99) :: cun = "un" ! Sea velocity
- CHARACTER(LEN=99) :: cub = "ub" ! Sea velocity
- CHARACTER(LEN=99) :: cvn = "vn" ! Sea velocity
- CHARACTER(LEN=99) :: cvb = "vb" ! Sea velocity
- CHARACTER(LEN=99) :: cssu_m = "ssu_m" ! Sea surf. velocity
- CHARACTER(LEN=99) :: cssv_m = "ssv_m" ! Sea surf. velocity
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: sss_m_an ! Sea surface salinity (jpi,jpj) of the analysis
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: sss_m_fc ! Sea surface salinity (jpi, jpj) of the forecast
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: sn_an ! Sea salinity (jpi,jpj,jpk) of the analysis
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: sn_fc ! Sea salinity (jpi,jpj,jpk) of the forecast
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: sst_m_an ! Sea surface temperature (jpi,jpj) of the analysis
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: sst_m_fc ! Sea surface temperature (jpi, jpj) of the forecast
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tn_an ! Sea temperature (jpi,jpj,jpk) of the analysis
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tn_fc ! Sea temperature (jpi,jpj,jpk) of the forecast
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: ub_an, ub_fc, un_an, un_fc ! Ocean velocity
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: vb_an, vb_fc, vn_an, vn_fc ! Ocean velocity
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ssu_m_an, ssu_m_fc ! Sea surface velocity
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ssv_m_an, ssv_m_fc ! Sea surface velocity
- REAL(wp) :: zalpha ! To discretize the thickness distribution
- REAL(wp) :: rn_himean ! Expected mean thickness (to construct the ITD bounds)
- REAL(wp) :: zhmax ! Max ITD bound (usually 3 x rn_himean)
- REAL(wp) :: znum ! temporary variable
- REAL(wp) :: zden ! temporary variable
- REAL(wp) :: zs ! temporary variable
- REAL(wp) :: r1_S0 ! ratio involved in the calculation of freezing point
- REAL(wp) :: zh ! Ratio between min thickness in
- ! category 1 and actual thickness in 1st
- ! category.
- REAL(wp) :: zda_i, zdv_i, zda_ex
- ! Possible excess of ice concentration
- ! 0.6 Variables for shift between categories
- INTEGER :: zshiftflag ! flag if at least one
- ! point in the domain
- ! has too thick/thin ice
- ! in the running category
- INTEGER, ALLOCATABLE, DIMENSION(:,:,:) :: idonor ! ice donor index. see below
- ! for detailed explanation
- INTEGER, ALLOCATABLE, DIMENSION(:,:,:) :: internal_melt ! Switch for internal melt
- ! of layers
- REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zdaice, zdvice
- ! Area and volume of ice
- ! transferred to other categories
- REAL(wp) :: ze_s ! local snow variable
- REAL(wp) :: zsaldiff, ztempdiff ! difference in
- ! salinity and temperature btw analysis and forecast
- REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zheat_res, zdmsnif
- ! Snow heat and mass release after melting
- LOGICAL :: l_adjust ! To tackle numerical
- ! problems with ice conc> 1 by epsilon
- ! 0.6 Switches
- REAL(wp) :: zindb, zindsn, zindic, zindg
- INTEGER :: num_sal = 2 !( see namelist )
- ! 0.6 Constants
- REAL(wp), PARAMETER :: epsi10 = 1.e-10_wp, epsi06 = 1.e-6_wp, epsi04 = 1.e-4_wp, &
- & epsi20= 1.e-20_wp, zbigvalue = 1.0e+20
- REAL(wp), PARAMETER :: zamax = 0.999 ! Maximum concentration -- see A. Barthélemy's modifs in the code
- REAL(wp), PARAMETER :: rtt = 273.16 ! 3ple point water
- REAL(wp), PARAMETER :: tmut = 0.054 ! Variation of sea ice melting point with temperature
- REAL(wp), PARAMETER :: zrho0 = 1020.0 ! Volumic mass water reference
- REAL(wp), PARAMETER :: zrhoic = 917.0 ! Volumic mass sea ice
- REAL(wp), PARAMETER :: zcpic = 2067.0 ! Specific heat for ice
- REAL(wp), PARAMETER :: zrhosn = 330.0 ! Volumic mass snow density
- REAL(wp), PARAMETER :: zlfus = 0.334e+6 ! Latent heat fusion fresh ice
- REAL(wp), PARAMETER :: zrcp = 4.0e+3 ! Specific heat for sea water
- REAL(wp), PARAMETER :: zhiclim = 0.10 ! hiclim in the namelist, i.e. minimal
- !ice thickness in the 1st category
- REAL(wp), PARAMETER :: rdt_ice = 21600.0 ! Ice time step.
- INTEGER , PARAMETER :: nn_fsbc = 6 ! Frequency of ice model call (1
- ! time unit = 1 ocean time step)
- ! 0.7 Debug
- LOGICAL :: ldebug = .TRUE. ! to display messages
- INTEGER :: jiindx = 106 , jjindx = 118 ! Grid index for debugging
- END MODULE my_variables
|