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.
Changeset 834 for trunk/NEMO/LIM_SRC_3/ice.F90 – NEMO

Ignore:
Timestamp:
2008-03-07T18:11:35+01:00 (16 years ago)
Author:
ctlod
Message:

Clean comments and useless lines, see ticket:#72

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC_3/ice.F90

    r825 r834  
    11MODULE ice 
    2    !!====================================================================== 
    3    !!                        ***  MODULE ice  *** 
    4    !! Sea Ice physics:  diagnostics variables of ice defined in memory 
    5    !!===================================================================== 
    62#if defined key_lim3 
    73   !!---------------------------------------------------------------------- 
    8    !!   'key_lim3' :                                   LIM sea-ice model 
     4   !!   'key_lim3' :                                   LIM3 sea-ice model 
    95   !!---------------------------------------------------------------------- 
    106   !! History : 
    117   !!   2.0  !  03-08  (C. Ethe)  F90: Free form and module 
     8   !!   3.0  !  08-03  (M. Vancoppenolle) : LIM3 ! 
    129   !!---------------------------------------------------------------------- 
    13    !!  LIM 2.0, UCL-LOCEAN-IPSL (2005) 
     10   !!  LIM 3.0, UCL-LOCEAN-IPSL (2005) 
    1411   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/LIM_SRC/ice.F90,v 1.4 2005/03/27 18:34:41 opalod Exp $ 
    1512   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
     
    2017   IMPLICIT NONE 
    2118   PRIVATE 
     19   !! 
     20   !!====================================================================== 
     21   !!                        ***  MODULE ice  *** 
     22   !! 
     23   !!                           ************** 
     24   !!                           * L I M  3.0 * 
     25   !!                           ************** 
     26   !! 
     27   !!                         ''in ice we trust'' 
     28   !! 
     29   !!                   This module contains the sea ice  
     30   !!                 diagnostics variables of ice defined  
     31   !!                             in memory 
     32   !! 
     33   !!====================================================================== 
     34   !! 
     35   !! LIM3 by the use of sweat, agile fingers and sometimes brain juice,  
     36   !!  was developed in Louvain-la-Neuve by :  
     37   !! 
     38   !!    * Martin Vancoppenolle (UCL-ASTR, Belgium) 
     39   !!    * Sylvain Bouillon (UCL-ASTR, Belgium) 
     40   !!    * Miguel Angel Morales Maqueda (POL, UK) 
     41   !!  
     42   !! Based on extremely valuable earlier work by 
     43   !! 
     44   !!    * Thierry Fichefet 
     45   !!    * Hugues Goosse 
     46   !! 
     47   !! The following persons also contributed to the code in various ways 
     48   !! 
     49   !!    * Gurvan Madec, Claude Talandier, Christian Ethe  
     50   !!      and Rachid Benshila (LOCEAN-IPSL, France) 
     51   !!    * Xavier Fettweis (UCL-ASTR), Ralph Timmermann (AWI, Germany) 
     52   !!    * Bill Lipscomb (LANL), Cecilia Bitz (UWa)  
     53   !!      and Elisabeth Hunke (LANL), USA. 
     54   !!  
     55   !! (c) UCL-ASTR, 2005-2008 
     56   !! 
     57   !! For more info, the interested user is kindly invited to consult the 
     58   !! following references 
     59   !!    For model description and validation : 
     60   !!    * Vancoppenolle et al., Ocean Modelling, 2008a. 
     61   !!    * Vancoppenolle et al., Ocean Modelling, 2008b. 
     62   !! 
     63   !!    For a specific description of EVP : 
     64   !!    * Bouillon et al., in prep for 2008. 
     65   !! 
     66   !!    Or the reference manual, that should be available by 2009 
     67   !! 
     68   !!====================================================================== 
     69   !!                                                                     | 
     70   !!            *****************************************                | 
     71   !!            *                                       *                | 
     72   !! ************ I C E   S T A T E   V A R I A B L E S **************** | 
     73   !!            *                                       *                | 
     74   !!            *****************************************                | 
     75   !!                                                                     | 
     76   !! Introduction :                                                      | 
     77   !! --------------                                                      | 
     78   !!                                                                     | 
     79   !! Every ice-covered grid cell is characterized by a series of state   | 
     80   !! variables. To account for unresolved spatial variability in ice     | 
     81   !! thickness, the ice cover in divided in ice thickness categories.    | 
     82   !!                                                                     | 
     83   !! Sea ice state variables depend on the ice thickness category        | 
     84   !!                                                                     | 
     85   !! Those variables are divided into two groups                         | 
     86   !! * Extensive (or global) variables.                                  | 
     87   !!   These are the variables that are transported by all means         | 
     88   !! * Intensive (or equivalent) variables.                              | 
     89   !!   These are the variables that are either physically more           | 
     90   !!   meaningful and/or used in ice thermodynamics                      | 
     91   !!                                                                     | 
     92   !! Routines in limvar.F90 perform conversions                          | 
     93   !!  - lim_var_glo2eqv  : from global to equivalent variables           | 
     94   !!  - lim_var_eqv2glo  : from equivalent to global variables           | 
     95   !!                                                                     | 
     96   !! For various purposes, the sea ice state variables have sometimes    | 
     97   !! to be aggregated over all ice thickness categories. This operation  | 
     98   !! is done in :                                                        | 
     99   !!  - lim_var_agg                                                      | 
     100   !!                                                                     | 
     101   !! in icestp.F90, the routines that compute the changes in the ice     | 
     102   !! state variables are called                                          | 
     103   !! - lim_dyn : ice dynamics                                            | 
     104   !! - lim_trp : ice transport                                           | 
     105   !! - lim_itd_me : mechanical redistribution (ridging and rafting)      | 
     106   !! - lim_thd : ice halo-thermodynamics                                 | 
     107   !! - lim_itd_th : thermodynamic changes in ice thickness distribution  | 
     108   !!                and creation of new ice                              | 
     109   !!                                                                     | 
     110   !! See the associated routines for more information                    | 
     111   !!                                                                     | 
     112   !! List of ice state variables :                                       | 
     113   !! -----------------------------                                       | 
     114   !!                                                                     | 
     115   !!-------------|-------------|---------------------------------|-------| 
     116   !!   name in   |   name in   |              meaning            | units | 
     117   !! 2D routines | 1D routines |                                 |       | 
     118   !!-------------|-------------|---------------------------------|-------| 
     119   !!                                                                     | 
     120   !! ******************************************************************* | 
     121   !! ***         Dynamical variables (prognostic)                    *** | 
     122   !! ******************************************************************* | 
     123   !!                                                                     | 
     124   !! u_ice       |      -      |    Comp. U of the ice velocity  | m/s   | 
     125   !! v_ice       |      -      |    Comp. V of the ice velocity  | m/s   | 
     126   !!                                                                     | 
     127   !! ******************************************************************* | 
     128   !! ***         Category dependent state variables (prognostic)     *** | 
     129   !! ******************************************************************* | 
     130   !!                                                                     | 
     131   !! ** Global variables                                                 | 
     132   !!                                                                     | 
     133   !!-------------|-------------|---------------------------------|-------| 
     134   !! a_i         | a_i_b       |    Ice concentration            |       | 
     135   !! v_i         |      -      |    Ice volume per unit area     | m     | 
     136   !! v_s         |      -      |    Snow volume per unit area    | m     | 
     137   !! smv_i       |      -      |    Sea ice salt content         | ppt.m | 
     138   !! oa_i        !      -      !    Sea ice areal age content    | day   | 
     139   !! e_i         !      -      !    Ice enthalpy                 | 10^9 J|  
     140   !!      -      ! q_i_b       !    Ice enthalpy per unit vol.   | J/m3  |  
     141   !! e_s         !      -      !    Snow enthalpy                | 10^9 J|  
     142   !!      -      ! q_s_b       !    Snow enthalpy per unit vol.  | J/m3  |  
     143   !!                                                                     | 
     144   !!-------------|-------------|---------------------------------|-------| 
     145   !!                                                                     | 
     146   !! ** Equivalent variables                                             | 
     147   !!                                                                     | 
     148   !!-------------|-------------|---------------------------------|-------| 
     149   !!                                                                     | 
     150   !! ht_i        | ht_i_b      |    Ice thickness                | m     | 
     151   !! ht_s        ! ht_s_b      |    Snow depth                   | m     | 
     152   !! sm_i        ! sm_i_b      |    Sea ice bulk salinity        ! ppt   | 
     153   !! s_i         ! s_i_b       |    Sea ice salinity profile     ! ppt   | 
     154   !! o_i         !      -      |    Sea ice Age                  ! days  | 
     155   !! t_i         ! t_i_b       |    Sea ice temperature          ! K     | 
     156   !! t_s         ! t_s_b       |    Snow temperature             ! K     | 
     157   !! t_su        ! t_su_b      |    Sea ice surface temperature  ! K     | 
     158   !!                                                                     | 
     159   !! notes: the ice model only sees a bulk (i.e., vertically averaged)   | 
     160   !!        salinity, except in thermodynamic computations, for which    | 
     161   !!        the salinity profile is computed as a function of bulk       | 
     162   !!        salinity                                                     | 
     163   !!                                                                     | 
     164   !!        the sea ice surface temperature is not associated to any     | 
     165   !!        heat content. Therefore, it is not a state variable and      | 
     166   !!        does not have to be advected. Nevertheless, it has to be     | 
     167   !!        computed to determine whether the ice is melting or not      | 
     168   !!                                                                     | 
     169   !! ******************************************************************* | 
     170   !! ***         Category-summed state variables (diagnostic)        *** | 
     171   !! ******************************************************************* | 
     172   !! at_i        | at_i_b      |    Total ice concentration      |       | 
     173   !! vt_i        |      -      |    Total ice vol. per unit area | m     | 
     174   !! vt_s        |      -      |    Total snow vol. per unit ar. | m     | 
     175   !! smt_i       |      -      |    Mean sea ice salinity        | ppt   | 
     176   !! tm_i        |      -      |    Mean sea ice temperature     | K     | 
     177   !! ot_i        !      -      !    Sea ice areal age content    | day   | 
     178   !! et_i        !      -      !    Total ice enthalpy           | 10^9 J|  
     179   !! et_s        !      -      !    Total snow enthalpy          | 10^9 J|  
     180   !! bv_i        !      -      !    Mean relative brine volume   | ???   |  
     181   !!                                                                     | 
     182   !!                                                                     | 
     183   !!===================================================================== 
    22184 
    23185   LOGICAL, PUBLIC ::    & 
    24186      con_i = .false.           ! switch for conservation test 
    25187 
     188   !!-------------------------------------------------------------------------- 
    26189   !! * Share Module variables 
    27    INTEGER , PUBLIC ::   & !!: ** ice-dynamic namelist (namicedyn) ** 
    28       nbiter = 1      ,  &  !: number of sub-time steps for relaxation 
    29       nbitdr = 250    ,  &  !: maximum number of iterations for relaxation 
    30       nevp   = 400    ,  &  !: number of iterations for subcycling 
    31       nlay_i = 5            !: number of layers in the ice 
    32  
    33    REAL(wp), PUBLIC ::   & !!: ** ice-dynamic namelist (namicedyn) ** 
    34       epsd   = 1.0e-20,  &  !: tolerance parameter for dynamic 
    35       alpha  = 0.5    ,  &  !: coefficient for semi-implicit coriolis 
    36       dm     = 0.6e+03,  &  !: diffusion constant for dynamics 
    37       om     = 0.5    ,  &  !: relaxation constant 
    38       resl   = 5.0e-05,  &  !: maximum value for the residual of relaxation 
    39       cw     = 5.0e-03,  &  !: drag coefficient for oceanic stress 
    40       angvg  = 0.0    ,  &  !: turning angle for oceanic stress 
    41       pstar  = 1.0e+04,  &  !: first bulk-rheology parameter 
    42       c_rhg  = 20.0   ,  &  !: second bulk-rhelogy parameter 
    43       etamn  = 0.0e+07,  &  !: minimun value for viscosity 
    44       creepl = 2.0e-08,  &  !: creep limit 
     190   !!-------------------------------------------------------------------------- 
     191   INTEGER , PUBLIC ::   &     !!: ** ice-dynamic namelist (namicedyn) ** 
     192      nbiter = 1      ,  &     !: number of sub-time steps for relaxation 
     193      nbitdr = 250    ,  &     !: maximum number of iterations for relaxation 
     194      nevp   = 400    ,  &     !: number of iterations for subcycling 
     195      nlay_i = 5               !: number of layers in the ice 
     196 
     197   REAL(wp), PUBLIC ::   &     !!: ** ice-dynamic namelist (namicedyn) ** 
     198      epsd   = 1.0e-20,  &     !: tolerance parameter for dynamic 
     199      alpha  = 0.5    ,  &     !: coefficient for semi-implicit coriolis 
     200      dm     = 0.6e+03,  &     !: diffusion constant for dynamics 
     201      om     = 0.5    ,  &     !: relaxation constant 
     202      resl   = 5.0e-05,  &     !: maximum value for the residual of relaxation 
     203      cw     = 5.0e-03,  &     !: drag coefficient for oceanic stress 
     204      angvg  = 0.0    ,  &     !: turning angle for oceanic stress 
     205      pstar  = 1.0e+04,  &     !: determines ice strength (N/M), Hibler JPO79 
     206      c_rhg  = 20.0   ,  &     !: determines changes in ice strength 
     207      etamn  = 0.0e+07,  &     !: minimun value for viscosity : has to be 0 
     208      creepl = 2.0e-08,  &     !: creep limit : has to be under 1.0e-9 
    45209      ecc    = 2.0    ,  &  !: eccentricity of the elliptical yield curve 
    46210      ahi0   = 350.e0 ,  &  !: sea-ice hor. eddy diffusivity coeff. (m2/s) 
    47       ! EVP1 
    48211      telast = 2880.0 ,  &  !: timescale for elastic waves (s) !SB 
    49212      alphaevp = 1.0  ,  &  !: coeficient of the internal stresses !SB 
     
    51214 
    52215   REAL(wp), PUBLIC ::   & !!: ** ice-salinity namelist (namicesal) ** 
    53       s_i_max  = 20.0 ,  &  !: maximum ice salinity 
    54       s_i_min  =  0.1 ,  &  !: minimum ice salinity 
     216      s_i_max  = 20.0 ,  &  !: maximum ice salinity (ppt) 
     217      s_i_min  =  0.1 ,  &  !: minimum ice salinity (ppt) 
    55218      s_i_0    =  3.5 ,  &  !: 1st sal. value for the computation of sal .prof. 
     219                            !: (ppt) 
    56220      s_i_1    =  4.5 ,  &  !: 2nd sal. value for the computation of sal .prof. 
     221                            !: (ppt) 
    57222      sal_G    = 5.00 ,  &  !: restoring salinity for gravity drainage 
     223                            !: (ppt) 
    58224      sal_F    = 2.50 ,  &  !: restoring salinity for flushing 
    59       time_G   = 1.728e+06,&!: restoring time constant for gravity drainage  
    60       time_F   = 1.728e+06,&!: restoring time constant for gravity drainage  
    61       bulk_sal = 4.0       !!: bulk salinity in case of constant salinity 
     225                            !: (ppt) 
     226      time_G   = 1.728e+06,&!: restoring time constant for gravity drainage 
     227                            !: (= 20 days, in s) 
     228      time_F   = 8.640e+05,&!: restoring time constant for gravity drainage  
     229                            !: (= 10 days, in s) 
     230      bulk_sal = 4.0        !: bulk salinity (ppt) in case of constant salinity 
    62231 
    63232   INTEGER , PUBLIC ::   & !!: ** ice-salinity namelist (namicesal) ** 
    64       num_sal  = 1    ,  &  !: 
     233      num_sal  = 1    ,  &  !: salinity configuration used in the model 
     234                            !: 1 - s constant in space and time 
     235                            !: 2 - prognostic salinity (s(z,t)) 
     236                            !: 3 - salinity profile, constant in time 
     237                            !: 4 - salinity variations affect only ice 
     238                            !      thermodynamics 
    65239      sal_prof = 1    ,  &  !: salinity profile or not  
    66       thcon_i_swi = 1       !: thermal conductivity of Untersteiner (1964) or 
    67                             !: Pringle et al (2007)  
     240      thcon_i_swi = 1       !: thermal conductivity of Untersteiner (1964) (1) or 
     241                            !: Pringle et al (2007) (2) 
    68242 
    69243   REAL(wp), PUBLIC ::   & !!: ** ice-mechanical redistribution namelist (namiceitdme) 
     
    74248      Gstar = 0.15    ,  & !!: fractional area of young ice contributing to ridging 
    75249      astar = 0.05    ,  & !!: equivalent of G* for an exponential participation function 
    76       Hstar = 100.0   ,  & !!: fractional area of young ice contributing to ridging 
    77       hparmeter = 0.75,  & !!: threshold thickness for rafting / ridging  
    78       Craft = 5.0     ,  & !!: coefficient for the hyperbolic tangent in rafting 
    79       ridge_por = 0.0 ,  & !!: initial porosity of ridges 
    80       sal_max_ridge = 15.0, & !!: maximum ridged ice salinity 
     250      Hstar = 100.0   ,  & !!: thickness that determines the maximal thickness of ridged 
     251                           !!: ice 
     252      hparmeter = 0.75,  & !!: threshold thickness (m) for rafting / ridging  
     253      Craft = 5.0     ,  & !!: coefficient for smoothness of the hyperbolic tangent in rafting 
     254      ridge_por = 0.0 ,  & !!: initial porosity of ridges (0.3 regular value) 
     255      sal_max_ridge = 15.0, & !!: maximum ridged ice salinity (ppt) 
    81256      betas    = 1.0      , & !:: coef. for partitioning of snowfall between leads and sea ice 
    82257      kappa_i  = 1.0      , & !!: coefficient for the extinction of radiation 
    83       nconv_i_thd = 50    , & !!: maximal number of iterations in heat diffusion 
    84       maxer_i_thd = 1.0e-4    !!: maximal tolerated error for heat diffusion 
     258                              !!: Grenfell et al. (2006) (m-1) 
     259      nconv_i_thd = 50    , & !!: maximal number of iterations for heat diffusion 
     260      maxer_i_thd = 1.0e-4    !!: maximal tolerated error (C) for heat diffusion 
    85261 
    86262   INTEGER , PUBLIC ::   & !!: ** ice-mechanical redistribution namelist (namiceitdme) 
    87263      ridge_scheme_swi = 0, & !!: scheme used for ice ridging 
    88264      raftswi          = 1, & !!: rafting of ice or not                         
    89       partfun_swi      = 1, & !!: participation function TH75 (0) or Letal07 (1)  
    90       transfun_swi     = 0, & !!: transfer function of H80 (0) or Letal07 (1) 
     265      partfun_swi      = 1, & !!: participation function Thorndike et al. JGR75 (0)  
     266                              !!: or Lipscomb et al. JGR07 (1)  
     267      transfun_swi     = 0, & !!: transfer function of Hibler, MWR80 (0)  
     268                              !!: or Lipscomb et al., 2007 (1) 
    91269      brinstren_swi    = 0    !!: use brine volume to diminish ice strength 
    92270 
     
    162340 
    163341   INTEGER, PUBLIC, DIMENSION(jpi, jpj, jpl) ::          &   !:: 
    164       patho_case ! number of the pathological case (if any) 
    165  
    166 !--------------------------------------------------------------------------------------------------- 
    167 !  ) Ice global state variables 
    168 !--------------------------------------------------------------------------------------------------- 
     342      patho_case ! number of the pathological case (if any, of course) 
     343 
     344   !!-------------------------------------------------------------------------- 
     345   !! * Ice global state variables 
     346   !!-------------------------------------------------------------------------- 
     347   !! Variables defined for each ice category 
    169348   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl)        ::   &  !: 
    170       ht_i   ,   &  !: Ice thickness 
    171       a_i    ,   &  !: Ice fractional areas 
    172       v_i    ,   &  !: Ice volume per unit area 
    173       v_s    ,   &  !: Snow volume per unit area 
    174       ht_s   ,   &  !: Snow thickness 
    175       t_su   ,   &  !: Sea-Ice Surface Temperature [K] 
    176       sm_i   ,   &  !: Sea-Ice Bulk salinity [ppt] 
    177       smv_i  ,   &  !: Sea-Ice Bulk salinity [ppt] times volume 
     349      ht_i   ,   &  !: Ice thickness (m) 
     350      a_i    ,   &  !: Ice fractional areas (concentration) 
     351      v_i    ,   &  !: Ice volume per unit area (m) 
     352      v_s    ,   &  !: Snow volume per unit area(m) 
     353      ht_s   ,   &  !: Snow thickness (m) 
     354      t_su   ,   &  !: Sea-Ice Surface Temperature (K) 
     355      sm_i   ,   &  !: Sea-Ice Bulk salinity (ppt) 
     356      smv_i  ,   &  !: Sea-Ice Bulk salinity times volume per area (ppt.m) 
     357                    !: this is an extensive variable that has to be transported 
    178358      o_i    ,   &  !: Sea-Ice Age (days) 
    179       ov_i   ,   &  !: Sea-Ice Age times volume / area (days.m) 
     359      ov_i   ,   &  !: Sea-Ice Age times volume per area (days.m) 
    180360      oa_i          !: Sea-Ice Age times ice area (days) 
    181361 
     362   !! Variables summed over all categories, or associated to  
     363   !! all the ice in a single grid cell 
    182364   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &  !: 
    183365      u_ice, v_ice,   &  !: two components of the ice velocity (m/s) 
    184366      tio_u, tio_v,   &  !: two components of the ice-ocean stress (N/m2) 
    185       vt_i        ,   &  !: ice total volume 
    186       vt_s        ,   &  !: snow total volume 
    187       at_i        ,   &  !: ice total fractional area 
    188       ato_i       ,   &  !: total open water fractional area 
     367      vt_i        ,   &  !: ice total volume per unit area (m) 
     368      vt_s        ,   &  !: snow total volume per unit area (m) 
     369      at_i        ,   &  !: ice total fractional area (ice concentration) 
     370      ato_i       ,   &  !: total open water fractional area (1-at_i) 
     371      et_i        ,   &  !: total ice heat content 
     372      et_s        ,   &  !: total snow heat content 
    189373      ot_i        ,   &  !: mean age over all categories 
    190       et_i        ,   &  !: total ice heat content 
    191       bv_i        ,   &  !: total ice heat content 
    192       tm_i        ,   &  !: mean ice temperature 
    193       et_s        ,   &  !: total snow heat content 
    194       smt_i 
     374      tm_i        ,   &  !: mean ice temperature over all categories 
     375      bv_i        ,   &  !: brine volume averaged over all categories 
     376      smt_i              !: mean sea ice salinity averaged over all categories 
    195377 
    196378   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpm) ::   &  !: 
     
    216398      reslum        !: Relative absorption of solar radiation in each ocean level 
    217399 
    218 !--------------------------------------------------------------------------------------------------- 
    219 !  ) Moments for Advection 
    220 !--------------------------------------------------------------------------------------------------- 
    221  
     400   !!-------------------------------------------------------------------------- 
     401   !! * Moments for advection 
     402   !!-------------------------------------------------------------------------- 
    222403   REAL(wp), PUBLIC, DIMENSION(jpi,jpj)     ::   &  !: 
    223404         sxopw, syopw, sxxopw, syyopw, sxyopw          !: open water in sea ice 
     
    234415         sxe ,  sye ,  sxxe ,  syye ,  sxye            !: ice layers heat content 
    235416 
    236 !--------------------------------------------------------------------------------------------------- 
    237 !  ) Old values of global variables 
    238 !--------------------------------------------------------------------------------------------------- 
     417   !!-------------------------------------------------------------------------- 
     418   !! * Old values of global variables 
     419   !!-------------------------------------------------------------------------- 
    239420   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   &  !:  
    240421      old_v_s, old_v_i,                          &  !: snow and ice volumes 
     
    247428      old_u_ice, old_v_ice 
    248429 
    249 !--------------------------------------------------------------------------------------------------- 
    250 !  ) Values of increments of global variables 
    251 !--------------------------------------------------------------------------------------------------- 
    252 ! thd refers to changes induced by thermodynamics 
    253 ! trp   ''         ''     ''       advection (transport of ice) 
    254  
     430   !!-------------------------------------------------------------------------- 
     431   !! * Increment of global variables 
     432   !!-------------------------------------------------------------------------- 
     433   ! thd refers to changes induced by thermodynamics 
     434   ! trp   ''         ''     ''       advection (transport of ice) 
    255435   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   &  !:  
    256436      d_a_i_thd  , d_a_i_trp ,                   &  !: icefractions                   
     
    271451      d_u_ice_dyn, d_v_ice_dyn 
    272452 
    273 !--------------------------------------------------------------------------------------------------- 
    274 !  ) Ice thickness distribution variables 
    275 !--------------------------------------------------------------------------------------------------- 
    276  
     453   !!-------------------------------------------------------------------------- 
     454   !! * Ice thickness distribution variables 
     455   !!-------------------------------------------------------------------------- 
     456   ! REMOVE 
    277457   INTEGER(wp), PUBLIC, DIMENSION(jpl)                ::   &  !: 
    278458      ice_types      !: Vector making the connection between types and categories 
    279459 
    280460   INTEGER(wp), PUBLIC, DIMENSION(jpm,2)              ::   &  !: 
    281       ice_cat_bounds !: Matrix containing the integer upper and lower boundaries of ice thickness categories 
    282  
     461      ice_cat_bounds !: Matrix containing the integer upper and  
     462                     !: lower boundaries of ice thickness categories 
     463 
     464   ! REMOVE 
    283465   INTEGER(wp), PUBLIC, DIMENSION(jpm)                ::   &  !: 
    284466      ice_ncat_types !: Vector containing the number of thickness categories in each ice type 
     
    290472      hi_mean         !: Mean ice thickness in catgories  
    291473 
     474   ! REMOVE 
    292475   REAL(wp), PUBLIC, DIMENSION(0:jpl,jpm)         ::   &  !: 
    293       hi_max_typ     !: Boundary of ice thickness categories in thickness space (same but specific for each ice type) 
    294  
    295 !--------------------------------------------------------------------------------------------------- 
    296 !  ) Ice diagnostics                      
    297 !--------------------------------------------------------------------------------------------------- 
     476      hi_max_typ     !: Boundary of ice thickness categories  
     477                     !:in thickness space (same but specific for each ice type) 
     478 
     479   !!-------------------------------------------------------------------------- 
     480   !! * Ice diagnostics 
     481   !!-------------------------------------------------------------------------- 
     482   !! Check if everything down here is necessary 
    298483   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &  !: volume of ice formed in the leads 
    299484      v_newice 
    300485   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpl) ::   &  !: thermodynamic growth rates  
    301486      dv_dt_thd,  & 
    302       izero, fstroc, fhbricat ! to remove 
    303  
     487      izero, fstroc, fhbricat 
    304488   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &  
    305489      diag_sni_gr,                           & ! snow ice growth  
     
    309493      diag_bot_me,                           & ! vertical bottom melt  
    310494      diag_sur_me                              ! vertical surface melt 
    311  
    312495   INTEGER , PUBLIC ::   &                      !: indexes of the debugging 
    313496      jiindex,           &                      !  point 
Note: See TracChangeset for help on using the changeset viewer.