my_variables.f90 9.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215
  1. # 0 "<stdin>"
  2. # 0 "<built-in>"
  3. # 0 "<command-line>"
  4. # 1 "/usr/include/stdc-predef.h" 1 3 4
  5. # 17 "/usr/include/stdc-predef.h" 3 4
  6. # 2 "<command-line>" 2
  7. # 1 "<stdin>"
  8. MODULE my_variables
  9. IMPLICIT NONE
  10. ! 0. Variable declaration
  11. ! -----------------------
  12. !
  13. ! 0.1 Type of real (that made me struggle so bad ARGH)
  14. INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND(12,307)
  15. INTEGER, PARAMETER :: wp = dp
  16. REAL(wp) :: rzero = 0._wp
  17. REAL(wp) :: rone = 1._wp
  18. ! 0.1 File names
  19. CHARACTER(LEN=99) :: cfile_analysis_ice, cfile_forecast_ice, cfile_analysis_oce, cfile_forecast_oce
  20. CHARACTER(LEN=99) :: cfileout_ice = "ice_out.nc"
  21. CHARACTER(LEN=99) :: cfileout_oce = "oce_out.nc"
  22. CHARACTER(LEN=99) :: cinteger, cinteger2 ! To convert integers to strings
  23. ! 0.2 Model variable names (e.g. a_i_htc, v_i_htc, ...)
  24. CHARACTER(LEN=99) :: cvarroot, cvarname
  25. ! 0.3 File Opening & Reading
  26. LOGICAL :: l_ex ! whether a file exists or not
  27. INTEGER :: incid_ice_an_in, incid_mask, incid_mesh, incid_oce_an_in,&
  28. &incid_ice_an_out, incid_oce_an_out, incid_oce_fc_in, incid_ice_fc_in
  29. INTEGER :: ierr, ivarid, idimid(5) ! Error log, variable id
  30. ! & variable dimension
  31. !INTEGER :: varID ! The id given by the
  32. ! Netcdf
  33. !
  34. ! 0.4 Geometrical data (mask, mesh, domain dimensions)
  35. INTEGER :: jpi, jpj ! Horizontal grid dimensions
  36. INTEGER :: jpk ! Vertical
  37. INTEGER :: jpl, nlay_i ! Number of ice categories and layers
  38. INTEGER :: nlay_s ! Number of snow layers
  39. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ze1t, ze2t ! Grid edge length
  40. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zcellarea ! The product ze1t*ze2t
  41. INTEGER, ALLOCATABLE, DIMENSION(:,:) :: ilandmask ! Horizontal land-sea mask
  42. CHARACTER(LEN=99), PARAMETER :: cmaskfile = "mask.nc"
  43. CHARACTER(LEN=99), PARAMETER :: cmaskvar = "tmask"
  44. CHARACTER(LEN=99), PARAMETER :: cmeshfile = "mesh_hgr.nc"
  45. CHARACTER(LEN=99), PARAMETER :: ce1tvar = "e1t"
  46. CHARACTER(LEN=99), PARAMETER :: ce2tvar = "e2t"
  47. ! 0.5 Ice variables of interest
  48. REAL(wp) :: ztime_counter ! iteration
  49. REAL(wp), DIMENSION(:), ALLOCATABLE :: hi_max
  50. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: a_i, v_i, ht_i, v_s,&
  51. & oa_i, smv_i, t_su,&
  52. & v_i_fc, v_s_fc
  53. ! -Ice concentration (jpi,jpj,jpl)
  54. ! -Ice volume per surface unit
  55. ! (jpi,jpj,jpl)
  56. ! -In situ thickness (jpi,jpj,jpl)
  57. ! -Snow volume per surface unit
  58. ! -Ice age
  59. ! -Ice salinity
  60. ! -Surface temperature
  61. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: at_i, snwice_mass, snwice_mass_b
  62. ! Total (sum over categories) of conc.
  63. ! Snow ice loads
  64. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: e_i, e_s
  65. ! ice enthalpy (jpi,jpi,nlay_i,jpl)
  66. ! snow ~
  67. CHARACTER(LEN=99) :: csss_m = "sss_m" ! Sea surf. salinity name in restart
  68. CHARACTER(LEN=99) :: csn = "sn" ! Sea salinity name in restart
  69. CHARACTER(LEN=99) :: csst_m = "sst_m" ! Sea surf. temperature name in restart
  70. CHARACTER(LEN=99) :: ctn = "tn" ! Sea temperature name in restart
  71. CHARACTER(LEN=99) :: cun = "un" ! Sea velocity
  72. CHARACTER(LEN=99) :: cub = "ub" ! Sea velocity
  73. CHARACTER(LEN=99) :: cvn = "vn" ! Sea velocity
  74. CHARACTER(LEN=99) :: cvb = "vb" ! Sea velocity
  75. CHARACTER(LEN=99) :: cssu_m = "ssu_m" ! Sea surf. velocity
  76. CHARACTER(LEN=99) :: cssv_m = "ssv_m" ! Sea surf. velocity
  77. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: sss_m_an ! Sea surface salinity (jpi,jpj) of the analysis
  78. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: sss_m_fc ! Sea surface salinity (jpi, jpj) of the forecast
  79. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: sn_an ! Sea salinity (jpi,jpj,jpk) of the analysis
  80. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: sn_fc ! Sea salinity (jpi,jpj,jpk) of the forecast
  81. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: sst_m_an ! Sea surface temperature (jpi,jpj) of the analysis
  82. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: sst_m_fc ! Sea surface temperature (jpi, jpj) of the forecast
  83. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tn_an ! Sea temperature (jpi,jpj,jpk) of the analysis
  84. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: tn_fc ! Sea temperature (jpi,jpj,jpk) of the forecast
  85. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: ub_an, ub_fc, un_an, un_fc ! Ocean velocity
  86. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: vb_an, vb_fc, vn_an, vn_fc ! Ocean velocity
  87. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ssu_m_an, ssu_m_fc ! Sea surface velocity
  88. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ssv_m_an, ssv_m_fc ! Sea surface velocity
  89. REAL(wp) :: zalpha ! To discretize the thickness distribution
  90. REAL(wp) :: rn_himean ! Expected mean thickness (to construct the ITD bounds)
  91. REAL(wp) :: zhmax ! Max ITD bound (usually 3 x rn_himean)
  92. REAL(wp) :: znum ! temporary variable
  93. REAL(wp) :: zden ! temporary variable
  94. REAL(wp) :: zs ! temporary variable
  95. REAL(wp) :: r1_S0 ! ratio involved in the calculation of freezing point
  96. REAL(wp) :: zh ! Ratio between min thickness in
  97. ! category 1 and actual thickness in 1st
  98. ! category.
  99. REAL(wp) :: zda_i, zdv_i, zda_ex
  100. ! Possible excess of ice concentration
  101. ! 0.6 Variables for shift between categories
  102. INTEGER :: zshiftflag ! flag if at least one
  103. ! point in the domain
  104. ! has too thick/thin ice
  105. ! in the running category
  106. INTEGER, ALLOCATABLE, DIMENSION(:,:,:) :: idonor ! ice donor index. see below
  107. ! for detailed explanation
  108. INTEGER, ALLOCATABLE, DIMENSION(:,:,:) :: internal_melt ! Switch for internal melt
  109. ! of layers
  110. REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zdaice, zdvice
  111. ! Area and volume of ice
  112. ! transferred to other categories
  113. REAL(wp) :: ze_s ! local snow variable
  114. REAL(wp) :: zsaldiff, ztempdiff ! difference in
  115. ! salinity and temperature btw analysis and forecast
  116. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zheat_res, zdmsnif
  117. ! Snow heat and mass release after melting
  118. LOGICAL :: l_adjust ! To tackle numerical
  119. ! problems with ice conc> 1 by epsilon
  120. ! 0.6 Switches
  121. REAL(wp) :: zindb, zindsn, zindic, zindg
  122. INTEGER :: num_sal = 2 !( see namelist )
  123. ! 0.6 Constants
  124. REAL(wp), PARAMETER :: epsi10 = 1.e-10_wp, epsi06 = 1.e-6_wp, epsi04 = 1.e-4_wp, &
  125. & epsi20= 1.e-20_wp, zbigvalue = 1.0e+20
  126. REAL(wp), PARAMETER :: zamax = 0.999 ! Maximum concentration -- see A. Barthélemy's modifs in the code
  127. REAL(wp), PARAMETER :: rtt = 273.16 ! 3ple point water
  128. REAL(wp), PARAMETER :: tmut = 0.054 ! Variation of sea ice melting point with temperature
  129. REAL(wp), PARAMETER :: zrho0 = 1020.0 ! Volumic mass water reference
  130. REAL(wp), PARAMETER :: zrhoic = 917.0 ! Volumic mass sea ice
  131. REAL(wp), PARAMETER :: zcpic = 2067.0 ! Specific heat for ice
  132. REAL(wp), PARAMETER :: zrhosn = 330.0 ! Volumic mass snow density
  133. REAL(wp), PARAMETER :: zlfus = 0.334e+6 ! Latent heat fusion fresh ice
  134. REAL(wp), PARAMETER :: zrcp = 4.0e+3 ! Specific heat for sea water
  135. REAL(wp), PARAMETER :: zhiclim = 0.10 ! hiclim in the namelist, i.e. minimal
  136. !ice thickness in the 1st category
  137. REAL(wp), PARAMETER :: rdt_ice = 2700.0 !21600.0 ! Ice time step.
  138. INTEGER , PARAMETER :: nn_fsbc = 1 !6 ! Frequency of ice model call (1
  139. ! time unit = 1 ocean time step)
  140. ! 0.7 Debug
  141. LOGICAL :: ldebug = .TRUE. ! to display messages
  142. INTEGER :: jiindx = 279 , jjindx = 292! 279 292 Grid index for debugging
  143. END MODULE my_variables