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 2475 – NEMO

Changeset 2475


Ignore:
Timestamp:
2010-12-17T07:45:43+01:00 (13 years ago)
Author:
gm
Message:

v3.3beta: #633 LIM-3 correct the hard coded num_sal in limrst + symmetric changes in LIM-2

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO
Files:
22 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/ice_2.F90

    r2370 r2475  
    1515   IMPLICIT NONE 
    1616   PRIVATE 
     17    
     18   INTEGER , PUBLIC ::   numit     !: ice iteration index 
     19   REAL(wp), PUBLIC ::   rdt_ice   !: ice time step 
    1720 
    18    !!* Share parameters namelist (namicerun read in iceini) * 
     21   !                                                                     !!* namicerun read in iceini * 
    1922   CHARACTER(len=32)     , PUBLIC ::   cn_icerst_in  = "restart_ice_in"   !: suffix of ice restart name (input) 
    2023   CHARACTER(len=32)     , PUBLIC ::   cn_icerst_out = "restart_ice"      !: suffix of ice restart name (output) 
     
    2225   LOGICAL               , PUBLIC ::   ln_limdmp     = .FALSE.            !: Ice damping 
    2326   LOGICAL               , PUBLIC ::   ln_nicep      = .TRUE.             !: flag grid points output (T) or not (F) 
    24    REAL(wp)              , PUBLIC ::   hsndif        = 0.e0               !: computation of temp. in snow (0) or not (9999) 
    25    REAL(wp)              , PUBLIC ::   hicdif        = 0.e0               !: computation of temp. in ice (0) or not (9999) 
    26    REAL(wp), DIMENSION(2), PUBLIC ::   acrit = (/ 1.e-06 , 1.e-06 /)      !: minimum fraction for leads in  
    27    !                                                                      !: north and south hemisphere 
    28    !!* ice-dynamic namelist (namicedyn) * 
    29    INTEGER , PUBLIC ::   nbiter = 1         !: number of sub-time steps for relaxation 
    30    INTEGER , PUBLIC ::   nbitdr = 250       !: maximum number of iterations for relaxation 
    31    INTEGER , PUBLIC ::   nevp   =   360     !: number of EVP subcycling iterations 
    32    INTEGER , PUBLIC ::   telast =  3600     !: timescale for EVP elastic waves 
    33    REAL(wp), PUBLIC ::   rdt_ice            !: ice time step 
    34    REAL(wp), PUBLIC ::   epsd   = 1.0e-20   !: tolerance parameter for dynamic 
    35    REAL(wp), PUBLIC ::   alpha  = 0.5       !: coefficient for semi-implicit coriolis 
    36    REAL(wp), PUBLIC ::   dm     = 0.6e+03   !: diffusion constant for dynamics 
    37    REAL(wp), PUBLIC ::   om     = 0.5       !: relaxation constant 
    38    REAL(wp), PUBLIC ::   resl   = 5.0e-05   !: maximum value for the residual of relaxation 
    39    REAL(wp), PUBLIC ::   cw     = 5.0e-03   !: drag coefficient for oceanic stress 
    40    REAL(wp), PUBLIC ::   angvg  = 0.e0      !: turning angle for oceanic stress 
    41    REAL(wp), PUBLIC ::   pstar  = 1.0e+04   !: first bulk-rheology parameter 
    42    REAL(wp), PUBLIC ::   c_rhg  = 20.e0     !: second bulk-rhelogy parameter 
    43    REAL(wp), PUBLIC ::   etamn  = 0.e+07    !: minimun value for viscosity 
    44    REAL(wp), PUBLIC ::   creepl = 2.e-08    !: creep limit 
    45    REAL(wp), PUBLIC ::   ecc    = 2.e0      !: eccentricity of the elliptical yield curve 
    46    REAL(wp), PUBLIC ::   ahi0   = 350.e0    !: sea-ice hor. eddy diffusivity coeff. (m2/s) 
    47    REAL(wp), PUBLIC ::   alphaevp = 1.e0    !: coefficient for the solution of EVP int. stresses 
     27   REAL(wp)              , PUBLIC ::   hsndif        = 0._wp              !: snow temp. computation (0) or not (9999) 
     28   REAL(wp)              , PUBLIC ::   hicdif        = 0._wp              !: ice  temp. computation (0) or not (9999) 
     29   REAL(wp), DIMENSION(2), PUBLIC ::   acrit = (/ 1.e-6_wp , 1.e-6_wp /)  !: minimum lead fraction in the 2 hemisphere 
     30    
     31   !                                          !!* ice-dynamic namelist (namicedyn) * 
     32   INTEGER , PUBLIC ::   nbiter =    1         !: number of sub-time steps for relaxation 
     33   INTEGER , PUBLIC ::   nbitdr =  250         !: maximum number of iterations for relaxation 
     34   INTEGER , PUBLIC ::   nevp   =  360         !: number of EVP subcycling iterations 
     35   INTEGER , PUBLIC ::   telast = 3600         !: timescale for EVP elastic waves 
     36   REAL(wp), PUBLIC ::   epsd   = 1.0e-20_wp   !: tolerance parameter for dynamic 
     37   REAL(wp), PUBLIC ::   alpha  = 0.5_wp       !: coefficient for semi-implicit coriolis 
     38   REAL(wp), PUBLIC ::   dm     = 0.6e+03_wp   !: diffusion constant for dynamics 
     39   REAL(wp), PUBLIC ::   om     = 0.5_wp       !: relaxation constant 
     40   REAL(wp), PUBLIC ::   resl   = 5.0e-05_wp   !: maximum value for the residual of relaxation 
     41   REAL(wp), PUBLIC ::   cw     = 5.0e-03_wp   !: drag coefficient for oceanic stress 
     42   REAL(wp), PUBLIC ::   angvg  = 0._wp        !: turning angle for oceanic stress 
     43   REAL(wp), PUBLIC ::   pstar  = 1.0e+04_wp   !: first bulk-rheology parameter 
     44   REAL(wp), PUBLIC ::   c_rhg  = 20._wp       !: second bulk-rhelogy parameter 
     45   REAL(wp), PUBLIC ::   etamn  = 0._wp        !: minimun value for viscosity 
     46   REAL(wp), PUBLIC ::   creepl = 2.e-08_wp    !: creep limit 
     47   REAL(wp), PUBLIC ::   ecc    = 2._wp        !: eccentricity of the elliptical yield curve 
     48   REAL(wp), PUBLIC ::   ahi0   = 350._wp      !: sea-ice hor. eddy diffusivity coeff. (m2/s) 
     49   REAL(wp), PUBLIC ::   alphaevp = 1._wp      !: coefficient for the solution of EVP int. stresses 
    4850 
    49    REAL(wp), PUBLIC ::   usecc2             !:  = 1.0 / ( ecc * ecc ) 
    50    REAL(wp), PUBLIC ::   rhoco              !: = rau0 * cw 
    51    REAL(wp), PUBLIC ::   sangvg, cangvg     !: sin and cos of the turning angle for ocean stress 
    52    REAL(wp), PUBLIC ::   pstarh             !: pstar / 2.0 
     51   REAL(wp), PUBLIC ::   usecc2                !:  = 1.0 / ( ecc * ecc ) 
     52   REAL(wp), PUBLIC ::   rhoco                 !: = rau0 * cw 
     53   REAL(wp), PUBLIC ::   sangvg, cangvg        !: sin and cos of the turning angle for ocean stress 
     54   REAL(wp), PUBLIC ::   pstarh                !: pstar / 2.0 
    5355 
    5456   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ahiu , ahiv   !: hor. diffusivity coeff. at ocean U- and V-points (m2/s) 
     
    5860   !!* Ice Rheology 
    5961# if defined key_lim2_vp 
    60    !                                                       !!* VP rheology * 
     62   !                                                      !!* VP rheology * 
    6163   LOGICAL , PUBLIC ::   lk_lim2_vp = .TRUE.               !: Visco-Plactic reology flag  
    6264   ! 
     
    6466   ! 
    6567# else 
    66    !                                                       !!* EVP rheology * 
     68   !                                                      !!* EVP rheology * 
    6769   LOGICAL , PUBLIC::   lk_lim2_vp = .FALSE.               !: Visco-Plactic reology flag  
    6870   ! 
     
    9698   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   rdmicif       !: Variation of ice mass 
    9799   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qldif         !: heat balance of the lead (or of the open ocean) 
    98    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qcmif         !: Energy needed to bring the ocean surface layer until its freezing  
     100   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qcmif         !: Energy needed to freeze the ocean surface layer 
    99101   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fdtcn         !: net downward heat flux from the ice to the ocean 
    100102   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qdtcn         !: energy from the ice to the ocean point (at a factor 2) 
    101103   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   thcm          !: part of the solar energy used in the lead heat budget 
    102104   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fstric        !: Solar flux transmitted trough the ice 
    103    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ffltbif       !: Array linked with the max heat contained in brine pockets (?) 
     105   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   ffltbif       !: linked with the max heat contained in brine pockets (?) 
    104106   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fscmbq        !: Linked with the solar flux below the ice (?) 
    105107   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   fsbbq         !: Also linked with the solar flux below the ice (?) 
    106    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qfvbq         !: Array used to store energy in case of toral lateral ablation (?) 
     108   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   qfvbq         !: used to store energy in case of toral lateral ablation (?) 
    107109   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   dmgwi         !: Variation of the mass of snow ice 
    108  
    109    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   u_ice, v_ice   !: two components of the ice   velocity at I-point (m/s) 
    110    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   u_oce, v_oce   !: two components of the ocean velocity at I-point (m/s) 
     110   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   u_ice, v_ice  !: two components of the ice   velocity at I-point (m/s) 
     111   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   u_oce, v_oce  !: two components of the ocean velocity at I-point (m/s) 
    111112 
    112113   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jplayersp1) ::   tbif  !: Temperature inside the ice/snow layer 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/iceini_2.F90

    r2319 r2475  
    3232   PUBLIC   ice_init_2               ! called by sbcice_lim_2.F90 
    3333 
    34    INTEGER, PUBLIC ::   numit   !: iteration number 
    35  
    3634   !!---------------------------------------------------------------------- 
    3735   !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010) 
    3836   !! $Id$  
    39    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     37   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4038   !!---------------------------------------------------------------------- 
    41  
    4239CONTAINS 
    4340 
     
    4946      !!---------------------------------------------------------------------- 
    5047      ! 
    51       ! Open the namelist file  
    52       CALL ctl_opn( numnam_ice, 'namelist_ice', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )       
    53       CALL ice_run_2                    !  read in namelist some run parameters 
    54                   
    55       ! Louvain la Neuve Ice model 
    56       rdt_ice = nn_fsbc * rdttra(1) 
     48      !                                ! Open the namelist file  
     49      CALL ctl_opn( numnam_ice, 'namelist_ice', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )  
     50      !     
     51      CALL ice_run_2                   ! read in namelist some run parameters 
     52      !           
     53      rdt_ice = nn_fsbc * rdttra(1)    ! sea-ice time step 
    5754      numit   = nit000 - 1 
    58  
    59       CALL lim_msh_2                  ! ice mesh initialization 
    60       
    61       ! Initial sea-ice state 
    62       IF( .NOT.ln_rstart ) THEN 
    63          CALL lim_istate_2            ! start from rest: sea-ice deduced from sst 
    64       ELSE 
    65          CALL lim_rst_read_2          ! start from a restart file 
     55      ! 
     56      CALL lim_msh_2                   ! ice mesh initialization 
     57      ! 
     58      !                                ! Initial sea-ice state 
     59      IF( .NOT.ln_rstart ) THEN   ;   CALL lim_istate_2     ! start from rest: sea-ice deduced from sst 
     60      ELSE                        ;   CALL lim_rst_read_2   ! start from a restart file 
    6661      ENDIF 
    67        
    68       tn_ice(:,:,1) = sist(:,:)         ! initialisation of ice temperature    
    69       fr_i  (:,:) = 1.0 - frld(:,:)   ! initialisation of sea-ice fraction     
     62      ! 
     63      tn_ice(:,:,1) = sist(:,:)        ! initialisation of ice temperature    
     64      fr_i  (:,:) = 1.0 - frld(:,:)    ! initialisation of sea-ice fraction     
    7065      ! 
    7166   END SUBROUTINE ice_init_2 
     
    8681      !!------------------------------------------------------------------- 
    8782      !                     
    88       REWIND ( numnam_ice )                       ! Read Namelist namicerun  
    89       READ   ( numnam_ice , namicerun ) 
    90  
    91       IF(lwp) THEN 
     83      REWIND( numnam_ice )                      ! Read Namelist namicerun  
     84      READ  ( numnam_ice , namicerun ) 
     85      ! 
     86      IF(lwp) THEN                              ! control print 
    9287         WRITE(numout,*) 
    9388         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice' 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_2/limrst_2.F90

    r2370 r2475  
    1212   !!   'key_lim2' :                                  LIM 2.0 sea-ice model 
    1313   !!---------------------------------------------------------------------- 
    14    !!---------------------------------------------------------------------- 
    1514   !!   lim_rst_opn_2   : open ice restart file 
    1615   !!   lim_rst_write_2 : write of the ice restart file  
    1716   !!   lim_rst_read_2  : read  the ice restart file  
    1817   !!---------------------------------------------------------------------- 
    19    USE dom_oce         ! ocean space and time domain 
    20    USE ice_2 
    21    USE sbc_oce 
    22    USE sbc_ice 
    23  
    24    USE in_out_manager 
    25    USE iom 
     18   USE dom_oce          ! ocean domain 
     19   USE ice_2            ! LIM-2: sea-ice variables 
     20   USE sbc_oce          ! Surface Boundary Condition: ocean 
     21   USE sbc_ice          ! Surface Boundary Condition: sea-ice 
     22   USE in_out_manager   ! I/O manager 
     23   USE iom              ! I/O library 
    2624 
    2725   IMPLICIT NONE 
     
    3836   !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010) 
    3937   !! $Id$ 
    40    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    41    !!---------------------------------------------------------------------- 
    42  
     38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     39   !!---------------------------------------------------------------------- 
    4340CONTAINS 
    4441 
     
    8481      ! 
    8582   END SUBROUTINE lim_rst_opn_2 
     83 
    8684 
    8785   SUBROUTINE lim_rst_write_2( kt ) 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/ice.F90

    r2287 r2475  
    11MODULE ice 
     2   !!====================================================================== 
     3   !!                        ***  MODULE ice  *** 
     4   !! LIM-3 Sea Ice physics:  diagnostics variables of ice defined in memory 
     5   !!===================================================================== 
     6   !! History :  3.0  ! 2008-03  (M. Vancoppenolle) : original code LIM-3 
     7   !!---------------------------------------------------------------------- 
    28#if defined key_lim3 
    39   !!---------------------------------------------------------------------- 
    410   !!   'key_lim3' :                                   LIM3 sea-ice model 
    511   !!---------------------------------------------------------------------- 
    6    !! History : 
    7    !!   2.0  !  03-08  (C. Ethe)  F90: Free form and module 
    8    !!   3.0  !  08-03  (M. Vancoppenolle) : LIM3 ! 
    9    !!---------------------------------------------------------------------- 
    10    !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    11    !! $Id$ 
    12    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    13    !!---------------------------------------------------------------------- 
    14    !! * Modules used 
    1512   USE par_ice          ! LIM sea-ice parameters 
    1613 
    1714   IMPLICIT NONE 
    1815   PRIVATE 
    19    !! 
     16 
    2017   !!====================================================================== 
    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    !! 
    3518   !! LIM3 by the use of sweat, agile fingers and sometimes brain juice,  
    3619   !!  was developed in Louvain-la-Neuve by :  
     
    6447   !!    * Bouillon et al., in prep for 2008. 
    6548   !! 
    66    !!    Or the reference manual, that should be available by 2009 
    67    !! 
     49   !!    Or the reference manual, that should be available by 2010 
    6850   !!====================================================================== 
    6951   !!                                                                     | 
    70    !!            *****************************************                | 
    71    !!            *                                       *                | 
    72    !! ************ I C E   S T A T E   V A R I A B L E S **************** | 
    73    !!            *                                       *                | 
    74    !!            *****************************************                | 
     52   !!              I C E   S T A T E   V A R I A B L E S                  | 
    7553   !!                                                                     | 
    7654   !! Introduction :                                                      | 
    7755   !! --------------                                                      | 
    78    !!                                                                     | 
    7956   !! Every ice-covered grid cell is characterized by a series of state   | 
    8057   !! variables. To account for unresolved spatial variability in ice     | 
     
    130107   !!                                                                     | 
    131108   !! ** Global variables                                                 | 
    132    !!                                                                     | 
    133109   !!-------------|-------------|---------------------------------|-------| 
    134110   !! a_i         | a_i_b       |    Ice concentration            |       | 
     
    145121   !!                                                                     | 
    146122   !! ** Equivalent variables                                             | 
    147    !!                                                                     | 
    148123   !!-------------|-------------|---------------------------------|-------| 
    149124   !!                                                                     | 
     
    179154   !! et_s        !      -      !    Total snow enthalpy          | 10^9 J|  
    180155   !! bv_i        !      -      !    Mean relative brine volume   | ???   |  
    181    !!                                                                     | 
    182    !!                                                                     | 
    183156   !!===================================================================== 
    184157 
    185    LOGICAL, PUBLIC ::    & 
    186       con_i = .false.           ! switch for conservation test 
     158   LOGICAL, PUBLIC ::   con_i = .false.   ! switch for conservation test 
    187159 
    188160   !!-------------------------------------------------------------------------- 
    189161   !! * Share Module variables 
    190162   !!-------------------------------------------------------------------------- 
    191    REAL(wp), PUBLIC ::   rdt_ice      !: ice time step 
     163   INTEGER , PUBLIC ::   nstart    !: iteration number of the begining of the run  
     164   INTEGER , PUBLIC ::   nlast     !: iteration number of the end of the run  
     165   INTEGER , PUBLIC ::   nitrun    !: number of iteration 
     166   INTEGER , PUBLIC ::   numit     !: iteration number 
     167   REAL(wp), PUBLIC ::   tpstot    !: time of the run in seconds 
     168   REAL(wp), PUBLIC ::   rdt_ice   !: ice time step 
    192169 
    193170   INTEGER , PUBLIC ::   &     !!: ** ice-dynamic namelist (namicedyn) ** 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/iceini.F90

    r2287 r2475  
    44   !!   Sea-ice model : LIM Sea ice model Initialization 
    55   !!====================================================================== 
     6   !! History :  3.0  ! 2008-03  (M. Vancoppenolle) LIM-3 original code 
     7   !!            3.3  ! 2010-12  (G. Madec) add call to lim_thd_init and lim_thd_sal_init 
     8   !!---------------------------------------------------------------------- 
    69#if defined key_lim3 
    710   !!---------------------------------------------------------------------- 
     
    1013   !!   ice_init       : sea-ice model initialization 
    1114   !!---------------------------------------------------------------------- 
    12    USE dom_oce 
    13    USE in_out_manager 
    14    USE sbc_oce         ! Surface boundary condition: ocean fields 
    15    USE sbc_ice         ! Surface boundary condition: ice fields 
    16    USE phycst          ! Define parameters for the routines 
    17    USE ice 
    18    USE limmsh 
    19    USE limistate 
    20    USE limrst 
    21    USE par_ice 
    22    USE limvar 
    23    USE lib_mpp 
     15   USE phycst         ! physical constants 
     16   USE dom_oce        ! ocean domain 
     17   USE sbc_oce        ! Surface boundary condition: ocean fields 
     18   USE sbc_ice        ! Surface boundary condition: ice fields 
     19   USE ice            ! LIM: sea-ice variables 
     20   USE limmsh         ! LIM: mesh 
     21   USE limistate      ! LIM: initial state 
     22   USE limrst         ! LIM: restart 
     23   USE limthd         ! LIM: ice thermodynamics 
     24   USE limthd_sal     ! LIM: ice thermodynamics: salinity 
     25   USE par_ice        ! LIM: sea-ice parameters 
     26   USE limvar         ! LIM: variables 
     27   USE in_out_manager ! I/O manager 
     28   USE lib_mpp        ! MPP library 
    2429 
    2530   IMPLICIT NONE 
    2631   PRIVATE 
    2732 
    28    !! * Routine accessibility 
    29    PUBLIC ice_init                 ! called by opa.F90 
    30    PUBLIC lim_itd_ini 
    31  
    32    !! * Share Module variables 
    33    INTEGER , PUBLIC  ::   &  !: 
    34       nstart ,            &  !: iteration number of the begining of the run  
    35       nlast  ,            &  !: iteration number of the end of the run  
    36       nitrun ,            &  !: number of iteration 
    37       numit                  !: iteration number 
    38    REAL(wp), PUBLIC  ::   &  !: 
    39       tpstot                 !: time of the run in seconds 
     33   PUBLIC   ice_init   ! called by opa.F90 
     34 
    4035   !!---------------------------------------------------------------------- 
    4136   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    4237   !! $Id$ 
    43    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    44    !!---------------------------------------------------------------------- 
    45  
     38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     39   !!---------------------------------------------------------------------- 
    4640CONTAINS 
    4741 
     
    5145      !! 
    5246      !! ** purpose :    
    53       !! 
    54       !! History : 
    55       !!   2.0  !  02-08  (G. Madec)  F90: Free form and modules 
    56       !!   3.0  !  08-03  (M. Vancop) ITD, salinity, EVP-C 
    5747      !!---------------------------------------------------------------------- 
    58  
    59       ! Open the namelist file  
     48      ! 
     49      !                                ! Open the namelist file  
    6050      CALL ctl_opn( numnam_ice, 'namelist_ice', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp ) 
    61  
    62       CALL ice_run                    !  read in namelist some run parameters 
    63  
    64       ! Louvain la Neuve Ice model 
    65       IF( nacc == 1 ) THEN 
    66          rdt_ice = nn_fsbc * rdtmin 
    67       ELSE 
    68          rdt_ice = nn_fsbc * rdt 
    69       ENDIF 
    70  
    71       CALL lim_msh                    ! ice mesh initialization 
    72  
    73       CALL lim_itd_ini                ! initialize the ice thickness 
    74       ! distribution 
    75       ! Initial sea-ice state 
    76       IF( .NOT.ln_rstart ) THEN 
     51      ! 
     52      CALL ice_run                     ! namelist read some ice run parameters 
     53      ! 
     54      CALL lim_thd_init                ! namelist read ice thermodynics parameters 
     55      ! 
     56      CALL lim_thd_sal_init            ! namelist read ice salinity parameters 
     57      ! 
     58      rdt_ice = nn_fsbc * rdttra(1)    ! sea-ice timestep 
     59      ! 
     60      CALL lim_msh                     ! ice mesh initialization 
     61      ! 
     62      CALL lim_itd_ini                 ! initialize the ice thickness distribution 
     63 
     64      !                                ! Initial sea-ice state 
     65      IF( .NOT.ln_rstart ) THEN              ! start from rest 
    7766         numit = 0 
    7867         numit = nit000 - 1 
    79          CALL lim_istate              ! start from rest: sea-ice deduced from sst 
    80          CALL lim_var_agg(1)          ! aggregate category variables in 
    81          ! bulk variables 
    82          CALL lim_var_glo2eqv         ! convert global variables in equivalent 
    83          ! variables 
    84       ELSE 
    85          CALL lim_rst_read            ! start from a restart file 
    86  
     68         CALL lim_istate                        ! start from rest: sea-ice deduced from sst 
     69         CALL lim_var_agg(1)                    ! aggregate category variables in bulk variables 
     70         CALL lim_var_glo2eqv                   ! convert global variables in equivalent variables 
     71      ELSE                                   ! start from a restart file 
     72         CALL lim_rst_read                      ! read the restart file 
    8773         numit = nit000 - 1 
    88          CALL lim_var_agg(1)          ! aggregate ice variables 
    89          CALL lim_var_glo2eqv         ! convert global var in equivalent variables 
    90       ENDIF 
    91  
     74         CALL lim_var_agg(1)                    ! aggregate ice variables 
     75         CALL lim_var_glo2eqv                   ! convert global var in equivalent variables 
     76      ENDIF 
     77      ! 
    9278      fr_i(:,:) = at_i(:,:)           ! initialisation of sea-ice fraction 
    93  
     79      ! 
    9480      nstart = numit  + nn_fsbc       
    9581      nitrun = nitend - nit000 + 1  
    9682      nlast  = numit  + nitrun  
    97  
    98       IF( nstock == 0  )  nstock = nlast + 1 
    99  
     83      ! 
     84      IF( nstock == 0  )   nstock = nlast + 1 
     85      ! 
    10086   END SUBROUTINE ice_init 
     87 
    10188 
    10289   SUBROUTINE ice_run 
     
    11097      !! 
    11198      !! ** input   :   Namelist namicerun 
    112       !! 
    113       !! history : 
    114       !!   2.0  !  03-08 (C. Ethe)  Original code 
    115       !!   3.0  !  08-03 (M. Vancop) LIM3 
    11699      !!------------------------------------------------------------------- 
    117100      NAMELIST/namicerun/ cn_icerst_in, cn_icerst_out, ln_limdyn, acrit, hsndif, hicdif, cai, cao, ln_nicep 
    118101      !!------------------------------------------------------------------- 
    119  
    120       !                                           ! Read Namelist namicerun  
    121       REWIND ( numnam_ice ) 
    122       READ   ( numnam_ice , namicerun ) 
    123  
     102      !                     
     103      REWIND( numnam_ice )                ! Read Namelist namicerun  
     104      READ  ( numnam_ice , namicerun ) 
     105      ! 
    124106      IF( lk_mpp .AND. ln_nicep ) THEN 
    125107         ln_nicep = .FALSE. 
    126108         CALL ctl_warn( 'ice_run : specific control print for LIM3 desactivated with MPI' ) 
    127109      ENDIF        
    128  
    129       IF(lwp) THEN 
     110      ! 
     111      IF(lwp) THEN                        ! control print 
    130112         WRITE(numout,*) 
    131113         WRITE(numout,*) 'ice_run : ice share parameters for dynamics/advection/thermo of sea-ice' 
     
    137119         WRITE(numout,*) '   atmospheric drag over sea ice                           = ', cai 
    138120         WRITE(numout,*) '   atmospheric drag over ocean                             = ', cao 
    139          WRITE(numout,*) '   Several ice points in the ice or not in ocean.output = ', ln_nicep 
    140       ENDIF 
    141  
     121         WRITE(numout,*) '   Several ice points in the ice or not in ocean.output    = ', ln_nicep 
     122      ENDIF 
     123      ! 
    142124   END SUBROUTINE ice_run 
     125 
    143126 
    144127   SUBROUTINE lim_itd_ini 
    145128      !!------------------------------------------------------------------ 
    146129      !!                ***  ROUTINE lim_itd_ini *** 
    147       !! ** Purpose : 
    148       !!            Initializes the ice thickness distribution 
    149       !! ** Method  : 
    150       !!            Very simple. Currently there are no ice types in the 
    151       !!            model... 
    152       !! 
    153       !! ** Arguments : 
    154       !!           kideb , kiut : Starting and ending points on which the 
    155       !!                         the computation is applied 
    156       !! 
    157       !! ** Inputs / Ouputs : (global commons) 
    158       !! 
    159       !! ** External : 
    160       !! 
    161       !! ** References : 
    162       !! 
    163       !! ** History : 
    164       !!           (12-2005) Martin Vancoppenolle 
    165       !! 
     130      !! 
     131      !! ** Purpose :   Initializes the ice thickness distribution 
     132      !! ** Method  :   ... 
    166133      !!------------------------------------------------------------------ 
    167       !! * Arguments 
    168  
    169       !! * Local variables 
    170       INTEGER ::   jl,       &   ! ice category dummy loop index 
    171          jm            ! ice types    dummy loop index 
    172  
    173       REAL(wp)  ::           &  ! constant values 
    174          zeps      =  1.0e-10,   & ! 
    175          zc1                 ,   & ! 
    176          zc2                 ,   & ! 
    177          zc3                 ,   & ! 
    178          zx1 
    179  
     134      INTEGER  ::   jl, jm               ! dummy loop index 
     135      REAL(wp) ::   zc1, zc2, zc3, zx1   ! local scalars 
     136      !!------------------------------------------------------------------ 
     137 
     138      IF(lwp) WRITE(numout,*) 
    180139      IF(lwp) WRITE(numout,*) 'lim_itd_ini : Initialization of ice thickness distribution ' 
    181140      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~' 
    182  
    183       !!-- End of declarations 
    184       !!------------------------------------------------------------------------------ 
    185141 
    186142      !------------------------------------------------------------------------------! 
     
    220176      !- Thickness categories boundaries  
    221177      !---------------------------------- 
    222       hi_max(:) = 0.0 
    223       hi_max_typ(:,:) = 0.0 
     178      hi_max(:) = 0._wp 
     179      hi_max_typ(:,:) = 0._wp 
    224180 
    225181      !- Type 1 - undeformed ice 
    226       zc1 = 3./REAL(ice_cat_bounds(1,2)-ice_cat_bounds(1,1)+1) 
    227       zc2 = 10.0*zc1 
    228       zc3 = 3.0 
     182      zc1 =  3._wp / REAL( ice_cat_bounds(1,2) - ice_cat_bounds(1,1) + 1 , wp ) 
     183      zc2 = 10._wp * zc1 
     184      zc3 =  3._wp 
    229185 
    230186      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) 
    231          zx1 = REAL(jl-1) / REAL(ice_cat_bounds(1,2)-ice_cat_bounds(1,1)+1) 
    232          hi_max(jl) = hi_max(jl-1) + zc1 + zc2 * (1.0 + TANH ( zc3 * (zx1 - 1.0 ) ) ) 
     187         zx1 = REAL( jl-1 , wp ) / REAL( ice_cat_bounds(1,2) - ice_cat_bounds(1,1) + 1 , wp ) 
     188         hi_max(jl) = hi_max(jl-1) + zc1 + zc2 * (1._wp + TANH( zc3 * (zx1 - 1._wp ) ) ) 
    233189      END DO 
    234190 
    235191      !- Fill in the hi_max_typ vector, useful in other circumstances 
    236       ! Tricky trick 
    237       ! hi_max_typ is actually not used in the code and will be removed in a 
    238       ! next flyspray at this time, the tricky trick will also be removed 
    239       ! Martin, march 08 
     192      ! Tricky trick: hi_max_typ is actually not used in the code and will be removed in a 
     193      ! next flyspray at this time, the tricky trick will also be removed (Martin, march 08) 
    240194      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) 
    241195         hi_max_typ(jl,1) = hi_max(jl) 
     
    252206         END DO 
    253207      ENDIF 
    254  
     208      ! 
    255209      DO jl = 1, jpl 
    256          hi_mean(jl) = ( hi_max(jl) + hi_max(jl-1) ) / 2.0 
    257       END DO 
    258  
     210         hi_mean(jl) = ( hi_max(jl) + hi_max(jl-1) ) * 0.5_wp 
     211      END DO 
     212      ! 
    259213      tn_ice(:,:,:) = t_su(:,:,:) 
    260  
     214      ! 
    261215   END SUBROUTINE lim_itd_ini 
    262216 
     
    268222   SUBROUTINE ice_init        ! Empty routine 
    269223   END SUBROUTINE ice_init 
    270  
    271    SUBROUTINE lim_itd_ini 
    272    END SUBROUTINE lim_itd_ini 
    273224#endif 
    274225 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limdia.F90

    r2439 r2475  
    1616   USE ice             ! LIM-3: sea-ice variable 
    1717   USE par_ice         ! LIM-3: ice parameters 
    18 !   USE ice_oce         ! LIM-3: ice-ocean share variables 
    19    USE iceini          ! LIM-3: sea-ice initialization 
    20    USE limistate       ! LIM-3: sea-ice initial state 
    2118   USE dom_ice         ! LIM-3: sea-ice domain 
    2219   USE dom_oce         ! ocean domain 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limdyn.F90

    r2370 r2475  
    2222   USE sbc_oce         ! Surface boundary condition: ocean fields 
    2323   USE sbc_ice         ! Surface boundary condition: ice fields 
    24    USE iceini 
    25    USE limistate 
    2624   USE limrhg          ! ice rheology 
    2725   USE lbclnk 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limistate.F90

    r2287 r2475  
    44   !!              Initialisation of diagnostics ice variables 
    55   !!====================================================================== 
     6   !! History :  2.0  ! 2004-01 (C. Ethe, G. Madec)  Original code 
     7   !!---------------------------------------------------------------------- 
    68#if defined key_lim3 
    79   !!---------------------------------------------------------------------- 
     
    1113   !!   lim_istate_init :  initialization of ice state and namelist read 
    1214   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
    14    USE phycst 
    15    USE oce             ! dynamics and tracers variables 
    16    USE dom_oce 
    17    USE sbc_oce         ! Surface boundary condition: ocean fields 
    18    USE par_ice         ! ice parameters 
    19    USE eosbn2          ! equation of state 
    20    USE in_out_manager 
    21    USE dom_ice 
    22    USE ice 
    23    USE lbclnk 
     15   USE phycst           ! physical constant 
     16   USE oce              ! dynamics and tracers variables 
     17   USE dom_oce          ! ocean domain 
     18   USE sbc_oce          ! Surface boundary condition: ocean fields 
     19   USE eosbn2           ! equation of state 
     20   USE ice              ! sea-ice variables 
     21   USE par_ice          ! ice parameters 
     22   USE dom_ice          ! sea-ice domain 
     23   USE in_out_manager   ! I/O manager 
     24   USE lbclnk           ! lateral boundary condition - MPP exchanges 
    2425 
    2526   IMPLICIT NONE 
    2627   PRIVATE 
    2728 
    28    !! * Accessibility 
    29    PUBLIC lim_istate      ! routine called by lim_init.F90 
    30  
    31    !! * Module variables 
    32    REAL(wp) ::             & !!! ** init namelist (namiceini) ** 
    33       ttest    = 2.0  ,    &  ! threshold water temperature for initial sea ice 
    34       hninn    = 0.5  ,    &  ! initial snow thickness in the north 
    35       hginn_u  = 2.5  ,    &  ! initial ice thickness in the north 
    36       aginn_u  = 0.7  ,    &  ! initial leads area in the north 
    37       hginn_d  = 5.0  ,    &  ! initial ice thickness in the north 
    38       aginn_d  = 0.25 ,    &  ! initial leads area in the north 
    39       hnins    = 0.1  ,    &  ! initial snow thickness in the south 
    40       hgins_u  = 1.0  ,    &  ! initial ice thickness in the south 
    41       agins_u  = 0.7  ,    &  ! initial leads area in the south 
    42       hgins_d  = 2.0  ,    &  ! initial ice thickness in the south 
    43       agins_d  = 0.2  ,    &  ! initial leads area in the south 
    44       sinn     = 6.301 ,   &  ! initial salinity  
    45       sins     = 6.301 
    46  
    47    REAL(wp)  ::            &  ! constant values 
    48       zzero   = 0.0     ,  & 
    49       zone    = 1.0 
     29   PUBLIC   lim_istate      ! routine called by lim_init.F90 
     30 
     31   !                                  !!** init namelist (namiceini) ** 
     32   REAL(wp) ::   ttest    = 2.0_wp     ! threshold water temperature for initial sea ice 
     33   REAL(wp) ::   hninn    = 0.5_wp     ! initial snow thickness in the north 
     34   REAL(wp) ::   hginn_u  = 2.5_wp     ! initial ice thickness in the north 
     35   REAL(wp) ::   aginn_u  = 0.7_wp     ! initial leads area in the north 
     36   REAL(wp) ::   hginn_d  = 5.0_wp     ! initial ice thickness in the north 
     37   REAL(wp) ::   aginn_d  = 0.25_wp    ! initial leads area in the north 
     38   REAL(wp) ::   hnins    = 0.1_wp     ! initial snow thickness in the south 
     39   REAL(wp) ::   hgins_u  = 1.0_wp     ! initial ice thickness in the south 
     40   REAL(wp) ::   agins_u  = 0.7_wp     ! initial leads area in the south 
     41   REAL(wp) ::   hgins_d  = 2.0_wp     ! initial ice thickness in the south 
     42   REAL(wp) ::   agins_d  = 0.2_wp     ! initial leads area in the south 
     43   REAL(wp) ::   sinn     = 6.301_wp   ! initial salinity  
     44   REAL(wp) ::   sins     = 6.301_wp   ! 
    5045 
    5146   !!---------------------------------------------------------------------- 
    5247   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    5348   !! $Id$ 
    54    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    55    !!---------------------------------------------------------------------- 
    56  
     49   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     50   !!---------------------------------------------------------------------- 
    5751CONTAINS 
    5852 
     
    6559      !! ** Method  :   restart from a state defined in a binary file 
    6660      !!                or from arbitrary sea-ice conditions 
    67       !! 
    68       !! History : 
    69       !!   2.0  !  01-04  (C. Ethe, G. Madec)  Original code 
    70       !!-------------------------------------------------------------------- 
    71  
    72       !! * Local variables 
     61      !!------------------------------------------------------------------- 
    7362      INTEGER  ::   ji, jj, jk, jl             ! dummy loop indices 
    74  
    75       REAL(wp) ::       &  ! temporary scalar 
    76          zeps6, zeps, ztmelts, & 
    77          epsi06 
    78       REAL(wp), DIMENSION(jpm) ::   & 
    79          zgfactorn, zhin, & 
    80          zgfactors, zhis 
    81       REAL(wp) ::  & 
    82          zvol, zare, zh, zh1, zh2, zh3, zan, zbn, zas, zbs  
    83       REAL(wp), DIMENSION(jpi,jpj) ::   zidto    ! ice indicator 
     63      REAL(wp) ::   zeps6, zeps, ztmelts, epsi06   ! local scalars 
     64      REAL(wp) ::  zvol, zare, zh, zh1, zh2, zh3, zan, zbn, zas, zbs  
     65      REAL(wp), DIMENSION(jpm)     ::   zgfactorn, zhin  
     66      REAL(wp), DIMENSION(jpm)     ::   zgfactors, zhis 
     67      REAL(wp), DIMENSION(jpi,jpj) ::   zidto      ! ice indicator 
    8468      !-------------------------------------------------------------------- 
    8569 
     
    8771      ! 1) Preliminary things  
    8872      !-------------------------------------------------------------------- 
    89       epsi06 = 1.0e-6 
     73      epsi06 = 1.e-6_wp 
    9074 
    9175      CALL lim_istate_init     !  reading the initials parameters of the ice 
     
    116100 
    117101      ! constants for heat contents 
    118       zeps   = 1.0d-20 
    119       zeps6  = 1.0d-06 
     102      zeps   = 1.e-20_wp 
     103      zeps6  = 1.e-06_wp 
    120104 
    121105      ! zgfactor for initial ice distribution 
    122       zgfactorn(:) = 0.0 
    123       zgfactors(:) = 0.0 
     106      zgfactorn(:) = 0._wp 
     107      zgfactors(:) = 0._wp 
    124108 
    125109      ! first ice type 
    126110      DO jl = ice_cat_bounds(1,1), ice_cat_bounds(1,2) 
    127          zhin (1)     = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
    128          zgfactorn(1) = zgfactorn(1) + exp(-(zhin(1)-hginn_u)*(zhin(1)-hginn_u)/2.0) 
    129          zhis (1)     = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
    130          zgfactors(1) = zgfactors(1) + exp(-(zhis(1)-hgins_u)*(zhis(1)-hgins_u)/2.0) 
     111         zhin (1)     = ( hi_max(jl-1) + hi_max(jl) ) * 0.5_wp 
     112         zgfactorn(1) = zgfactorn(1) + exp(-(zhin(1)-hginn_u)*(zhin(1)-hginn_u) * 0.5_wp ) 
     113         zhis (1)     = ( hi_max(jl-1) + hi_max(jl) ) * 0.5_wp 
     114         zgfactors(1) = zgfactors(1) + exp(-(zhis(1)-hgins_u)*(zhis(1)-hgins_u) * 0.5_wp ) 
    131115      END DO ! jl 
    132116      zgfactorn(1) = aginn_u / zgfactorn(1) 
     
    135119      ! ------------- 
    136120      ! new distribution, polynom of second order, conserving area and volume 
    137       zh1 = 0.0 
    138       zh2 = 0.0 
    139       zh3 = 0.0 
     121      zh1 = 0._wp 
     122      zh2 = 0._wp 
     123      zh3 = 0._wp 
    140124      DO jl = 1, jpl 
    141          zh = ( hi_max(jl-1) + hi_max(jl) ) / 2.0 
     125         zh = ( hi_max(jl-1) + hi_max(jl) ) * 0.5_wp 
    142126         zh1 = zh1 + zh 
    143          zh2 = zh2 + zh*zh 
    144          zh3 = zh3 + zh*zh*zh 
     127         zh2 = zh2 + zh * zh 
     128         zh3 = zh3 + zh * zh * zh 
    145129      END DO 
    146130      IF(lwp) WRITE(numout,*) ' zh1 : ', zh1 
     
    148132      IF(lwp) WRITE(numout,*) ' zh3 : ', zh3 
    149133 
    150       zvol = aginn_u*hginn_u 
     134      zvol = aginn_u * hginn_u 
    151135      zare = aginn_u 
    152       IF ( jpl .GE. 2 ) THEN 
     136      IF( jpl >= 2 ) THEN 
    153137         zbn = ( zvol*zh2 - zare*zh3 ) / ( zh2*zh2 - zh1*zh3) 
    154138         zan = ( zare - zbn*zh1 ) / zh2 
     
    160144      IF(lwp) WRITE(numout,*) ' zan : ', zan  
    161145 
    162       zvol = agins_u*hgins_u 
     146      zvol = agins_u * hgins_u 
    163147      zare = agins_u 
    164       IF ( jpl .GE. 2 ) THEN 
     148      IF( jpl >= 2 ) THEN 
    165149         zbs = ( zvol*zh2 - zare*zh3 ) / ( zh2*zh2 - zh1*zh3) 
    166150         zas = ( zare - zbs*zh1 ) / zh2 
     
    205189            !--- Northern hemisphere 
    206190            !---------------------------------------------------------------- 
    207             IF( fcor(ji,jj) >= 0.e0 ) THEN     
     191            IF( fcor(ji,jj) >= 0._wp ) THEN     
    208192 
    209193               !----------------------- 
     
    453437            ENDIF ! on fcor 
    454438 
    455          ENDDO 
    456       ENDDO 
     439         END DO 
     440      END DO 
    457441 
    458442      !-------------------------------------------------------------------- 
     
    494478 
    495479      DO jl = 1, jpl 
    496  
    497480         CALL lbc_lnk( a_i(:,:,jl)  , 'T', 1. ) 
    498481         CALL lbc_lnk( v_i(:,:,jl)  , 'T', 1. ) 
     
    500483         CALL lbc_lnk( smv_i(:,:,jl), 'T', 1. ) 
    501484         CALL lbc_lnk( oa_i(:,:,jl) , 'T', 1. ) 
    502  
     485         ! 
    503486         CALL lbc_lnk( ht_i(:,:,jl) , 'T', 1. ) 
    504487         CALL lbc_lnk( ht_s(:,:,jl) , 'T', 1. ) 
     
    514497            CALL lbc_lnk(e_i(:,:,jk,jl), 'T', 1. ) 
    515498         END DO 
    516  
    517          a_i (:,:,jl) = tms(:,:) * a_i(:,:,jl) 
    518  
     499         ! 
     500         a_i(:,:,jl) = tms(:,:) * a_i(:,:,jl) 
    519501      END DO 
    520502 
    521503      CALL lbc_lnk( at_i , 'T', 1. ) 
    522504      at_i(:,:) = tms(:,:) * at_i(:,:)                       ! put 0 over land 
    523  
     505      ! 
    524506      CALL lbc_lnk( fsbbq  , 'T', 1. ) 
    525  
     507      ! 
    526508   END SUBROUTINE lim_istate 
     509 
    527510 
    528511   SUBROUTINE lim_istate_init 
     
    532515      !! ** Purpose : Definition of initial state of the ice  
    533516      !! 
    534       !! ** Method : Read the namiceini namelist and check the parameter  
    535       !!       values called at the first timestep (nit000) 
     517      !! ** Method :   Read the namiceini namelist and check the parameter  
     518      !!             values called at the first timestep (nit000) 
    536519      !! 
    537       !! ** input :  
    538       !!        Namelist namiceini 
    539       !! 
    540       !! history : 
    541       !!  8.5  ! 03-08 (C. Ethe) original code 
     520      !! ** input  :   namelist namiceini 
    542521      !!----------------------------------------------------------------------------- 
    543       NAMELIST/namiceini/ ttest, hninn, hginn_u, aginn_u, hginn_d, aginn_d, hnins, & 
    544          hgins_u, agins_u, hgins_d, agins_d, sinn, sins 
     522      NAMELIST/namiceini/ ttest, hninn, hginn_u, aginn_u, hginn_d, aginn_d, hnins,   & 
     523         &                hgins_u, agins_u, hgins_d, agins_d, sinn, sins 
    545524      !!----------------------------------------------------------------------------- 
    546  
    547       ! Define the initial parameters 
    548       ! ------------------------- 
    549  
    550       ! Read Namelist namiceini  
    551       REWIND ( numnam_ice ) 
     525      ! 
     526      REWIND ( numnam_ice )               ! Read Namelist namiceini  
    552527      READ   ( numnam_ice , namiceini ) 
    553       IF(lwp) THEN 
     528      ! 
     529      IF(lwp) THEN                        ! control print 
    554530         WRITE(numout,*) 
    555531         WRITE(numout,*) 'lim_istate_init : ice parameters inititialisation ' 
     
    569545         WRITE(numout,*) '   initial  ice salinity       in the south     sins       = ', sins 
    570546      ENDIF 
    571  
     547      ! 
    572548   END SUBROUTINE lim_istate_init 
    573549 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limitd_me.F90

    r2287 r2475  
    1919   USE sbc_oce          ! Surface boundary condition: ocean fields 
    2020   USE thd_ice 
    21    USE limistate 
    2221   USE in_out_manager 
    2322   USE ice 
     
    2524   USE limthd_lac 
    2625   USE limvar 
    27    USE iceini 
    2826   USE limcons 
    2927   USE prtctl           ! Print control 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limitd_th.F90

    r2287 r2475  
    11MODULE limitd_th 
    2 #if defined key_lim3 
    3    !!---------------------------------------------------------------------- 
    4    !!   'key_lim3' :                                   LIM3 sea-ice model 
    5    !!---------------------------------------------------------------------- 
    62   !!====================================================================== 
    73   !!                       ***  MODULE limitd_th *** 
     
    95   !!                   computation of changes in g(h)       
    106   !!====================================================================== 
    11  
     7#if defined key_lim3 
    128   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
     9   !!   'key_lim3' :                                   LIM3 sea-ice model 
     10   !!---------------------------------------------------------------------- 
     11   !!---------------------------------------------------------------------- 
    1412   USE dom_ice 
    1513   USE par_oce          ! ocean parameters 
     
    1715   USE phycst           ! physical constants (ocean directory)  
    1816   USE thd_ice 
    19    USE limistate 
    20    USE in_out_manager 
    2117   USE ice 
    2218   USE par_ice 
    2319   USE limthd_lac 
    2420   USE limvar 
    25    USE iceini 
    2621   USE limcons 
    2722   USE prtctl           ! Print control 
     23   USE in_out_manager 
    2824   USE lib_mpp  
    2925 
     
    3127   PRIVATE 
    3228 
    33    !! * Routine accessibility 
    3429   PUBLIC lim_itd_th        ! called by ice_stp 
    3530   PUBLIC lim_itd_th_rem 
     
    3833   PUBLIC lim_itd_shiftice 
    3934 
    40    !! * Module variables 
    4135   REAL(wp)  ::           &  ! constant values 
    4236      epsi20 = 1e-20   ,  & 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limrhg.F90

    r2370 r2475  
    2828   USE ice              ! LIM-3: ice variables 
    2929   USE dom_ice          ! LIM-3: ice domain 
    30    USE iceini           ! LIM-3: ice initialisation 
    3130   USE limitd_me        ! LIM-3:  
    3231#else 
    3332   USE ice_2            ! LIM2: ice variables 
    3433   USE dom_ice_2        ! LIM2: ice domain 
    35    USE iceini_2         ! LIM2: ice initialisation 
    3634#endif 
    3735 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limrst.F90

    r2287 r2475  
    44   !! Ice restart :  write the ice restart file 
    55   !!====================================================================== 
     6   !! History:   -   ! 2005-04 (M. Vancoppenolle) Original code 
     7   !!           3.0  ! 2008-03 (C. Ethe) restart files in using IOM interface 
     8   !!---------------------------------------------------------------------- 
    69#if defined key_lim3 
    710   !!---------------------------------------------------------------------- 
     
    1215   !!   lim_rst_read    : read  the restart file  
    1316   !!---------------------------------------------------------------------- 
    14    !! * Modules used 
    15    USE ice 
    16    USE par_ice 
    17    USE in_out_manager 
    18    USE dom_oce 
    19    USE sbc_oce         ! Surface boundary condition: ocean fields 
    20    USE sbc_ice         ! Surface boundary condition: ice fields 
    21    USE iom 
     17   USE ice              ! sea-ice variables 
     18   USE par_ice          ! sea-ice parameters 
     19   USE dom_oce          ! ocean domain 
     20   USE sbc_oce          ! Surface boundary condition: ocean fields 
     21   USE sbc_ice          ! Surface boundary condition: ice fields 
     22   USE in_out_manager   ! I/O manager 
     23   USE iom              ! I/O library 
    2224 
    2325   IMPLICIT NONE 
    2426   PRIVATE 
    2527 
    26    !! * Accessibility 
    27    PUBLIC lim_rst_opn    ! routine called by icestep.F90 
    28    PUBLIC lim_rst_write  ! routine called by icestep.F90 
    29    PUBLIC lim_rst_read   ! routine called by iceinit.F90 
     28   PUBLIC   lim_rst_opn    ! routine called by icestep.F90 
     29   PUBLIC   lim_rst_write  ! routine called by icestep.F90 
     30   PUBLIC   lim_rst_read   ! routine called by iceini.F90 
    3031 
    3132   LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the ice restart write  
     
    3536   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    3637   !! $Id$ 
    37    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    38    !!---------------------------------------------------------------------- 
    39  
     38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     39   !!---------------------------------------------------------------------- 
    4040CONTAINS 
    4141 
     
    4848      INTEGER, INTENT(in) ::   kt       ! number of iteration 
    4949      ! 
    50       CHARACTER(LEN=20)   ::   clkt     ! ocean time-step deine as a character 
     50      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character 
    5151      CHARACTER(LEN=50)   ::   clname   ! ice output restart file name 
    5252      !!---------------------------------------------------------------------- 
     
    5454      IF( kt == nit000 )   lrst_ice = .FALSE.   ! default definition 
    5555 
    56       ! to get better performances with NetCDF format: 
    57       ! we open and define the ice restart file one ice time step before writing the data (-> at nitrst - 2*nn_fsbc + 1) 
    58       ! except if we write ice restart files every ice time step or if an ice restart file was writen at nitend - 2*nn_fsbc + 1 
    59       IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nstock == nn_fsbc .OR. ( kt == nitend - nn_fsbc + 1 .AND. .NOT. lrst_ice ) ) THEN 
     56      ! in order to get better performances with NetCDF format, we open and define the ice restart file  
     57      ! one ice time step before writing the data (-> at nitrst - 2*nn_fsbc + 1), except if we write ice  
     58      ! restart files every ice time step or if an ice restart file was writen at nitend - 2*nn_fsbc + 1 
     59      IF( kt == nitrst - 2*nn_fsbc + 1 .OR. nstock == nn_fsbc    & 
     60         &                             .OR. ( kt == nitend - nn_fsbc + 1 .AND. .NOT. lrst_ice ) ) THEN 
    6061         ! beware of the format used to write kt (default is i8.8, that should be large enough...) 
    6162         IF( nitrst > 99999999 ) THEN   ;   WRITE(clkt, *       ) nitrst 
     
    7576            ENDIF 
    7677         ENDIF 
    77  
     78         ! 
    7879         CALL iom_open( clname, numriw, ldwrt = .TRUE., kiolib = jprstlib ) 
    7980         lrst_ice = .TRUE. 
     
    8283   END SUBROUTINE lim_rst_opn 
    8384 
     85 
    8486   SUBROUTINE lim_rst_write( kt ) 
    8587      !!---------------------------------------------------------------------- 
     
    8789      !! 
    8890      !! ** purpose  :   output of sea-ice variable in a netcdf file 
     91      !!---------------------------------------------------------------------- 
     92      INTEGER, INTENT(in) ::   kt     ! number of iteration 
    8993      !! 
    90       !!---------------------------------------------------------------------- 
    91       ! Arguments : 
    92       INTEGER, INTENT(in) ::   kt     ! number of iteration 
    93  
    94       ! Local variables : 
     94      INTEGER ::   ji, jj, jk ,jl   ! dummy loop indices 
     95      INTEGER ::   iter 
     96      CHARACTER(len=15) ::   znam 
     97      CHARACTER(len=1)  ::   zchar, zchar1 
    9598      REAL(wp), DIMENSION(jpi,jpj) :: z2d 
    96       INTEGER :: ji, jj, jk ,jl 
    97       INTEGER :: iter 
    98       CHARACTER(len=15) :: znam 
    99       CHARACTER(len=1)  :: zchar, zchar1 
    10099      !!---------------------------------------------------------------------- 
    101100 
     
    111110      ! ------------------  
    112111      !                                                                        ! calendar control 
    113       CALL iom_rstput( iter, nitrst, numriw, 'nn_fsbc', REAL( nn_fsbc, wp) )      ! time-step  
    114       CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter , wp) )        ! date 
     112      CALL iom_rstput( iter, nitrst, numriw, 'nn_fsbc', REAL( nn_fsbc, wp ) )      ! time-step  
     113      CALL iom_rstput( iter, nitrst, numriw, 'kt_ice' , REAL( iter   , wp ) )      ! date 
    115114 
    116115      ! Prognostic variables  
     
    288287      ENDIF 
    289288      ! 
    290  
    291       IF( ln_nicep) THEN 
    292          WRITE(numout,*) 
    293          WRITE(numout,*) ' lim_rst_write : CHUKCHI SEA POINT ' 
    294          WRITE(numout,*) ' ~~~~~~~~~~' 
    295          WRITE(numout,*) ' ~~~ Arctic' 
    296  
    297          ji = jiindx 
    298          jj = jjindx 
    299  
    300          WRITE(numout,*) ' ji, jj ', ji, jj 
    301          WRITE(numout,*) ' ICE VARIABLES ' 
    302          WRITE(numout,*) ' open water ', ato_i(ji,jj) 
    303          DO jl = 1, jpl 
    304             WRITE(numout,*) ' *** CATEGORY NUMBER *** ', jl 
    305             WRITE(numout,*) ' ' 
    306             WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)      
    307             WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)  
    308             WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)     
    309             WRITE(numout,*) ' e_s        : ', e_s(ji,jj,1,jl)/1.0e9 
    310             WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)/1.0e9       
    311             WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)/1.0e9       
    312             WRITE(numout,*) ' smv_i      : ', smv_i(ji,jj,jl)   
    313             WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl) 
    314             WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl) 
    315          END DO 
    316  
    317          WRITE(numout,*) ' MOMENTS OF ADVECTION ' 
    318  
    319          WRITE(numout,*) ' open water ' 
    320          WRITE(numout,*) ' sxopw  ', sxopw(ji,jj) 
    321          WRITE(numout,*) ' syopw  ', syopw(ji,jj) 
    322          WRITE(numout,*) ' sxxopw ', sxxopw(ji,jj) 
    323          WRITE(numout,*) ' syyopw ', syyopw(ji,jj) 
    324          WRITE(numout,*) ' sxyopw ', sxyopw(ji,jj) 
    325          DO jl = 1, jpl 
    326             WRITE(numout,*) ' jl, ice volume content ', jl 
    327             WRITE(numout,*) ' sxice  ', sxice(ji,jj,jl) 
    328             WRITE(numout,*) ' syice  ', syice(ji,jj,jl) 
    329             WRITE(numout,*) ' sxxice ', sxxice(ji,jj,jl) 
    330             WRITE(numout,*) ' syyice ', syyice(ji,jj,jl) 
    331             WRITE(numout,*) ' sxyice ', sxyice(ji,jj,jl) 
    332             WRITE(numout,*) ' jl, snow volume content ', jl 
    333             WRITE(numout,*) ' sxsn   ', sxsn(ji,jj,jl) 
    334             WRITE(numout,*) ' sysn   ', sysn(ji,jj,jl) 
    335             WRITE(numout,*) ' sxxsn  ', sxxsn(ji,jj,jl) 
    336             WRITE(numout,*) ' syysn  ', syysn(ji,jj,jl) 
    337             WRITE(numout,*) ' sxysn  ', sxysn(ji,jj,jl) 
    338             WRITE(numout,*) ' jl, ice area in category ', jl 
    339             WRITE(numout,*) ' sxa    ', sxa (ji,jj,jl) 
    340             WRITE(numout,*) ' sya    ', sya (ji,jj,jl) 
    341             WRITE(numout,*) ' sxxa   ', sxxa (ji,jj,jl) 
    342             WRITE(numout,*) ' syya   ', syya (ji,jj,jl) 
    343             WRITE(numout,*) ' sxya   ', sxya (ji,jj,jl) 
    344             WRITE(numout,*) ' jl, snow temp ', jl 
    345             WRITE(numout,*) ' sxc0   ', sxc0(ji,jj,jl) 
    346             WRITE(numout,*) ' syc0   ', syc0(ji,jj,jl) 
    347             WRITE(numout,*) ' sxxc0  ', sxxc0(ji,jj,jl) 
    348             WRITE(numout,*) ' syyc0  ', syyc0(ji,jj,jl) 
    349             WRITE(numout,*) ' sxyc0  ', sxyc0(ji,jj,jl) 
    350             WRITE(numout,*) ' jl, ice salinity ', jl 
    351             WRITE(numout,*) ' sxsal  ', sxsal(ji,jj,jl) 
    352             WRITE(numout,*) ' sysal  ', sysal(ji,jj,jl) 
    353             WRITE(numout,*) ' sxxsal ', sxxsal(ji,jj,jl) 
    354             WRITE(numout,*) ' syysal ', syysal(ji,jj,jl) 
    355             WRITE(numout,*) ' sxysal ', sxysal(ji,jj,jl) 
    356             WRITE(numout,*) ' jl, ice age      ', jl 
    357             WRITE(numout,*) ' sxage  ', sxage(ji,jj,jl) 
    358             WRITE(numout,*) ' syage  ', syage(ji,jj,jl) 
    359             WRITE(numout,*) ' sxxage ', sxxage(ji,jj,jl) 
    360             WRITE(numout,*) ' syyage ', syyage(ji,jj,jl) 
    361             WRITE(numout,*) ' sxyage ', sxyage(ji,jj,jl) 
    362          END DO 
    363          DO jl = 1, jpl 
    364             DO jk = 1, nlay_i 
    365                WRITE(numout,*) ' jk, jl, ice heat content', jk, jl 
    366                WRITE(numout,*) ' sxe    ', sxe(ji,jj,jk,jl) 
    367                WRITE(numout,*) ' sye    ', sye(ji,jj,jk,jl) 
    368                WRITE(numout,*) ' sxxe   ', sxxe(ji,jj,jk,jl) 
    369                WRITE(numout,*) ' syye   ', syye(ji,jj,jk,jl) 
    370                WRITE(numout,*) ' sxye   ', sxye(ji,jj,jk,jl) 
    371             END DO 
    372          END DO 
    373  
    374       ENDIF 
    375  
    376289   END SUBROUTINE lim_rst_write 
     290 
    377291 
    378292   SUBROUTINE lim_rst_read 
     
    382296      !! ** purpose  :   read of sea-ice variable restart in a netcdf file 
    383297      !!---------------------------------------------------------------------- 
    384       ! Local variables 
    385298      INTEGER :: ji, jj, jk, jl, indx 
    386299      REAL(wp) ::   zfice, ziter 
    387       REAL(wp) :: & !parameters for the salinity profile 
    388          zs_inf, z_slope_s, zsmax, zsmin, zalpha, zindb 
    389       REAL(wp), DIMENSION(nlay_i) :: zs_zero  
    390       REAL(wp), DIMENSION(jpi,jpj) :: z2d 
    391       CHARACTER(len=15) :: znam 
    392       CHARACTER(len=1)  :: zchar, zchar1 
    393       INTEGER           :: jlibalt = jprstlib 
    394       LOGICAL           :: llok 
     300      REAL(wp) ::   zs_inf, z_slope_s, zsmax, zsmin, zalpha, zindb   ! local scalars used for the salinity profile 
     301      REAL(wp), DIMENSION(nlay_i)  ::   zs_zero  
     302      REAL(wp), DIMENSION(jpi,jpj) ::   z2d 
     303      CHARACTER(len=15) ::   znam 
     304      CHARACTER(len=1)  ::   zchar, zchar1 
     305      INTEGER           ::   jlibalt = jprstlib 
     306      LOGICAL           ::   llok 
    395307      !!---------------------------------------------------------------------- 
    396308 
     
    469381      END DO 
    470382 
    471       ! Salinity profile 
    472       !----------------- 
    473       WRITE(numout,*) ' num_sal - will restart understand salinity profile ', num_sal 
    474  
    475       num_sal = 2 
    476       IF(num_sal.eq.2) THEN 
    477          !     CALL lim_var_salprof 
     383      IF( num_sal == 2 ) THEN      ! Salinity profile 
    478384         DO jl = 1, jpl 
    479385            DO jk = 1, nlay_i 
     
    481387                  DO ji = 1, jpi 
    482388                     zs_inf        = sm_i(ji,jj,jl) 
    483                      z_slope_s     = 2.0*sm_i(ji,jj,jl)/MAX(0.01,ht_i(ji,jj,jl)) 
     389                     z_slope_s     = 2._wp * sm_i(ji,jj,jl) / MAX( 0.01_wp , ht_i(ji,jj,jl) ) 
    484390                     !- slope of the salinity profile 
    485                      zs_zero(jk)   = z_slope_s * ( FLOAT(jk)-1.0/2.0 ) * & 
    486                         ht_i(ji,jj,jl) / FLOAT(nlay_i) 
    487                      zsmax = 4.5 
    488                      zsmin = 3.5 
     391                     zs_zero(jk)   = z_slope_s * ( REAL(jk,wp) - 0.5_wp ) * ht_i(ji,jj,jl) / REAL(nlay_i,wp) 
     392                     zsmax = 4.5_wp 
     393                     zsmin = 3.5_wp 
    489394                     IF( sm_i(ji,jj,jl) .LT. zsmin ) THEN 
    490                         zalpha = 1.0 
     395                        zalpha = 1._wp 
    491396                     ELSEIF( sm_i(ji,jj,jl) .LT.zsmax ) THEN 
    492                         zalpha = sm_i(ji,jj,jl) / (zsmin-zsmax) + zsmax / (zsmax-zsmin) 
     397                        zalpha = sm_i(ji,jj,jl) / ( zsmin - zsmax ) + zsmax / ( zsmax - zsmin ) 
    493398                     ELSE 
    494                         zalpha = 0.0 
     399                        zalpha = 0._wp 
    495400                     ENDIF 
    496                      s_i(ji,jj,jk,jl) = zalpha*zs_zero(jk) + ( 1.0 - zalpha )*zs_inf 
     401                     s_i(ji,jj,jk,jl) = zalpha * zs_zero(jk) + ( 1._wp - zalpha ) * zs_inf 
    497402                  END DO 
    498403               END DO 
     
    646551         END DO 
    647552      END DO 
    648  
     553      ! 
    649554      CALL iom_close( numrir ) 
    650  
    651       !+++++++++++ CHECK EVERYTHING ++++++++++ 
    652  
    653       WRITE(numout,*) 
    654       WRITE(numout,*) ' lim_rst_read  : CHUKCHI SEA POINT ' 
    655       WRITE(numout,*) ' ~~~~~~~~~~' 
    656       WRITE(numout,*) ' ~~~ Arctic' 
    657  
    658       indx = 1 
    659       ji = 24 
    660       jj = 24 
    661       WRITE(numout,*) ' ji, jj ', ji, jj 
    662       WRITE(numout,*) ' ICE VARIABLES ' 
    663       WRITE(numout,*) ' open water ', ato_i(ji,jj) 
    664  
    665       DO jl = 1, jpl 
    666          WRITE(numout,*) ' *** CATEGORY NUMBER *** ', jl 
    667          WRITE(numout,*) ' ' 
    668          WRITE(numout,*) ' a_i        : ', a_i(ji,jj,jl)      
    669          WRITE(numout,*) ' v_i        : ', v_i(ji,jj,jl)  
    670          WRITE(numout,*) ' v_s        : ', v_s(ji,jj,jl)     
    671          WRITE(numout,*) ' e_i1       : ', e_i(ji,jj,1,jl)/1.0e9       
    672          WRITE(numout,*) ' e_i2       : ', e_i(ji,jj,2,jl)/1.0e9       
    673          WRITE(numout,*) ' e_s        : ', e_s(ji,jj,1,jl)       
    674          WRITE(numout,*) ' smv_i      : ', smv_i(ji,jj,jl)   
    675          WRITE(numout,*) ' oa_i       : ', oa_i(ji,jj,jl) 
    676          WRITE(numout,*) ' t_su       : ', t_su(ji,jj,jl) 
    677       END DO 
    678  
    679       WRITE(numout,*) ' open water ' 
    680       WRITE(numout,*) ' sxopw  ', sxopw(ji,jj) 
    681       WRITE(numout,*) ' syopw  ', syopw(ji,jj) 
    682       WRITE(numout,*) ' sxxopw ', sxxopw(ji,jj) 
    683       WRITE(numout,*) ' syyopw ', syyopw(ji,jj) 
    684       WRITE(numout,*) ' sxyopw ', sxyopw(ji,jj) 
    685       DO jl = 1, jpl 
    686          WRITE(numout,*) ' jl, ice volume content ', jl 
    687          WRITE(numout,*) ' sxice  ', sxice(ji,jj,jl) 
    688          WRITE(numout,*) ' syice  ', syice(ji,jj,jl) 
    689          WRITE(numout,*) ' sxxice ', sxxice(ji,jj,jl) 
    690          WRITE(numout,*) ' syyice ', syyice(ji,jj,jl) 
    691          WRITE(numout,*) ' sxyice ', sxyice(ji,jj,jl) 
    692          WRITE(numout,*) ' jl, snow volume content ', jl 
    693          WRITE(numout,*) ' sxsn   ', sxsn(ji,jj,jl) 
    694          WRITE(numout,*) ' sysn   ', sysn(ji,jj,jl) 
    695          WRITE(numout,*) ' sxxsn  ', sxxsn(ji,jj,jl) 
    696          WRITE(numout,*) ' syysn  ', syysn(ji,jj,jl) 
    697          WRITE(numout,*) ' sxysn  ', sxysn(ji,jj,jl) 
    698          WRITE(numout,*) ' jl, ice area in category ', jl 
    699          WRITE(numout,*) ' sxa    ', sxa (ji,jj,jl) 
    700          WRITE(numout,*) ' sya    ', sya (ji,jj,jl) 
    701          WRITE(numout,*) ' sxxa   ', sxxa (ji,jj,jl) 
    702          WRITE(numout,*) ' syya   ', syya (ji,jj,jl) 
    703          WRITE(numout,*) ' sxya   ', sxya (ji,jj,jl) 
    704          WRITE(numout,*) ' jl, snow temp ', jl 
    705          WRITE(numout,*) ' sxc0   ', sxc0(ji,jj,jl) 
    706          WRITE(numout,*) ' syc0   ', syc0(ji,jj,jl) 
    707          WRITE(numout,*) ' sxxc0  ', sxxc0(ji,jj,jl) 
    708          WRITE(numout,*) ' syyc0  ', syyc0(ji,jj,jl) 
    709          WRITE(numout,*) ' sxyc0  ', sxyc0(ji,jj,jl) 
    710          WRITE(numout,*) ' jl, ice salinity ', jl 
    711          WRITE(numout,*) ' sxsal  ', sxsal(ji,jj,jl) 
    712          WRITE(numout,*) ' sysal  ', sysal(ji,jj,jl) 
    713          WRITE(numout,*) ' sxxsal ', sxxsal(ji,jj,jl) 
    714          WRITE(numout,*) ' syysal ', syysal(ji,jj,jl) 
    715          WRITE(numout,*) ' sxysal ', sxysal(ji,jj,jl) 
    716          WRITE(numout,*) ' jl, ice age      ', jl 
    717          WRITE(numout,*) ' sxage  ', sxage(ji,jj,jl) 
    718          WRITE(numout,*) ' syage  ', syage(ji,jj,jl) 
    719          WRITE(numout,*) ' sxxage ', sxxage(ji,jj,jl) 
    720          WRITE(numout,*) ' syyage ', syyage(ji,jj,jl) 
    721          WRITE(numout,*) ' sxyage ', sxyage(ji,jj,jl) 
    722       END DO 
    723       DO jl = 1, jpl 
    724          DO jk = 1, nlay_i 
    725             WRITE(numout,*) ' jk, jl, ice heat content', jk, jl 
    726             WRITE(numout,*) ' sxe    ', sxe(ji,jj,jk,jl) 
    727             WRITE(numout,*) ' sye    ', sye(ji,jj,jk,jl) 
    728             WRITE(numout,*) ' sxxe   ', sxxe(ji,jj,jk,jl) 
    729             WRITE(numout,*) ' syye   ', syye(ji,jj,jk,jl) 
    730             WRITE(numout,*) ' sxye   ', sxye(ji,jj,jk,jl) 
    731          END DO 
    732       END DO 
    733  
    734       !+++++++++++ END CHECK +++++++++++++++++ 
    735  
     555      ! 
    736556   END SUBROUTINE lim_rst_read 
    737  
    738557 
    739558#else 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limsbc.F90

    r2383 r2475  
    2323   USE sbc_oce          ! Surface boundary condition: ocean fields 
    2424   USE phycst           ! physical constants 
     25   USE albedo           ! albedo parameters 
    2526   USE ice              ! LIM sea-ice variables 
    26    USE iceini           ! ??? 
    27  
    2827   USE lbclnk           ! ocean lateral boundary condition 
    2928   USE in_out_manager   ! I/O manager 
    30    USE albedo           ! albedo parameters 
    3129   USE prtctl           ! Print control 
    3230 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limthd.F90

    r2383 r2475  
    2727   USE dom_ice         ! LIM sea-ice domain 
    2828   USE domvvl          ! domain: variable volume level 
    29    USE iceini          ! LIM: sea-ice initialization 
    3029   USE limthd_dif      ! LIM: thermodynamics, vertical diffusion 
    3130   USE limthd_dh       ! LIM: thermodynamics, ice and snow thickness variation 
     
    3332   USE limthd_ent      ! LIM: thermodynamics, ice enthalpy redistribution 
    3433   USE limtab          ! LIM: 1D <==> 2D transformation 
    35    USE limvar          ! LIM: ??? 
     34   USE limvar          ! LIM: sea-ice variables 
    3635   USE lbclnk          ! lateral boundary condition - MPP links 
    3736   USE lib_mpp         ! MPP library 
     
    4241   PRIVATE 
    4342 
    44    PUBLIC   lim_thd    ! called by lim_step 
     43   PUBLIC   lim_thd        ! called by limstp module 
     44   PUBLIC   lim_thd_init   ! called by iceini module 
    4545 
    4646   REAL(wp) ::   epsi20 = 1e-20_wp   ! constant values 
     
    9090      REAL(wp), DIMENSION(jpi,jpj) ::   zqlbsbq   ! link with lead energy budget qldif 
    9191      !!------------------------------------------------------------------- 
    92  
    93       IF( numit == nstart )   CALL lim_thd_init      ! Initialization (first time-step only) 
    94  
    95       IF( numit == nstart )   CALL lim_thd_sal_init  ! Initialization (first time-step only) 
    9692       
    9793      !------------------------------------------------------------------------------! 
     
    823819         &                kappa_i, nconv_i_thd, maxer_i_thd, thcon_i_swi 
    824820      !!------------------------------------------------------------------- 
    825  
     821      ! 
    826822      IF(lwp) THEN 
    827823         WRITE(numout,*) 
     
    829825         WRITE(numout,*) '~~~~~~~' 
    830826      ENDIF 
    831  
     827      ! 
    832828      REWIND( numnam_ice )                  ! read Namelist numnam_ice 
    833829      READ  ( numnam_ice , namicethd ) 
    834        
     830      ! 
    835831      IF(lwp) THEN                          ! control print 
    836832         WRITE(numout,*) 
     
    870866#else 
    871867   !!---------------------------------------------------------------------- 
    872    !!   Default option                               NO  LIM3 sea-ice model 
     868   !!   Default option         Dummy module          NO  LIM3 sea-ice model 
    873869   !!---------------------------------------------------------------------- 
    874 CONTAINS 
    875    SUBROUTINE lim_thd         ! Empty routine 
    876    END SUBROUTINE lim_thd 
    877    SUBROUTINE lim_thd_con_dif 
    878    END SUBROUTINE lim_thd_con_dif 
    879870#endif 
    880871 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limthd_dh.F90

    r2287 r2475  
    1717   USE phycst           ! physical constants (OCE directory)  
    1818   USE sbc_oce          ! Surface boundary condition: ocean fields 
    19    USE thd_ice 
    20    USE iceini 
    21    USE limistate 
    22    USE in_out_manager 
    2319   USE ice 
    2420   USE par_ice 
     21   USE thd_ice 
     22   USE in_out_manager 
    2523   USE lib_mpp 
    2624 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limthd_dif.F90

    r2287 r2475  
    11MODULE limthd_dif 
    2 #if defined key_lim3 
    3    !!---------------------------------------------------------------------- 
    4    !!   'key_lim3'                                      LIM3 sea-ice model 
    5    !!---------------------------------------------------------------------- 
    62   !!====================================================================== 
    73   !!                       ***  MODULE limthd_dif *** 
     
    95   !!                   computation of surface and inner T   
    106   !!====================================================================== 
    11  
    127   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
     8#if defined key_lim3 
     9   !!---------------------------------------------------------------------- 
     10   !!   'key_lim3'                                      LIM3 sea-ice model 
     11   !!---------------------------------------------------------------------- 
    1412   USE par_oce          ! ocean parameters 
    1513   USE phycst           ! physical constants (ocean directory)  
    1614   USE thd_ice 
    17    USE iceini 
    18    USE limistate 
    1915   USE in_out_manager 
    2016   USE ice 
     
    2521   PRIVATE 
    2622 
    27    !! * Routine accessibility 
    28    PUBLIC lim_thd_dif        ! called by lim_thd 
    29  
    30    !! * Module variables 
     23   PUBLIC   lim_thd_dif   ! called by lim_thd 
     24 
    3125   REAL(wp)  ::           &  ! constant values 
    3226      epsi20 = 1e-20   ,  & 
     
    4034   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    4135   !!---------------------------------------------------------------------- 
    42  
    4336CONTAINS 
    4437 
     
    872865   END SUBROUTINE lim_thd_dif 
    873866#endif 
     867   !!====================================================================== 
    874868END MODULE limthd_dif 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limthd_ent.F90

    r2287 r2475  
    11MODULE limthd_ent 
    2 #if defined key_lim3 
    3    !!---------------------------------------------------------------------- 
    4    !!   'key_lim3'                                      LIM3 sea-ice model 
    5    !!---------------------------------------------------------------------- 
    62   !!====================================================================== 
    73   !!                       ***  MODULE limthd_ent   *** 
     
    106   !!                       after vertical growth/decay 
    117   !!====================================================================== 
     8#if defined key_lim3 
     9   !!---------------------------------------------------------------------- 
     10   !!   'key_lim3'                                      LIM3 sea-ice model 
     11   !!---------------------------------------------------------------------- 
    1212   !!   lim_thd_ent : ice redistribution of enthalpy 
    13  
    14    !! * Modules used 
     13   !!---------------------------------------------------------------------- 
    1514   USE par_oce          ! ocean parameters 
    1615   USE dom_oce 
     
    1918   USE phycst 
    2019   USE thd_ice 
    21    USE iceini 
    22    USE limistate 
    2320   USE ice 
    2421   USE limvar 
     
    2926   PRIVATE 
    3027 
    31    !! * Routine accessibility 
    32    PUBLIC  lim_thd_ent     ! called by lim_thd 
    33  
    34    !! * Module variables 
     28   PUBLIC   lim_thd_ent     ! called by lim_thd 
     29 
    3530   REAL(wp)  ::           &  ! constant values 
    3631      epsi20 = 1.e-20  ,  & 
     
    3934      zone   = 1.e0    ,  & 
    4035      epsi10 = 1.0e-10 
    41  
    4236   !!---------------------------------------------------------------------- 
    4337   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    4438   !! $Id$ 
    45    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     39   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4640   !!---------------------------------------------------------------------- 
    47  
    4841CONTAINS 
    4942 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limthd_lac.F90

    r2287 r2475  
    11MODULE limthd_lac 
    2    !!---------------------------------------------------------------------- 
    3    !!   'key_lim3'                                      LIM3 sea-ice model 
    4    !!---------------------------------------------------------------------- 
    52   !!====================================================================== 
    63   !!                       ***  MODULE limthd_lac   *** 
     
    96#if defined key_lim3 
    107   !!---------------------------------------------------------------------- 
     8   !!   'key_lim3'                                      LIM3 sea-ice model 
     9   !!---------------------------------------------------------------------- 
    1110   !!   lim_lat_acr    : lateral accretion of ice 
    12    !! * Modules used 
     11   !!---------------------------------------------------------------------- 
    1312   USE par_oce          ! ocean parameters 
    1413   USE dom_oce 
     
    2120   USE par_ice 
    2221   USE ice 
    23    USE iceini 
    2422   USE limtab 
    2523   USE limcons 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limthd_sal.F90

    r2287 r2475  
    11MODULE limthd_sal 
    2    !!---------------------------------------------------------------------- 
    3    !!   'key_lim3'                                      LIM3 sea-ice model 
    4    !!---------------------------------------------------------------------- 
    52   !!====================================================================== 
    63   !!                       ***  MODULE limthd_sal *** 
    7    !!                   computation salinity variations in 
    8    !!                               the ice 
     4   !! LIM-3 sea-ice :  computation of salinity variations in the ice 
    95   !!====================================================================== 
     6   !! History :   -   ! 2003-05 (M. Vancoppenolle) UCL-ASTR first coding for LIM3-1D 
     7   !!            3.0  ! 2005-12 (M. Vancoppenolle) adapted to the 3-D version 
     8   !!--------------------------------------------------------------------- 
    109#if defined key_lim3 
    1110   !!---------------------------------------------------------------------- 
     11   !!   'key_lim3'                                      LIM-3 sea-ice model 
     12   !!---------------------------------------------------------------------- 
    1213   !!   lim_thd_sal : salinity variations in the ice 
    13    !! * Modules used 
     14   !!---------------------------------------------------------------------- 
    1415   USE par_oce          ! ocean parameters 
    1516   USE phycst           ! physical constants (ocean directory) 
    1617   USE sbc_oce          ! Surface boundary condition: ocean fields 
    17    USE thd_ice 
    18    USE iceini 
    19    USE ice 
    20    USE limistate 
    21    USE in_out_manager 
    22    USE limvar 
    23    USE par_ice 
     18   USE ice              ! LIM: sea-ice variables 
     19   USE par_ice          ! LIM: sea-ice parameters 
     20   USE thd_ice          ! LIM: sea-ice thermodynamics 
     21   USE limvar           ! LIM: sea-ice variables 
     22   USE in_out_manager   ! I/O manager 
    2423 
    2524   IMPLICIT NONE 
    2625   PRIVATE 
    2726 
    28    !! * Routine accessibility 
    29    PUBLIC lim_thd_sal        ! called by lim_thd 
    30    PUBLIC lim_thd_sal_init   ! called by lim_thd 
    31  
    32    !! * Module variables 
    33    REAL(wp)  ::           &  ! constant values 
    34       epsi20 = 1e-20   ,  & 
    35       epsi13 = 1e-13   ,  & 
    36       zzero  = 0.e0    ,  & 
    37       zone   = 1.e0 
     27   PUBLIC   lim_thd_sal        ! called by limthd module 
     28   PUBLIC   lim_thd_sal_init   ! called by iceini module 
    3829 
    3930   !!---------------------------------------------------------------------- 
    4031   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    4132   !! $Id$ 
    42    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    43    !!---------------------------------------------------------------------- 
    44  
     33   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     34   !!---------------------------------------------------------------------- 
    4535CONTAINS 
    4636 
    47    SUBROUTINE lim_thd_sal(kideb,kiut) 
     37   SUBROUTINE lim_thd_sal( kideb, kiut ) 
    4838      !!------------------------------------------------------------------- 
    49       !!                ***  ROUTINE lim_thd_sal  ***        
    50       !! ** Purpose : 
    51       !!        This routine computes new salinities in the ice 
     39      !!                ***  ROUTINE lim_thd_sal  ***     
     40      !!    
     41      !! ** Purpose :  computes new salinities in the ice 
    5242      !! 
    5343      !! ** Method  :  4 possibilities 
     
    5646      !!               -> num_sal = 3 -> S = S(z)   [multiyear ice] 
    5747      !!               -> num_sal = 4 -> S = S(h)   [Cox and Weeks 74] 
    58       !!            
    59       !! ** Steps 
    60       !! 
    61       !! ** Arguments 
    62       !! 
    63       !! ** Inputs / Outputs 
    64       !! 
    65       !! ** External 
    66       !! 
    67       !! ** References 
    68       !! 
    69       !! ** History  :  
    70       !! 
    71       !! "Je ne suis pour l'instant qu'a 80% de ma condition, mais c'est  
    72       !!  les 30% qui restent qui seront les plus difficiles" 
    73       !!                                           E. Mpenza 
    74       !! 
    75       !!------------------------------------------------------------------- 
    76       !! History : 
    77       !!   ori  !  03-05 M. Vancoppenolle UCL-ASTR first coding for LIM-1D 
    78       !!   3.0  !  05-12 Routine rewritten for the 3-D version 
    7948      !!--------------------------------------------------------------------- 
    80       !! 
    81       !! * Local variables 
    82       INTEGER, INTENT(in) :: & 
    83          kideb, kiut             !: thickness category index 
    84  
    85       INTEGER ::             & 
    86          ji, jk ,            &   !: geographic and layer index  
    87          zji, zjj 
    88  
    89       REAL(wp) ::            & 
    90          zsold,              &   !: old salinity 
    91          zeps=1.0e-06   ,    &   !: very small 
    92          iflush         ,    &   !: flushing (1) or not (0) 
    93          iaccrbo        ,    &   !: bottom accretion (1) or not (0) 
    94          igravdr        ,    &   !: gravity drainage or not 
    95          isnowic        ,    &   !: gravity drainage or not 
    96          i_ice_switch   ,    &   !: ice thickness above a certain treshold or not 
    97          ztmelts        ,    &   !: freezing point of sea ice 
    98          zaaa           ,    &   !: dummy factor 
    99          zbbb           ,    &   !: dummy factor 
    100          zccc           ,    &   !: dummy factor 
    101          zdiscrim                !: dummy factor 
    102  
    103       REAL(wp), DIMENSION(jpij) ::          & 
    104          ze_init        ,    &   !initial total enthalpy 
    105          zhiold         ,    & 
    106          zsiold 
    107  
     49      INTEGER, INTENT(in) ::  kideb, kiut   ! thickness category index 
     50      ! 
     51      INTEGER  ::   ji, jk     ! dummy loop indices  
     52      INTEGER  ::   zji, zjj   ! local integers 
     53      REAL(wp) ::   zsold, zeps, iflush, iaccrbo, igravdr, isnowic, i_ice_switch,  ztmelts   ! local scalars 
     54      REAL(wp) ::   zaaa, zbbb, zccc, zdiscrim   ! local scalars 
     55      REAL(wp), DIMENSION(jpij) ::   ze_init, zhiold, zsiold   ! 1D workspace 
    10856      !!--------------------------------------------------------------------- 
    10957 
     58      zeps=1.0e-06_wp 
     59 
    11060      !------------------------------------------------------------------------------| 
    11161      ! 1) Constant salinity, constant in time                                       | 
    11262      !------------------------------------------------------------------------------| 
    11363 
    114       IF (num_sal.eq.1) THEN 
    115  
    116          !         WRITE(numout,*) 
    117          !         WRITE(numout,*) 'lim_thd_sal : Ice salinity computation module ', & 
    118          !         num_sal 
    119          !         WRITE(numout,*) '~~~~~~~~~~~~' 
    120  
     64      IF( num_sal == 1 ) THEN 
    12165         DO jk = 1, nlay_i 
    12266            DO ji = kideb, kiut 
     
    12468            END DO ! ji 
    12569         END DO ! jk 
    126  
     70         ! 
    12771         DO ji = kideb, kiut 
    12872            sm_i_b(ji)      =  bulk_sal  
    12973         END DO ! ji 
    130  
    131       ENDIF ! num_sal .EQ. 1 
     74         ! 
     75      ENDIF 
    13276 
    13377      !------------------------------------------------------------------------------| 
     
    176120            ! isnowic : 1 if snow ice formation 
    177121            i_ice_switch = 1.0 - MAX ( 0.0 , SIGN ( 1.0 , - ht_i_b(ji) + 1.0e-2 ) ) 
    178             isnowic      = 1.0 - MAX ( 0.0 , SIGN ( 1.0 , - dh_snowice(ji) ) ) * & 
    179                i_ice_switch 
     122            isnowic      = 1.0 - MAX ( 0.0 , SIGN ( 1.0 , - dh_snowice(ji) ) ) * i_ice_switch 
    180123 
    181124            !--------------------- 
     
    184127 
    185128            ! drainage by gravity drainage 
    186             dsm_i_gd_1d(ji) = - igravdr *                                     &  
    187                MAX( sm_i_b(ji) - sal_G , 0.0 ) /             & 
    188                time_G * rdt_ice  
     129            dsm_i_gd_1d(ji) = - igravdr * MAX( sm_i_b(ji) - sal_G , 0._wp ) / time_G * rdt_ice  
    189130 
    190131            ! drainage by flushing   
    191             dsm_i_fl_1d(ji)  = - iflush *                                     & 
    192                MAX( sm_i_b(ji) - sal_F , 0.0 ) /             &  
    193                time_F * rdt_ice 
     132            dsm_i_fl_1d(ji)  = - iflush * MAX( sm_i_b(ji) - sal_F , 0._wp ) / time_F * rdt_ice 
    194133 
    195134            !----------------- 
     
    201140            ! to conserve energy 
    202141            zsiold(ji) = sm_i_b(ji) 
    203             sm_i_b(ji) = sm_i_b(ji)                                           & 
    204                + dsm_i_fl_1d(ji) + dsm_i_gd_1d(ji)  !                 & 
     142            sm_i_b(ji) = sm_i_b(ji) + dsm_i_fl_1d(ji) + dsm_i_gd_1d(ji) 
    205143 
    206144            ! if no ice, salinity eq 0.1 
    207             i_ice_switch  = 1.0 - MAX ( 0.0, SIGN (1.0 , - ht_i_b(ji) ) ) 
    208             sm_i_b(ji)    = i_ice_switch*sm_i_b(ji) + s_i_min * ( 1.0 -       & 
    209                i_ice_switch ) 
     145            i_ice_switch = 1._wp - MAX ( 0._wp, SIGN( 1._wp , - ht_i_b(ji) ) ) 
     146            sm_i_b(ji)   = i_ice_switch*sm_i_b(ji) + s_i_min * ( 1._wp - i_ice_switch ) 
    210147         END DO ! ji 
    211148 
    212149         ! Salinity profile 
    213          CALL lim_var_salprof1d(kideb,kiut) 
     150         CALL lim_var_salprof1d( kideb, kiut ) 
    214151 
    215152         !---------------------------- 
     
    219156         DO ji = kideb, kiut 
    220157            ! iflush  : 1 if summer  
    221             iflush       =  MAX( 0.0 , SIGN ( 1.0 , t_su_b(ji) - rtt ) )  
     158            iflush  =  MAX( 0._wp , SIGN ( 1._wp , t_su_b(ji) - rtt ) )  
    222159            ! igravdr : 1 if t_su lt t_bo 
    223             igravdr      =  MAX( 0.0 , SIGN ( 1.0 , t_bo_b(ji) - t_su_b(ji) ) )  
     160            igravdr =  MAX( 0._wp , SIGN ( 1._wp , t_bo_b(ji) - t_su_b(ji) ) )  
    224161            ! iaccrbo : 1 if bottom accretion 
    225             iaccrbo      =  MAX( 0.0 , SIGN ( 1.0 , dh_i_bott(ji) ) ) 
    226  
    227             fhbri_1d(ji) = 0.0 
     162            iaccrbo =  MAX( 0._wp , SIGN ( 1._wp , dh_i_bott(ji) ) ) 
     163            ! 
     164            fhbri_1d(ji) = 0._wp 
    228165         END DO ! ji 
    229166 
     
    232169         !---------------------------- 
    233170         DO ji = kideb, kiut 
    234             i_ice_switch  = 1.0 - MAX ( 0.0, SIGN (1.0 , - ht_i_b(ji) ) ) 
    235             fsbri_1d(ji) = fsbri_1d(ji) -  & 
    236                i_ice_switch * rhoic * a_i_b(ji) * ht_i_b(ji) *  & 
    237                ( MAX(dsm_i_gd_1d(ji) + dsm_i_fl_1d(ji), & 
    238                sm_i_b(ji) - zsiold(ji) ) ) / rdt_ice 
    239             IF ( num_sal .EQ. 4 ) fsbri_1d(ji) = 0.0 
    240  
     171            i_ice_switch = 1._wp - MAX ( 0._wp, SIGN( 1._wp , - ht_i_b(ji) ) ) 
     172            fsbri_1d(ji) = fsbri_1d(ji) - i_ice_switch * rhoic * a_i_b(ji) * ht_i_b(ji)         & 
     173               &         * ( MAX(dsm_i_gd_1d(ji) + dsm_i_fl_1d(ji), sm_i_b(ji) - zsiold(ji) ) ) / rdt_ice 
     174            IF( num_sal == 4 ) fsbri_1d(ji) = 0._wp 
    241175         END DO ! ji 
    242176 
     
    246180         !-------------------- 
    247181         DO jk = 1, nlay_i 
    248  
    249182            DO ji = kideb, kiut 
    250  
    251183               ztmelts    =  -tmut*s_i_b(ji,jk) + rtt 
    252184               !Conversion q(S,T) -> T (second order equation) 
    253185               zaaa         =  cpic 
    254                zbbb         =  ( rcp - cpic ) * ( ztmelts - rtt ) + & 
    255                   q_i_b(ji,jk) / rhoic - lfus 
     186               zbbb         =  ( rcp - cpic ) * ( ztmelts - rtt ) + q_i_b(ji,jk) / rhoic - lfus 
    256187               zccc         =  lfus * ( ztmelts - rtt ) 
    257188               zdiscrim     =  SQRT( MAX(zbbb*zbbb - 4.0*zaaa*zccc,0.0) ) 
    258                t_i_b(ji,jk) =  rtt - ( zbbb + zdiscrim ) / &  
    259                   ( 2.0 *zaaa ) 
     189               t_i_b(ji,jk) =  rtt - ( zbbb + zdiscrim ) / ( 2.0 *zaaa ) 
    260190            END DO !ji 
    261  
    262191         END DO !jk 
    263  
     192         ! 
    264193      ENDIF ! num_sal .EQ. 2 
    265194 
     
    268197      !------------------------------------------------------------------------------| 
    269198 
    270       IF ( num_sal .EQ. 3 ) THEN 
     199      IF( num_sal .EQ. 3 ) THEN 
    271200 
    272201         WRITE(numout,*) 
     
    322251            zji                 = MOD( npb(ji) - 1, jpi ) + 1 
    323252            zjj                 = ( npb(ji) - 1 ) / jpi + 1 
    324             fseqv_1d(ji) = fseqv_1d(ji)              + &  
    325                ( sss_m(zji,zjj) - bulk_sal    ) * &  
    326                rhoic * a_i_b(ji) * & 
    327                MAX( dh_i_bott(ji) , 0.0 ) / rdt_ice 
     253            fseqv_1d(ji) = fseqv_1d(ji) + ( sss_m(zji,zjj) - bulk_sal    )               & 
     254               &                        * rhoic * a_i_b(ji) * MAX( dh_i_bott(ji) , 0.0 ) / rdt_ice 
    328255         END DO 
    329256      ELSE 
     
    331258            zji                 = MOD( npb(ji) - 1, jpi ) + 1 
    332259            zjj                 = ( npb(ji) - 1 ) / jpi + 1 
    333             fseqv_1d(ji) = fseqv_1d(ji)              + &  
    334                ( sss_m(zji,zjj) - s_i_new(ji) ) * &  
    335                rhoic * a_i_b(ji) * & 
    336                MAX( dh_i_bott(ji) , 0.0 ) / rdt_ice 
     260            fseqv_1d(ji) = fseqv_1d(ji) + ( sss_m(zji,zjj) - s_i_new(ji) )               & 
     261               &                        * rhoic * a_i_b(ji) * MAX( dh_i_bott(ji) , 0.0 ) / rdt_ice 
    337262         END DO ! ji 
    338263      ENDIF 
    339  
    340       !-- End of salinity computations 
     264      ! 
    341265   END SUBROUTINE lim_thd_sal 
    342    !============================================================================== 
     266 
    343267 
    344268   SUBROUTINE lim_thd_sal_init 
     
    348272      !! ** Purpose :   initialization of ice salinity parameters 
    349273      !! 
    350       !! ** Method  : Read the namicesal namelist and check the parameter 
    351       !!       values called at the first timestep (nit000) 
     274      !! ** Method  :   Read the namicesal namelist and check the parameter 
     275      !!              values called at the first timestep (nit000) 
    352276      !! 
    353277      !! ** input   :   Namelist namicesal 
    354       !! 
    355       !! history : 
    356       !!   3.0  !  July 2005 M. Vancoppenolle  Original code 
    357278      !!------------------------------------------------------------------- 
    358       NAMELIST/namicesal/ num_sal, bulk_sal, sal_G, time_G, sal_F, time_F, & 
    359          s_i_max, s_i_min, s_i_0, s_i_1 
     279      NAMELIST/namicesal/ num_sal, bulk_sal, sal_G, time_G, sal_F, time_F,   & 
     280         &                s_i_max, s_i_min, s_i_0, s_i_1 
    360281      !!------------------------------------------------------------------- 
    361  
    362       ! Read Namelist namicesal 
    363       REWIND ( numnam_ice ) 
    364       READ   ( numnam_ice  , namicesal ) 
    365       IF(lwp) THEN 
     282      ! 
     283      REWIND( numnam_ice )                   ! Read Namelist namicesal 
     284      READ  ( numnam_ice  , namicesal ) 
     285      ! 
     286      IF(lwp) THEN                           ! control print 
    366287         WRITE(numout,*) 
    367288         WRITE(numout,*) 'lim_thd_sal_init : Ice parameters for salinity ' 
     
    378299         WRITE(numout,*) ' 2nd salinity for salinity profile  : ', s_i_1 
    379300      ENDIF 
    380  
     301      ! 
    381302   END SUBROUTINE lim_thd_sal_init 
    382303 
    383304#else 
    384305   !!---------------------------------------------------------------------- 
    385    !!   Default option         Empty Module                No sea-ice model 
    386    !!---------------------------------------------------------------------- 
    387 CONTAINS 
    388    SUBROUTINE lim_thd_sal        ! Empty routine 
    389    END SUBROUTINE lim_thd_sal 
     306   !!   Default option         Dummy Module          No LIM-3 sea-ice model 
     307   !!---------------------------------------------------------------------- 
    390308#endif 
    391309   !!====================================================================== 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limtrp.F90

    r2287 r2475  
    1111   !!   lim_trp_init : initialization and namelist read 
    1212   !!---------------------------------------------------------------------- 
    13    !! * Modules used 
    1413   USE phycst 
    1514   USE dom_oce 
     
    1817   USE dom_ice 
    1918   USE ice 
    20    USE iceini 
    21    USE limistate 
    2219   USE limadv 
    2320   USE limhdf 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limupdate.F90

    r2287 r2475  
    1313   !!   'key_lim3'                                      LIM3 sea-ice model 
    1414   !!---------------------------------------------------------------------- 
    15    !!    lim_update   : computes update of sea-ice global variables  
    16    !!                   from trend terms 
     15   !!    lim_update   : computes update of sea-ice global variables from trend terms 
    1716   !!---------------------------------------------------------------------- 
    18    !! * Modules used 
    19    USE limistate 
    2017   USE limrhg          ! ice rheology 
    2118   USE lbclnk 
     
    2926   USE phycst          ! Define parameters for the routines 
    3027   USE ice 
    31    USE iceini 
    3228   USE lbclnk 
    3329   USE limdyn 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/LIM_SRC_3/limwri.F90

    r2364 r2475  
    11MODULE limwri 
    2    !!---------------------------------------------------------------------- 
    3    !!   'key_lim3'                                      LIM3 sea-ice model 
    4    !!---------------------------------------------------------------------- 
    52   !!====================================================================== 
    63   !!                     ***  MODULE  limwri  *** 
     
    96#if defined key_lim3 
    107   !!---------------------------------------------------------------------- 
    11    !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
    12    !! $Id$ 
    13    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     8   !!   'key_lim3'                                      LIM3 sea-ice model 
    149   !!---------------------------------------------------------------------- 
    1510   !!   lim_wri      : write of the diagnostics variables in ouput file  
    1611   !!   lim_wri_init : initialization and namelist read 
    1712   !!---------------------------------------------------------------------- 
    18    !! * Modules used 
    1913   USE ioipsl 
    2014   USE dianam          ! build name of file (routine) 
     
    2620   USE dom_ice 
    2721   USE ice 
    28    USE iceini 
    2922   USE lbclnk 
    3023   USE par_ice 
     
    6457      zzero  = 0.e0     ,  & 
    6558      zone   = 1.e0 
    66  
     59       
     60   !!---------------------------------------------------------------------- 
     61   !! NEMO/LIM3 3.3 , UCL - NEMO Consortium (2010) 
     62   !! $Id$ 
     63   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     64   !!---------------------------------------------------------------------- 
    6765CONTAINS 
     66 
    6867#if defined key_dimgout 
    69  
    7068# include "limwri_dimg.h90" 
    71  
    7269#else 
    7370 
Note: See TracChangeset for help on using the changeset viewer.