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 8531 for branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

Ignore:
Timestamp:
2017-09-15T20:07:33+02:00 (7 years ago)
Author:
clem
Message:

changes in style - part6 - more clarity (still not finished)

Location:
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3
Files:
2 added
2 deleted
17 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/ice.F90

    r8518 r8531  
    153153   !! * Share Module variables 
    154154   !!-------------------------------------------------------------------------- 
    155    !                                     !!** ice-generic parameters namelist (namice_run) ** 
     155   !                                     !!** ice-generic parameters namelist (nampar) ** 
    156156   INTEGER           , PUBLIC ::   jpl             !: number of ice  categories  
    157157   INTEGER           , PUBLIC ::   nlay_i          !: number of ice  layers  
    158158   INTEGER           , PUBLIC ::   nlay_s          !: number of snow layers  
     159   INTEGER           , PUBLIC ::   nn_monocat      !: virtual ITD mono-category parameterizations (1-4) or not (0) 
    159160   LOGICAL           , PUBLIC ::   ln_icedyn       !: flag for ice dynamics (T) or not (F) 
    160161   LOGICAL           , PUBLIC ::   ln_icethd       !: flag for ice thermo   (T) or not (F) 
     
    166167   CHARACTER(len=256), PUBLIC ::   cn_icerst_outdir!: ice restart output directory 
    167168 
    168    !                                     !!** ice-itd namelist (namice_itd) ** 
     169   !                                     !!** ice-itd namelist (namitd) ** 
    169170   REAL(wp), PUBLIC ::   rn_himin         !: minimum ice thickness 
    170171    
    171    !                                     !!** ice-dynamics namelist (namice_dyn) ** 
     172   !                                     !!** ice-dynamics namelist (namdyn) ** 
    172173   REAL(wp), PUBLIC ::   rn_ishlat        !: lateral boundary condition for sea-ice 
    173174   REAL(wp), PUBLIC ::   rn_cio           !: drag coefficient for oceanic stress 
     
    177178   REAL(wp), PUBLIC ::   rn_lfrelax       !:    relaxation time scale (s-1) to reach static friction (landfast ice)  
    178179   ! 
    179    !                                     !!** ice-rheology namelist (namice_rhg) ** 
     180   !                                     !!** ice-rheology namelist (namrhg) ** 
    180181   REAL(wp), PUBLIC ::   rn_creepl        !: creep limit : has to be under 1.0e-9 
    181182   REAL(wp), PUBLIC ::   rn_ecc           !: eccentricity of the elliptical yield curve 
     
    183184   REAL(wp), PUBLIC ::   rn_relast        !: ratio => telast/rdt_ice (1/3 or 1/9 depending on nb of subcycling nevp)  
    184185   ! 
    185    !                                     !!** ice-thermodynamics namelist (namice_thd) ** 
    186                                           ! -- icethd_dif -- ! 
    187    REAL(wp), PUBLIC ::   rn_kappa_i       !: coef. for the extinction of radiation Grenfell et al. (2006) [1/m] 
    188    LOGICAL , PUBLIC ::   ln_cndi_U64      !: thermal conductivity: Untersteiner (1964) 
    189    LOGICAL , PUBLIC ::   ln_cndi_P07      !: thermal conductivity: Pringle et al (2007) 
    190    LOGICAL , PUBLIC ::   ln_dqns_i        !: change non-solar surface flux with changing surface temperature (T) or not (F) 
    191    INTEGER , PUBLIC ::   nn_monocat       !: virtual ITD mono-category parameterizations (1-4) or not (0) 
    192    REAL(wp), PUBLIC ::   rn_cnd_s         !: thermal conductivity of the snow [W/m/K] 
     186   !                                     !!** ice-thermodynamics namelist (namthd) ** 
    193187                                          ! -- icethd_dh -- ! 
    194    LOGICAL , PUBLIC ::   ln_icedH         !: activate ice thickness change from growing/melting (T) or not (F) 
    195188   REAL(wp), PUBLIC ::   rn_blow_s        !: coef. for partitioning of snowfall between leads and sea ice 
    196                                           ! -- icethd_da -- ! 
    197    LOGICAL , PUBLIC ::   ln_icedA         !: activate lateral melting param. (T) or not (F) 
    198    REAL(wp), PUBLIC ::   rn_beta          !: coef. beta for lateral melting param. 
    199    REAL(wp), PUBLIC ::   rn_dmin          !: minimum floe diameter for lateral melting param. 
    200                                           ! -- icethd_lac -- ! 
    201    LOGICAL , PUBLIC ::   ln_icedO         !: activate ice growth in open-water (T) or not (F) 
    202    REAL(wp), PUBLIC ::   rn_hinew         !: thickness for new ice formation (m) 
    203    LOGICAL , PUBLIC ::   ln_frazil        !: use of frazil ice collection as function of wind (T) or not (F) 
    204    REAL(wp), PUBLIC ::   rn_maxfraz       !: maximum portion of frazil ice collecting at the ice bottom 
    205    REAL(wp), PUBLIC ::   rn_vfraz         !: threshold drift speed for collection of bottom frazil ice 
    206    REAL(wp), PUBLIC ::   rn_Cfraz         !: squeezing coefficient for collection of bottom frazil ice 
    207189                                          ! -- icethd -- ! 
    208190   INTEGER , PUBLIC ::   nn_iceflx        !: Redistribute heat flux over ice categories 
     
    213195   !                                      !   = 2  Redistribute a single flux over categories 
    214196 
    215    !                                     !!** ice-salinity namelist (namice_sal) ** 
     197   !                                     !!** ice-salinity namelist (namthd_sal) ** 
    216198   INTEGER , PUBLIC ::   nn_icesal        !: salinity configuration used in the model 
    217199   !                                      ! 1 - constant salinity in both space and time 
     
    223205 
    224206   ! MV MP 2016 
    225    !                                     !!** melt pond namelist (namicemp) 
     207   !                                     !!** melt pond namelist (nammp) 
    226208   LOGICAL , PUBLIC ::   ln_pnd           !: activate ponds or not 
    227209   LOGICAL , PUBLIC ::   ln_pnd_rad       !: ponds radiatively active or not 
     
    231213   REAL(wp), PUBLIC ::   rn_hpnd          !: prescribed pond depth    (0<rn_hpnd<1), only if nn_pnd_scheme = 0 
    232214   ! END MV MP 2016 
    233    !                                     !!** ice-diagnostics namelist (namice_dia) ** 
     215   !                                     !!** ice-diagnostics namelist (namdia) ** 
    234216   LOGICAL , PUBLIC ::   ln_icediachk     !: flag for ice diag (T) or not (F) 
    235217   LOGICAL , PUBLIC ::   ln_icediahsb     !: flag for ice diag (T) or not (F) 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv.F90

    r8518 r8531  
    4242   INTEGER, PARAMETER ::   np_advUMx = 2   ! Ultimate-Macho scheme 
    4343   ! 
    44    ! ** namelist (namice_adv) ** 
     44   ! ** namelist (namdyn_adv) ** 
    4545   LOGICAL ::   ln_adv_Pra   ! Prather        advection scheme 
    4646   LOGICAL ::   ln_adv_UMx   ! Ultimate-Macho advection scheme 
     
    132132      !!      dynamics 
    133133      !! 
    134       !! ** Method  :  Read the namice_adv namelist and check the ice-dynamic 
     134      !! ** Method  :  Read the namdyn_adv namelist and check the ice-dynamic 
    135135      !!       parameter values called at the first timestep (nit000) 
    136136      !! 
    137       !! ** input   :   Namelist namice_adv 
     137      !! ** input   :   Namelist namdyn_adv 
    138138      !!------------------------------------------------------------------- 
    139139      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read 
    140140      !! 
    141       NAMELIST/namice_adv/ ln_adv_Pra, ln_adv_UMx, nn_UMx 
     141      NAMELIST/namdyn_adv/ ln_adv_Pra, ln_adv_UMx, nn_UMx 
    142142      !!------------------------------------------------------------------- 
    143143      ! 
    144       REWIND( numnam_ice_ref )         ! Namelist namice_adv in reference namelist : Ice dynamics 
    145       READ  ( numnam_ice_ref, namice_adv, IOSTAT = ios, ERR = 901) 
    146 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_adv in reference namelist', lwp ) 
     144      REWIND( numnam_ice_ref )         ! Namelist namdyn_adv in reference namelist : Ice dynamics 
     145      READ  ( numnam_ice_ref, namdyn_adv, IOSTAT = ios, ERR = 901) 
     146901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_adv in reference namelist', lwp ) 
    147147      ! 
    148       REWIND( numnam_ice_cfg )         ! Namelist namice_adv in configuration namelist : Ice dynamics 
    149       READ  ( numnam_ice_cfg, namice_adv, IOSTAT = ios, ERR = 902 ) 
    150 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_adv in configuration namelist', lwp ) 
    151       IF(lwm) WRITE ( numoni, namice_adv ) 
     148      REWIND( numnam_ice_cfg )         ! Namelist namdyn_adv in configuration namelist : Ice dynamics 
     149      READ  ( numnam_ice_cfg, namdyn_adv, IOSTAT = ios, ERR = 902 ) 
     150902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_adv in configuration namelist', lwp ) 
     151      IF(lwm) WRITE ( numoni, namdyn_adv ) 
    152152      ! 
    153153      IF(lwp) THEN                     ! control print 
     
    155155         WRITE(numout,*) 'ice_adv_init: ice parameters for ice dynamics ' 
    156156         WRITE(numout,*) '~~~~~~~~~~~~' 
    157          WRITE(numout,*) '   Namelist namice_adv' 
    158          WRITE(numout,*) '      type of advection scheme (Prather)                     ln_adv_Pra = ', ln_adv_Pra  
    159          WRITE(numout,*) '      type of advection scheme (Ulimate-Macho)               ln_adv_UMx = ', ln_adv_UMx  
    160          WRITE(numout,*) '         order of the Ultimate-Macho scheme                      nn_UMx = ', nn_UMx 
     157         WRITE(numout,*) '   Namelist namdyn_adv:' 
     158         WRITE(numout,*) '      type of advection scheme (Prather)             ln_adv_Pra = ', ln_adv_Pra  
     159         WRITE(numout,*) '      type of advection scheme (Ulimate-Macho)       ln_adv_UMx = ', ln_adv_UMx  
     160         WRITE(numout,*) '         order of the Ultimate-Macho scheme          nn_UMx    = ', nn_UMx 
    161161      ENDIF 
    162162      ! 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icealb.F90

    r8517 r8531  
    3434   REAL(wp) , PARAMETER ::   r1_c2 = 1. / rc2 
    3535   ! 
    36    ! ** albedo namelist (namice_alb) 
     36   ! ** albedo namelist (namalb) 
    3737   INTEGER  ::   nn_ice_alb       ! type of albedo scheme: 0: Shine & Henderson-Sellers (JGR 1985) 
    3838   !                                      !                         1: "home made" based on Brandt et al. (JClim 2005) 
     
    310310      !! ** Purpose :   initializations for the albedo parameters 
    311311      !! 
    312       !! ** Method  :   Read the namelist namice_alb 
     312      !! ** Method  :   Read the namelist namalb 
    313313      !!---------------------------------------------------------------------- 
    314314      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    315315      !! 
    316       NAMELIST/namice_alb/ nn_ice_alb, rn_alb_sdry, rn_alb_smlt, rn_alb_idry, rn_alb_imlt, rn_alb_dpnd 
    317       !!---------------------------------------------------------------------- 
    318       ! 
    319       REWIND( numnam_ice_ref )              ! Namelist namice_alb in reference namelist : Albedo parameters 
    320       READ  ( numnam_ice_ref, namice_alb, IOSTAT = ios, ERR = 901) 
    321 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_alb in reference namelist', lwp ) 
    322  
    323       REWIND( numnam_ice_cfg )              ! Namelist namice_alb in configuration namelist : Albedo parameters 
    324       READ  ( numnam_ice_cfg, namice_alb, IOSTAT = ios, ERR = 902 ) 
    325 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_alb in configuration namelist', lwp ) 
    326       IF(lwm) WRITE ( numoni, namice_alb ) 
     316      NAMELIST/namalb/ nn_ice_alb, rn_alb_sdry, rn_alb_smlt, rn_alb_idry, rn_alb_imlt, rn_alb_dpnd 
     317      !!---------------------------------------------------------------------- 
     318      ! 
     319      REWIND( numnam_ice_ref )              ! Namelist namalb in reference namelist : Albedo parameters 
     320      READ  ( numnam_ice_ref, namalb, IOSTAT = ios, ERR = 901) 
     321901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namalb in reference namelist', lwp ) 
     322 
     323      REWIND( numnam_ice_cfg )              ! Namelist namalb in configuration namelist : Albedo parameters 
     324      READ  ( numnam_ice_cfg, namalb, IOSTAT = ios, ERR = 902 ) 
     325902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namalb in configuration namelist', lwp ) 
     326      IF(lwm) WRITE ( numoni, namalb ) 
    327327      ! 
    328328      IF(lwp) THEN                      ! Control print 
     
    330330         WRITE(numout,*) 'ice_alb_init: set albedo parameters' 
    331331         WRITE(numout,*) '~~~~~~~~~~~~' 
    332          WRITE(numout,*) '   Namelist namice_alb : albedo ' 
     332         WRITE(numout,*) '   Namelist namalb:' 
    333333         WRITE(numout,*) '      choose the albedo parameterization   nn_ice_alb  = ', nn_ice_alb 
    334334         WRITE(numout,*) '      albedo of dry snow                   rn_alb_sdry = ', rn_alb_sdry 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedia.F90

    r8522 r8531  
    4848   INTEGER FUNCTION ice_dia_alloc() 
    4949      !!---------------------------------------------------------------------! 
    50       !!                ***  ROUTINE ice_rdgrft_alloc *** 
     50      !!                ***  ROUTINE ice_dia_alloc *** 
    5151      !!---------------------------------------------------------------------! 
    5252      ALLOCATE( vol_loc_ini(jpi,jpj), sal_loc_ini(jpi,jpj), tem_loc_ini(jpi,jpj), STAT=ice_dia_alloc ) 
     
    175175      INTEGER            ::   ios, ierror   ! local integer 
    176176      !! 
    177       NAMELIST/namice_dia/ ln_icediachk, ln_icediahsb, ln_icectl, iiceprt, jiceprt   
     177      NAMELIST/namdia/ ln_icediachk, ln_icediahsb, ln_icectl, iiceprt, jiceprt   
    178178      !!---------------------------------------------------------------------- 
    179179      ! 
    180       REWIND( numnam_ice_ref )      ! Namelist namice_dia in reference namelist : Parameters for ice 
    181       READ  ( numnam_ice_ref, namice_dia, IOSTAT = ios, ERR = 901) 
    182 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dia in reference namelist', lwp ) 
    183  
    184       REWIND( numnam_ice_cfg )      ! Namelist namice_dia in configuration namelist : Parameters for ice 
    185       READ  ( numnam_ice_cfg, namice_dia, IOSTAT = ios, ERR = 902 ) 
    186 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dia in configuration namelist', lwp ) 
    187       IF(lwm) WRITE ( numoni, namice_dia ) 
     180      REWIND( numnam_ice_ref )      ! Namelist namdia in reference namelist : Parameters for ice 
     181      READ  ( numnam_ice_ref, namdia, IOSTAT = ios, ERR = 901) 
     182901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdia in reference namelist', lwp ) 
     183 
     184      REWIND( numnam_ice_cfg )      ! Namelist namdia in configuration namelist : Parameters for ice 
     185      READ  ( numnam_ice_cfg, namdia, IOSTAT = ios, ERR = 902 ) 
     186902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdia in configuration namelist', lwp ) 
     187      IF(lwm) WRITE ( numoni, namdia ) 
    188188      ! 
    189189      IF(lwp) THEN                  ! control print 
     
    191191         WRITE(numout,*) 'ice_dia_init: ice diagnostics' 
    192192         WRITE(numout,*) ' ~~~~~~~~~~~' 
    193          WRITE(numout,*) '   Namelist namice_dia : ' 
     193         WRITE(numout,*) '   Namelist namdia:' 
    194194         WRITE(numout,*) '      Diagnose online heat/mass/salt budget      ln_icediachk = ', ln_icediachk 
    195195         WRITE(numout,*) '      Output          heat/mass/salt budget      ln_icediahsb = ', ln_icediahsb 
    196          WRITE(numout,*) '      control prints for a given grid point         ln_icectl = ', ln_icectl 
     196         WRITE(numout,*) '      control prints for a given grid point      ln_icectl    = ', ln_icectl 
    197197         WRITE(numout,*) '         chosen grid point position         (iiceprt,jiceprt) = (', iiceprt,',', jiceprt,')' 
    198198      ENDIF 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedyn.F90

    r8518 r8531  
    2525   USE lib_mpp        ! MPP library 
    2626   USE in_out_manager ! I/O manager 
     27   USE iom            ! I/O manager 
    2728   USE lib_fortran    ! glob_sum 
    2829   USE timing         ! Timing 
     
    209210      !!      dynamics 
    210211      !! 
    211       !! ** Method  :  Read the namice_dyn namelist and check the ice-dynamic 
     212      !! ** Method  :  Read the namdyn namelist and check the ice-dynamic 
    212213      !!       parameter values called at the first timestep (nit000) 
    213214      !! 
    214       !! ** input   :   Namelist namice_dyn 
     215      !! ** input   :   Namelist namdyn 
    215216      !!------------------------------------------------------------------- 
    216217      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read 
    217218      !! 
    218       NAMELIST/namice_dyn/ ln_dynFULL, ln_dynRHGADV, ln_dynADV, rn_uice, rn_vice,  & 
    219          &                 rn_ishlat  , rn_cio   ,                         & 
    220          &                 ln_landfast, rn_gamma , rn_icebfr, rn_lfrelax 
    221       !!------------------------------------------------------------------- 
    222       ! 
    223       REWIND( numnam_ice_ref )         ! Namelist namice_dyn in reference namelist : Ice dynamics 
    224       READ  ( numnam_ice_ref, namice_dyn, IOSTAT = ios, ERR = 901) 
    225 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dyn in reference namelist', lwp ) 
    226       ! 
    227       REWIND( numnam_ice_cfg )         ! Namelist namice_dyn in configuration namelist : Ice dynamics 
    228       READ  ( numnam_ice_cfg, namice_dyn, IOSTAT = ios, ERR = 902 ) 
    229 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dyn in configuration namelist', lwp ) 
    230       IF(lwm) WRITE ( numoni, namice_dyn ) 
     219      NAMELIST/namdyn/ ln_dynFULL, ln_dynRHGADV, ln_dynADV, rn_uice, rn_vice,  & 
     220         &             rn_ishlat  ,                                            & 
     221         &             ln_landfast, rn_gamma , rn_icebfr, rn_lfrelax 
     222      !!------------------------------------------------------------------- 
     223      ! 
     224      REWIND( numnam_ice_ref )         ! Namelist namdyn in reference namelist : Ice dynamics 
     225      READ  ( numnam_ice_ref, namdyn, IOSTAT = ios, ERR = 901) 
     226901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn in reference namelist', lwp ) 
     227      ! 
     228      REWIND( numnam_ice_cfg )         ! Namelist namdyn in configuration namelist : Ice dynamics 
     229      READ  ( numnam_ice_cfg, namdyn, IOSTAT = ios, ERR = 902 ) 
     230902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn in configuration namelist', lwp ) 
     231      IF(lwm) WRITE ( numoni, namdyn ) 
    231232      ! 
    232233      IF(lwp) THEN                     ! control print 
     
    234235         WRITE(numout,*) 'ice_dyn_init: ice parameters for ice dynamics ' 
    235236         WRITE(numout,*) '~~~~~~~~~~~~' 
    236          WRITE(numout,*) '   Namelist namice_dyn' 
     237         WRITE(numout,*) '   Namelist namdyn:' 
    237238         WRITE(numout,*) '      Full ice dynamics      (rhg + adv + ridge/raft + corr)  ln_dynFULL   = ', ln_dynFULL 
    238239         WRITE(numout,*) '      No ridge/raft & No cor (rhg + adv)                      ln_dynRHGADV = ', ln_dynRHGADV 
     
    240241         WRITE(numout,*) '           with prescribed velocity given by ' 
    241242         WRITE(numout,*) '               a uniform field               (u,v)_ice = (rn_uice,rn_vice) = (', rn_uice,',', rn_vice,')' 
    242          WRITE(numout,*) '      lateral boundary condition for sea ice dynamics        rn_ishlat     = ', rn_ishlat 
    243          WRITE(numout,*) '      drag coefficient for oceanic stress                    rn_cio        = ', rn_cio 
    244          WRITE(numout,*) '      Landfast: param (T or F)                               ln_landfast   = ', ln_landfast 
    245          WRITE(numout,*) '         fraction of ocean depth that ice must reach         rn_gamma      = ', rn_gamma 
    246          WRITE(numout,*) '         maximum bottom stress per unit area of contact      rn_icebfr     = ', rn_icebfr 
    247          WRITE(numout,*) '         relax time scale (s-1) to reach static friction     rn_lfrelax    = ', rn_lfrelax 
     243         WRITE(numout,*) '      lateral boundary condition for sea ice dynamics         rn_ishlat    = ', rn_ishlat 
     244         WRITE(numout,*) '      Landfast: param (T or F)                                ln_landfast  = ', ln_landfast 
     245         WRITE(numout,*) '         fraction of ocean depth that ice must reach          rn_gamma     = ', rn_gamma 
     246         WRITE(numout,*) '         maximum bottom stress per unit area of contact       rn_icebfr    = ', rn_icebfr 
     247         WRITE(numout,*) '         relax time scale (s-1) to reach static friction      rn_lfrelax   = ', rn_lfrelax 
    248248      ENDIF 
    249249      !                             !== set the choice of ice dynamics ==! 
     
    267267      ENDIF 
    268268      !                                      !--- NO Landfast ice : set to zero once for all 
    269       IF( .NOT. ln_landfast )   tau_icebfr(:,:) = 0._wp  
     269      IF( .NOT. ln_landfast )   tau_icebfr(:,:) = 0._wp 
     270      ! 
     271      CALL ice_rdgrft_init          ! set ice ridging/rafting parameters 
     272      CALL ice_rhg_init             ! set ice rheology parameters 
     273      CALL ice_adv_init             ! set ice advection parameters 
    270274      ! 
    271275   END SUBROUTINE ice_dyn_init 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceforcing.F90

    r8514 r8531  
    3030   PRIVATE 
    3131 
    32    PUBLIC ice_forcing_tau  ! routine called by icestp.F90 
    33    PUBLIC ice_forcing_flx  ! routine called by icestp.F90 
     32   PUBLIC ice_forcing_tau   ! called by icestp.F90 
     33   PUBLIC ice_forcing_flx   ! called by icestp.F90 
     34   PUBLIC ice_forcing_init  ! called by icestp.F90 
    3435 
    3536   !! * Substitutions 
     
    257258   END SUBROUTINE ice_flx_dist 
    258259 
     260   SUBROUTINE ice_forcing_init 
     261      !!------------------------------------------------------------------- 
     262      !!                  ***  ROUTINE ice_forcing_init  *** 
     263      !! 
     264      !! ** Purpose : Physical constants and parameters linked to the ice 
     265      !!      dynamics 
     266      !! 
     267      !! ** Method  :  Read the namforcing namelist and check the ice-dynamic 
     268      !!       parameter values called at the first timestep (nit000) 
     269      !! 
     270      !! ** input   :   Namelist namforcing 
     271      !!------------------------------------------------------------------- 
     272      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read 
     273      !! 
     274      NAMELIST/namforcing/ rn_cio, rn_blow_s, nn_iceflx 
     275      !!------------------------------------------------------------------- 
     276      ! 
     277      REWIND( numnam_ice_ref )         ! Namelist namforcing in reference namelist : Ice dynamics 
     278      READ  ( numnam_ice_ref, namforcing, IOSTAT = ios, ERR = 901) 
     279901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namforcing in reference namelist', lwp ) 
     280      ! 
     281      REWIND( numnam_ice_cfg )         ! Namelist namforcing in configuration namelist : Ice dynamics 
     282      READ  ( numnam_ice_cfg, namforcing, IOSTAT = ios, ERR = 902 ) 
     283902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namforcing in configuration namelist', lwp ) 
     284      IF(lwm) WRITE ( numoni, namforcing ) 
     285      ! 
     286      IF(lwp) THEN                     ! control print 
     287         WRITE(numout,*) 
     288         WRITE(numout,*) 'ice_forcing_init: ice parameters for ice dynamics ' 
     289         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
     290         WRITE(numout,*) '   Namelist namforcing:' 
     291         WRITE(numout,*) '      drag coefficient for oceanic stress              rn_cio    = ', rn_cio 
     292         WRITE(numout,*) '      coefficient for ice-lead partition of snowfall   rn_blow_s = ', rn_blow_s 
     293         WRITE(numout,*) '      Multicategory heat flux formulation              nn_iceflx = ', nn_iceflx 
     294      ENDIF 
     295      ! 
     296      IF(lwp) WRITE(numout,*) 
     297      SELECT CASE( nn_iceflx )         ! ESIM Multi-category heat flux formulation 
     298      CASE( -1  ) 
     299         IF(lwp) WRITE(numout,*) '   ESIM: use per-category fluxes (nn_iceflx = -1) ' 
     300         IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for ESIM in coupled mode must be 0 or 2' ) 
     301      CASE(  0  ) 
     302         IF(lwp) WRITE(numout,*) '   ESIM: use average per-category fluxes (nn_iceflx = 0) ' 
     303      CASE(  1  ) 
     304         IF(lwp) WRITE(numout,*) '   ESIM: use average then redistribute per-category fluxes (nn_iceflx = 1) ' 
     305         IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for ESIM in coupled mode must be 0 or 2' ) 
     306      CASE(  2  ) 
     307         IF(lwp) WRITE(numout,*) '   ESIM: Redistribute a single flux over categories (nn_iceflx = 2) ' 
     308         IF( .NOT. ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for ESIM in forced mode cannot be 2' ) 
     309      CASE DEFAULT 
     310         CALL ctl_stop( 'ice_thd_init: ESIM option, nn_iceflx, should be between -1 and 2' ) 
     311      END SELECT 
     312      ! 
     313   END SUBROUTINE ice_forcing_init 
     314 
    259315#else 
    260316   !!---------------------------------------------------------------------- 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceistate.F90

    r8518 r8531  
    4949   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   si  ! structure of input fields (file informations, fields read) 
    5050   ! 
    51    ! ** namelist (namice_ini) ** 
     51   ! ** namelist (namini) ** 
    5252   LOGICAL  ::   ln_iceini        ! initialization or not 
    5353   LOGICAL  ::   ln_iceini_file   ! Ice initialization state from 2D netcdf file 
     
    512512      !! ** Purpose : Definition of initial state of the ice  
    513513      !! 
    514       !! ** Method : Read the namice_ini namelist and check the parameter  
     514      !! ** Method : Read the namini namelist and check the parameter  
    515515      !!       values called at the first timestep (nit000) 
    516516      !! 
    517517      !! ** input :  
    518       !!        Namelist namice_ini 
     518      !!        Namelist namini 
    519519      !! 
    520520      !! history : 
     
    531531      TYPE(FLD_N), DIMENSION(jpfldi) ::   slf_i                 ! array of namelist informations on the fields to read 
    532532      ! 
    533       NAMELIST/namice_ini/ ln_iceini, ln_iceini_file, rn_thres_sst, rn_hts_ini_n, rn_hts_ini_s,  & 
    534          &                rn_hti_ini_n, rn_hti_ini_s, rn_ati_ini_n, rn_ati_ini_s, rn_smi_ini_n, & 
    535          &                rn_smi_ini_s, rn_tmi_ini_n, rn_tmi_ini_s,                             & 
    536          &                sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, cn_dir 
     533      NAMELIST/namini/ ln_iceini, ln_iceini_file, rn_thres_sst, rn_hts_ini_n, rn_hts_ini_s,  & 
     534         &             rn_hti_ini_n, rn_hti_ini_s, rn_ati_ini_n, rn_ati_ini_s, rn_smi_ini_n, & 
     535         &             rn_smi_ini_s, rn_tmi_ini_n, rn_tmi_ini_s,                             & 
     536         &             sn_hti, sn_hts, sn_ati, sn_tsu, sn_tmi, sn_smi, cn_dir 
    537537      !!----------------------------------------------------------------------------- 
    538538      ! 
    539       REWIND( numnam_ice_ref )              ! Namelist namice_ini in reference namelist : Ice initial state 
    540       READ  ( numnam_ice_ref, namice_ini, IOSTAT = ios, ERR = 901) 
    541 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_ini in reference namelist', lwp ) 
    542  
    543       REWIND( numnam_ice_cfg )              ! Namelist namice_ini in configuration namelist : Ice initial state 
    544       READ  ( numnam_ice_cfg, namice_ini, IOSTAT = ios, ERR = 902 ) 
    545 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_ini in configuration namelist', lwp ) 
    546       IF(lwm) WRITE ( numoni, namice_ini ) 
     539      REWIND( numnam_ice_ref )              ! Namelist namini in reference namelist : Ice initial state 
     540      READ  ( numnam_ice_ref, namini, IOSTAT = ios, ERR = 901) 
     541901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namini in reference namelist', lwp ) 
     542 
     543      REWIND( numnam_ice_cfg )              ! Namelist namini in configuration namelist : Ice initial state 
     544      READ  ( numnam_ice_cfg, namini, IOSTAT = ios, ERR = 902 ) 
     545902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namini in configuration namelist', lwp ) 
     546      IF(lwm) WRITE ( numoni, namini ) 
    547547 
    548548      slf_i(jp_hti) = sn_hti  ;  slf_i(jp_hts) = sn_hts 
     
    555555         WRITE(numout,*) 'ice_istate_init: ice parameters inititialisation ' 
    556556         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    557          WRITE(numout,*) '   Namelist namice_ini' 
     557         WRITE(numout,*) '   Namelist namini:' 
    558558         WRITE(numout,*) '      initialization with ice (T) or not (F)                 ln_iceini     = ', ln_iceini 
    559559         WRITE(numout,*) '      ice initialization from a netcdf file                ln_iceini_file  = ', ln_iceini_file 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceitd.F90

    r8517 r8531  
    3838   PUBLIC   ice_itd_reb   ! called in iceerr 
    3939 
    40    ! ** ice-thickness distribution namelist (namice_itd) ** 
     40   ! ** ice-thickness distribution namelist (namitd) ** 
    4141   REAL(wp) ::   rn_himean        ! mean thickness of the domain (used to compute the distribution) 
    4242 
     
    643643      !! ** Purpose :   Initializes the ice thickness distribution 
    644644      !! ** Method  :   ... 
    645       !! ** input   :   Namelist namice_itd 
     645      !! ** input   :   Namelist namitd 
    646646      !!------------------------------------------------------------------- 
    647647      INTEGER  ::   jl    ! dummy loop index 
     
    649649      REAL(wp) ::   zhmax, znum, zden, zalpha   !   -      - 
    650650      !! 
    651       NAMELIST/namice_itd/ rn_himean, rn_himin 
    652       !!------------------------------------------------------------------ 
    653       ! 
    654       REWIND( numnam_ice_ref )      ! Namelist namice_itd in reference namelist : Parameters for ice 
    655       READ  ( numnam_ice_ref, namice_itd, IOSTAT = ios, ERR = 901) 
    656 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_itd in reference namelist', lwp ) 
    657  
    658       REWIND( numnam_ice_cfg )      ! Namelist namice_itd in configuration namelist : Parameters for ice 
    659       READ  ( numnam_ice_cfg, namice_itd, IOSTAT = ios, ERR = 902 ) 
    660 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_itd in configuration namelist', lwp ) 
    661       IF(lwm) WRITE ( numoni, namice_itd ) 
     651      NAMELIST/namitd/ rn_himean, rn_himin 
     652      !!------------------------------------------------------------------ 
     653      ! 
     654      REWIND( numnam_ice_ref )      ! Namelist namitd in reference namelist : Parameters for ice 
     655      READ  ( numnam_ice_ref, namitd, IOSTAT = ios, ERR = 901) 
     656901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namitd in reference namelist', lwp ) 
     657 
     658      REWIND( numnam_ice_cfg )      ! Namelist namitd in configuration namelist : Parameters for ice 
     659      READ  ( numnam_ice_cfg, namitd, IOSTAT = ios, ERR = 902 ) 
     660902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namitd in configuration namelist', lwp ) 
     661      IF(lwm) WRITE ( numoni, namitd ) 
    662662      ! 
    663663      IF(lwp) THEN                  ! control print 
     
    665665         WRITE(numout,*) 'ice_itd_init: Initialization of ice cat distribution ' 
    666666         WRITE(numout,*) '~~~~~~~~~~~~' 
    667          WRITE(numout,*) '   Namelist namice_itd : ' 
     667         WRITE(numout,*) '   Namelist namitd: ' 
    668668         WRITE(numout,*) '      mean ice thickness in the domain               rn_himean = ', rn_himean 
    669669         WRITE(numout,*) '      minimum ice thickness                          rn_himin  = ', rn_himin  
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerdgrft.F90

    r8518 r8531  
    1212   !!   'key_lim3'                                      LIM-3 sea-ice model 
    1313   !!---------------------------------------------------------------------- 
    14    USE par_oce        ! ocean parameters 
    1514   USE dom_oce        ! ocean domain 
    1615   USE phycst         ! physical constants (ocean directory)  
     
    3130   PRIVATE 
    3231 
    33    PUBLIC   ice_rdgrft               ! called by ice_stp 
    34    PUBLIC   ice_rdgrft_strength      ! called by icerhg_evp 
    35    PUBLIC   ice_rdgrft_init          ! called by ice_stp 
     32   PUBLIC   ice_rdgrft        ! called by icestp 
     33   PUBLIC   ice_strength      ! called by icerhg_evp 
     34   PUBLIC   ice_rdgrft_init   ! called by icedyn 
    3635 
    3736   ! Variables shared among ridging subroutines 
    3837   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   asum     ! sum of total ice and open water area 
    3938   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   aksum    ! ratio of area removed to area ridged 
    40    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   athorn   ! participation function; fraction of ridging/closing associated w/ category n 
     39   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   apartf   ! participation function; fraction of ridging/closing associated w/ category n 
    4140   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hrmin    ! minimum ridge thickness 
    4241   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hrmax    ! maximum ridge thickness 
    4342   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hraft    ! thickness of rafted ice 
    44    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   krdg     ! thickness of ridging ice / mean ridge thickness 
     43   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hi_hrdg  ! thickness of ridging ice / mean ridge thickness 
    4544   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   aridge   ! participating ice ridging 
    4645   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   araft    ! participating ice rafting 
    4746   ! 
    48    REAL(wp), PARAMETER ::   krdgmin = 1.1_wp    ! min ridge thickness multiplier 
    49    REAL(wp), PARAMETER ::   kraft   = 0.5_wp    ! rafting multipliyer 
    50    REAL(wp)            ::   zdrho               !  
     47   REAL(wp), PARAMETER ::   hrdg_hi_min = 1.1_wp    ! min ridge thickness multiplier: min(hrdg/hi) 
     48   REAL(wp), PARAMETER ::   hi_hrft     = 0.5_wp    ! rafting multipliyer: (hi/hraft) 
     49   REAL(wp)            ::   zdrho                   !  
    5150   ! 
    52    ! ** namelist (namice_rdgrft) ** 
     51   ! ** namelist (namdyn_rdgrft) ** 
    5352   LOGICAL  ::   ln_str_H79       ! ice strength parameterization (Hibler79) 
    5453   REAL(wp) ::   rn_pstar         ! determines ice strength, Hibler JPO79 
     
    8382      !!                ***  ROUTINE ice_rdgrft_alloc *** 
    8483      !!---------------------------------------------------------------------! 
    85       ALLOCATE( asum (jpi,jpj)     , athorn(jpi,jpj,0:jpl) , aksum (jpi,jpj)     ,     & 
    86          &      hrmin(jpi,jpj,jpl) , hraft (jpi,jpj,jpl)   , aridge(jpi,jpj,jpl) ,     & 
    87          &      hrmax(jpi,jpj,jpl) , krdg  (jpi,jpj,jpl)   , araft (jpi,jpj,jpl) , STAT=ice_rdgrft_alloc ) 
     84      ALLOCATE( asum (jpi,jpj)     , apartf (jpi,jpj,0:jpl) , aksum (jpi,jpj)     ,     & 
     85         &      hrmin(jpi,jpj,jpl) , hraft  (jpi,jpj,jpl)   , aridge(jpi,jpj,jpl) ,     & 
     86         &      hrmax(jpi,jpj,jpl) , hi_hrdg(jpi,jpj,jpl)   , araft (jpi,jpj,jpl) , STAT=ice_rdgrft_alloc ) 
    8887 
    8988      IF( lk_mpp                )   CALL mpp_sum ( ice_rdgrft_alloc ) 
     
    124123      INTEGER  ::   niter              ! local integer  
    125124      INTEGER  ::   iterate_ridging    ! if =1, repeat the ridging 
    126       REAL(wp) ::   z               ! local scalar 
     125      REAL(wp) ::   zfac               ! local scalar 
    127126      REAL(wp), DIMENSION(jpi,jpj) ::   closing_net     ! net rate at which area is removed    (1/s) 
    128127      !                                                 ! (ridging ice area - area of new ridges) / dt 
     
    150149      !-----------------------------------------------------------------------------! 
    151150      ! 
    152       CALL ice_rdgrft_prep                             ! prepare ridging 
     151      CALL rdgrft_prep                             ! prepare ridging 
    153152      ! 
    154153      DO jj = 1, jpj                                        ! Initialize arrays. 
     
    203202      DO WHILE ( iterate_ridging > 0 .AND. niter < nitermax ) 
    204203 
    205          ! 3.2 closing_gross 
     204         ! 3.1 closing_gross 
    206205         !-----------------------------------------------------------------------------! 
    207206         ! Based on the ITD of ridging and ridged ice, convert the net 
     
    216215         DO jj = 1, jpj 
    217216            DO ji = 1, jpi 
    218                za   = ( opning(ji,jj) - athorn(ji,jj,0) * closing_gross(ji,jj) ) * rdt_ice 
    219                IF    ( za < 0._wp .AND. za > - ato_i(ji,jj) ) THEN                  ! would lead to negative ato_i 
    220                   opning(ji,jj) = athorn(ji,jj,0) * closing_gross(ji,jj) - ato_i(ji,jj) * r1_rdtice  
    221                ELSEIF( za > 0._wp .AND. za > ( asum(ji,jj) - ato_i(ji,jj) ) ) THEN  ! would lead to ato_i > asum 
    222                   opning(ji,jj) = athorn(ji,jj,0) * closing_gross(ji,jj) + ( asum(ji,jj) - ato_i(ji,jj) ) * r1_rdtice  
     217               zfac   = ( opning(ji,jj) - apartf(ji,jj,0) * closing_gross(ji,jj) ) * rdt_ice 
     218               IF    ( zfac < 0._wp .AND. zfac > - ato_i(ji,jj) ) THEN                  ! would lead to negative ato_i 
     219                  opning(ji,jj) = apartf(ji,jj,0) * closing_gross(ji,jj) - ato_i(ji,jj) * r1_rdtice  
     220               ELSEIF( zfac > 0._wp .AND. zfac > ( asum(ji,jj) - ato_i(ji,jj) ) ) THEN  ! would lead to ato_i > asum 
     221                  opning(ji,jj) = apartf(ji,jj,0) * closing_gross(ji,jj) + ( asum(ji,jj) - ato_i(ji,jj) ) * r1_rdtice  
    223222               ENDIF 
    224223            END DO 
     
    232231            DO jj = 1, jpj 
    233232               DO ji = 1, jpi 
    234                   za = athorn(ji,jj,jl) * closing_gross(ji,jj) * rdt_ice 
    235                   IF( za  >  a_i(ji,jj,jl) ) THEN 
    236                      closing_gross(ji,jj) = closing_gross(ji,jj) * a_i(ji,jj,jl) / za 
     233                  zfac = apartf(ji,jj,jl) * closing_gross(ji,jj) * rdt_ice 
     234                  IF( zfac  >  a_i(ji,jj,jl) ) THEN 
     235                     closing_gross(ji,jj) = closing_gross(ji,jj) * a_i(ji,jj,jl) / zfac 
    237236                  ENDIF 
    238237               END DO 
     
    240239         END DO 
    241240 
    242          ! 3.3 Redistribute area, volume, and energy. 
     241         ! 3.2 Redistribute area, volume, and energy. 
    243242         !-----------------------------------------------------------------------------! 
    244          CALL ice_rdgrft_ridgeshift( opning, closing_gross ) 
     243         CALL rdgrft_shift( opning, closing_gross ) 
    245244          
    246          ! 3.4 Compute total area of ice plus open water after ridging. 
     245         ! 3.3 Compute total area of ice plus open water after ridging. 
    247246         !-----------------------------------------------------------------------------! 
    248247         ! This is in general not equal to one because of divergence during transport 
    249248         asum(:,:) = ato_i(:,:) + SUM( a_i, dim=3 ) 
    250249 
    251          ! 3.5 Do we keep on iterating? 
     250         ! 3.4 Do we keep on iterating? 
    252251         !-----------------------------------------------------------------------------! 
    253252         ! Check whether asum = 1.  If not (because the closing and opening 
     
    276275         ! 
    277276         IF( iterate_ridging == 1 ) THEN 
    278             CALL ice_rdgrft_prep 
     277            CALL rdgrft_prep 
    279278            IF( niter  >  nitermax ) THEN 
    280279               WRITE(numout,*) ' ALERTE : non-converging ridging scheme ' 
     
    295294 
    296295 
    297    SUBROUTINE ice_rdgrft_prep 
     296   SUBROUTINE rdgrft_prep 
    298297      !!---------------------------------------------------------------------! 
    299       !!                ***  ROUTINE ice_rdgrft_prep *** 
     298      !!                ***  ROUTINE rdgrft_prep *** 
    300299      !! 
    301300      !! ** Purpose :   preparation for ridging and strength calculations 
     
    319318      END WHERE 
    320319 
    321       !------------------------------------------------------------------------------! 
    322       ! 1) Participation function  
    323       !------------------------------------------------------------------------------! 
     320      !----------------------------------------------------------------- 
     321      ! 1) Participation function: a(h) = b(h).g(h) (apartf) 
     322      !----------------------------------------------------------------- 
     323      ! Compute the participation function apartf; this is analogous to 
     324      ! a(h) = b(h)g(h) as defined in Thorndike et al. (1975). 
     325      ! area lost from category n due to ridging/closing 
     326      ! apartf(n)   = total area lost due to ridging/closing 
     327      ! assume b(h) = (2/Gstar) * (1 - G(h)/Gstar).  
     328      ! 
     329      ! The expressions for apartf are found by integrating b(h)g(h) between 
     330      ! the category boundaries. 
     331      ! apartf is always >= 0 and SUM(apartf(0:jpl))=1 
     332      !----------------------------------------------------------------- 
    324333      ! 
    325334      ! Compute total area of ice plus open water. 
     
    337346      END DO 
    338347 
    339       ! 1.3 Compute participation function a(h) = b(h).g(h) (athorn) 
    340       !-------------------------------------------------------------------------------------------------- 
    341       ! Compute the participation function athorn; this is analogous to 
    342       ! a(h) = b(h)g(h) as defined in Thorndike et al. (1975). 
    343       ! area lost from category n due to ridging/closing 
    344       ! athorn(n)   = total area lost due to ridging/closing 
    345       ! assume b(h) = (2/Gstar) * (1 - G(h)/Gstar).  
    346       ! 
    347       ! The expressions for athorn are found by integrating b(h)g(h) between 
    348       ! the category boundaries. 
    349       ! athorn is always >= 0 and SUM(athorn(0:jpl))=1 
    350       !----------------------------------------------------------------- 
    351348      ! 
    352349      IF( ln_partf_lin ) THEN          !--- Linear formulation (Thorndike et al., 1975) 
     
    355352               DO ji = 1, jpi 
    356353                  IF    ( zGsum(ji,jj,jl)   < rn_gstar ) THEN 
    357                      athorn(ji,jj,jl) = z1_gstar * ( zGsum(ji,jj,jl) - zGsum(ji,jj,jl-1) ) * & 
     354                     apartf(ji,jj,jl) = z1_gstar * ( zGsum(ji,jj,jl) - zGsum(ji,jj,jl-1) ) * & 
    358355                        &                          ( 2._wp - ( zGsum(ji,jj,jl-1) + zGsum(ji,jj,jl) ) * z1_gstar ) 
    359356                  ELSEIF( zGsum(ji,jj,jl-1) < rn_gstar ) THEN 
    360                      athorn(ji,jj,jl) = z1_gstar * ( rn_gstar        - zGsum(ji,jj,jl-1) ) *  & 
     357                     apartf(ji,jj,jl) = z1_gstar * ( rn_gstar        - zGsum(ji,jj,jl-1) ) *  & 
    361358                        &                          ( 2._wp - ( zGsum(ji,jj,jl-1) + rn_gstar        ) * z1_gstar ) 
    362359                  ELSE 
    363                      athorn(ji,jj,jl) = 0._wp 
     360                     apartf(ji,jj,jl) = 0._wp 
    364361                  ENDIF 
    365362               END DO 
     
    374371         END DO 
    375372         DO jl = 0, jpl 
    376             athorn(:,:,jl) = zGsum(:,:,jl-1) - zGsum(:,:,jl) 
     373            apartf(:,:,jl) = zGsum(:,:,jl-1) - zGsum(:,:,jl) 
    377374         END DO 
    378375         ! 
     
    384381            DO jj = 1, jpj  
    385382               DO ji = 1, jpi 
    386                   aridge(ji,jj,jl) = ( 1._wp + TANH ( rn_craft * ( ht_i(ji,jj,jl) - rn_hraft ) ) ) * 0.5_wp * athorn(ji,jj,jl) 
    387                   araft (ji,jj,jl) = athorn(ji,jj,jl) - aridge(ji,jj,jl) 
     383                  aridge(ji,jj,jl) = ( 1._wp + TANH ( rn_craft * ( ht_i(ji,jj,jl) - rn_hraft ) ) ) * 0.5_wp * apartf(ji,jj,jl) 
     384                  araft (ji,jj,jl) = apartf(ji,jj,jl) - aridge(ji,jj,jl) 
    388385               END DO 
    389386            END DO 
    390387         END DO 
    391388      ELSEIF( ln_ridging .AND. .NOT. ln_rafting ) THEN   !- ridging alone 
    392          aridge(:,:,:) = athorn(:,:,1:jpl) 
     389         aridge(:,:,:) = apartf(:,:,1:jpl) 
    393390         araft (:,:,:) = 0._wp 
    394391      ELSEIF( ln_rafting .AND. .NOT. ln_ridging ) THEN   !- rafting alone    
    395392        aridge(:,:,:) = 0._wp 
    396          araft (:,:,:) = athorn(:,:,1:jpl) 
     393         araft (:,:,:) = apartf(:,:,1:jpl) 
    397394      ELSE                                               !- no ridging & no rafting 
    398395         aridge(:,:,:) = 0._wp 
     
    408405      ! This parameterization is a modified version of Hibler (1980). 
    409406      ! The mean ridging thickness, zhmean, is proportional to hi^(0.5) 
    410       !  and for very thick ridging ice must be >= krdgmin*hi 
     407      !  and for very thick ridging ice must be >= hrdg_hi_min*hi 
    411408      ! 
    412409      ! The minimum ridging thickness, hrmin, is equal to 2*hi  
     
    426423      !----------------------------------------------------------------- 
    427424 
    428       aksum(:,:) = athorn(:,:,0) 
     425      aksum(:,:) = apartf(:,:,0) 
     426      zdummy = 1._wp / hi_hrft 
    429427      ! Transfer function 
    430428      DO jl = 1, jpl !all categories have a specific transfer function 
    431429         DO jj = 1, jpj 
    432430            DO ji = 1, jpi 
    433                IF ( athorn(ji,jj,jl) > 0._wp ) THEN 
    434                   zhmean          = MAX( SQRT( rn_hstar * ht_i(ji,jj,jl) ), ht_i(ji,jj,jl) * krdgmin ) 
    435                   hrmin(ji,jj,jl) = MIN( 2._wp * ht_i(ji,jj,jl), 0.5_wp * ( zhmean + ht_i(ji,jj,jl) ) ) 
    436                   hrmax(ji,jj,jl) = 2._wp * zhmean - hrmin(ji,jj,jl) 
    437                   hraft(ji,jj,jl) = ht_i(ji,jj,jl) / kraft 
    438                   krdg (ji,jj,jl) = ht_i(ji,jj,jl) / MAX( zhmean, epsi20 ) 
     431               IF ( apartf(ji,jj,jl) > 0._wp ) THEN 
     432                  zhmean            = MAX( SQRT( rn_hstar * ht_i(ji,jj,jl) ), ht_i(ji,jj,jl) * hrdg_hi_min ) 
     433                  hrmin  (ji,jj,jl) = MIN( 2._wp * ht_i(ji,jj,jl), 0.5_wp * ( zhmean + ht_i(ji,jj,jl) ) ) 
     434                  hrmax  (ji,jj,jl) = 2._wp * zhmean - hrmin(ji,jj,jl) 
     435                  hraft  (ji,jj,jl) = ht_i(ji,jj,jl) * zdummy 
     436                  hi_hrdg(ji,jj,jl) = ht_i(ji,jj,jl) / MAX( zhmean, epsi20 ) 
    439437                  ! 
    440438                  ! Normalization factor : aksum, ensures mass conservation 
    441                   aksum(ji,jj) = aksum(ji,jj) + aridge(ji,jj,jl) * ( 1._wp - krdg(ji,jj,jl) )    & 
    442                      &                        + araft (ji,jj,jl) * ( 1._wp - kraft          ) 
     439                  aksum(ji,jj) = aksum(ji,jj) + aridge(ji,jj,jl) * ( 1._wp - hi_hrdg(ji,jj,jl) )    & 
     440                     &                        + araft (ji,jj,jl) * ( 1._wp - hi_hrft ) 
    443441               ELSE 
    444                   hrmin(ji,jj,jl) = 0._wp  
    445                   hrmax(ji,jj,jl) = 0._wp  
    446                   hraft(ji,jj,jl) = 0._wp  
    447                   krdg (ji,jj,jl) = 1._wp 
     442                  hrmin  (ji,jj,jl) = 0._wp  
     443                  hrmax  (ji,jj,jl) = 0._wp  
     444                  hraft  (ji,jj,jl) = 0._wp  
     445                  hi_hrdg(ji,jj,jl) = 1._wp 
    448446               ENDIF 
    449447            END DO 
     
    451449      END DO 
    452450      ! 
    453    END SUBROUTINE ice_rdgrft_prep 
    454  
    455  
    456    SUBROUTINE ice_rdgrft_ridgeshift( opning, closing_gross ) 
     451   END SUBROUTINE rdgrft_prep 
     452 
     453 
     454   SUBROUTINE rdgrft_shift( opning, closing_gross ) 
    457455      !!---------------------------------------------------------------------- 
    458       !!                ***  ROUTINE ice_rdgrft_strength *** 
     456      !!                ***  ROUTINE rdgrft_shift *** 
    459457      !! 
    460458      !! ** Purpose :   shift ridging ice among thickness categories of ice thickness 
     
    463461      !!              and add to thicker ice categories. 
    464462      !!---------------------------------------------------------------------- 
    465       REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   opning         ! rate of opening due to divergence/shear 
    466       REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   closing_gross  ! rate at which area retreats, excluding area of new ridges 
    467       ! 
    468       INTEGER ::   ji, jj, jl, jl1, jl2, jk   ! dummy loop indices 
    469       INTEGER ::   ij                ! horizontal index, combines i and j loops 
    470       INTEGER ::   icells            ! number of cells with a_i > puny 
    471       REAL(wp) ::   hL, hR, farea    ! left and right limits of integration and new area going to jl2 
    472  
    473       INTEGER , DIMENSION(jpij) ::   indxi, indxj   ! compressed indices 
    474       REAL(wp), DIMENSION(jpij) ::   zswitch, fvol   ! new ridge volume going to jl2 
     463      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   opning         ! rate of opening due to divergence/shear 
     464      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   closing_gross  ! rate at which area retreats, excluding area of new ridges 
     465      ! 
     466      INTEGER  ::   ji, jj, jl, jl1, jl2, jk   ! dummy loop indices 
     467      INTEGER  ::   ij                         ! horizontal index, combines i and j loops 
     468      INTEGER  ::   icells                     ! number of cells with a_i > puny 
     469      REAL(wp) ::   hL, hR, farea              ! left and right limits of integration and new area going to jl2 
     470 
     471      INTEGER , DIMENSION(jpij) ::   indxi, indxj     ! compressed indices 
     472      REAL(wp), DIMENSION(jpij) ::   zswitch, fvol    ! new ridge volume going to jl2 
    475473 
    476474      REAL(wp), DIMENSION(jpij) ::   afrac            ! fraction of category area ridged  
     
    482480      REAL(wp), DIMENSION(jpij) ::   aprdg2           ! pond area of ridging ice 
    483481      ! END MV MP 2016 
    484       REAL(wp), DIMENSION(jpij) ::   dhr   , dhr2     ! hrmax - hrmin  &  hrmax^2 - hrmin^2 
    485  
    486       REAL(wp), DIMENSION(jpij) ::   vrdg1   ! volume of ice ridged 
    487       REAL(wp), DIMENSION(jpij) ::   vrdg2   ! volume of new ridges 
    488       REAL(wp), DIMENSION(jpij) ::   vsw     ! volume of seawater trapped into ridges 
    489       REAL(wp), DIMENSION(jpij) ::   srdg1   ! sal*volume of ice ridged 
    490       REAL(wp), DIMENSION(jpij) ::   srdg2   ! sal*volume of new ridges 
    491       REAL(wp), DIMENSION(jpij) ::   smsw    ! sal*volume of water trapped into ridges 
     482      REAL(wp), DIMENSION(jpij) ::   dhr, dhr2        ! hrmax - hrmin  &  hrmax^2 - hrmin^2 
     483 
     484      REAL(wp), DIMENSION(jpij) ::   vrdg1            ! volume of ice ridged 
     485      REAL(wp), DIMENSION(jpij) ::   vrdg2            ! volume of new ridges 
     486      REAL(wp), DIMENSION(jpij) ::   vsw              ! volume of seawater trapped into ridges 
     487      REAL(wp), DIMENSION(jpij) ::   srdg1            ! sal*volume of ice ridged 
     488      REAL(wp), DIMENSION(jpij) ::   srdg2            ! sal*volume of new ridges 
     489      REAL(wp), DIMENSION(jpij) ::   smsw             ! sal*volume of water trapped into ridges 
    492490      REAL(wp), DIMENSION(jpij) ::   oirdg1, oirdg2   ! ice age of ice ridged 
    493491 
     
    503501      REAL(wp), DIMENSION(jpij) ::   oirft1, oirft2   ! ice age of ice rafted 
    504502 
    505       REAL(wp), DIMENSION(jpij,nlay_i) ::   eirft      ! ice energy of rafting ice 
    506       REAL(wp), DIMENSION(jpij,nlay_i) ::   erdg1      ! enth*volume of ice ridged 
    507       REAL(wp), DIMENSION(jpij,nlay_i) ::   erdg2      ! enth*volume of new ridges 
    508       REAL(wp), DIMENSION(jpij,nlay_i) ::   ersw       ! enth of water trapped into ridges 
     503      REAL(wp), DIMENSION(jpij,nlay_i) ::   eirft     ! ice energy of rafting ice 
     504      REAL(wp), DIMENSION(jpij,nlay_i) ::   erdg1     ! enth*volume of ice ridged 
     505      REAL(wp), DIMENSION(jpij,nlay_i) ::   erdg2     ! enth*volume of new ridges 
     506      REAL(wp), DIMENSION(jpij,nlay_i) ::   ersw      ! enth of water trapped into ridges 
    509507      !!---------------------------------------------------------------------- 
    510508 
     
    515513         DO ji = 1, jpi 
    516514            ato_i(ji,jj) = MAX( 0._wp, ato_i(ji,jj) +  & 
    517                &                     ( opning(ji,jj) - athorn(ji,jj,0) * closing_gross(ji,jj) ) * rdt_ice ) 
     515               &                     ( opning(ji,jj) - apartf(ji,jj,0) * closing_gross(ji,jj) ) * rdt_ice ) 
    518516         END DO 
    519517      END DO 
    520518 
    521519      !----------------------------------------------------------------- 
    522       ! 3) Pump everything from ice which is being ridged / rafted 
     520      ! 2) Pump everything from ice which is being ridged / rafted 
    523521      !----------------------------------------------------------------- 
    524522      ! Compute the area, volume, and energy of ice ridging in each 
     
    528526 
    529527         !------------------------------------------------ 
    530          ! 3.1) Identify grid cells with nonzero ridging 
     528         ! 2.1) Identify grid cells with nonzero ridging 
    531529         !------------------------------------------------ 
    532530         icells = 0 
    533531         DO jj = 1, jpj 
    534532            DO ji = 1, jpi 
    535                IF( athorn(ji,jj,jl1) > 0._wp .AND. closing_gross(ji,jj) > 0._wp ) THEN 
     533               IF( apartf(ji,jj,jl1) > 0._wp .AND. closing_gross(ji,jj) > 0._wp ) THEN 
    536534                  icells = icells + 1 
    537535                  indxi(icells) = ji 
     
    545543 
    546544            !-------------------------------------------------------------------- 
    547             ! 3.2) Compute area of ridging ice (ardg1) and of new ridge (ardg2) 
     545            ! 2.2) Compute area of ridging ice (ardg1) and of new ridge (ardg2) 
    548546            !-------------------------------------------------------------------- 
    549547            ardg1(ij) = aridge(ji,jj,jl1) * closing_gross(ji,jj) * rdt_ice 
     
    551549 
    552550            !--------------------------------------------------------------- 
    553             ! 3.3) Compute ridging /rafting fractions, make sure afrac <=1  
     551            ! 2.3) Compute ridging /rafting fractions, make sure afrac <=1  
    554552            !--------------------------------------------------------------- 
    555553            afrac(ij) = ardg1(ij) / a_i(ji,jj,jl1) !ridging 
    556554            afrft(ij) = arft1(ij) / a_i(ji,jj,jl1) !rafting 
    557             ardg2(ij) = ardg1(ij) * krdg(ji,jj,jl1) 
    558             arft2(ij) = arft1(ij) * kraft 
     555            ardg2(ij) = ardg1(ij) * hi_hrdg(ji,jj,jl1) 
     556            arft2(ij) = arft1(ij) * hi_hrft 
    559557 
    560558            !-------------------------------------------------------------------------- 
    561             ! 3.4) Substract area, volume, and energy from ridging  
     559            ! 2.4) Substract area, volume, and energy from ridging  
    562560            !     / rafting category n1. 
    563561            !-------------------------------------------------------------------------- 
     
    571569            IF ( nn_pnd_scheme > 0 ) THEN 
    572570               aprdg1(ij) = a_ip(ji,jj, jl1) * afrac(ij) 
    573                aprdg2(ij) = a_ip(ji,jj, jl1) * afrac(ij) * krdg(ji,jj,jl1) 
     571               aprdg2(ij) = a_ip(ji,jj, jl1) * afrac(ij) * hi_hrdg(ji,jj,jl1) 
    574572               vprdg(ij)  = v_ip(ji,jj, jl1) * afrac(ij) 
    575573            ENDIF 
     
    577575            srdg1 (ij) = smv_i(ji,jj,  jl1) * afrac(ij) 
    578576            oirdg1(ij) = oa_i (ji,jj,  jl1) * afrac(ij) 
    579             oirdg2(ij) = oa_i (ji,jj,  jl1) * afrac(ij) * krdg(ji,jj,jl1)  
     577            oirdg2(ij) = oa_i (ji,jj,  jl1) * afrac(ij) * hi_hrdg(ji,jj,jl1)  
    580578 
    581579            ! rafting volumes, heat contents ... 
     
    585583            IF ( nn_pnd_scheme > 0 ) THEN 
    586584               aprft1(ij) = a_ip (ji,jj,  jl1) * afrft(ij) 
    587                aprft2(ij) = a_ip (ji,jj,  jl1) * afrft(ij) * kraft 
     585               aprft2(ij) = a_ip (ji,jj,  jl1) * afrft(ij) * hi_hrft 
    588586               vprft(ij)  = v_ip(ji,jj,jl1)    * afrft(ij) 
    589587            ENDIF 
     
    593591            smrft (ij) = smv_i(ji,jj,  jl1) * afrft(ij)  
    594592            oirft1(ij) = oa_i (ji,jj,  jl1) * afrft(ij)  
    595             oirft2(ij) = oa_i (ji,jj,  jl1) * afrft(ij) * kraft  
     593            oirft2(ij) = oa_i (ji,jj,  jl1) * afrft(ij) * hi_hrft  
    596594 
    597595            !----------------------------------------------------------------- 
    598             ! 3.5) Compute properties of new ridges 
     596            ! 2.5) Compute properties of new ridges 
    599597            !----------------------------------------------------------------- 
    600598            smsw(ij)  = vsw(ij) * sss_m(ji,jj)                   ! salt content of seawater frozen in voids 
     
    612610 
    613611            !------------------------------------------             
    614             ! 3.7 Put the snow somewhere in the ocean 
     612            ! 2.6 Put the snow somewhere in the ocean 
    615613            !------------------------------------------             
    616614            !  Place part of the snow lost by ridging into the ocean.  
     
    627625            ! MV MP 2016 
    628626            !------------------------------------------             
    629             ! 3.X Put the melt pond water in the ocean 
     627            ! 2.7 Put the melt pond water in the ocean 
    630628            !------------------------------------------             
    631629            !  Place part of the melt pond volume into the ocean.  
     
    637635 
    638636            !----------------------------------------------------------------- 
    639             ! 3.8 Compute quantities used to apportion ice among categories 
     637            ! 2.8 Compute quantities used to apportion ice among categories 
    640638            ! in the n2 loop below 
    641639            !----------------------------------------------------------------- 
     
    662660 
    663661         !-------------------------------------------------------------------- 
    664          ! 3.9 Compute ridging ice enthalpy, remove it from ridging ice and 
     662         ! 2.9 Compute ridging ice enthalpy, remove it from ridging ice and 
    665663         !      compute ridged ice enthalpy  
    666664         !-------------------------------------------------------------------- 
     
    689687 
    690688         !------------------------------------------------------------------------------- 
    691          ! 4) Add area, volume, and energy of new ridge to each category jl2 
     689         ! 3) Add area, volume, and energy of new ridge to each category jl2 
    692690         !------------------------------------------------------------------------------- 
    693691         DO jl2  = 1, jpl  
     
    710708!!gm see above               IF( hraft(ji,jj,jl1) <= hi_max(jl2) .AND. hraft(ji,jj,jl1) >  hi_max(jl2-1) ) THEN 
    711709               IF( hi_max(jl2-1) < hraft(ji,jj,jl1) .AND. hraft(ji,jj,jl1) <= hi_max(jl2)  ) THEN   ;   zswitch(ij) = 1._wp 
    712                ELSE                                                                                 ;   zswitch(ij) = 0._wp                   
     710               ELSE                                                                                 ;   zswitch(ij) = 0._wp 
    713711               ENDIF 
    714712               ! 
     
    743741      END DO ! jl1 (deforming categories) 
    744742      ! 
    745    END SUBROUTINE ice_rdgrft_ridgeshift 
    746  
    747  
    748    SUBROUTINE ice_rdgrft_strength 
     743   END SUBROUTINE rdgrft_shift 
     744 
     745 
     746   SUBROUTINE ice_strength 
    749747      !!---------------------------------------------------------------------- 
    750       !!                ***  ROUTINE ice_rdgrft_strength *** 
     748      !!                ***  ROUTINE ice_strength *** 
    751749      !! 
    752750      !! ** Purpose :   computes ice strength used in dynamics routines of ice thickness 
     
    767765 
    768766      !                              !--------------------------------------------------! 
    769       CALL ice_rdgrft_prep           ! Thickness distribution of ridging and ridged ice ! 
     767      CALL rdgrft_prep               ! Thickness distribution of ridging and ridged ice ! 
    770768      !                              !--------------------------------------------------! 
    771769 
     
    775773         z1_3 = 1._wp / 3._wp 
    776774         DO jl = 1, jpl 
    777             WHERE( athorn(:,:,jl) > 0._wp ) 
    778                strength(:,:) =  -         athorn(:,:,jl) * ht_i(:,:,jl) * ht_i(:,:,jl)   &  ! PE loss from deforming ice 
    779                   &             + 2._wp * araft (:,:,jl) * ht_i(:,:,jl) * ht_i(:,:,jl)   &  ! PE gain from rafting ice 
    780                   &             +         aridge(:,:,jl) * krdg(:,:,jl) * z1_3 *   &        ! PE gain from ridging ice 
    781                   &                      ( hrmax(:,:,jl) * hrmax(:,:,jl) +         & 
    782                   &                        hrmin(:,:,jl) * hrmin(:,:,jl) +         & 
    783                   &                        hrmax(:,:,jl) * hrmin(:,:,jl) ) 
     775            WHERE( apartf(:,:,jl) > 0._wp ) 
     776               strength(:,:) =  -         apartf(:,:,jl) * ht_i   (:,:,jl) * ht_i(:,:,jl)   &  ! PE loss from deforming ice 
     777                  &             + 2._wp * araft (:,:,jl) * ht_i   (:,:,jl) * ht_i(:,:,jl)   &  ! PE gain from rafting ice 
     778                  &             +         aridge(:,:,jl) * hi_hrdg(:,:,jl) * z1_3 *         &  ! PE gain from ridging ice 
     779                  &                      ( hrmax(:,:,jl) * hrmax  (:,:,jl) +                & 
     780                  &                        hrmin(:,:,jl) * hrmin  (:,:,jl) +                & 
     781                  &                        hrmax(:,:,jl) * hrmin  (:,:,jl) ) 
    784782            ELSEWHERE 
    785783               strength(:,:) = 0._wp 
     
    844842      END SELECT 
    845843      ! 
    846    END SUBROUTINE ice_rdgrft_strength 
     844   END SUBROUTINE ice_strength 
    847845 
    848846 
     
    854852      !!                to the mechanical ice redistribution 
    855853      !! 
    856       !! ** Method  :   Read the namice_rdgrft namelist  
     854      !! ** Method  :   Read the namdyn_rdgrft namelist  
    857855      !!                and check the parameters values  
    858856      !!                called at the first timestep (nit000) 
    859857      !! 
    860       !! ** input   :   Namelist namice_rdgrft 
     858      !! ** input   :   Namelist namdyn_rdgrft 
    861859      !!------------------------------------------------------------------- 
    862860      INTEGER :: ios                 ! Local integer output status for namelist read 
    863861      !! 
    864       NAMELIST/namice_rdgrft/ ln_str_H79, rn_pstar, rn_crhg, & 
     862      NAMELIST/namdyn_rdgrft/ ln_str_H79, rn_pstar, rn_crhg, & 
    865863         &                    ln_str_R75, rn_perdg,          & 
    866864         &                    rn_csrdg  ,                    & 
     
    872870      ! 
    873871      REWIND( numnam_ice_ref )              ! Namelist namicetdme in reference namelist : Ice mechanical ice redistribution 
    874       READ  ( numnam_ice_ref, namice_rdgrft, IOSTAT = ios, ERR = 901) 
    875 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_rdgrft in reference namelist', lwp ) 
    876       ! 
    877       REWIND( numnam_ice_cfg )              ! Namelist namice_rdgrft in configuration namelist : Ice mechanical ice redistribution 
    878       READ  ( numnam_ice_cfg, namice_rdgrft, IOSTAT = ios, ERR = 902 ) 
    879 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_rdgrft in configuration namelist', lwp ) 
    880       IF(lwm) WRITE ( numoni, namice_rdgrft ) 
     872      READ  ( numnam_ice_ref, namdyn_rdgrft, IOSTAT = ios, ERR = 901) 
     873901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_rdgrft in reference namelist', lwp ) 
     874      ! 
     875      REWIND( numnam_ice_cfg )              ! Namelist namdyn_rdgrft in configuration namelist : Ice mechanical ice redistribution 
     876      READ  ( numnam_ice_cfg, namdyn_rdgrft, IOSTAT = ios, ERR = 902 ) 
     877902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_rdgrft in configuration namelist', lwp ) 
     878      IF(lwm) WRITE ( numoni, namdyn_rdgrft ) 
    881879      ! 
    882880      IF (lwp) THEN                          ! control print 
     
    884882         WRITE(numout,*) 'ice_rdgrft_init: ice parameters for ridging/rafting ' 
    885883         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    886          WRITE(numout,*) '   Namelist namice_rdgrft' 
     884         WRITE(numout,*) '   Namelist namdyn_rdgrft:' 
    887885         WRITE(numout,*) '      ice strength parameterization Hibler (1979)              ln_str_H79   = ', ln_str_H79  
    888886         WRITE(numout,*) '            1st bulk-rheology parameter                        rn_pstar     = ', rn_pstar 
     
    915913      ENDIF 
    916914      !                              ! allocate tke arrays 
    917       IF( ice_rdgrft_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'ice_rdgrft_init : unable to allocate arrays' ) 
     915      IF( ice_rdgrft_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'ice_rdgrft_init: unable to allocate arrays' ) 
    918916      ! 
    919917  END SUBROUTINE ice_rdgrft_init 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerhg.F90

    r8518 r8531  
    101101      !!      dynamics 
    102102      !! 
    103       !! ** Method  :  Read the namice_rhg namelist and check the ice-dynamic 
     103      !! ** Method  :  Read the namdyn_rhg namelist and check the ice-dynamic 
    104104      !!       parameter values called at the first timestep (nit000) 
    105105      !! 
    106       !! ** input   :   Namelist namice_rhg 
     106      !! ** input   :   Namelist namdyn_rhg 
    107107      !!------------------------------------------------------------------- 
    108108      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read 
    109109      !! 
    110       NAMELIST/namice_rhg/  ln_rhg_EVP, rn_creepl, rn_ecc , nn_nevp, rn_relast 
     110      NAMELIST/namdyn_rhg/  ln_rhg_EVP, rn_creepl, rn_ecc , nn_nevp, rn_relast 
    111111      !!------------------------------------------------------------------- 
    112112      ! 
    113       REWIND( numnam_ice_ref )         ! Namelist namice_rhg in reference namelist : Ice dynamics 
    114       READ  ( numnam_ice_ref, namice_rhg, IOSTAT = ios, ERR = 901) 
    115 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_rhg in reference namelist', lwp ) 
     113      REWIND( numnam_ice_ref )         ! Namelist namdyn_rhg in reference namelist : Ice dynamics 
     114      READ  ( numnam_ice_ref, namdyn_rhg, IOSTAT = ios, ERR = 901) 
     115901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_rhg in reference namelist', lwp ) 
    116116      ! 
    117       REWIND( numnam_ice_cfg )         ! Namelist namice_rhg in configuration namelist : Ice dynamics 
    118       READ  ( numnam_ice_cfg, namice_rhg, IOSTAT = ios, ERR = 902 ) 
    119 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_rhg in configuration namelist', lwp ) 
    120       IF(lwm) WRITE ( numoni, namice_rhg ) 
     117      REWIND( numnam_ice_cfg )         ! Namelist namdyn_rhg in configuration namelist : Ice dynamics 
     118      READ  ( numnam_ice_cfg, namdyn_rhg, IOSTAT = ios, ERR = 902 ) 
     119902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn_rhg in configuration namelist', lwp ) 
     120      IF(lwm) WRITE ( numoni, namdyn_rhg ) 
    121121      ! 
    122122      IF(lwp) THEN                     ! control print 
     
    124124         WRITE(numout,*) 'ice_rhg_init: ice parameters for ice dynamics ' 
    125125         WRITE(numout,*) '~~~~~~~~~~~~' 
    126          WRITE(numout,*) '   Namelist namice_rhg' 
    127          WRITE(numout,*) '      rheology EVP (icerhg_evp)                                   ln_rhg_EVP    = ', ln_rhg_EVP 
    128          WRITE(numout,*) '         creep limit                                              rn_creepl     = ', rn_creepl 
    129          WRITE(numout,*) '         eccentricity of the elliptical yield curve               rn_ecc        = ', rn_ecc 
    130          WRITE(numout,*) '         number of iterations for subcycling                      nn_nevp       = ', nn_nevp 
    131          WRITE(numout,*) '         ratio of elastic timescale over ice time step            rn_relast     = ', rn_relast 
     126         WRITE(numout,*) '   Namelist namdyn_rhg:' 
     127         WRITE(numout,*) '      rheology EVP (icerhg_evp)                            ln_rhg_EVP = ', ln_rhg_EVP 
     128         WRITE(numout,*) '         creep limit                                       rn_creepl  = ', rn_creepl 
     129         WRITE(numout,*) '         eccentricity of the elliptical yield curve        rn_ecc     = ', rn_ecc 
     130         WRITE(numout,*) '         number of iterations for subcycling               nn_nevp    = ', nn_nevp 
     131         WRITE(numout,*) '         ratio of elastic timescale over ice time step     rn_relast  = ', rn_relast 
    132132      ENDIF 
    133133      ! 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerhg_evp.F90

    r8518 r8531  
    253253 
    254254      ! Ice strength 
    255       CALL ice_rdgrft_strength 
     255      CALL ice_strength 
    256256 
    257257      ! scale factors 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90

    r8518 r8531  
    142142         ! --- ice dynamics and advection  --- ! 
    143143         !-------------------------------------! 
    144          CALL ice_diag0             ! set diag of mass, heat and salt fluxes to 0 
     144         CALL diag_set0             ! set diag of mass, heat and salt fluxes to 0 
    145145         CALL ice_rst_opn( kt )     ! Open Ice restart file (if necessary)  
    146146         ! 
     
    243243      IF(lwm) CALL ctl_opn( numoni, 'output.namelist.ice', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, 1 ) 
    244244      ! 
    245       CALL ice_run_init                ! set some ice run parameters 
     245      CALL par_init                ! set some ice run parameters 
    246246      ! 
    247247      !                                ! Allocate the ice arrays (sbc_ice already allocated in sbc_init) 
     
    268268      CALL ice_var_glo2eqv 
    269269      ! 
     270      CALL ice_forcing_init            ! set ice-ocean and ice-atm. coupling parameters 
     271      ! 
    270272      IF( ln_icedyn ) THEN 
    271273         CALL ice_dyn_init             ! set ice dynamics parameters 
    272          CALL ice_rdgrft_init          ! set ice ridging/rafting parameters 
    273          CALL ice_rhg_init             ! set ice rheology parameters 
    274          CALL ice_adv_init             ! set ice advection parameters 
    275274      ENDIF 
    276  
     275      ! 
    277276      IF( ln_icethd ) THEN 
    278277         CALL ice_thd_init             ! set ice thermodynics parameters 
    279          CALL ice_thd_sal_init         ! set ice salinity parameters 
    280278      ENDIF    
    281279      ! 
     
    299297 
    300298 
    301    SUBROUTINE ice_run_init 
     299   SUBROUTINE par_init 
    302300      !!------------------------------------------------------------------- 
    303       !!                  ***  ROUTINE ice_run_init *** 
     301      !!                  ***  ROUTINE par_init *** 
    304302      !! 
    305303      !! ** Purpose :   Definition some run parameter for ice model 
    306304      !! 
    307       !! ** Method  :   Read the namice_run namelist and check the parameter 
     305      !! ** Method  :   Read the nampar namelist and check the parameter 
    308306      !!                values called at the first timestep (nit000) 
    309307      !! 
    310       !! ** input   :   Namelist namice_run 
     308      !! ** input   :   Namelist nampar 
    311309      !!------------------------------------------------------------------- 
    312310      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    313       NAMELIST/namice_run/ jpl, nlay_i, nlay_s, nn_monocat, ln_icedyn, ln_icethd, rn_amax_n, rn_amax_s,  & 
    314          &                 cn_icerst_in, cn_icerst_indir, cn_icerst_out, cn_icerst_outdir 
     311      NAMELIST/nampar/ jpl, nlay_i, nlay_s, nn_monocat, ln_icedyn, ln_icethd, rn_amax_n, rn_amax_s,  & 
     312         &             cn_icerst_in, cn_icerst_indir, cn_icerst_out, cn_icerst_outdir 
    315313      !!------------------------------------------------------------------- 
    316314      ! 
    317       REWIND( numnam_ice_ref )      ! Namelist namice_run in reference namelist : Parameters for ice 
    318       READ  ( numnam_ice_ref, namice_run, IOSTAT = ios, ERR = 901) 
    319 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_run in reference namelist', lwp ) 
    320  
    321       REWIND( numnam_ice_cfg )      ! Namelist namice_run in configuration namelist : Parameters for ice 
    322       READ  ( numnam_ice_cfg, namice_run, IOSTAT = ios, ERR = 902 ) 
    323 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_run in configuration namelist', lwp ) 
    324       IF(lwm) WRITE ( numoni, namice_run ) 
     315      REWIND( numnam_ice_ref )      ! Namelist nampar in reference namelist : Parameters for ice 
     316      READ  ( numnam_ice_ref, nampar, IOSTAT = ios, ERR = 901) 
     317901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampar in reference namelist', lwp ) 
     318 
     319      REWIND( numnam_ice_cfg )      ! Namelist nampar in configuration namelist : Parameters for ice 
     320      READ  ( numnam_ice_cfg, nampar, IOSTAT = ios, ERR = 902 ) 
     321902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampar in configuration namelist', lwp ) 
     322      IF(lwm) WRITE ( numoni, nampar ) 
    325323      ! 
    326324      IF(lwp) THEN                  ! control print 
    327325         WRITE(numout,*) 
    328          WRITE(numout,*) 'ice_run_init : ice share parameters for dynamics/advection/thermo of sea-ice' 
    329          WRITE(numout,*) ' ~~~~~~' 
    330          WRITE(numout,*) '   Namelist namice_run : ' 
     326         WRITE(numout,*) 'par_init: ice parameters shared among all the routines' 
     327         WRITE(numout,*) ' ~~~~~~~' 
     328         WRITE(numout,*) '   Namelist nampar: ' 
    331329         WRITE(numout,*) '      number of ice  categories                              jpl    = ', jpl 
    332330         WRITE(numout,*) '      number of ice  layers                                  nlay_i = ', nlay_i 
    333331         WRITE(numout,*) '      number of snow layers                                  nlay_s = ', nlay_s 
    334332         WRITE(numout,*) '      virtual ITD mono-category param (1-4) or not (0)   nn_monocat = ', nn_monocat 
    335          WRITE(numout,*) '      Ice dynamics       (T) or not (F)                  ln_icedyn = ', ln_icedyn 
    336          WRITE(numout,*) '      Ice thermodynamics (T) or not (F)                  ln_icethd = ', ln_icethd 
     333         WRITE(numout,*) '      Ice dynamics       (T) or not (F)                   ln_icedyn = ', ln_icedyn 
     334         WRITE(numout,*) '      Ice thermodynamics (T) or not (F)                   ln_icethd = ', ln_icethd 
    337335         WRITE(numout,*) '      maximum ice concentration for NH                              = ', rn_amax_n  
    338336         WRITE(numout,*) '      maximum ice concentration for SH                              = ', rn_amax_s 
     
    346344      ENDIF 
    347345      IF ( jpl == 1 .AND. nn_monocat == 0 ) THEN 
    348          CALL ctl_stop( 'STOP', 'ice_run_init : if jpl=1 then nn_monocat should be between 1 and 4' ) 
     346         CALL ctl_stop( 'STOP', 'par_init : if jpl=1 then nn_monocat should be between 1 and 4' ) 
    349347      ENDIF 
    350348      ! 
    351       IF( ln_bdy .AND. ln_icediachk )   CALL ctl_warn('ice_run_init: online conservation check does not work with BDY') 
     349      IF( ln_bdy .AND. ln_icediachk )   CALL ctl_warn('par_init: online conservation check does not work with BDY') 
    352350      ! 
    353351      rdt_ice   = REAL(nn_fsbc) * rdt          !--- sea-ice timestep and inverse 
     
    358356      r1_nlay_s = 1._wp / REAL( nlay_s, wp ) 
    359357      ! 
    360    END SUBROUTINE ice_run_init 
     358   END SUBROUTINE par_init 
    361359 
    362360 
     
    393391 
    394392 
    395    SUBROUTINE ice_diag0 
    396       !!---------------------------------------------------------------------- 
    397       !!                  ***  ROUTINE ice_diag0  *** 
     393   SUBROUTINE diag_set0 
     394      !!---------------------------------------------------------------------- 
     395      !!                  ***  ROUTINE diag_set0  *** 
    398396      !! 
    399397      !! ** purpose :  set ice-ocean and ice-atm. fluxes to zeros at the beggining 
     
    442440      tau_icebfr(:,:) = 0._wp; ! landfast ice param only (clem: important to keep the init here) 
    443441       
    444    END SUBROUTINE ice_diag0 
     442   END SUBROUTINE diag_set0 
    445443 
    446444#else 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd.F90

    r8522 r8531  
    2828      &                 fr1_i0, fr2_i0 
    2929   USE ice1D          ! thermodynamic sea-ice variables 
    30    USE icethd_dif     ! vertical diffusion 
     30   USE icethd_zdf     ! vertical diffusion 
    3131   USE icethd_dh      ! ice-snow growth and melt 
    3232   USE icethd_da      ! lateral melting 
    3333   USE icethd_sal     ! ice salinity 
    3434   USE icethd_ent     ! ice enthalpy redistribution 
    35    USE icethd_lac     ! lateral accretion 
     35   USE icethd_do      ! lateral accretion 
    3636   USE iceitd         ! remapping thickness distribution 
    3737   USE icetab         ! 1D <==> 2D transformation 
     
    5151   PUBLIC   ice_thd_init    ! called by ice_init 
    5252 
     53   !!** namelist (namthd) ** 
     54   LOGICAL ::   ln_icedH         ! activate ice thickness change from growing/melting (T) or not (F) 
     55   LOGICAL ::   ln_icedA         ! activate lateral melting param. (T) or not (F) 
     56   LOGICAL ::   ln_icedO         ! activate ice growth in open-water (T) or not (F) 
     57   LOGICAL ::   ln_icedS         ! activate gravity drainage and flushing (T) or not (F) 
     58 
    5359   !! * Substitutions 
    5460#  include "vectopt_loop_substitute.h90" 
     
    7076      !!               at the ice base, snow acc.,heat budget of the leads) 
    7177      !!             - selection of the icy points and put them in an array 
    72       !!             - call ice_thd_dif  for vertical heat diffusion 
     78      !!             - call ice_thd_zdf  for vertical heat diffusion 
    7379      !!             - call ice_thd_dh   for vertical ice growth and melt 
    7480      !!             - call ice_thd_ent  for enthalpy remapping 
    7581      !!             - call ice_thd_sal  for ice desalination 
    7682      !!             - call ice_thd_temp to  retrieve temperature from ice enthalpy 
     83      !!             - call ice_thd_lam  for extra lateral ice melt if monocat 
     84      !!             - call ice_thd_da   for lateral ice melt 
    7785      !!             - back to the geographic grid 
    7886      !!--------------------------------------------------------------------- 
     
    223231            ! 
    224232            IF( ln_icedH ) THEN                                     ! --- growing/melting --- ! 
    225                               CALL ice_thd_dif                             ! Ice/Snow Temperature profile 
     233                              CALL ice_thd_zdf                             ! Ice/Snow Temperature profile 
    226234                              CALL ice_thd_dh                              ! Ice/Snow thickness    
    227235                              CALL ice_thd_ent( e_i_1d(1:nidx,:) )         ! Ice enthalpy remapping 
    228236            ENDIF 
    229237            ! 
    230                               CALL ice_thd_sal                      ! --- Ice salinity --- !     
     238                              CALL ice_thd_sal( ln_icedS )          ! --- Ice salinity --- !     
    231239            ! 
    232240                              CALL ice_thd_temp                     ! --- temperature update --- ! 
     
    261269      IF( jpl > 1 )        CALL ice_itd_rem( kt )          ! --- Transport ice between thickness categories --- ! 
    262270      ! 
    263       IF( ln_icedO )       CALL ice_thd_lac                ! --- frazil ice growing in leads --- ! 
     271      IF( ln_icedO )       CALL ice_thd_do                 ! --- frazil ice growing in leads --- ! 
    264272      ! 
    265273      ! controls 
     
    523531      !!                   ***  ROUTINE ice_thd_init ***  
    524532      !!                  
    525       !! ** Purpose :   Physical constants and parameters linked to the ice  
    526       !!              thermodynamics 
     533      !! ** Purpose :   Physical constants and parameters associated with 
     534      !!                ice thermodynamics 
    527535      !! 
    528       !! ** Method  :   Read the namice_thd namelist and check the ice-thermo 
    529       !!              parameter values called at the first timestep (nit000) 
     536      !! ** Method  :   Read the namthd namelist and check the parameters 
     537      !!                called at the first timestep (nit000) 
    530538      !! 
    531       !! ** input   :   Namelist namicether 
     539      !! ** input   :   Namelist namthd 
    532540      !!------------------------------------------------------------------- 
    533541      INTEGER  ::   ios   ! Local integer output status for namelist read 
    534542      !! 
    535       NAMELIST/namice_thd/ rn_kappa_i, ln_cndi_U64, ln_cndi_P07, ln_dqns_i, rn_cnd_s,   & 
    536          &                 ln_icedH, rn_blow_s,                                                    & 
    537          &                 ln_icedA, rn_beta, rn_dmin,                                             & 
    538          &                 ln_icedO, rn_hinew, ln_frazil, rn_maxfraz, rn_vfraz, rn_Cfraz,          & 
    539          &                 nn_iceflx 
     543      NAMELIST/namthd/ ln_icedH, ln_icedA, ln_icedO, ln_icedS 
    540544      !!------------------------------------------------------------------- 
    541545      ! 
    542       REWIND( numnam_ice_ref )              ! Namelist namice_thd in reference namelist : Ice thermodynamics 
    543       READ  ( numnam_ice_ref, namice_thd, IOSTAT = ios, ERR = 901) 
    544 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_thd in reference namelist', lwp ) 
    545  
    546       REWIND( numnam_ice_cfg )              ! Namelist namice_thd in configuration namelist : Ice thermodynamics 
    547       READ  ( numnam_ice_cfg, namice_thd, IOSTAT = ios, ERR = 902 ) 
    548 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_thd in configuration namelist', lwp ) 
    549       IF(lwm) WRITE ( numoni, namice_thd ) 
     546      REWIND( numnam_ice_ref )              ! Namelist namthd in reference namelist : Ice thermodynamics 
     547      READ  ( numnam_ice_ref, namthd, IOSTAT = ios, ERR = 901) 
     548901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd in reference namelist', lwp ) 
     549 
     550      REWIND( numnam_ice_cfg )              ! Namelist namthd in configuration namelist : Ice thermodynamics 
     551      READ  ( numnam_ice_cfg, namthd, IOSTAT = ios, ERR = 902 ) 
     552902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd in configuration namelist', lwp ) 
     553      IF(lwm) WRITE ( numoni, namthd ) 
    550554      ! 
    551555      ! 
    552556      IF(lwp) THEN                          ! control print 
    553          WRITE(numout,*) 'ice_thd_init : Ice Thermodynamics' 
    554          WRITE(numout,*) '~~~~~~~~~~~~~' 
    555          WRITE(numout,*) '   Namelist namice_thd' 
    556          WRITE(numout,*) '   -- icethd_dif --' 
    557          WRITE(numout,*) '      extinction radiation parameter in sea ice               rn_kappa_i   = ', rn_kappa_i 
    558          WRITE(numout,*) '      thermal conductivity in the ice (Untersteiner 1964)     ln_cndi_U64  = ', ln_cndi_U64 
    559          WRITE(numout,*) '      thermal conductivity in the ice (Pringle et al 2007)    ln_cndi_P07  = ', ln_cndi_P07 
    560          WRITE(numout,*) '      change the surface non-solar flux with Tsu or not       ln_dqns_i    = ', ln_dqns_i 
    561          WRITE(numout,*) '      thermal conductivity of the snow                        rn_cnd_s     = ', rn_cnd_s 
    562          WRITE(numout,*) '   -- icethd_dh --' 
    563          WRITE(numout,*) '      activate ice thick change from top/bot (T) or not (F)   ln_icedH     = ', ln_icedH 
    564          WRITE(numout,*) '      coefficient for ice-lead partition of snowfall          rn_blow_s    = ', rn_blow_s 
    565          WRITE(numout,*) '   -- icethd_da --' 
    566          WRITE(numout,*) '      activate lateral melting (T) or not (F)                 ln_icedA     = ', ln_icedA 
    567          WRITE(numout,*) '      Coef. beta for lateral melting param.                   rn_beta      = ', rn_beta 
    568          WRITE(numout,*) '      Minimum floe diameter for lateral melting param.        rn_dmin      = ', rn_dmin 
    569          WRITE(numout,*) '   -- icethd_lac --' 
    570          WRITE(numout,*) '      activate ice growth in open-water (T) or not (F)        ln_icedO     = ', ln_icedO 
    571          WRITE(numout,*) '      ice thickness for lateral accretion                     rn_hinew     = ', rn_hinew 
    572          WRITE(numout,*) '      Frazil ice thickness as a function of wind or not       ln_frazil    = ', ln_frazil 
    573          WRITE(numout,*) '      Maximum proportion of frazil ice collecting at bottom   rn_maxfraz   = ', rn_maxfraz 
    574          WRITE(numout,*) '      Threshold relative drift speed for collection of frazil rn_vfraz     = ', rn_vfraz 
    575          WRITE(numout,*) '      Squeezing coefficient for collection of frazil          rn_Cfraz     = ', rn_Cfraz 
    576          WRITE(numout,*) '   -- icestp --' 
    577          WRITE(numout,*) '      Multicategory heat flux formulation                     nn_iceflx    = ', nn_iceflx 
     557         WRITE(numout,*) 'ice_thd_init: Ice Thermodynamics' 
     558         WRITE(numout,*) '~~~~~~~~~~~~' 
     559         WRITE(numout,*) '   Namelist namthd:' 
     560         WRITE(numout,*) '      activate ice thick change from top/bot (T) or not (F)   ln_icedH  = ', ln_icedH 
     561         WRITE(numout,*) '      activate lateral melting (T) or not (F)                 ln_icedA  = ', ln_icedA 
     562         WRITE(numout,*) '      activate ice growth in open-water (T) or not (F)        ln_icedO  = ', ln_icedO 
     563         WRITE(numout,*) '      activate gravity drainage and flushing (T) or not (F)   ln_icedS  = ', ln_icedS 
     564     ENDIF 
     565      ! 
     566                       CALL ice_thd_zdf_init   ! set ice heat diffusion parameters 
     567      IF( ln_icedA )   CALL ice_thd_da_init    ! set ice lateral melting parameters 
     568      IF( ln_icedO )   CALL ice_thd_do_init    ! set ice growth in open water parameters 
     569                       CALL ice_thd_sal_init   ! set ice salinity parameters 
     570      ! 
     571      IF( ln_icedS .AND. nn_icesal == 1 ) THEN 
     572         ln_icedS = .FALSE. 
     573         CALL ctl_warn('ln_icedS is set to false since constant ice salinity is chosen (nn_icesal=1)') 
    578574      ENDIF 
    579       ! 
    580       IF ( ( ln_cndi_U64 .AND. ln_cndi_P07 ) .OR. ( .NOT.ln_cndi_U64 .AND. .NOT.ln_cndi_P07 ) ) THEN 
    581          CALL ctl_stop( 'ice_thd_init: choose one and only one formulation for thermal conductivity (ln_cndi_U64 or ln_cndi_P07)' ) 
    582       ENDIF 
    583       ! 
    584       IF ( rn_hinew < rn_himin )   CALL ctl_stop( 'ice_thd_init : rn_hinew should be >= rn_himin' ) 
    585       ! 
    586       IF(lwp) WRITE(numout,*) 
    587       SELECT CASE( nn_iceflx )         ! LIM3 Multi-category heat flux formulation 
    588       CASE( -1  ) 
    589          IF(lwp) WRITE(numout,*) '   LIM3: use per-category fluxes (nn_iceflx = -1) ' 
    590          IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for LIM3 in coupled mode must be 0 or 2' ) 
    591       CASE(  0  ) 
    592          IF(lwp) WRITE(numout,*) '   LIM3: use average per-category fluxes (nn_iceflx = 0) ' 
    593       CASE(  1  ) 
    594          IF(lwp) WRITE(numout,*) '   LIM3: use average then redistribute per-category fluxes (nn_iceflx = 1) ' 
    595          IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for LIM3 in coupled mode must be 0 or 2' ) 
    596       CASE(  2  ) 
    597          IF(lwp) WRITE(numout,*) '   LIM3: Redistribute a single flux over categories (nn_iceflx = 2) ' 
    598          IF( .NOT. ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for LIM3 in forced mode cannot be 2' ) 
    599       CASE DEFAULT 
    600          CALL ctl_stop( 'ice_thd_init: LIM3 option, nn_iceflx, should be between -1 and 2' ) 
    601       END SELECT 
    602575      ! 
    603576   END SUBROUTINE ice_thd_init 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_da.F90

    r8498 r8531  
    1717   USE ice1D          ! sea-ice: thermodynamic 1D variables 
    1818   ! 
     19   USE in_out_manager ! I/O manager 
    1920   USE lib_mpp        ! MPP library 
    2021   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     
    2324   PRIVATE 
    2425 
    25    PUBLIC   ice_thd_da   ! called by icethd.F90 
     26   PUBLIC   ice_thd_da        ! called by icethd.F90 
     27   PUBLIC   ice_thd_da_init   ! called by icestp.F90 
     28 
     29   ! ** namelist (namthd_da) ** 
     30   REAL(wp) ::   rn_beta     ! coef. beta for lateral melting param. 
     31   REAL(wp) ::   rn_dmin     ! minimum floe diameter for lateral melting param. 
    2632 
    2733   !!---------------------------------------------------------------------- 
     
    149155      ! 
    150156   END SUBROUTINE ice_thd_da 
    151     
     157 
     158   SUBROUTINE ice_thd_da_init 
     159      !!----------------------------------------------------------------------- 
     160      !!                   ***  ROUTINE ice_thd_da_init ***  
     161      !!                  
     162      !! ** Purpose :   Physical constants and parameters associated with 
     163      !!                ice thermodynamics 
     164      !! 
     165      !! ** Method  :   Read the namthd_da namelist and check the parameters 
     166      !!                called at the first timestep (nit000) 
     167      !! 
     168      !! ** input   :   Namelist namthd_da 
     169      !!------------------------------------------------------------------- 
     170      INTEGER  ::   ios   ! Local integer output status for namelist read 
     171      !! 
     172      NAMELIST/namthd_da/ rn_beta, rn_dmin 
     173      !!------------------------------------------------------------------- 
     174      ! 
     175      REWIND( numnam_ice_ref )              ! Namelist namthd_da in reference namelist : Ice thermodynamics 
     176      READ  ( numnam_ice_ref, namthd_da, IOSTAT = ios, ERR = 901) 
     177901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd_da in reference namelist', lwp ) 
     178 
     179      REWIND( numnam_ice_cfg )              ! Namelist namthd_da in configuration namelist : Ice thermodynamics 
     180      READ  ( numnam_ice_cfg, namthd_da, IOSTAT = ios, ERR = 902 ) 
     181902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd_da in configuration namelist', lwp ) 
     182      IF(lwm) WRITE ( numoni, namthd_da ) 
     183      ! 
     184      ! 
     185      IF(lwp) THEN                          ! control print 
     186         WRITE(numout,*) 'ice_thd_da_init: Ice lateral melting' 
     187         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
     188         WRITE(numout,*) '   Namelist namthd_da:' 
     189         WRITE(numout,*) '      Coef. beta for lateral melting param.               rn_beta = ', rn_beta 
     190         WRITE(numout,*) '      Minimum floe diameter for lateral melting param.    rn_dmin = ', rn_dmin 
     191      ENDIF 
     192      ! 
     193   END SUBROUTINE ice_thd_da_init 
     194   
    152195#else 
    153196   !!---------------------------------------------------------------------- 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_ent.F90

    r8486 r8531  
    3333   PRIVATE 
    3434 
    35    PUBLIC   ice_thd_ent         ! called by icethd and icethd_lac 
     35   PUBLIC   ice_thd_ent         ! called by icethd and icethd_do 
    3636 
    3737   !!---------------------------------------------------------------------- 
     
    130130 
    131131      ! --- diag error on heat remapping --- ! 
    132       ! comment: if input h_i_old and eh_i_old are already multiplied by a_i (as in icethd_lac),  
     132      ! comment: if input h_i_old and eh_i_old are already multiplied by a_i (as in icethd_do),  
    133133      ! then we should not (* a_i) again but not important since this is just to check that remap error is ~0 
    134134      DO ji = 1, nidx 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_sal.F90

    r8518 r8531  
    2727   PRIVATE 
    2828 
    29    PUBLIC   ice_thd_sal        ! called by icethd module 
     29   PUBLIC   ice_thd_sal        ! called by icethd 
    3030   PUBLIC   ice_thd_sal_init   ! called by ice_init 
    3131    
    32    ! ** namelist (namsal) ** 
    33    LOGICAL  ::   ln_icedS         ! activate gravity drainage and flushing (T) or not (F) 
    34    REAL(wp) ::   rn_sal_gd        !    restoring salinity for gravity drainage [PSU] 
    35    REAL(wp) ::   rn_time_gd       !    restoring time constant for gravity drainage (= 20 days) [s] 
    36    REAL(wp) ::   rn_sal_fl        !    restoring salinity for flushing [PSU] 
    37    REAL(wp) ::   rn_time_fl       !    restoring time constant for gravity drainage (= 10 days) [s] 
     32   ! ** namelist (namthd_sal) ** 
     33   REAL(wp) ::   rn_sal_gd        ! restoring salinity for gravity drainage [PSU] 
     34   REAL(wp) ::   rn_time_gd       ! restoring time constant for gravity drainage (= 20 days) [s] 
     35   REAL(wp) ::   rn_sal_fl        ! restoring salinity for flushing [PSU] 
     36   REAL(wp) ::   rn_time_fl       ! restoring time constant for gravity drainage (= 10 days) [s] 
    3837 
    3938   !!---------------------------------------------------------------------- 
     
    4443CONTAINS 
    4544 
    46    SUBROUTINE ice_thd_sal 
     45   SUBROUTINE ice_thd_sal( ld_sal ) 
    4746      !!------------------------------------------------------------------- 
    4847      !!                ***  ROUTINE ice_thd_sal  ***     
     
    5554      !!               -> nn_icesal = 3 -> Sice = S(z)   [multiyear ice] 
    5655      !!--------------------------------------------------------------------- 
     56      LOGICAL, INTENT(in) ::   ld_sal            ! gravity drainage and flushing or not  
    5757      INTEGER  ::   ji, jk                       ! dummy loop indices  
    5858      REAL(wp) ::   iflush, igravdr              ! local scalars 
     
    7878            sm_i_1d(ji) = sm_i_1d(ji) + zsm_i_bg + zsm_i_si 
    7979 
    80             IF( ln_icedS ) THEN 
     80            IF( ld_sal ) THEN 
    8181               !--------------------------------------------------------- 
    8282               !  Update ice salinity from brine drainage and flushing 
     
    114114      !! ** Purpose :   initialization of ice salinity parameters 
    115115      !! 
    116       !! ** Method  :   Read the namice_sal namelist and check the parameter 
    117       !!              values called at the first timestep (nit000) 
     116      !! ** Method  :   Read the namthd_sal namelist and check the parameter 
     117      !!                values called at the first timestep (nit000) 
    118118      !! 
    119       !! ** input   :   Namelist namice_sal 
     119      !! ** input   :   Namelist namthd_sal 
    120120      !!------------------------------------------------------------------- 
    121121      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    122122      !! 
    123       NAMELIST/namice_sal/ ln_icedS , nn_icesal , rn_icesal, rn_sal_gd, rn_time_gd,   & 
     123      NAMELIST/namthd_sal/ nn_icesal, rn_icesal, rn_sal_gd, rn_time_gd,   & 
    124124         &                 rn_sal_fl, rn_time_fl, rn_simax , rn_simin  
    125125      !!------------------------------------------------------------------- 
    126126      ! 
    127       REWIND( numnam_ice_ref )              ! Namelist namice_sal in reference namelist : Ice salinity 
    128       READ  ( numnam_ice_ref, namice_sal, IOSTAT = ios, ERR = 901) 
    129 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_sal in reference namelist', lwp ) 
     127      REWIND( numnam_ice_ref )              ! Namelist namthd_sal in reference namelist : Ice salinity 
     128      READ  ( numnam_ice_ref, namthd_sal, IOSTAT = ios, ERR = 901) 
     129901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd_sal in reference namelist', lwp ) 
    130130      ! 
    131       REWIND( numnam_ice_cfg )              ! Namelist namice_sal in configuration namelist : Ice salinity 
    132       READ  ( numnam_ice_cfg, namice_sal, IOSTAT = ios, ERR = 902 ) 
    133 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_sal in configuration namelist', lwp ) 
    134       IF(lwm) WRITE ( numoni, namice_sal ) 
     131      REWIND( numnam_ice_cfg )              ! Namelist namthd_sal in configuration namelist : Ice salinity 
     132      READ  ( numnam_ice_cfg, namthd_sal, IOSTAT = ios, ERR = 902 ) 
     133902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namthd_sal in configuration namelist', lwp ) 
     134      IF(lwm) WRITE ( numoni, namthd_sal ) 
    135135      ! 
    136136      IF(lwp) THEN                           ! control print 
     
    138138         WRITE(numout,*) 'ice_thd_sal_init : Ice parameters for salinity ' 
    139139         WRITE(numout,*) '~~~~~~~~~~~~~~~~' 
    140          WRITE(numout,*) '   Namelist namice_sal' 
    141          WRITE(numout,*) '      activate gravity drainage and flushing (T) or not (F)   ln_icedS   = ', ln_icedS 
     140         WRITE(numout,*) '   Namelist namthd_sal:' 
    142141         WRITE(numout,*) '      switch for salinity                                     nn_icesal  = ', nn_icesal 
    143142         WRITE(numout,*) '      bulk salinity value if nn_icesal = 1                    rn_icesal  = ', rn_icesal 
     
    148147         WRITE(numout,*) '      Maximum tolerated ice salinity                          rn_simax   = ', rn_simax 
    149148         WRITE(numout,*) '      Minimum tolerated ice salinity                          rn_simin   = ', rn_simin 
    150       ENDIF 
    151       ! 
    152       IF( ln_icedS .AND. nn_icesal == 1 ) THEN 
    153          ln_icedS = .FALSE. 
    154          CALL ctl_warn('ln_icedS is set to false since constant ice salinity is chosen (nn_icesal=1)') 
    155149      ENDIF 
    156150      ! 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limmp.F90

    r8411 r8531  
    7979      !!      over sea ice 
    8080      !! 
    81       !! ** Method  :  Read the namicemp  namelist and check the melt pond   
     81      !! ** Method  :  Read the nammp  namelist and check the melt pond   
    8282      !!       parameter values called at the first timestep (nit000) 
    8383      !! 
    84       !! ** input   :   Namelist namicemp   
     84      !! ** input   :   Namelist nammp   
    8585      !!------------------------------------------------------------------- 
    8686      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    87       NAMELIST/namicemp/  ln_pnd, ln_pnd_rad, ln_pnd_fw, nn_pnd_scheme, rn_apnd, rn_hpnd 
     87      NAMELIST/nammp/  ln_pnd, ln_pnd_rad, ln_pnd_fw, nn_pnd_scheme, rn_apnd, rn_hpnd 
    8888      !!------------------------------------------------------------------- 
    8989 
    90       REWIND( numnam_ice_ref )              ! Namelist namicemp  in reference namelist : Melt Ponds   
    91       READ  ( numnam_ice_ref, namicemp, IOSTAT = ios, ERR = 901) 
    92 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicemp  in reference namelist', lwp ) 
    93  
    94       REWIND( numnam_ice_cfg )              ! Namelist namicemp  in configuration namelist : Melt Ponds 
    95       READ  ( numnam_ice_cfg, namicemp, IOSTAT = ios, ERR = 902 ) 
    96 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicemp in configuration namelist', lwp ) 
    97       IF(lwm) WRITE ( numoni, namicemp ) 
     90      REWIND( numnam_ice_ref )              ! Namelist nammp  in reference namelist : Melt Ponds   
     91      READ  ( numnam_ice_ref, nammp, IOSTAT = ios, ERR = 901) 
     92901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammp  in reference namelist', lwp ) 
     93 
     94      REWIND( numnam_ice_cfg )              ! Namelist nammp  in configuration namelist : Melt Ponds 
     95      READ  ( numnam_ice_cfg, nammp, IOSTAT = ios, ERR = 902 ) 
     96902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammp in configuration namelist', lwp ) 
     97      IF(lwm) WRITE ( numoni, nammp ) 
    9898       
    9999      IF(lwp) THEN                        ! control print 
Note: See TracChangeset for help on using the changeset viewer.