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

Changeset 8534


Ignore:
Timestamp:
2017-09-18T16:54:04+02:00 (7 years ago)
Author:
clem
Message:

changes in style - part6 - pure cosmetics

Location:
branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3
Files:
6 added
6 deleted
23 edited

Legend:

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

    r8531 r8534  
    11MODULE ice 
    22   !!====================================================================== 
    3    !!                        ***  MODULE ice  *** 
    4    !! LIM-3 Sea Ice physics:  diagnostics variables of ice defined in memory 
    5    !!===================================================================== 
     3   !!                        ***  MODULE  ice  *** 
     4   !!   sea-ice:  ice variables defined in memory 
     5   !!====================================================================== 
    66   !! History :  3.0  ! 2008-03  (M. Vancoppenolle) original code LIM-3 
    77   !!            4.0  ! 2011-02  (G. Madec) dynamical allocation 
     
    99#if defined key_lim3 
    1010   !!---------------------------------------------------------------------- 
    11    !!   'key_lim3'                                      LIM-3 sea-ice model 
     11   !!   'key_lim3'                                       ESIM sea-ice model 
    1212   !!---------------------------------------------------------------------- 
    1313   USE in_out_manager ! I/O manager 
     
    150150   !!===================================================================== 
    151151 
    152    !!-------------------------------------------------------------------------- 
     152   !!---------------------------------------------------------------------- 
    153153   !! * Share Module variables 
    154    !!-------------------------------------------------------------------------- 
     154   !!---------------------------------------------------------------------- 
    155155   !                                     !!** ice-generic parameters namelist (nampar) ** 
    156156   INTEGER           , PUBLIC ::   jpl             !: number of ice  categories  
     
    308308   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ftr_ice        !: transmitted solar radiation under ice 
    309309 
    310    !!-------------------------------------------------------------------------- 
     310   !!---------------------------------------------------------------------- 
    311311   !! * Ice global state variables 
    312    !!-------------------------------------------------------------------------- 
     312   !!---------------------------------------------------------------------- 
    313313   !! Variables defined for each ice category 
    314314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_i      !: Ice thickness (m) 
     
    356356   ! END MV MP 2016 
    357357 
    358    !!-------------------------------------------------------------------------- 
     358   !!---------------------------------------------------------------------- 
    359359   !! * Moments for advection 
    360    !!-------------------------------------------------------------------------- 
     360   !!---------------------------------------------------------------------- 
    361361   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   sxopw, syopw, sxxopw, syyopw, sxyopw   !: open water in sea ice 
    362362   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxice, syice, sxxice, syyice, sxyice   !: ice thickness  
     
    372372   ! END MV MP 2016 
    373373 
    374    !!-------------------------------------------------------------------------- 
     374   !!---------------------------------------------------------------------- 
    375375   !! * Old values of global variables 
    376    !!-------------------------------------------------------------------------- 
     376   !!---------------------------------------------------------------------- 
    377377   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, ht_s_b, ht_i_b  !: snow and ice volumes/thickness 
    378378   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, smv_i_b, oa_i_b        !: 
     
    382382   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i_b                        !: ice concentration (total) 
    383383             
    384    !!-------------------------------------------------------------------------- 
     384   !!---------------------------------------------------------------------- 
    385385   !! * Ice thickness distribution variables 
    386    !!-------------------------------------------------------------------------- 
     386   !!---------------------------------------------------------------------- 
    387387   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_max         !: Boundary of ice thickness categories in thickness space 
    388388   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_mean        !: Mean ice thickness in catgories  
    389389   ! 
    390    !!-------------------------------------------------------------------------- 
     390   !!---------------------------------------------------------------------- 
    391391   !! * Ice diagnostics 
    392    !!-------------------------------------------------------------------------- 
     392   !!---------------------------------------------------------------------- 
    393393   ! thd refers to changes induced by thermodynamics 
    394394   ! trp   ''         ''     ''       advection (transport of ice) 
     
    406406 
    407407   ! 
    408    !!-------------------------------------------------------------------------- 
     408   !!---------------------------------------------------------------------- 
    409409   !! * SIMIP extra diagnostics 
    410    !!-------------------------------------------------------------------------- 
     410   !!---------------------------------------------------------------------- 
    411411   ! Extra sea ice diagnostics to address the data request 
    412412   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   t_si          !: Temperature at Snow-ice interface (K)  
     
    541541#else 
    542542   !!---------------------------------------------------------------------- 
    543    !!   Default option         Empty module            NO LIM sea-ice model 
     543   !!   Default option         Empty module           NO ESIM sea-ice model 
    544544   !!---------------------------------------------------------------------- 
    545545#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/ice1D.F90

    r8518 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE ice1D  *** 
    4    !! LIM sea-ice :   Ice thermodynamics in 1D 
     4   !! sea-ice :   Ice thermodynamics variables in 1D 
    55   !!===================================================================== 
    66   !! History :  3.0  !  2002-11  (C. Ethe)  F90: Free form and module 
     
    88#if defined key_lim3 
    99   !!---------------------------------------------------------------------- 
    10    !!   'key_lim3'                                       LIM3 sea-ice model 
     10   !!   'key_lim3'                                       ESIM sea-ice model 
    1111   !!---------------------------------------------------------------------- 
    1212   USE ice     , ONLY :   nlay_i, nlay_s, jpl   ! number of ice/snow layers and categories 
     
    223223#else 
    224224   !!---------------------------------------------------------------------- 
    225    !!   Default option :         Empty module          NO LIM sea-ice model 
     225   !!   Default option :         Empty module         NO ESIM sea-ice model 
    226226   !!---------------------------------------------------------------------- 
    227227CONTAINS 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icealb.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE  icealb  *** 
    4    !! Ocean forcing:  bulk thermohaline forcing of the ice 
     4   !! Atmospheric forcing:  Albedo over sea ice 
    55   !!===================================================================== 
    66   !! History :  4.0  ! 2017-07  (C. Rousset) Split ice and ocean albedos 
     
    88#if defined key_lim3 
    99   !!---------------------------------------------------------------------- 
    10    !!   'key_lim3'                                    LIM 3.0 sea-ice model 
    11    !!---------------------------------------------------------------------- 
    12    !!   ice_alb       : albedo for ice (clear and overcast skies) 
    13    !!   alb_init      : initialisation of albedo computation 
     10   !!   'key_lim3'                                       ESIM sea-ice model 
     11   !!---------------------------------------------------------------------- 
     12   !!   ice_alb        : albedo for ice (clear and overcast skies) 
     13   !!   ice_alb_init   : initialisation of albedo computation 
    1414   !!---------------------------------------------------------------------- 
    1515   USE ice, ONLY: jpl ! sea-ice: number of categories 
     
    1919   USE lib_mpp        ! MPP library 
    2020   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     21   USE timing         ! Timing 
    2122 
    2223   IMPLICIT NONE 
     
    109110      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zafrac_pnd      ! relative ice fraction (effective) 
    110111      !!--------------------------------------------------------------------- 
    111  
     112      ! 
     113      IF( nn_timing == 1 )   CALL timing_start('icealb') 
     114      ! 
    112115      !----------------------------------------------------- 
    113116      !  Snow-free albedo (no ice thickness dependence yet) 
     
    147150         ENDIF  
    148151         ! 
    149 !!gm: optimization ( rn_alb_smlt - rn_alb_imlt ) * r1_c2 can be computed one for all  
    150 !!gm  before the DO-loop below 
    151152         DO jl = 1, jpl 
    152153            DO jj = 1, jpj 
     
    301302      END SELECT 
    302303      ! 
     304      IF( nn_timing == 1 )   CALL timing_stop('icealb') 
     305      ! 
    303306   END SUBROUTINE ice_alb 
    304307 
     
    343346#else 
    344347   !!---------------------------------------------------------------------- 
    345    !!   Default option           Dummy module      NO LIM 3.0 sea-ice model 
     348   !!   Default option           Dummy module         NO ESIM sea-ice model 
    346349   !!---------------------------------------------------------------------- 
    347350#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icecor.F90

    r8517 r8534  
    22   !!====================================================================== 
    33   !!                     ***  MODULE  icecor  *** 
    4    !!   LIM-3 : Update of sea-ice global variables at the end of the time step 
     4   !!   ESIM : Corrections on sea-ice variables at the end of the time step 
    55   !!====================================================================== 
    66   !! History :  3.0  !  2006-04  (M. Vancoppenolle) Original code 
     
    99#if defined key_lim3 
    1010   !!---------------------------------------------------------------------- 
    11    !!   'key_lim3'                                       LIM3 sea-ice model 
     11   !!   'key_lim3'                                       ESIM sea-ice model 
    1212   !!---------------------------------------------------------------------- 
    13    !!    ice_cor      : computes update of sea-ice global variables from trend terms 
     13   !!    ice_cor      : corrections on sea-ice variables 
    1414   !!---------------------------------------------------------------------- 
    1515   USE dom_oce        ! ocean domain 
     
    2222   ! 
    2323   USE in_out_manager ! I/O manager 
    24    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
    25    USE lbclnk         ! lateral boundary condition - MPP link 
     24   USE iom            ! I/O manager library 
    2625   USE lib_mpp        ! MPP library 
     26   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     27   USE lbclnk         ! lateral boundary conditions (or mpp links) 
    2728   USE timing         ! Timing 
    28    USE iom            ! 
    2929 
    3030   IMPLICIT NONE 
     
    4747      !!                
    4848      !! ** Purpose :   Computes corrections on sea-ice global variables at  
    49       !!              the end of the dynamics. 
     49      !!              the end of the dynamics (kn=1) and thermodynamics (kn=2) 
    5050      !!---------------------------------------------------------------------- 
    5151      INTEGER, INTENT(in) ::   kt    ! number of iteration 
     
    184184#else 
    185185   !!---------------------------------------------------------------------- 
    186    !!   Default option           Dummy module      NO LIM 3.0 sea-ice model 
     186   !!   Default option           Dummy module         NO ESIM sea-ice model 
    187187   !!---------------------------------------------------------------------- 
    188188#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icectl.F90

    r8517 r8534  
    22   !!====================================================================== 
    33   !!                     ***  MODULE  icectl  *** 
    4    !!   LIM-3 : control and printing 
     4   !!   sea-ice : controls and prints 
    55   !!====================================================================== 
    66   !! History :  3.5  !  2015-01  (M. Vancoppenolle) Original code 
     
    99#if defined key_lim3 
    1010   !!---------------------------------------------------------------------- 
    11    !!   'key_lim3'                                       LIM3 sea-ice model 
    12    !!---------------------------------------------------------------------- 
    13    !!    ice_ctl   : control prints in case of crash 
    14    !!    ice_prt   : ice control print at a given grid point 
    15    !!    ice_prt3D : control prints of ice arrays 
    16    !!---------------------------------------------------------------------- 
     11   !!   'key_lim3'                                       ESIM sea-ice model 
     12   !!---------------------------------------------------------------------- 
     13   !!    ice_cons_hsm     : conservation tests on heat, salt and mass 
     14   !!    ice_cons_final   : conservation tests on heat, salt and mass at end of time step 
     15   !!    ice_ctl          : control prints in case of crash 
     16   !!    ice_prt          : control prints at a given grid point 
     17   !!    ice_prt3D        : control prints of ice arrays 
     18   !!---------------------------------------------------------------------- 
     19   USE phycst         ! physical constants 
    1720   USE oce            ! ocean dynamics and tracers 
    1821   USE dom_oce        ! ocean space and time domain 
    19    USE ice            ! LIM-3: ice variables 
    20    USE ice1D          ! LIM-3: thermodynamical variables 
     22   USE ice            ! sea-ice: variables 
     23   USE ice1D          ! sea-ice: thermodynamics variables 
    2124   USE sbc_oce        ! Surface boundary condition: ocean fields 
    2225   USE sbc_ice        ! Surface boundary condition: ice   fields 
    23    USE phycst         ! Define parameters for the routines 
    2426   ! 
     27   USE in_out_manager ! I/O manager 
    2528   USE lib_mpp        ! MPP library 
     29   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
    2630   USE timing         ! Timing 
    27    USE in_out_manager ! I/O manager 
    2831   USE prtctl         ! Print control 
    29    USE lib_fortran    !  
    3032 
    3133   IMPLICIT NONE 
     
    4850 
    4951   SUBROUTINE ice_cons_hsm( icount, cd_routine, pdiag_v, pdiag_s, pdiag_t, pdiag_fv, pdiag_fs, pdiag_ft ) 
    50       !!---------------------------------------------------------------------- 
     52      !!------------------------------------------------------------------- 
    5153      !!                       ***  ROUTINE ice_cons_hsm *** 
    5254      !! 
     
    6062      !!              For salt and heat thresholds, ice is considered to have a salinity of 10  
    6163      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)  
    62       !!---------------------------------------------------------------------- 
     64      !!------------------------------------------------------------------- 
    6365      INTEGER         , INTENT(in)    ::   icount        ! called at: =0 the begining of the routine, =1  the end 
    6466      CHARACTER(len=*), INTENT(in)    ::   cd_routine    ! name of the routine 
     
    7072      REAL(wp) ::   zarea, zv_sill, zs_sill, zt_sill 
    7173      REAL(wp), PARAMETER ::   zconv = 1.e-9 ! convert W to GW and kg to Mt 
    72       !!---------------------------------------------------------------------- 
     74      !!------------------------------------------------------------------- 
    7375      ! 
    7476      IF( icount == 0 ) THEN 
     
    143145            IF ( ABS( zs   ) > zs_sill )   WRITE(numout,*) 'violation saline [psu*Mt/day] (',cd_routine,') = ',zs 
    144146            IF ( ABS( zt   ) > zt_sill )   WRITE(numout,*) 'violation enthalpy [GW]       (',cd_routine,') = ',zt 
    145             IF ( ABS(zvtrp ) > zv_sill .AND. cd_routine == 'iceadv' ) THEN 
     147            IF ( ABS(zvtrp ) > zv_sill .AND. cd_routine == 'icedyn_adv' ) THEN 
    146148                                           WRITE(numout,*) 'violation vtrp [Mt/day]       (',cd_routine,') = ',zvtrp 
    147149                                           WRITE(numout,*) 'violation etrp [GW]           (',cd_routine,') = ',zetrp 
    148150            ENDIF 
    149151            IF ( zvmin < -epsi10 )         WRITE(numout,*) 'violation v_i<0  [m]          (',cd_routine,') = ',zvmin 
    150             IF ( zamax > MAX(rn_amax_n,rn_amax_s) + epsi10 .AND. cd_routine /= 'iceadv' .AND. cd_routine /= 'icerdgrft' )  & 
     152            IF ( zamax > MAX(rn_amax_n,rn_amax_s)+epsi10 .AND. cd_routine /= 'icedyn_adv' .AND. cd_routine /= 'icedyn_rdgrft' )  & 
    151153               &                           WRITE(numout,*) 'violation a_i>amax            (',cd_routine,') = ',zamax 
    152154            IF ( zamin < -epsi10 )         WRITE(numout,*) 'violation a_i<0               (',cd_routine,') = ',zamin 
     
    159161 
    160162   SUBROUTINE ice_cons_final( cd_routine ) 
    161       !!---------------------------------------------------------------------- 
     163      !!------------------------------------------------------------------- 
    162164      !!                     ***  ROUTINE ice_cons_final *** 
    163165      !! 
     
    170172      !!              For salt and heat thresholds, ice is considered to have a salinity of 10  
    171173      !!              and a heat content of 3e5 J/kg (=latent heat of fusion)  
    172       !!---------------------------------------------------------------------- 
     174      !!------------------------------------------------------------------- 
    173175      CHARACTER(len=*), INTENT(in)    :: cd_routine    ! name of the routine 
    174176      REAL(wp)                        :: zhfx, zsfx, zvfx 
    175177      REAL(wp)                        :: zarea, zv_sill, zs_sill, zt_sill 
    176178      REAL(wp), PARAMETER             :: zconv = 1.e-9 ! convert W to GW and kg to Mt 
    177       !!---------------------------------------------------------------------- 
     179      !!------------------------------------------------------------------- 
    178180 
    179181      ! water flux 
     
    204206    
    205207   SUBROUTINE ice_ctl( kt ) 
    206       !!----------------------------------------------------------------------- 
     208      !!------------------------------------------------------------------- 
    207209      !!                   ***  ROUTINE ice_ctl ***  
    208210      !!                  
     
    415417    
    416418   SUBROUTINE ice_prt( kt, ki, kj, kn, cd1 ) 
    417       !!----------------------------------------------------------------------- 
     419      !!------------------------------------------------------------------- 
    418420      !!                   ***  ROUTINE ice_prt ***  
    419421      !!                  
     
    596598 
    597599   SUBROUTINE ice_prt3D( cd_routine ) 
    598       !!--------------------------------------------------------------------------------------------------------- 
    599       !!                                   ***  ROUTINE ice_prt3D *** 
     600      !!------------------------------------------------------------------- 
     601      !!                  ***  ROUTINE ice_prt3D *** 
    600602      !! 
    601603      !! ** Purpose : CTL prints of ice arrays in case ln_ctl is activated  
    602604      !! 
    603       !!--------------------------------------------------------------------------------------------------------- 
     605      !!------------------------------------------------------------------- 
    604606      CHARACTER(len=*), INTENT(in)  :: cd_routine    ! name of the routine 
    605607      INTEGER                       :: jk, jl        ! dummy loop indices 
     
    664666 
    665667#else 
    666    !!-------------------------------------------------------------------------- 
    667    !!   Default option         Empty Module               No LIM3 sea-ice model 
    668    !!-------------------------------------------------------------------------- 
     668   !!---------------------------------------------------------------------- 
     669   !!   Default option         Empty Module           No ESIM sea-ice model 
     670   !!---------------------------------------------------------------------- 
    669671#endif 
    670672 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedia.F90

    r8531 r8534  
    1515   !!    ice_dia_rst  : read/write budgets restart 
    1616   !!---------------------------------------------------------------------- 
    17    USE ice            ! LIM-3: sea-ice variable 
    1817   USE dom_oce        ! ocean domain 
    1918   USE phycst         ! physical constant 
    2019   USE daymod         ! model calendar 
    2120   USE sbc_oce , ONLY : sfx, nn_fsbc   ! surface boundary condition: ocean fields 
    22    USE icerst         ! ice restart 
     21   USE ice            ! sea-ice: variables 
     22   USE icerst         ! sea-ice: restart 
    2323   ! 
    2424   USE in_out_manager ! I/O manager 
     25   USE iom            ! I/O manager library 
    2526   USE lib_mpp        ! MPP library 
    26    USE timing         ! preformance summary 
    27    USE iom            ! I/O manager 
    28    USE lib_fortran    ! glob_sum 
     27   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     28   USE timing         ! Timing 
    2929 
    3030   IMPLICIT NONE 
     
    279279#else 
    280280   !!---------------------------------------------------------------------- 
    281    !!   Default option :         Empty module          NO LIM sea-ice model 
     281   !!   Default option :         Empty module         NO ESIM sea-ice model 
    282282   !!---------------------------------------------------------------------- 
    283283#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedyn.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                     ***  MODULE  icedyn  *** 
    4    !!   Sea-Ice dynamics :  
     4   !!   Sea-Ice dynamics : master routine for sea ice dynamics  
    55   !!====================================================================== 
    66   !! history :  4.0  ! 2017-09  (C. Rousset)  original code  
     
    88#if defined key_lim3 
    99   !!---------------------------------------------------------------------- 
    10    !!   'key_lim3'                                       LIM3 sea-ice model 
     10   !!   'key_lim3'                                       ESIM sea-ice model 
    1111   !!---------------------------------------------------------------------- 
    1212   !!   ice_dyn       : dynamics of sea ice 
    13    !!   ice_dyn_init  : initialisation of sea-ice dynamics 
     13   !!   ice_dyn_init  : initialization and namelist read 
    1414   !!---------------------------------------------------------------------- 
    1515   USE phycst         ! physical constants 
    1616   USE dom_oce        ! ocean space and time domain 
    1717   USE ice            ! sea-ice: variables 
    18    USE icerhg         ! sea-ice: rheology 
    19    USE iceadv         ! sea-ice: advection 
    20    USE icerdgrft      ! sea-ice: ridging/rafting 
     18   USE icedyn_rhg     ! sea-ice: rheology 
     19   USE icedyn_adv     ! sea-ice: advection 
     20   USE icedyn_rdgrft  ! sea-ice: ridging/rafting 
    2121   USE icecor         ! sea-ice: corrections 
    2222   USE icevar         ! sea-ice: operations 
    2323   ! 
    24    USE lbclnk         ! lateral boundary conditions - MPP exchanges 
     24   USE in_out_manager ! I/O manager 
     25   USE iom            ! I/O manager library 
    2526   USE lib_mpp        ! MPP library 
    26    USE in_out_manager ! I/O manager 
    27    USE iom            ! I/O manager 
    28    USE lib_fortran    ! glob_sum 
     27   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     28   USE lbclnk         ! lateral boundary conditions (or mpp links) 
    2929   USE timing         ! Timing 
    3030 
     
    7373      !!-------------------------------------------------------------------- 
    7474      ! 
    75       IF( nn_timing == 1 )  CALL timing_start('icedyn') 
     75      IF( nn_timing == 1 )   CALL timing_start('icedyn') 
    7676      ! 
    7777      IF( kt == nit000 .AND. lwp ) THEN 
     
    104104 
    105105      CASE ( np_dynFULL )          !==  all dynamical processes  ==! 
    106          CALL ice_rhg   ( kt )                            ! -- rheology   
    107          CALL ice_adv   ( kt )   ;   CALL Hbig( zhmax )   ! -- advection of ice + correction on ice thickness 
    108          CALL ice_rdgrft( kt )                            ! -- ridging/rafting  
    109          CALL ice_cor   ( kt , 1 )                        ! -- Corrections 
     106         CALL ice_dyn_rhg   ( kt )                            ! -- rheology   
     107         CALL ice_dyn_adv   ( kt )   ;   CALL Hbig( zhmax )   ! -- advection of ice + correction on ice thickness 
     108         CALL ice_dyn_rdgrft( kt )                            ! -- ridging/rafting  
     109         CALL ice_cor       ( kt , 1 )                        ! -- Corrections 
    110110 
    111111      CASE ( np_dynRHGADV1 )       !==  no ridge/raft ==!   (mono cat. case 2) 
    112          CALL ice_rhg   ( kt )                            ! -- rheology   
    113          CALL ice_adv   ( kt )                            ! -- advection of ice 
    114          CALL Hpiling                                     ! -- simple pile-up (replaces ridging/rafting) 
    115          CALL ice_cor   ( kt , 1 )                        ! -- Corrections 
     112         CALL ice_dyn_rhg   ( kt )                            ! -- rheology   
     113         CALL ice_dyn_adv   ( kt )                            ! -- advection of ice 
     114         CALL Hpiling                                         ! -- simple pile-up (replaces ridging/rafting) 
     115         CALL ice_cor       ( kt , 1 )                        ! -- Corrections 
    116116 
    117117      CASE ( np_dynRHGADV2 )       !==  no ridge/raft & no corrections ==! 
    118          CALL ice_rhg   ( kt )                            ! -- rheology   
    119          CALL ice_adv   ( kt )                            ! -- advection of ice 
    120          CALL Hpiling                                     ! -- simple pile-up (replaces ridging/rafting) 
     118         CALL ice_dyn_rhg   ( kt )                            ! -- rheology   
     119         CALL ice_dyn_adv   ( kt )                            ! -- advection of ice 
     120         CALL Hpiling                                         ! -- simple pile-up (replaces ridging/rafting) 
    121121 
    122122      CASE ( np_dynADV )           !==  pure advection ==!   (prescribed velocities) 
     
    125125         !!CALL RANDOM_NUMBER(u_ice(:,:)) 
    126126         !!CALL RANDOM_NUMBER(v_ice(:,:)) 
    127          CALL ice_adv   ( kt )                            ! -- advection of ice 
     127         CALL ice_dyn_adv   ( kt )                            ! -- advection of ice 
    128128 
    129129      END SELECT 
     
    269269      IF( .NOT. ln_landfast )   tau_icebfr(:,:) = 0._wp 
    270270      ! 
    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 
     271      CALL ice_dyn_rdgrft_init          ! set ice ridging/rafting parameters 
     272      CALL ice_dyn_rhg_init             ! set ice rheology parameters 
     273      CALL ice_dyn_adv_init             ! set ice advection parameters 
    274274      ! 
    275275   END SUBROUTINE ice_dyn_init 
     
    277277#else 
    278278   !!---------------------------------------------------------------------- 
    279    !!   Default option         Empty module          NO LIM-3 sea-ice model 
     279   !!   Default option         Empty module           NO ESIM sea-ice model 
    280280   !!---------------------------------------------------------------------- 
    281281#endif  
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceforcing.F90

    r8531 r8534  
    88#if defined key_lim3 
    99   !!---------------------------------------------------------------------- 
    10    !!   'key_lim3' :                                  LIM 3.0 sea-ice model 
     10   !!   'key_lim3' :                                     ESIM sea-ice model 
    1111   !!---------------------------------------------------------------------- 
    1212   USE oce            ! ocean dynamics and tracers 
    1313   USE dom_oce        ! ocean space and time domain 
    14    USE ice            ! sea-ice variables 
     14   USE ice            ! sea-ice: variables 
    1515   USE sbc_oce        ! Surface boundary condition: ocean fields 
    1616   USE sbc_ice        ! Surface boundary condition: ice   fields 
    17    USE usrdef_sbc     ! user defined: surface boundary condition 
     17   USE usrdef_sbc     ! Surface boundary condition: user defined 
    1818   USE sbcblk         ! Surface boundary condition: bulk 
    1919   USE sbccpl         ! Surface boundary condition: coupled interface 
    20    USE icealb         ! ice albedo 
     20   USE icealb         ! sae-ice: albedo 
    2121   ! 
     22   USE in_out_manager ! I/O manager 
    2223   USE iom            ! I/O manager library 
    23    USE in_out_manager ! I/O manager 
    24    USE lbclnk         ! lateral boundary condition - MPP link 
    2524   USE lib_mpp        ! MPP library 
    26    USE lib_fortran    ! 
     25   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     26   USE lbclnk         ! lateral boundary conditions (or mpp links) 
    2727   USE timing         ! Timing 
    2828 
     
    4444 
    4545   SUBROUTINE ice_forcing_tau( kt, ksbc, utau_ice, vtau_ice ) 
    46       !!--------------------------------------------------------------------- 
     46      !!------------------------------------------------------------------- 
    4747      !!                  ***  ROUTINE ice_forcing_tau  *** 
    4848      !! 
     
    5151      !! ** Action  : It provides the following fields: 
    5252      !!              utau_ice, vtau_ice : surface ice stress (U- & V-points) [N/m2] 
    53       !!--------------------------------------------------------------------- 
     53      !!------------------------------------------------------------------- 
    5454      INTEGER, INTENT(in) ::   kt      ! ocean time step 
    5555      INTEGER, INTENT(in) ::   ksbc    ! type of sbc flux ( 1 = user defined formulation,  
     
    6060      INTEGER  ::   ji, jj                 ! dummy loop index 
    6161      REAL(wp), DIMENSION(jpi,jpj) ::   zutau_ice, zvtau_ice  
    62       !!---------------------------------------------------------------------- 
    63  
    64       IF( nn_timing == 1 )   CALL timing_start('ice_forcing_tau') 
     62      !!------------------------------------------------------------------- 
     63 
     64      IF( nn_timing == 1 )   CALL timing_start('ice_forcing') 
    6565 
    6666      IF( kt == nit000 .AND. lwp ) THEN 
     
    8787      ENDIF 
    8888 
    89       IF( nn_timing == 1 )   CALL timing_stop('ice_forcing_tau') 
     89      IF( nn_timing == 1 )   CALL timing_stop('ice_forcing') 
    9090      ! 
    9191   END SUBROUTINE ice_forcing_tau 
     
    9393    
    9494   SUBROUTINE ice_forcing_flx( kt, ksbc ) 
    95       !!--------------------------------------------------------------------- 
     95      !!------------------------------------------------------------------- 
    9696      !!                  ***  ROUTINE ice_forcing_flx  *** 
    9797      !! 
     
    112112      !!                tprecip                                  = total  precipitation                          [Kg/m2/s] 
    113113      !!                alb_ice                                  = albedo above sea ice 
    114       !!--------------------------------------------------------------------- 
     114      !!------------------------------------------------------------------- 
    115115      INTEGER, INTENT(in) ::   kt     ! ocean time step 
    116116      INTEGER, INTENT(in) ::   ksbc   ! flux formulation (user defined, bulk or Pure Coupled) 
     
    119119      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalb_os, zalb_cs  ! ice albedo under overcast/clear sky 
    120120      REAL(wp), DIMENSION(jpi,jpj)     ::   zalb              ! 2D workspace 
    121       !!---------------------------------------------------------------------- 
    122       ! 
    123       IF( nn_timing == 1 )   CALL timing_start('ice_forcing_flx') 
     121      !!-------------------------------------------------------------------- 
     122      ! 
     123      IF( nn_timing == 1 )   CALL timing_start('ice_forcing') 
    124124 
    125125      IF( kt == nit000 .AND. lwp ) THEN 
     
    164164      ENDIF 
    165165      ! 
    166       IF( nn_timing == 1 )   CALL timing_stop('ice_forcing_flx') 
     166      IF( nn_timing == 1 )   CALL timing_stop('ice_forcing') 
    167167      ! 
    168168   END SUBROUTINE ice_forcing_flx 
     
    170170 
    171171   SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_iceflx ) 
    172       !!--------------------------------------------------------------------- 
     172      !!------------------------------------------------------------------- 
    173173      !!                  ***  ROUTINE ice_flx_dist  *** 
    174174      !! 
     
    184184      !!                                                 using T-ice and albedo sensitivity 
    185185      !!                =  2  Redistribute a single flux over categories 
    186       !!--------------------------------------------------------------------- 
     186      !!------------------------------------------------------------------- 
    187187      INTEGER                   , INTENT(in   ) ::   k_iceflx   ! redistributor 
    188188      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   ptn_ice    ! ice surface temperature 
     
    206206      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   ztem_m    ! Mean temperature over all categories 
    207207      !!---------------------------------------------------------------------- 
    208       ! 
    209       IF( nn_timing == 1 )  CALL timing_start('ice_flx_dist') 
    210208      ! 
    211209      WHERE ( at_i (:,:) > 0._wp )   ; z1_at_i(:,:) = 1._wp / at_i (:,:) 
     
    253251         ! 
    254252      END SELECT 
    255       ! 
    256       IF( nn_timing == 1 )  CALL timing_stop('ice_flx_dist') 
    257253      ! 
    258254   END SUBROUTINE ice_flx_dist 
     
    315311#else 
    316312   !!---------------------------------------------------------------------- 
    317    !!   Default option :         Empty module          NO LIM sea-ice model 
     313   !!   Default option :         Empty module         NO ESIM sea-ice model 
    318314   !!---------------------------------------------------------------------- 
    319315#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceistate.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                     ***  MODULE  iceistate  *** 
    4    !!              Initialisation of diagnostics ice variables 
     4   !!   sea-ice : Initialization of ice variables 
    55   !!====================================================================== 
    66   !! History :  2.0  ! 2004-01 (C. Ethe, G. Madec)  Original code 
     
    1212#if defined key_lim3 
    1313   !!---------------------------------------------------------------------- 
    14    !!   'key_lim3'                                       LIM3 sea-ice model 
     14   !!   'key_lim3'                                       ESIM sea-ice model 
    1515   !!---------------------------------------------------------------------- 
    1616   !!   ice_istate       :  initialization of diagnostics ice variables 
    1717   !!   ice_istate_init  :  initialization of ice state and namelist read 
    1818   !!---------------------------------------------------------------------- 
    19    USE par_oce        ! ocean parameters 
    2019   USE phycst         ! physical constant 
    2120   USE oce            ! dynamics and tracers variables 
     
    2928   ! 
    3029   USE in_out_manager ! I/O manager 
     30   USE iom            ! I/O manager library 
    3131   USE lib_mpp        ! MPP library 
    32    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     32   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
    3333   USE fldread        ! read input fields 
    34    USE iom 
    3534 
    3635   IMPLICIT NONE 
     
    8281      !!                values in the namelist             
    8382      !! 
    84       !! ** Steps   :   1) Read namelist 
    85       !!                2) Basal temperature; ice and hemisphere masks 
     83      !! ** Steps   :   1) Set initial surface and basal temperatures 
     84      !!                2) Recompute or read sea ice state variables 
    8685      !!                3) Fill in the ice thickness distribution using gaussian 
    8786      !!                4) Fill in space-dependent arrays for state variables 
    88       !!                5) Diagnostic arrays 
    89       !!                6) Lateral boundary conditions 
     87      !!                5) snow-ice mass computation 
     88      !!                6) store before fields 
    9089      !! 
    9190      !! ** Notes   : o_i, t_su, t_s, t_i, s_i must be filled everywhere, even 
     
    109108 
    110109      !-------------------------------------------------------------------- 
    111       ! 1) Read namelist 
     110      ! 1) Set surface and bottom temperatures to initial values 
    112111      !-------------------------------------------------------------------- 
    113112      ! 
     
    122121      t_bo(:,:) = ( t_bo(:,:) + rt0 ) * tmask(:,:,1)  
    123122 
    124       !-------------------------------------------------------------------- 
    125       ! 2) Initialization of sea ice state variables 
    126       !-------------------------------------------------------------------- 
    127123      IF( ln_iceini ) THEN 
     124         !----------------------------------------------------------- 
     125         ! 2) Compute or read sea ice variables ===> single category 
     126         !----------------------------------------------------------- 
    128127         ! 
    129          IF( ln_iceini_file )THEN 
    130          ! 
     128         !                             !---------------! 
     129         IF( ln_iceini_file )THEN      ! Read a file   ! 
     130            !                          !---------------! 
     131            ! 
    131132            zht_i_ini(:,:)  = si(jp_hti)%fnow(:,:,1) 
    132133            zht_s_ini(:,:)  = si(jp_hts)%fnow(:,:,1) 
     
    139140            ELSEWHERE                       ; zswitch(:,:) = 0._wp 
    140141            END WHERE 
     142            zvt_i_ini(:,:) = zht_i_ini(:,:) * zat_i_ini(:,:) 
    141143            ! 
    142          ELSE ! ln_iceini_file = F 
    143  
    144             !-------------------------------------------------------------------- 
    145             ! 3) Basal temperature, ice mask 
    146             !-------------------------------------------------------------------- 
    147             ! no ice if sst <= t-freez + ttest 
     144         !                             !---------------! 
     145         ELSE                          ! Read namelist ! 
     146            !                          !---------------! 
     147 
     148           ! no ice if sst <= t-freez + ttest 
    148149            WHERE( ( sst_m(:,:) - (t_bo(:,:) - rt0) ) * tmask(:,:,1) >= rn_thres_sst ) ; zswitch(:,:) = 0._wp  
    149150            ELSEWHERE                                                                  ; zswitch(:,:) = tmask(:,:,1) 
    150151            END WHERE 
    151152 
    152             !----------------------------- 
    153             ! 3.1) Hemisphere-dependent arrays 
    154             !----------------------------- 
    155153            ! assign initial thickness, concentration, snow depth and salinity to an hemisphere-dependent array 
    156154            WHERE( ff_t(:,:) >= 0._wp ) 
     
    169167               ztm_i_ini(:,:) = rn_tmi_ini_s * zswitch(:,:) 
    170168            END WHERE 
     169            zvt_i_ini(:,:) = zht_i_ini(:,:) * zat_i_ini(:,:) 
    171170            ! 
    172          ENDIF ! ln_iceini_file 
     171         ENDIF 
    173172          
    174          zvt_i_ini(:,:) = zht_i_ini(:,:) * zat_i_ini(:,:)   ! ice volume 
    175          !--------------------------------------------------------------------- 
    176          ! 3.2) Distribute ice concentration and thickness into the categories 
    177          !--------------------------------------------------------------------- 
     173         !------------------------------------------------------------------ 
     174         ! 3) Distribute ice concentration and thickness into the categories 
     175         !------------------------------------------------------------------ 
    178176         ! a gaussian distribution for ice concentration is used 
    179177         ! then we check whether the distribution fullfills 
     
    187185               IF( zat_i_ini(ji,jj) > 0._wp .AND. zht_i_ini(ji,jj) > 0._wp )THEN 
    188186 
    189                   !--- jl0: most likely index where cc will be maximum 
     187                  ! find which category (jl0) the input ice thickness falls into 
    190188                  jl0 = jpl 
    191189                  DO jl = 1, jpl 
     
    196194                  END DO 
    197195                  ! 
    198                   ! initialisation of tests 
    199                   itest(:)  = 0 
    200                    
    201                   i_fill = jpl + 1                                             !==================================== 
    202                   DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )  ! iterative loop on i_fill categories 
    203                      ! iteration                                               !==================================== 
     196                  itest(:) = 0 
     197                  i_fill   = jpl + 1                                            !------------------------------------ 
     198                  DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )   ! iterative loop on i_fill categories 
     199                     !                                                          !------------------------------------ 
    204200                     i_fill = i_fill - 1 
    205  
    206                      ! initialisation of ice variables for each try 
     201                     ! 
    207202                     zh_i_ini(ji,jj,:) = 0._wp  
    208203                     za_i_ini(ji,jj,:) = 0._wp 
    209204                     itest(:) = 0 
    210205                     ! 
    211                      ! *** case very thin ice: fill only category 1 
    212                      IF ( i_fill == 1 ) THEN 
     206                     IF ( i_fill == 1 ) THEN      !-- case very thin ice: fill only category 1 
    213207                        zh_i_ini(ji,jj,1) = zht_i_ini(ji,jj) 
    214208                        za_i_ini(ji,jj,1) = zat_i_ini(ji,jj) 
    215  
    216                      ! *** case ice is thicker: fill categories >1 
    217                      ELSE 
    218  
    219                         ! Fill ice thicknesses in the (i_fill-1) cat by hmean  
     209                     ELSE                         !-- case ice is thicker: fill categories >1 
     210                        ! thickness 
    220211                        DO jl = 1, i_fill-1 
    221212                           zh_i_ini(ji,jj,jl) = hi_mean(jl) 
    222213                        END DO 
    223214                        ! 
    224                         !--- Concentrations 
     215                        ! concentration 
    225216                        za_i_ini(ji,jj,jl0) = zat_i_ini(ji,jj) / SQRT(REAL(jpl)) 
    226217                        DO jl = 1, i_fill - 1 
     
    230221                           ENDIF 
    231222                        END DO 
    232                         ! 
    233                         ! Concentration in the last (i_fill) category 
     223 
     224                        ! last category 
    234225                        za_i_ini(ji,jj,i_fill) = zat_i_ini(ji,jj) - SUM( za_i_ini(ji,jj,1:i_fill-1) ) 
    235  
    236                         ! Ice thickness in the last (i_fill) category 
    237226                        zV = SUM( za_i_ini(ji,jj,1:i_fill-1) * zh_i_ini(ji,jj,1:i_fill-1) ) 
    238227                        zh_i_ini(ji,jj,i_fill) = ( zvt_i_ini(ji,jj) - zV ) / MAX( za_i_ini(ji,jj,i_fill), epsi10 )  
     
    252241                        ENDIF 
    253242                        ! 
    254                      ENDIF ! case ice is thick or thin 
    255  
    256                      !--------------------- 
     243                     ENDIF 
     244 
    257245                     ! Compatibility tests 
    258                      !--------------------- 
    259                      ! Test 1: area conservation 
    260                      zconv = ABS( zat_i_ini(ji,jj) - SUM( za_i_ini(ji,jj,1:jpl) ) ) 
     246                     zconv = ABS( zat_i_ini(ji,jj) - SUM( za_i_ini(ji,jj,1:jpl) ) )           ! Test 1: area conservation 
    261247                     IF ( zconv < epsi06 ) itest(1) = 1 
    262248                      
    263                      ! Test 2: volume conservation 
    264                      zconv = ABS(       zat_i_ini(ji,jj)       * zht_i_ini(ji,jj)   & 
     249                     zconv = ABS(       zat_i_ini(ji,jj)       * zht_i_ini(ji,jj)   &         ! Test 2: volume conservation 
    265250                        &        - SUM( za_i_ini (ji,jj,1:jpl) * zh_i_ini (ji,jj,1:jpl) ) ) 
    266251                     IF ( zconv < epsi06 ) itest(2) = 1 
    267252                      
    268                      ! Test 3: thickness of the last category is in-bounds ? 
    269                      IF ( zh_i_ini(ji,jj,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1 
     253                     IF ( zh_i_ini(ji,jj,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1           ! Test 3: thickness of the last category is in-bounds ? 
    270254                      
    271                      ! Test 4: positivity of ice concentrations 
    272255                     itest(4) = 1 
    273256                     DO jl = 1, i_fill 
    274                         IF ( za_i_ini(ji,jj,jl) < 0._wp ) itest(4) = 0 
     257                        IF ( za_i_ini(ji,jj,jl) < 0._wp ) itest(4) = 0                        ! Test 4: positivity of ice concentrations 
    275258                     END DO 
    276                      !                                      !============================ 
    277                   END DO                                    ! end iteration on categories 
    278                   !                                         !============================ 
     259                     !                                                          !---------------------------- 
     260                  END DO                                                        ! end iteration on categories 
     261                  !                                                             !---------------------------- 
    279262                  ! 
    280263                  IF( lwp .AND. SUM(itest) /= 4 ) THEN  
     
    288271                  ENDIF 
    289272                
    290                ENDIF !  zat_i_ini(ji,jj) > 0._wp .AND. zht_i_ini(ji,jj) > 0._wp 
     273               ENDIF 
    291274               ! 
    292275            END DO    
     
    294277 
    295278         !--------------------------------------------------------------------- 
    296          ! 3.3) Space-dependent arrays for ice state variables 
     279         ! 4) Fill in sea ice arrays 
    297280         !--------------------------------------------------------------------- 
    298281 
     
    426409         at_i (:,:) = at_i (:,:) + a_i (:,:,jl) 
    427410      END DO 
    428  
    429       !-------------------------------------------------------------------- 
    430       ! 4) Global ice variables for output diagnostics                    |  
    431       !-------------------------------------------------------------------- 
     411      ! 
     412      ! --- set ice velocities --- ! 
    432413      u_ice (:,:)     = 0._wp 
    433414      v_ice (:,:)     = 0._wp 
    434415      ! 
    435       !-------------------------------------------------------------------- 
    436       ! Snow-ice mass (case ice is fully embedded)                    |  
    437       !-------------------------------------------------------------------- 
     416      !---------------------------------------------- 
     417      ! 5) Snow-ice mass (case ice is fully embedded) 
     418      !---------------------------------------------- 
    438419      snwice_mass  (:,:) = tmask(:,:,1) * ( rhosn * vt_s(:,:) + rhoic * vt_i(:,:)  )   ! snow+ice mass 
    439420      snwice_mass_b(:,:) = snwice_mass(:,:) 
     
    556537         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    557538         WRITE(numout,*) '   Namelist namini:' 
    558          WRITE(numout,*) '      initialization with ice (T) or not (F)                 ln_iceini     = ', ln_iceini 
    559          WRITE(numout,*) '      ice initialization from a netcdf file                ln_iceini_file  = ', ln_iceini_file 
    560          WRITE(numout,*) '      max delta ocean temp. above Tfreeze with initial ice   rn_thres_sst  = ', rn_thres_sst 
    561          WRITE(numout,*) '      initial snow thickness in the north                    rn_hts_ini_n  = ', rn_hts_ini_n 
    562          WRITE(numout,*) '      initial snow thickness in the south                    rn_hts_ini_s  = ', rn_hts_ini_s  
    563          WRITE(numout,*) '      initial ice thickness  in the north                    rn_hti_ini_n  = ', rn_hti_ini_n 
    564          WRITE(numout,*) '      initial ice thickness  in the south                    rn_hti_ini_s  = ', rn_hti_ini_s 
    565          WRITE(numout,*) '      initial ice concentr.  in the north                    rn_ati_ini_n  = ', rn_ati_ini_n 
    566          WRITE(numout,*) '      initial ice concentr.  in the north                    rn_ati_ini_s  = ', rn_ati_ini_s 
    567          WRITE(numout,*) '      initial  ice salinity  in the north                    rn_smi_ini_n  = ', rn_smi_ini_n 
    568          WRITE(numout,*) '      initial  ice salinity  in the south                    rn_smi_ini_s  = ', rn_smi_ini_s 
    569          WRITE(numout,*) '      initial  ice/snw temp  in the north                    rn_tmi_ini_n  = ', rn_tmi_ini_n 
    570          WRITE(numout,*) '      initial  ice/snw temp  in the south                    rn_tmi_ini_s  = ', rn_tmi_ini_s 
     539         WRITE(numout,*) '      initialization with ice (T) or not (F)                 ln_iceini       = ', ln_iceini 
     540         WRITE(numout,*) '      ice initialization from a netcdf file                  ln_iceini_file  = ', ln_iceini_file 
     541         WRITE(numout,*) '      max delta ocean temp. above Tfreeze with initial ice   rn_thres_sst    = ', rn_thres_sst 
     542         WRITE(numout,*) '      initial snow thickness in the north                    rn_hts_ini_n    = ', rn_hts_ini_n 
     543         WRITE(numout,*) '      initial snow thickness in the south                    rn_hts_ini_s    = ', rn_hts_ini_s  
     544         WRITE(numout,*) '      initial ice thickness  in the north                    rn_hti_ini_n    = ', rn_hti_ini_n 
     545         WRITE(numout,*) '      initial ice thickness  in the south                    rn_hti_ini_s    = ', rn_hti_ini_s 
     546         WRITE(numout,*) '      initial ice concentr.  in the north                    rn_ati_ini_n    = ', rn_ati_ini_n 
     547         WRITE(numout,*) '      initial ice concentr.  in the north                    rn_ati_ini_s    = ', rn_ati_ini_s 
     548         WRITE(numout,*) '      initial  ice salinity  in the north                    rn_smi_ini_n    = ', rn_smi_ini_n 
     549         WRITE(numout,*) '      initial  ice salinity  in the south                    rn_smi_ini_s    = ', rn_smi_ini_s 
     550         WRITE(numout,*) '      initial  ice/snw temp  in the north                    rn_tmi_ini_n    = ', rn_tmi_ini_n 
     551         WRITE(numout,*) '      initial  ice/snw temp  in the south                    rn_tmi_ini_s    = ', rn_tmi_ini_s 
    571552      ENDIF 
    572553 
     
    595576#else 
    596577   !!---------------------------------------------------------------------- 
    597    !!   Default option :         Empty module          NO LIM sea-ice model 
     578   !!   Default option :         Empty module         NO ESIM sea-ice model 
    598579   !!---------------------------------------------------------------------- 
    599580#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceitd.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE iceitd *** 
    4    !!   LIM3 ice model : ice thickness distribution: Thermodynamics 
     4   !!   sea-ice : ice thickness distribution 
    55   !!====================================================================== 
    66   !! History :   -   !          (W. H. Lipscomb and E.C. Hunke) CICE (c) original code 
     
    1111#if defined key_lim3 
    1212   !!---------------------------------------------------------------------- 
    13    !!   'key_lim3'                                       LIM3 sea-ice model 
     13   !!   'key_lim3'                                       ESIM sea-ice model 
    1414   !!---------------------------------------------------------------------- 
    15    !!   ice_itd_rem   : 
    16    !!   ice_itd_reb   : 
    17    !!   ice_itd_glinear  : 
    18    !!   ice_itd_shiftice : 
     15   !!   ice_itd_init   : read ice thicknesses mean and min from namelist 
     16   !!   ice_itd_rem    : redistribute ice thicknesses after thermo growth and melt 
     17   !!   ice_itd_reb    : rebin ice thicknesses into bounded categories 
    1918   !!---------------------------------------------------------------------- 
    20    USE par_oce        ! ocean parameters 
    2119   USE dom_oce        ! ocean domain 
    2220   USE phycst         ! physical constants  
     
    2624   USE icetab         ! sea-ice: convert 1D<=>2D 
    2725   ! 
    28    USE prtctl         ! Print control 
    2926   USE in_out_manager ! I/O manager 
    3027   USE lib_mpp        ! MPP library 
    31    USE lib_fortran    ! to use key_nosignedzero 
     28   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     29   USE prtctl         ! Print control 
    3230 
    3331   IMPLICIT NONE 
     
    3634   PUBLIC   ice_itd_init  ! called in icestp 
    3735   PUBLIC   ice_itd_rem   ! called in icethd 
    38    PUBLIC   ice_itd_reb   ! called in iceerr 
    39  
    40    ! ** ice-thickness distribution namelist (namitd) ** 
    41    REAL(wp) ::   rn_himean        ! mean thickness of the domain (used to compute the distribution) 
     36   PUBLIC   ice_itd_reb   ! called in icecor 
     37 
     38   ! ** namelist (namitd) ** 
     39   REAL(wp) ::   rn_himean   ! mean thickness of the domain 
    4240 
    4341   !!---------------------------------------------------------------------- 
     
    5351      !! 
    5452      !! ** Purpose :   computes the redistribution of ice thickness 
    55       !!              after thermodynamic growth of ice thickness 
    56       !! 
    57       !! ** Method  : Linear remapping  
    58       !! 
    59       !! References : W.H. Lipscomb, JGR 2001 
     53      !!                after thermodynamic growth of ice thickness 
     54      !! 
     55      !! ** Method  :   Linear remapping  
     56      !! 
     57      !! References :   W.H. Lipscomb, JGR 2001 
    6058      !!------------------------------------------------------------------ 
    6159      INTEGER , INTENT (in) ::   kt      ! Ocean time step  
     
    696694#else 
    697695   !!---------------------------------------------------------------------- 
    698    !!   Default option :         Empty module          NO LIM sea-ice model 
     696   !!   Default option :         Empty module         NO ESIM sea-ice model 
    699697   !!---------------------------------------------------------------------- 
    700698#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icerst.F90

    r8518 r8534  
    22   !!====================================================================== 
    33   !!                     ***  MODULE  icerst  *** 
    4    !! Ice restart :  write the ice restart file 
     4   !!   sea-ice :  write/read the ice restart file 
    55   !!====================================================================== 
    66   !! History:   3.0  ! 2005-04 (M. Vancoppenolle) Original code 
     
    1010#if defined key_lim3 
    1111   !!---------------------------------------------------------------------- 
    12    !!   'key_lim3'                                        LIM sea-ice model 
    13    !!---------------------------------------------------------------------- 
    14    !!   ice_rst_opn   : open ice restart file 
    15    !!   ice_rst_write : write of the restart file  
    16    !!   ice_rst_read  : read  the restart file  
     12   !!   'key_lim3'                                       ESIM sea-ice model 
     13   !!---------------------------------------------------------------------- 
     14   !!   ice_rst_opn   : open restart file 
     15   !!   ice_rst_write : write restart file  
     16   !!   ice_rst_read  : read  restart file  
    1717   !!---------------------------------------------------------------------- 
    1818   USE ice            ! sea-ice variables 
     
    2222   ! 
    2323   USE in_out_manager ! I/O manager 
    24    USE iom            ! I/O library 
     24   USE iom            ! I/O manager library 
    2525   USE lib_mpp        ! MPP library 
    26    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     26   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     27   USE timing         ! Timing 
    2728 
    2829   IMPLICIT NONE 
     
    4445      !!                    ***  ice_rst_opn  *** 
    4546      !! 
    46       !! ** purpose  :   output of sea-ice variable in a netcdf file 
     47      !! ** purpose  :   open restart file 
    4748      !!---------------------------------------------------------------------- 
    4849      INTEGER, INTENT(in) ::   kt       ! number of iteration 
     
    9596      !!                    ***  ice_rst_write  *** 
    9697      !! 
    97       !! ** purpose  :   output of sea-ice variable in a netcdf file 
     98      !! ** purpose  :   write restart file 
    9899      !!---------------------------------------------------------------------- 
    99100      INTEGER, INTENT(in) ::   kt     ! number of iteration 
     
    105106      REAL(wp), DIMENSION(jpi,jpj) :: z2d 
    106107      !!---------------------------------------------------------------------- 
     108 
     109      IF( nn_timing == 1 )   CALL timing_start('ice_rst') 
    107110 
    108111      iter = kt + nn_fsbc - 1   ! ice restarts are written at kt == nitrst - nn_fsbc + 1 
     
    184187      ENDIF 
    185188      ! 
     189      IF( nn_timing == 1 ) CALL timing_stop('ice_rst') 
    186190      ! 
    187191   END SUBROUTINE ice_rst_write 
     
    192196      !!                    ***  ice_rst_read  *** 
    193197      !! 
    194       !! ** purpose  :   read of sea-ice variable restart in a netcdf file 
     198      !! ** purpose  :   read restart file 
    195199      !!---------------------------------------------------------------------- 
    196200      INTEGER  :: jk, jl 
     
    202206      LOGICAL           ::   llok 
    203207      !!---------------------------------------------------------------------- 
     208 
     209      IF( nn_timing == 1 )   CALL timing_start('ice_rst') 
    204210 
    205211      IF(lwp) THEN 
     
    279285      CALL iom_get( numrir, jpdom_autoglo, 'v_ice', v_ice ) 
    280286 
     287      IF( nn_timing == 1 ) CALL timing_stop('ice_rst') 
     288 
    281289   END SUBROUTINE ice_rst_read 
    282290 
    283291#else 
    284292   !!---------------------------------------------------------------------- 
    285    !!   Default option :       Empty module            NO LIM sea-ice model 
     293   !!   Default option :       Empty module           NO ESIM sea-ice model 
    286294   !!---------------------------------------------------------------------- 
    287295#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90

    r8531 r8534  
    33   !!                       ***  MODULE  icestp  *** 
    44   !! Surface module :  update the ocean surface boundary condition over ice 
    5    !!       &           covered area using LIM sea-ice model 
    6    !! Sea-Ice model  :  LIM-3 Sea ice model time-stepping 
     5   !!                   covered area using ESIM sea-ice model 
    76   !!===================================================================== 
    87   !! History :  2.0  ! 2006-12  (M. Vancoppenolle) Original code 
     
    1716#if defined key_lim3 
    1817   !!---------------------------------------------------------------------- 
    19    !!   'key_lim3'                                    LIM 3.0 sea-ice model 
    20    !!---------------------------------------------------------------------- 
    21    !!   ice_stp       : sea-ice model time-stepping and update ocean surf. boundary cond. over ice-covered area 
    22    !!   ice_init      : 
    23    !!   ice_run_init  :  
     18   !!   'key_lim3'                                       ESIM sea-ice model 
     19   !!---------------------------------------------------------------------- 
     20   !!   ice_stp       : sea-ice model time-stepping and update ocean SBC over ice-covered area 
     21   !!   ice_init      : initialize sea-ice 
    2422   !!---------------------------------------------------------------------- 
    2523   USE oce            ! ocean dynamics and tracers 
     
    2927   USE ice1D          ! sea-ice: thermodynamical 1D variables 
    3028   ! 
     29   USE phycst         ! Define parameters for the routines 
     30   USE eosbn2         ! equation of state 
    3131   USE sbc_oce        ! Surface boundary condition: ocean fields 
    3232   USE sbc_ice        ! Surface boundary condition: ice   fields 
     33   ! 
    3334   USE iceforcing     ! sea-ice: Surface boundary condition       !!gm why not icesbc module name 
    34    ! 
    35    USE phycst         ! Define parameters for the routines 
    36    USE eosbn2         ! equation of state 
    37    USE icerhg         ! sea-ice: rheology 
    38    USE iceadv         ! sea-ice: advection 
    3935   USE icedyn         ! sea-ice: dynamics 
    4036   USE icethd         ! sea-ice: thermodynamics 
    41    USE icerdgrft      ! sea-ice: ridging/rafting 
     37   USE limmp          ! sea-ice: melt ponds 
     38   USE icecor         ! sea-ice: corrections 
    4239   USE iceupdate      ! sea-ice: sea surface boundary condition update 
    4340   USE icedia         ! sea-ice: budget diagnostics 
    4441   USE icewri         ! sea-ice: outputs 
    4542   USE icerst         ! sea-ice: restarts 
    46    USE icecor         ! sea-ice: corrections 
    4743   USE icevar         ! sea-ice: operations 
    4844   USE icectl         ! sea-ice: control 
    49    ! MV MP 2016 
    50    USE limmp          ! sea-ice: melt ponds 
    51    ! END MV MP 2016 
    5245   USE iceistate      ! sea-ice: initial state 
    53    USE icethd_sal     ! sea-ice: thermodynamics and salinity 
    5446   USE iceitd         ! sea-ice: remapping thickness distribution 
    5547   USE icealb         ! sea-ice: albedo 
     
    6557   USE in_out_manager ! I/O manager 
    6658   USE iom            ! I/O manager library 
     59   USE lib_mpp        ! MPP library 
     60   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     61   USE timing         ! Timing 
    6762   USE prtctl         ! Print control 
    68    USE lib_fortran    !  
    69    USE lbclnk         ! lateral boundary condition - MPP link 
    70    USE lib_mpp        ! MPP library 
    71    USE timing         ! Timing 
    7263 
    7364   IMPLICIT NONE 
     
    202193!!         IF( .NOT. Agrif_Root() )   CALL Agrif_ParentGrid_To_ChildGrid() 
    203194!!# endif 
    204          IF( ln_icediahsb )         CALL ice_dia( kt )        ! -- Diagnostics and outputs  
    205          ! 
    206                                     CALL ice_wri( 1 )         ! -- Ice outputs  
    207          ! 
    208          ! 
    209          IF( lrst_ice )             CALL ice_rst_write( kt )  ! -- Ice restart file  
    210          ! 
    211          IF( ln_icectl )            CALL ice_ctl( kt )        ! alerts in case of model crash 
     195         IF( ln_icediahsb )         CALL ice_dia( kt )          ! -- Diagnostics and outputs  
     196         ! 
     197                                    CALL ice_wri( 1 )           ! -- Ice outputs  
     198         ! 
     199         ! 
     200         IF( lrst_ice )             CALL ice_rst_write( kt )    ! -- Ice restart file  
     201         ! 
     202         IF( ln_icectl )            CALL ice_ctl( kt )          ! -- alerts in case of model crash 
    212203         ! 
    213204      ENDIF   ! End sea-ice time step only 
     
    230221      !!                  ***  ROUTINE ice_init  *** 
    231222      !! 
    232       !! ** purpose :   Allocate all the dynamic arrays of the LIM-3 modules 
     223      !! ** purpose :   Initialize sea-ice parameters 
    233224      !!---------------------------------------------------------------------- 
    234225      INTEGER :: ji, jj, ierr 
     
    265256         CALL ice_rst_read 
    266257      ENDIF 
     258      CALL ice_var_glo2eqv 
    267259      CALL ice_var_agg(2) 
    268       CALL ice_var_glo2eqv 
    269260      ! 
    270261      CALL ice_forcing_init            ! set ice-ocean and ice-atm. coupling parameters 
     
    301292      !!                  ***  ROUTINE par_init *** 
    302293      !! 
    303       !! ** Purpose :   Definition some run parameter for ice model 
    304       !! 
    305       !! ** Method  :   Read the nampar namelist and check the parameter 
     294      !! ** Purpose :   Definition generic parameters for ice model 
     295      !! 
     296      !! ** Method  :   Read namelist and check the parameter 
    306297      !!                values called at the first timestep (nit000) 
    307298      !! 
     
    444435#else 
    445436   !!---------------------------------------------------------------------- 
    446    !!   Default option           Dummy module      NO LIM 3.0 sea-ice model 
     437   !!   Default option           Dummy module         NO ESIM sea-ice model 
    447438   !!---------------------------------------------------------------------- 
    448439CONTAINS 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icetab.F90

    r8486 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icetab   *** 
    4    !!   LIM ice model : transform 1D (2D) array to a 2D (1D) table 
     4   !!   sea-ice : transform 1D (2D) array to a 2D (1D) table 
    55   !!====================================================================== 
    66#if defined key_lim3 
    77   !!---------------------------------------------------------------------- 
    8    !!   'key_lim3'                                      LIM3 sea-ice model 
     8   !!   'key_lim3'                                       ESIM sea-ice model 
    99   !!---------------------------------------------------------------------- 
     10   !!   tab_3d_2d  : 3-D <==> 2-D 
     11   !!   tab_2d_3d  : 2-D <==> 3-D 
    1012   !!   tab_2d_1d  : 2-D <==> 1-D 
    1113   !!   tab_1d_2d  : 1-D <==> 2-D 
     
    111113#else 
    112114   !!---------------------------------------------------------------------- 
    113    !!   Default option           Dummy module      NO LIM 3.0 sea-ice model 
     115   !!   Default option           Dummy module         NO ESIM sea-ice model 
    114116   !!---------------------------------------------------------------------- 
    115117#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                  ***  MODULE icethd   *** 
    4    !!  LIM-3 :   ice thermodynamic 
     4   !!   sea-ice : master routine for thermodynamics 
    55   !!====================================================================== 
    66   !! History :  LIM  ! 2000-01 (M.A. Morales Maqueda, H. Goosse, T. Fichefet) LIM-1 
     
    1515#if defined key_lim3 
    1616   !!---------------------------------------------------------------------- 
    17    !!   'key_lim3'                                       LIM3 sea-ice model 
    18    !!---------------------------------------------------------------------- 
    19    !!   ice_thd       : thermodynamic of sea ice 
    20    !!   ice_thd_init  : initialisation of sea-ice thermodynamic 
     17   !!   'key_lim3'                                       ESIM sea-ice model 
     18   !!---------------------------------------------------------------------- 
     19   !!   ice_thd       : thermodynamics of sea ice 
     20   !!   ice_thd_init  : initialisation of sea-ice thermodynamics 
    2121   !!---------------------------------------------------------------------- 
    2222   USE phycst         ! physical constants 
    2323   USE dom_oce        ! ocean space and time domain variables 
    24    USE ice            ! sea-ice variables 
     24   USE ice            ! sea-ice: variables 
    2525!!gm list trop longue ==>>> why not passage en argument d'appel ? 
    2626   USE sbc_oce , ONLY : sss_m, sst_m, e3t_m, utau, vtau, ssu_m, ssv_m, frq_m, qns_tot, qsr_tot, sprecip, ln_cpl 
    2727   USE sbc_ice , ONLY : qsr_oce, qns_oce, qemp_oce, qsr_ice, qns_ice, dqns_ice, evap_ice, qprec_ice, qevap_ice, & 
    2828      &                 fr1_i0, fr2_i0 
    29    USE ice1D          ! thermodynamic sea-ice variables 
    30    USE icethd_zdf     ! vertical diffusion 
    31    USE icethd_dh      ! ice-snow growth and melt 
    32    USE icethd_da      ! lateral melting 
    33    USE icethd_sal     ! ice salinity 
    34    USE icethd_ent     ! ice enthalpy redistribution 
    35    USE icethd_do      ! lateral accretion 
    36    USE iceitd         ! remapping thickness distribution 
    37    USE icetab         ! 1D <==> 2D transformation 
    38    USE icevar         ! 
    39    USE icectl         ! control print 
     29   USE ice1D          ! sea-ice: thermodynamics variables 
     30   USE icethd_zdf     ! sea-ice: vertical heat diffusion 
     31   USE icethd_dh      ! sea-ice: ice-snow growth and melt 
     32   USE icethd_da      ! sea-ice: lateral melting 
     33   USE icethd_sal     ! sea-ice: salinity 
     34   USE icethd_ent     ! sea-ice: enthalpy redistribution 
     35   USE icethd_do      ! sea-ice: growth in open water 
     36   USE iceitd         ! sea-ice: remapping thickness distribution 
     37   USE icetab         ! sea-ice: 1D <==> 2D transformation 
     38   USE icevar         ! sea-ice: operations 
     39   USE icectl         ! sea-ice: control print 
    4040   ! 
    4141   USE in_out_manager ! I/O manager 
    42    USE lbclnk         ! lateral boundary condition - MPP links 
    4342   USE lib_mpp        ! MPP library 
    44    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     43   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     44   USE lbclnk         ! lateral boundary conditions (or mpp links) 
    4545   USE timing         ! Timing 
    4646 
     
    8484      !!             - call ice_thd_da   for lateral ice melt 
    8585      !!             - back to the geographic grid 
     86      !!             - call ice_thd_rem  for remapping thickness distribution 
     87      !!             - call ice_thd_do   for ice growth in leads 
    8688      !!--------------------------------------------------------------------- 
    8789      INTEGER, INTENT(in) :: kt    ! number of iteration 
     
    578580#else 
    579581   !!---------------------------------------------------------------------- 
    580    !!   Default option         Dummy module          NO  LIM3 sea-ice model 
     582   !!   Default option         Dummy module          NO  ESIM sea-ice model 
    581583   !!---------------------------------------------------------------------- 
    582584#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_da.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icethd_da *** 
    4    !! LIM-3 sea-ice :  computation of lateral melting in the ice 
     4   !!   sea-ice : lateral melting 
    55   !!====================================================================== 
    66   !! History :  4.0  ! 2016-03 (C. Rousset)  original code 
     
    88#if defined key_lim3 
    99   !!---------------------------------------------------------------------- 
    10    !!   'key_lim3'                                      LIM-3 sea-ice model 
    11    !!---------------------------------------------------------------------- 
    12    !!   ice_thd_da    : sea ice lateral melting 
     10   !!   'key_lim3'                                       ESIM sea-ice model 
     11   !!---------------------------------------------------------------------- 
     12   !!   ice_thd_da        : sea ice lateral melting 
     13   !!   ice_thd_da_init   : sea ice lateral melting initialization 
    1314   !!---------------------------------------------------------------------- 
    1415   USE par_oce        ! ocean parameters 
     
    195196#else 
    196197   !!---------------------------------------------------------------------- 
    197    !!   Default option         Dummy Module          No LIM-3 sea-ice model 
     198   !!   Default option         Dummy Module           NO ESIM sea-ice model 
    198199   !!---------------------------------------------------------------------- 
    199200#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_dh.F90

    r8522 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icethd_dh *** 
    4    !!  LIM-3 :   thermodynamic growth and decay of the ice  
     4   !!   seaice : thermodynamic growth and melt  
    55   !!====================================================================== 
    66   !! History :  LIM  ! 2003-05 (M. Vancoppenolle) Original code in 1D 
     
    1212#if defined key_lim3 
    1313   !!---------------------------------------------------------------------- 
    14    !!   'key_lim3'                                       LIM3 sea-ice model 
     14   !!   'key_lim3'                                       ESIM sea-ice model 
    1515   !!---------------------------------------------------------------------- 
    16    !!   ice_thd_dh    : vertical accr./abl. and lateral ablation of sea ice 
    17    !!---------------------------------------------------------------------- 
    18    USE par_oce        ! ocean parameters 
    19    USE phycst         ! physical constants (OCE directory)  
    20    USE ice            ! LIM variables 
    21    USE ice1D          ! LIM thermodynamics 
     16   !!   ice_thd_dh        : vertical sea-ice growth and melt 
     17   !!   ice_thd_snwblow   : distribute snow fall between ice and ocean 
     18  !!---------------------------------------------------------------------- 
     19   USE dom_oce        ! ocean space and time domain 
     20   USE phycst         ! physical constants 
     21   USE ice            ! sea-ice: variables 
     22   USE ice1D          ! sea-ice: thermodynamics variables 
    2223   USE icethd_sal     ! sea-ice: salinity profiles 
    2324   ! 
    2425   USE in_out_manager ! I/O manager 
    2526   USE lib_mpp        ! MPP library 
    26    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     27   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
    2728    
    2829   IMPLICIT NONE 
    2930   PRIVATE 
    3031 
    31    PUBLIC   ice_thd_dh      ! called by ice_thd 
    32    PUBLIC   ice_thd_snwblow ! called in sbcblk/sbcclio/sbccpl and here 
     32   PUBLIC   ice_thd_dh        ! called by ice_thd 
     33   PUBLIC   ice_thd_snwblow   ! called in sbcblk/sbcclio/sbccpl and here 
    3334 
    3435   INTERFACE ice_thd_snwblow 
     
    4748      !!                ***  ROUTINE ice_thd_dh  *** 
    4849      !! 
    49       !! ** Purpose :   determines variations of ice and snow thicknesses. 
     50      !! ** Purpose :   compute ice and snow thickness changes due to growing/melting 
    5051      !! 
    5152      !! ** Method  :   Ice/Snow surface melting arises from imbalance in surface fluxes 
     
    679680#else 
    680681   !!---------------------------------------------------------------------- 
    681    !!   Default option                               NO  LIM3 sea-ice model 
     682   !!   Default option                                NO ESIM sea-ice model 
    682683   !!---------------------------------------------------------------------- 
    683684#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_do.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icethd_do   *** 
    4    !!                lateral thermodynamic growth of the ice  
     4   !!   sea-ice: sea ice growth in the leads (open water)  
    55   !!====================================================================== 
    66   !! History :  LIM  ! 2005-12 (M. Vancoppenolle)  Original code 
     
    1111#if defined key_lim3 
    1212   !!---------------------------------------------------------------------- 
    13    !!   'key_lim3'                                       LIM3 sea-ice model 
    14    !!---------------------------------------------------------------------- 
    15    !!   ice_thd_do   : ice growth in open water (=lateral accretion of ice) 
    16    !!---------------------------------------------------------------------- 
    17    USE par_oce        ! ocean parameters 
    18    USE dom_oce        ! domain variables 
     13   !!   'key_lim3'                                       ESIM sea-ice model 
     14   !!---------------------------------------------------------------------- 
     15   !!   ice_thd_do        : ice growth in open water (=lateral accretion of ice) 
     16   !!   ice_thd_do_init   : initialization 
     17   !!---------------------------------------------------------------------- 
     18   USE dom_oce        ! ocean space and time domain 
    1919   USE phycst         ! physical constants 
    2020   USE sbc_oce , ONLY : sss_m 
    2121   USE sbc_ice , ONLY : utau_ice, vtau_ice 
    22    USE ice1D          ! sea-ice: thermodynamics 
     22   USE ice1D          ! sea-ice: thermodynamics variables 
    2323   USE ice            ! sea-ice: variables 
    2424   USE icetab         ! sea-ice: 2D <==> 1D 
     
    3030   USE in_out_manager ! I/O manager 
    3131   USE lib_mpp        ! MPP library 
    32    USE lbclnk         ! ocean lateral boundary conditions (or mpp link) 
    33    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     32   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     33   USE lbclnk         ! lateral boundary conditions (or mpp links) 
    3434 
    3535   IMPLICIT NONE 
     
    5959      !! ** Purpose : Computation of the evolution of the ice thickness and  
    6060      !!      concentration as a function of the heat balance in the leads. 
    61       !!      It is only used for lateral accretion 
    6261      !!        
    6362      !! ** Method  : Ice is formed in the open water when ocean lose heat 
     
    495494      !!                  
    496495      !! ** Purpose :   Physical constants and parameters associated with 
    497       !!                ice thermodynamics 
     496      !!                ice growth in the leads 
    498497      !! 
    499498      !! ** Method  :   Read the namthd_do namelist and check the parameters 
     
    534533#else 
    535534   !!---------------------------------------------------------------------- 
    536    !!   Default option                               NO  LIM3 sea-ice model 
     535   !!   Default option                                NO ESIM sea-ice model 
    537536   !!---------------------------------------------------------------------- 
    538537#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_ent.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icethd_ent   *** 
    4    !!                  Redistribution of Enthalpy in the ice 
    5    !!                        on the new vertical grid 
    6    !!                       after vertical growth/decay 
     4   !!   sea-ice: redistribution of enthalpy in the ice on the new vertical grid 
     5   !!                       after vertical growth/melt 
    76   !!====================================================================== 
    87   !! History :  LIM  ! 2003-05 (M. Vancoppenolle) Original code in 1D 
     
    1514#if defined key_lim3 
    1615   !!---------------------------------------------------------------------- 
    17    !!   'key_lim3'                                       LIM3 sea-ice model 
     16   !!   'key_lim3'                                       ESIM sea-ice model 
    1817   !!---------------------------------------------------------------------- 
    1918   !!   ice_thd_ent   : ice redistribution of enthalpy 
    2019   !!---------------------------------------------------------------------- 
    21    USE par_oce        ! ocean parameters 
    2220   USE dom_oce        ! domain variables 
    2321   USE domain         ! 
    2422   USE phycst         ! physical constants 
    25    USE ice            ! LIM variables 
    26    USE ice1D          ! LIM thermodynamics 
     23   USE ice            ! sea-ice: variables 
     24   USE ice1D          ! sea-ice: thermodynamics variables 
    2725   ! 
    2826   USE in_out_manager ! I/O manager 
     
    6765      !! References : Bitz & Lipscomb, JGR 99; Vancoppenolle et al., GRL, 2005 
    6866      !!------------------------------------------------------------------- 
    69       REAL(wp), INTENT(inout), DIMENSION(:,:) :: qnew          ! new enthlapies (J.m-3, remapped) 
    70  
     67      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   qnew             ! new enthlapies (J.m-3, remapped) 
     68      ! 
    7169      INTEGER  :: ji         !  dummy loop indices 
    7270      INTEGER  :: jk0, jk1   !  old/new layer indices 
    7371      ! 
    74       REAL(wp), DIMENSION(jpij,0:nlay_i+2) :: zeh_cum0, zh_cum0   ! old cumulative enthlapies and layers interfaces 
    75       REAL(wp), DIMENSION(jpij,0:nlay_i)   :: zeh_cum1, zh_cum1   ! new cumulative enthlapies and layers interfaces 
    76       REAL(wp), DIMENSION(jpij)            :: zhnew               ! new layers thicknesses 
     72      REAL(wp), DIMENSION(jpij,0:nlay_i+2) ::   zeh_cum0, zh_cum0   ! old cumulative enthlapies and layers interfaces 
     73      REAL(wp), DIMENSION(jpij,0:nlay_i)   ::   zeh_cum1, zh_cum1   ! new cumulative enthlapies and layers interfaces 
     74      REAL(wp), DIMENSION(jpij)            ::   zhnew               ! new layers thicknesses 
    7775      !!------------------------------------------------------------------- 
    7876 
     
    141139#else 
    142140   !!---------------------------------------------------------------------- 
    143    !!   Default option                               NO  LIM3 sea-ice model 
     141   !!   Default option                                NO ESIM sea-ice model 
    144142   !!---------------------------------------------------------------------- 
    145143#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_sal.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icethd_sal *** 
    4    !! LIM-3 sea-ice : computation of salinity variations in the ice 
     4   !!   sea-ice : computation of salinity variations in the ice 
    55   !!====================================================================== 
    66   !! History :   -   ! 2003-05 (M. Vancoppenolle) UCL-ASTR first coding for LIM3-1D 
     
    1010#if defined key_lim3 
    1111   !!---------------------------------------------------------------------- 
    12    !!   'key_lim3'                                      LIM-3 sea-ice model 
     12   !!   'key_lim3'                                       ESIM sea-ice model 
    1313   !!---------------------------------------------------------------------- 
    14    !!   ice_thd_sal   : salinity variations in the ice 
     14   !!   ice_thd_sal        : salinity variations in the ice 
     15   !!   ice_thd_sal_init   : initialization 
    1516   !!---------------------------------------------------------------------- 
    16    USE par_oce        ! ocean parameters 
    17    USE phycst         ! physical constants (ocean directory) 
    18    USE ice            ! LIM variables 
    19    USE ice1D          ! LIM thermodynamics 
    20    USE icevar         ! LIM variables 
     17   USE dom_oce        ! ocean space and time domain 
     18   USE phycst         ! physical constants 
     19   USE ice            ! sea-ice: variables 
     20   USE ice1D          ! sea-ice: thermodynamics variables 
     21   USE icevar         ! sea-ice: operations 
    2122   ! 
    2223   USE in_out_manager ! I/O manager 
    2324   USE lib_mpp        ! MPP library 
    24    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     25   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
    2526 
    2627   IMPLICIT NONE 
     
    153154#else 
    154155   !!---------------------------------------------------------------------- 
    155    !!   Default option         Dummy Module          No LIM-3 sea-ice model 
     156   !!   Default option         Dummy Module           No ESIM sea-ice model 
    156157   !!---------------------------------------------------------------------- 
    157158#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_zdf.F90

    r8531 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icethd_zdf *** 
    4    !!                       heat diffusion in sea ice  
    5    !!                   computation of surface and inner T   
     4   !!   sea-ice: vertical heat diffusion in sea ice (computation of temperatures)  
    65   !!====================================================================== 
    76   !! History :  LIM  ! 02-2003 (M. Vancoppenolle) original 1D code 
     
    1413#if defined key_lim3 
    1514   !!---------------------------------------------------------------------- 
    16    !!   'key_lim3'                                      LIM3 sea-ice model 
     15   !!   'key_lim3'                                       ESIM sea-ice model 
    1716   !!---------------------------------------------------------------------- 
    18    USE par_oce        ! ocean parameters 
     17   USE dom_oce        ! ocean space and time domain 
    1918   USE phycst         ! physical constants (ocean directory)  
    2019   USE ice            ! sea-ice: variables 
    21    USE ice1D          ! sea-ice: thermodynamics 
     20   USE ice1D          ! sea-ice: thermodynamics variables 
    2221   ! 
    2322   USE in_out_manager ! I/O manager 
    2423   USE lib_mpp        ! MPP library 
    25    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     24   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
    2625 
    2726   IMPLICIT NONE 
    2827   PRIVATE 
    2928 
    30    PUBLIC   ice_thd_zdf        ! called by ice_thd 
    31    PUBLIC   ice_thd_zdf_init   ! called by ice_stp 
     29   PUBLIC   ice_thd_zdf        ! called by icethd 
     30   PUBLIC   ice_thd_zdf_init   ! called by icestp 
    3231 
    3332   !!** namelist (namthd_zdf) ** 
     
    4746 
    4847   SUBROUTINE ice_thd_zdf 
    49       !!------------------------------------------------------------------ 
     48      !!------------------------------------------------------------------- 
    5049      !!                ***  ROUTINE ice_thd_zdf  *** 
    5150      !! ** Purpose : 
     
    6362      !! 
    6463      !!           The successive steps of this routine are 
    65       !!           1.  Thermal conductivity at the interfaces of the ice layers 
    66       !!           2.  Internal absorbed radiation 
    67       !!           3.  Scale factors due to non-uniform grid 
     64      !!           1.  initialization of ice-snow layers thicknesses 
     65      !!           2.  Internal absorbed and transmitted radiation 
     66      !!           Then iterative procedure begins 
     67      !!           3.  Thermal conductivity 
    6868      !!           4.  Kappa factors 
    69       !!           Then iterative procedure begins 
    7069      !!           5.  specific heat in the ice 
    7170      !!           6.  eta factors 
     
    7574      !!           Iterative procedure ends according to a criterion on evolution 
    7675      !!           of temperature 
     76      !!           10. Fluxes at the interfaces 
    7777      !! 
    7878      !! ** Inputs / Ouputs : (global commons) 
     
    8282      !!           number of layers in the ice/snow: nlay_i, nlay_s 
    8383      !!           total ice/snow thickness : ht_i_1d, ht_s_1d 
    84       !!------------------------------------------------------------------ 
     84      !!------------------------------------------------------------------- 
    8585      INTEGER ::   ji, jk         ! spatial loop index 
    8686      INTEGER ::   numeq          ! current reference number of equation 
     
    149149      END DO 
    150150 
    151       !------------------------------------------------------------------------------! 
    152       ! 1) Initialization                                                            ! 
    153       !------------------------------------------------------------------------------! 
     151      !------------------ 
     152      ! 1) Initialization 
     153      !------------------ 
    154154      DO ji = 1, nidx 
    155155         isnow(ji)= 1._wp - MAX( 0._wp , SIGN(1._wp, - ht_s_1d(ji) ) )  ! is there snow or not 
     
    173173      t_su_1d(1:nidx)   = MIN( t_su_1d(1:nidx), rt0 - ztsu_err )   ! necessary 
    174174      ! 
    175       !------------------------------------------------------------------------------| 
    176       ! 2) Radiation                                                              | 
    177       !------------------------------------------------------------------------------| 
     175      !------------- 
     176      ! 2) Radiation 
     177      !------------- 
    178178      ! 
    179179      z1_hsu = 1._wp / 0.1_wp ! threshold for the computation of i0 
    180180      DO ji = 1, nidx 
    181          !------------------- 
    182          ! Computation of i0 
    183          !------------------- 
     181         ! --- Computation of i0 --- ! 
    184182         ! i0 describes the fraction of solar radiation which does not contribute 
    185183         ! to the surface energy budget but rather penetrates inside the ice. 
     
    193191         i0(ji) = ( 1._wp - isnow(ji) ) * ( fr1_i0_1d(ji) + zfac * fr2_i0_1d(ji) ) 
    194192 
    195          !------------------------------------------------------- 
    196          ! Solar radiation absorbed / transmitted at the surface 
    197          ! Derivative of the non solar flux 
    198          !------------------------------------------------------- 
     193         ! --- Solar radiation absorbed / transmitted at the surface --- ! 
     194         !     Derivative of the non solar flux 
    199195         zfsw   (ji)     =  qsr_ice_1d(ji) * ( 1 - i0(ji) )   ! Shortwave radiation absorbed at surface 
    200196         zftrice(ji)     =  qsr_ice_1d(ji) *       i0(ji)     ! Solar radiation transmitted below the surface layer 
     
    203199      END DO 
    204200 
    205       !--------------------------------------------------------- 
    206       ! Transmission - absorption of solar radiation in the ice 
    207       !--------------------------------------------------------- 
     201      ! --- Transmission/absorption of solar radiation in the ice --- ! 
    208202      zradtr_s(1:nidx,0) = zftrice(1:nidx) 
    209203      DO jk = 1, nlay_s 
     
    227221 
    228222      ftr_ice_1d(1:nidx) = zradtr_i(1:nidx,nlay_i)   ! record radiation transmitted below the ice 
    229  
    230       !------------------------------------------------------------------------------| 
    231       !  3) Iterative procedure begins                                               | 
    232       !------------------------------------------------------------------------------| 
    233223      ! 
    234224      iconv    =  0          ! number of iterations 
    235225      zdti_max =  1000._wp   ! maximal value of error on all points 
    236       DO WHILE ( zdti_max > zdti_bnd .AND. iconv < iconv_max ) 
     226      !                                                          !----------------------------! 
     227      DO WHILE ( zdti_max > zdti_bnd .AND. iconv < iconv_max )   ! Iterative procedure begins ! 
     228         !                                                       !----------------------------! 
    237229         ! 
    238230         iconv = iconv + 1 
     
    241233         ztsb(1:nidx,:) = t_s_1d(1:nidx,:) 
    242234         ! 
    243          !------------------------------------------------------------------------------| 
    244          ! 4) Sea ice thermal conductivity                                              | 
    245          !------------------------------------------------------------------------------| 
    246          ! 
     235         !-------------------------------- 
     236         ! 3) Sea ice thermal conductivity 
     237         !-------------------------------- 
    247238         IF( ln_cndi_U64 ) THEN         !-- Untersteiner (1964) formula: k = k0 + beta.S/T 
    248239            ! 
     
    277268         ztcond_i(1:nidx,:) = MAX( zkimin, ztcond_i(1:nidx,:) )         
    278269         ! 
    279          !------------------------------------------------------------------------------| 
    280          !  5) G(he) - enhancement of thermal conductivity in mono-category case        | 
    281          !------------------------------------------------------------------------------| 
    282          ! 
     270         !--- G(he) : enhancement of thermal conductivity in mono-category case 
    283271         ! Computation of effective thermal conductivity G(h) 
    284272         ! Used in mono-category case only to simulate an ITD implicitly 
     
    309297         END SELECT 
    310298         ! 
    311          !------------------------------------------------------------------------------| 
    312          !  6) kappa factors                                                            | 
    313          !------------------------------------------------------------------------------| 
    314          ! 
     299         !----------------- 
     300         ! 4) kappa factors 
     301         !----------------- 
    315302         !--- Snow 
    316303         DO jk = 0, nlay_s-1 
     
    338325         END DO 
    339326         ! 
    340          !------------------------------------------------------------------------------| 
    341          ! 7) Sea ice specific heat, eta factors                                        | 
    342          !------------------------------------------------------------------------------| 
    343          ! 
     327         !-------------------------------------- 
     328         ! 5) Sea ice specific heat, eta factors 
     329         !-------------------------------------- 
    344330         DO jk = 1, nlay_i 
    345331            DO ji = 1, nidx 
     
    355341         END DO 
    356342         ! 
    357          !------------------------------------------------------------------------------| 
    358          ! 8) surface flux computation                                                  | 
    359          !------------------------------------------------------------------------------| 
    360          ! 
     343         !---------------------------- 
     344         ! 6) surface flux computation 
     345         !---------------------------- 
    361346         IF ( ln_dqns_i ) THEN  
    362347            DO ji = 1, nidx 
     
    370355         END DO 
    371356         ! 
    372          !------------------------------------------------------------------------------| 
    373          ! 9) tridiagonal system terms                                                  | 
    374          !------------------------------------------------------------------------------| 
    375          ! 
     357         !---------------------------- 
     358         ! 7) tridiagonal system terms 
     359         !---------------------------- 
    376360         !!layer denotes the number of the layer in the snow or in the ice 
    377361         !!numeq denotes the reference number of the equation in the tridiagonal 
     
    414398 
    415399         DO ji = 1, nidx 
    416             IF ( ht_s_1d(ji) > 0.0 ) THEN 
    417                ! 
    418                !------------------------------------------------------------------------------| 
    419                !  snow-covered cells                                                          | 
    420                !------------------------------------------------------------------------------| 
     400            !                               !---------------------! 
     401            IF ( ht_s_1d(ji) > 0.0 ) THEN   !  snow-covered cells ! 
     402               !                            !---------------------! 
    421403               ! 
    422404               !!snow interior terms (bottom equation has the same form as the others) 
     
    435417               ENDIF 
    436418 
    437                IF ( t_su_1d(ji) < rt0 ) THEN 
    438  
    439                   !------------------------------------------------------------------------------| 
    440                   !  case 1 : no surface melting - snow present                                  | 
    441                   !------------------------------------------------------------------------------| 
     419               IF ( t_su_1d(ji) < rt0 ) THEN   !--  case 1 : no surface melting 
     420 
    442421                  numeqmin(ji)    =  1 
    443422                  numeqmax(ji)    =  nlay_i + nlay_s + 1 
     
    455434                  zindterm(ji,2) =  ztsold(ji,1) + zeta_s(ji,1) * zradab_s(ji,1) 
    456435 
    457                ELSE  
    458                   ! 
    459                   !------------------------------------------------------------------------------| 
    460                   !  case 2 : surface is melting - snow present                                  | 
    461                   !------------------------------------------------------------------------------| 
     436               ELSE                            !--  case 2 : surface is melting 
    462437                  ! 
    463438                  numeqmin(ji)    =  2 
     
    471446                     &             ( zradab_s(ji,1) + zkappa_s(ji,0) * zg1s * t_su_1d(ji) )  
    472447               ENDIF 
    473             ELSE 
     448            !                               !---------------------! 
     449            ELSE                            ! cells without snow  ! 
     450               !                            !---------------------! 
    474451               ! 
    475                !------------------------------------------------------------------------------| 
    476                !  cells without snow                                                          | 
    477                !------------------------------------------------------------------------------| 
    478                ! 
    479                IF ( t_su_1d(ji) < rt0 ) THEN 
    480                   ! 
    481                   !------------------------------------------------------------------------------| 
    482                   !  case 3 : no surface melting - no snow                                       | 
    483                   !------------------------------------------------------------------------------| 
     452               IF ( t_su_1d(ji) < rt0 ) THEN   !--  case 1 : no surface melting 
    484453                  ! 
    485454                  numeqmin(ji)      =  nlay_s + 1 
     
    512481                  ENDIF 
    513482 
    514                ELSE 
    515  
    516                   ! 
    517                   !------------------------------------------------------------------------------| 
    518                   ! case 4 : surface is melting - no snow                                        | 
    519                   !------------------------------------------------------------------------------| 
    520                   ! 
     483               ELSE                            !--  case 2 : surface is melting 
     484 
    521485                  numeqmin(ji)    =  nlay_s + 2 
    522486                  numeqmax(ji)    =  nlay_i + nlay_s + 1 
     
    543507         END DO 
    544508         ! 
    545          !------------------------------------------------------------------------------| 
    546          ! 10) tridiagonal system solving                                               | 
    547          !------------------------------------------------------------------------------| 
    548          ! 
     509         !------------------------------ 
     510         ! 8) tridiagonal system solving 
     511         !------------------------------ 
    549512         ! Solve the tridiagonal system with Gauss elimination method. 
    550          ! Thomas algorithm, from Computational fluid Dynamics, J.D. ANDERSON,  
    551          ! McGraw-Hill 1984.   
     513         ! Thomas algorithm, from Computational fluid Dynamics, J.D. ANDERSON, McGraw-Hill 1984.    
    552514 
    553515         maxnumeqmax = 0 
     
    595557         END DO 
    596558         ! 
    597          !-------------------------------------------------------------------------- 
    598          !  11) Has the scheme converged ?, end of the iterative procedure         | 
    599          !-------------------------------------------------------------------------- 
    600          ! 
     559         !-------------------------------------------------------------- 
     560         ! 9) Has the scheme converged ?, end of the iterative procedure 
     561         !-------------------------------------------------------------- 
    601562         ! check that nowhere it has started to melt 
    602563         ! zdti_max is a measure of error, it has to be under zdti_bnd 
     
    632593         WRITE(numout,*) ' iconv    : ', iconv 
    633594      ENDIF 
    634  
    635       ! 
    636       !-------------------------------------------------------------------------! 
    637       !   12) Fluxes at the interfaces                                          ! 
    638       !-------------------------------------------------------------------------! 
     595      ! 
     596      !----------------------------- 
     597      ! 10) Fluxes at the interfaces 
     598      !----------------------------- 
    639599      DO ji = 1, nidx 
    640600         !                                ! surface ice conduction flux 
     
    694654 
    695655   SUBROUTINE ice_thd_enmelt 
    696       !!----------------------------------------------------------------------- 
     656      !!------------------------------------------------------------------- 
    697657      !!                   ***  ROUTINE ice_thd_enmelt ***  
    698658      !!                  
     
    764724      ! 
    765725      IF ( ( ln_cndi_U64 .AND. ln_cndi_P07 ) .OR. ( .NOT.ln_cndi_U64 .AND. .NOT.ln_cndi_P07 ) ) THEN 
    766          CALL ctl_stop( 'ice_thd_zdf_init: choose one and only one formulation for thermal conductivity (ln_cndi_U64 or ln_cndi_P07)' ) 
     726         CALL ctl_stop( 'ice_thd_zdf_init: choose one and only one formulation for thermal conduction (ln_cndi_U64 or ln_cndi_P07)' ) 
    767727      ENDIF 
    768728      ! 
     
    771731#else 
    772732   !!---------------------------------------------------------------------- 
    773    !!                   Dummy Module                 No ESIM sea-ice model 
     733   !!   Default option       Dummy Module             No ESIM sea-ice model 
    774734   !!---------------------------------------------------------------------- 
    775735#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceupdate.F90

    r8518 r8534  
    1616#if defined key_lim3 
    1717   !!---------------------------------------------------------------------- 
    18    !!   'key_lim3'                                    LIM 3.0 sea-ice model 
     18   !!   'key_lim3'                                       ESIM sea-ice model 
    1919   !!---------------------------------------------------------------------- 
    2020   !!   ice_update_alloc : allocate the iceupdate arrays 
     
    2323   !!   ice_update_tau   : update i- and j-stresses, and its modulus at the ocean surface 
    2424   !!---------------------------------------------------------------------- 
    25    USE par_oce        ! ocean parameters 
    2625   USE oce     , ONLY : sshn, sshb 
    2726   USE phycst         ! physical constants 
     
    4241   ! 
    4342   USE in_out_manager ! I/O manager 
    44    USE iom            ! xIO server 
    45    USE lbclnk         ! ocean lateral boundary condition - MPP exchanges 
     43   USE iom            ! I/O manager library 
    4644   USE lib_mpp        ! MPP library 
    47    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     45   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     46   USE lbclnk         ! lateral boundary conditions (or mpp links) 
    4847   USE timing         ! Timing 
    4948 
     
    110109      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zalb_cs, zalb_os     ! 3D workspace 
    111110      !!--------------------------------------------------------------------- 
    112       IF( nn_timing == 1 )  CALL timing_start('ice_update_flx') 
     111      IF( nn_timing == 1 )  CALL timing_start('ice_update') 
    113112 
    114113      IF( kt == nit000 .AND. lwp ) THEN 
     
    213212      IF( ln_icectl                      )   CALL ice_prt       (kt, iiceprt, jiceprt, 3, 'Final state ice_update') ! prints 
    214213      IF( ln_ctl                         )   CALL ice_prt3D     ('iceupdate')                                       ! prints 
    215       IF( nn_timing == 1                 )   CALL timing_stop   ('ice_update_flx')                                  ! timing 
     214      IF( nn_timing == 1                 )   CALL timing_stop   ('ice_update')                                      ! timing 
    216215      ! 
    217216   END SUBROUTINE ice_update_flx 
     
    251250      !!--------------------------------------------------------------------- 
    252251 
    253       IF( nn_timing == 1 )  CALL timing_start('ice_update_tau') 
     252      IF( nn_timing == 1 )  CALL timing_start('ice_update') 
    254253 
    255254      IF( kt == nit000 .AND. lwp ) THEN 
     
    297296      CALL lbc_lnk_multi( utau, 'U', -1., vtau, 'V', -1. )   ! lateral boundary condition 
    298297      ! 
    299       IF( nn_timing == 1 )  CALL timing_stop('ice_update_tau') 
     298      IF( nn_timing == 1 )  CALL timing_stop('ice_update') 
    300299      !   
    301300   END SUBROUTINE ice_update_tau 
     
    373372#else 
    374373   !!---------------------------------------------------------------------- 
    375    !!   Default option         Dummy module          NO  LIM3 sea-ice model 
     374   !!   Default option         Dummy module           NO ESIM sea-ice model 
    376375   !!---------------------------------------------------------------------- 
    377376#endif  
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icevar.F90

    r8522 r8534  
    22   !!====================================================================== 
    33   !!                       ***  MODULE icevar *** 
    4    !!                 Different sets of ice model variables  
     4   !!   sea-ice:     Different sets of ice model variables  
    55   !!                   how to switch from one to another 
    66   !! 
     
    3636#if defined key_lim3 
    3737   !!---------------------------------------------------------------------- 
    38    !!   'key_lim3'                                      LIM3 sea-ice model 
     38   !!   'key_lim3'                                       ESIM sea-ice model 
    3939   !!---------------------------------------------------------------------- 
    4040   !!   ice_var_agg       : integrate variables over layers and categories 
     
    4747   !!   ice_var_itd       : convert 1-cat to multiple cat 
    4848   !!---------------------------------------------------------------------- 
    49    USE par_oce        ! ocean parameters 
     49   USE dom_oce        ! ocean space and time domain 
    5050   USE phycst         ! physical constants (ocean directory)  
    5151   USE sbc_oce , ONLY : sss_m 
    52    USE ice            ! ice variables 
    53    USE ice1D          ! ice variables (thermodynamics) 
     52   USE ice            ! sea-ice: variables 
     53   USE ice1D          ! sea-ice: thermodynamics variables 
    5454   ! 
    5555   USE in_out_manager ! I/O manager 
    5656   USE lib_mpp        ! MPP library 
    57    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)   
     57   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
    5858 
    5959   IMPLICIT NONE 
     
    7777 
    7878   SUBROUTINE ice_var_agg( kn ) 
    79       !!------------------------------------------------------------------ 
     79      !!------------------------------------------------------------------- 
    8080      !!                ***  ROUTINE ice_var_agg  *** 
    8181      !! 
    8282      !! ** Purpose :   aggregates ice-thickness-category variables to  
    8383      !!              all-ice variables, i.e. it turns VGLO into VAGG 
    84       !!------------------------------------------------------------------ 
     84      !!------------------------------------------------------------------- 
    8585      INTEGER, INTENT( in ) ::   kn     ! =1 state variables only 
    8686      !                                 ! >1 state variables + others 
     
    8888      INTEGER ::   ji, jj, jk, jl   ! dummy loop indices 
    8989      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z1_at_i, z1_vt_i 
    90       !!------------------------------------------------------------------ 
     90      !!------------------------------------------------------------------- 
    9191      ! 
    9292      !                                      ! integrated values 
     
    143143 
    144144   SUBROUTINE ice_var_glo2eqv 
    145       !!------------------------------------------------------------------ 
     145      !!------------------------------------------------------------------- 
    146146      !!                ***  ROUTINE ice_var_glo2eqv *** 
    147147      !! 
    148148      !! ** Purpose :   computes equivalent variables as function of   
    149149      !!              global variables, i.e. it turns VGLO into VEQV 
    150       !!------------------------------------------------------------------ 
     150      !!------------------------------------------------------------------- 
    151151      INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices 
    152152      REAL(wp) ::   ze_i             ! local scalars 
     
    155155      REAL(wp) ::   zlay_i, zlay_s                  !   -      - 
    156156      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z1_a_i, z1_v_i 
    157       !!------------------------------------------------------------------ 
     157      !!------------------------------------------------------------------- 
    158158 
    159159!!gm Question 2:  It is possible to define existence of sea-ice in a common way between  
     
    242242 
    243243   SUBROUTINE ice_var_eqv2glo 
    244       !!------------------------------------------------------------------ 
     244      !!------------------------------------------------------------------- 
    245245      !!                ***  ROUTINE ice_var_eqv2glo *** 
    246246      !! 
    247247      !! ** Purpose :   computes global variables as function of  
    248248      !!              equivalent variables,  i.e. it turns VEQV into VGLO 
    249       !!------------------------------------------------------------------ 
     249      !!------------------------------------------------------------------- 
    250250      ! 
    251251      v_i  (:,:,:) = ht_i(:,:,:) * a_i(:,:,:) 
     
    257257 
    258258   SUBROUTINE ice_var_salprof 
    259       !!------------------------------------------------------------------ 
     259      !!------------------------------------------------------------------- 
    260260      !!                ***  ROUTINE ice_var_salprof *** 
    261261      !! 
     
    270270      !! 
    271271      !! ** References : Vancoppenolle et al., 2007 
    272       !!------------------------------------------------------------------ 
     272      !!------------------------------------------------------------------- 
    273273      INTEGER  ::   ji, jj, jk, jl   ! dummy loop index 
    274274      REAL(wp) ::   zsal, z1_dS 
     
    277277      REAL(wp), PARAMETER :: zsi0 = 3.5_wp 
    278278      REAL(wp), PARAMETER :: zsi1 = 4.5_wp 
    279       !!------------------------------------------------------------------ 
     279      !!------------------------------------------------------------------- 
    280280 
    281281!!gm Question: Remove the option 3 ?  How many years since it last use ?  
     
    355355 
    356356   SUBROUTINE ice_var_bv 
    357       !!------------------------------------------------------------------ 
     357      !!------------------------------------------------------------------- 
    358358      !!                ***  ROUTINE ice_var_bv *** 
    359359      !! 
     
    363363      !! 
    364364      !! References : Vancoppenolle et al., JGR, 2007 
    365       !!------------------------------------------------------------------ 
     365      !!------------------------------------------------------------------- 
    366366      INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices 
    367       !!------------------------------------------------------------------ 
     367      !!------------------------------------------------------------------- 
    368368      ! 
    369369!!gm I prefere to use WHERE / ELSEWHERE  to set it to zero only where needed   <<<=== to be done 
     
    398398      REAL(wp), PARAMETER :: zsi0 = 3.5_wp 
    399399      REAL(wp), PARAMETER :: zsi1 = 4.5_wp 
    400       !!--------------------------------------------------------------------- 
     400      !!------------------------------------------------------------------- 
    401401      ! 
    402402      SELECT CASE ( nn_icesal ) 
     
    543543 
    544544   SUBROUTINE ice_var_itd( zhti, zhts, zai, zht_i, zht_s, za_i ) 
    545       !!------------------------------------------------------------------ 
     545      !!------------------------------------------------------------------- 
    546546      !!                ***  ROUTINE ice_var_itd   *** 
    547547      !! 
     
    579579      INTEGER , DIMENSION(4)                  ::   itest 
    580580      !!------------------------------------------------------------------- 
    581  
    582       !-------------------------------------------------------------------- 
    583       ! initialisation of variables 
    584       !-------------------------------------------------------------------- 
     581      ! 
     582      ! ---------------------------------------- 
     583      ! distribution over the jpl ice categories 
     584      ! ---------------------------------------- 
     585      ! a gaussian distribution for ice concentration is used 
     586      ! then we check whether the distribution fullfills 
     587      ! volume and area conservation, positivity and ice categories bounds 
    585588      ijpij = SIZE( zhti , 1 ) 
    586589      zht_i(1:ijpij,1:jpl) = 0._wp 
     
    588591      za_i (1:ijpij,1:jpl) = 0._wp 
    589592 
    590       ! ---------------------------------------- 
    591       ! distribution over the jpl ice categories 
    592       ! ---------------------------------------- 
    593593      DO ji = 1, ijpij 
    594594          
     
    604604            END DO 
    605605 
    606             ! initialisation of tests 
    607             itest(:)  = 0 
    608           
    609             i_fill = jpl + 1                                             !==================================== 
    610             DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )  ! iterative loop on i_fill categories 
    611                ! iteration                                               !==================================== 
     606            itest(:) = 0 
     607            i_fill   = jpl + 1                                            !------------------------------------ 
     608            DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )   ! iterative loop on i_fill categories 
     609               !                                                          !------------------------------------ 
    612610               i_fill = i_fill - 1 
    613                 
    614                ! initialisation of ice variables for each try 
     611               ! 
    615612               zht_i(ji,1:jpl) = 0._wp 
    616613               za_i (ji,1:jpl) = 0._wp 
    617614               itest(:)        = 0       
    618615                
    619                ! *** case very thin ice: fill only category 1 
    620                IF ( i_fill == 1 ) THEN 
     616               IF ( i_fill == 1 ) THEN      !-- case very thin ice: fill only category 1 
    621617                  zht_i(ji,1) = zhti(ji) 
    622618                  za_i (ji,1) = zai (ji) 
    623                    
    624                ! *** case ice is thicker: fill categories >1 
    625                ELSE 
    626  
    627                   ! Fill ice thicknesses in the (i_fill-1) cat by hmean  
     619               ELSE                         !-- case ice is thicker: fill categories >1 
     620                  ! thickness 
    628621                  DO jl = 1, i_fill - 1 
    629622                     zht_i(ji,jl) = hi_mean(jl) 
    630623                  END DO 
    631624                   
    632                   ! Concentrations in the (i_fill-1) categories  
     625                  ! concentration 
    633626                  za_i(ji,jl0) = zai(ji) / SQRT(REAL(jpl)) 
    634627                  DO jl = 1, i_fill - 1 
     
    639632                  END DO 
    640633                   
    641                   ! Concentration in the last (i_fill) category 
     634                  ! last category 
    642635                  za_i(ji,i_fill) = zai(ji) - SUM( za_i(ji,1:i_fill-1) ) 
    643                    
    644                   ! Ice thickness in the last (i_fill) category 
    645636                  zV = SUM( za_i(ji,1:i_fill-1) * zht_i(ji,1:i_fill-1) ) 
    646637                  zht_i(ji,i_fill) = ( zhti(ji) * zai(ji) - zV ) / MAX( za_i(ji,i_fill), epsi10 )  
     
    659650                  ENDIF 
    660651                
    661                ENDIF ! case ice is thick or thin 
     652               ENDIF 
    662653             
    663                !--------------------- 
    664654               ! Compatibility tests 
    665                !---------------------  
    666                ! Test 1: area conservation 
    667                zconv = ABS( zai(ji) - SUM( za_i(ji,1:jpl) ) ) 
    668                IF ( zconv < epsi06 ) itest(1) = 1 
     655               zconv = ABS( zai(ji) - SUM( za_i(ji,1:jpl) ) )  
     656               IF ( zconv < epsi06 ) itest(1) = 1                                        ! Test 1: area conservation 
    669657             
    670                ! Test 2: volume conservation 
    671658               zconv = ABS( zhti(ji)*zai(ji) - SUM( za_i(ji,1:jpl)*zht_i(ji,1:jpl) ) ) 
    672                IF ( zconv < epsi06 ) itest(2) = 1 
     659               IF ( zconv < epsi06 ) itest(2) = 1                                        ! Test 2: volume conservation 
    673660                
    674                ! Test 3: thickness of the last category is in-bounds ? 
    675                IF ( zht_i(ji,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1 
     661               IF ( zht_i(ji,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1                  ! Test 3: thickness of the last category is in-bounds ? 
    676662                
    677                ! Test 4: positivity of ice concentrations 
    678663               itest(4) = 1 
    679664               DO jl = 1, i_fill 
    680                   IF ( za_i(ji,jl) < 0._wp ) itest(4) = 0 
     665                  IF ( za_i(ji,jl) < 0._wp ) itest(4) = 0                                ! Test 4: positivity of ice concentrations 
    681666               END DO 
    682                !                                         !============================ 
     667               !                                         !---------------------------- 
    683668            END DO                                       ! end iteration on categories 
    684                !                                         !============================ 
    685          ENDIF ! if zhti > 0 
    686       END DO ! i loop 
    687  
    688       ! ------------------------------------------------ 
    689       ! Adding Snow in each category where za_i is not 0 
    690       ! ------------------------------------------------  
     669               !                                         !---------------------------- 
     670         ENDIF 
     671      END DO 
     672 
     673      ! Add Snow in each category where za_i is not 0 
    691674      DO jl = 1, jpl 
    692675         DO ji = 1, ijpij 
     
    707690#else 
    708691   !!---------------------------------------------------------------------- 
    709    !!   Default option         Dummy module          NO  LIM3 sea-ice model 
     692   !!   Default option         Dummy module           NO ESIM sea-ice model 
    710693   !!---------------------------------------------------------------------- 
    711694#endif 
  • branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icewri.F90

    r8522 r8534  
    22   !!====================================================================== 
    33   !!                     ***  MODULE  icewri  *** 
    4    !!         Ice diagnostics :  write ice output files 
     4   !!   sea-ice : output ice variables 
    55   !!====================================================================== 
    66#if defined key_lim3 
    77   !!---------------------------------------------------------------------- 
    8    !!   'key_lim3'                                      LIM3 sea-ice model 
     8   !!   'key_lim3'                                       ESIM sea-ice model 
    99   !!---------------------------------------------------------------------- 
    1010   !!   ice_wri       : write of the diagnostics variables in ouput file  
     
    2020   ! 
    2121   USE ioipsl         ! 
    22    USE in_out_manager ! 
    23    USE lbclnk         ! 
     22   USE in_out_manager ! I/O manager 
     23   USE iom            ! I/O manager library 
    2424   USE lib_mpp        ! MPP library 
    25    USE iom            ! 
     25   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero) 
     26   USE lbclnk         ! lateral boundary conditions (or mpp links) 
    2627   USE timing         ! Timing 
    27    USE lib_fortran    ! Fortran utilities 
    2828 
    2929   IMPLICIT NONE 
     
    485485#else 
    486486   !!---------------------------------------------------------------------- 
    487    !!   Default option :         Empty module          NO LIM sea-ice model 
     487   !!   Default option :         Empty module         NO ESIM sea-ice model 
    488488   !!---------------------------------------------------------------------- 
    489489#endif 
Note: See TracChangeset for help on using the changeset viewer.