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 4147 for branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/ICB – NEMO

Ignore:
Timestamp:
2013-11-04T12:51:55+01:00 (10 years ago)
Author:
cetlod
Message:

merge in dev_LOCEAN_2013, the 1st development branch dev_r3853_CNRS9_Confsetting, from its starting point ( r3853 ) on the trunk: see ticket #1169

Location:
branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/ICB
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/ICB/icb_oce.F90

    r3614 r4147  
    4444   PUBLIC   icb_alloc   ! routine called by icb_init in icbini.F90 module 
    4545 
    46    INTEGER, PUBLIC, PARAMETER ::   nclasses = 10   !: Number of ice bergs classes 
     46INTEGER, PUBLIC, PARAMETER ::   nclasses = 10   !: Number of icebergs classes    
     47!!INTEGER, PUBLIC & 
     48!!#if !defined key_agrif  
     49!!           , PARAMETER & 
     50!!#endif 
     51!!     :: & 
     52!!     nclasses = 10   !: Number of icebergs classes 
    4753   INTEGER, PUBLIC, PARAMETER ::   nkounts  =  3   !: Number of integers combined for unique naming 
    4854 
     
    109115 
    110116   !                                                         !!* namberg namelist parameters (and defaults) ** 
    111    LOGICAL , PUBLIC ::   ln_bergdia               = .true.    !: Calculate budgets 
    112    INTEGER , PUBLIC ::   nn_verbose_level         = 0         !: Turn on debugging when level > 0 
    113    INTEGER , PUBLIC ::   nn_test_icebergs         = 0         !: Create icebergs in absence of a restart file from the supplied class nb 
    114    REAL(wp), PUBLIC, DIMENSION(4) ::   rn_test_box = (/ 0._wp, 1._wp, 0._wp, 1._wp /)   !: lon1,lon2,lat1,lat2 box to create them in 
    115    INTEGER , PUBLIC ::   nn_sample_rate           = 0         !: Timesteps between sampling of position for trajectory storage 
    116    INTEGER , PUBLIC ::   nn_verbose_write         = 15        !: timesteps between verbose messages 
    117    REAL(wp), PUBLIC ::   rn_rho_bergs             = 850._wp   !: Density of icebergs 
    118    REAL(wp), PUBLIC ::   rn_LoW_ratio             = 1.5_wp    !: Initial ratio L/W for newly calved icebergs 
    119    REAL(wp), PUBLIC ::   rn_bits_erosion_fraction = 0.        !: Fraction of erosion melt flux to divert to bergy bits 
    120    REAL(wp), PUBLIC ::   rn_sicn_shift            = 0._wp     !: Shift of sea-ice concentration in erosion flux modulation (0<sicn_shift<1) 
    121    LOGICAL , PUBLIC ::   ln_operator_splitting    = .true.    !: Use first order operator splitting for thermodynamics 
    122    LOGICAL , PUBLIC ::   ln_passive_mode          = .false.   !: iceberg - ocean decoupling 
    123    LOGICAL , PUBLIC ::   ln_time_average_weight   = .false.   !: Time average the weight on the ocean    !!gm I don't understand that ! 
    124    REAL(wp), PUBLIC ::   rn_speed_limit           = 0._wp     !: CFL speed limit for a berg 
     117   LOGICAL , PUBLIC ::   ln_bergdia                      !: Calculate budgets 
     118   INTEGER , PUBLIC ::   nn_verbose_level                !: Turn on debugging when level > 0 
     119   INTEGER , PUBLIC ::   nn_test_icebergs                !: Create icebergs in absence of a restart file from the supplied class nb 
     120   REAL(wp), PUBLIC, DIMENSION(4) ::   rn_test_box       !: lon1,lon2,lat1,lat2 box to create them in 
     121   INTEGER , PUBLIC ::   nn_sample_rate                  !: Timesteps between sampling of position for trajectory storage 
     122   INTEGER , PUBLIC ::   nn_verbose_write                !: timesteps between verbose messages 
     123   REAL(wp), PUBLIC ::   rn_rho_bergs                    !: Density of icebergs 
     124   REAL(wp), PUBLIC ::   rn_LoW_ratio                    !: Initial ratio L/W for newly calved icebergs 
     125   REAL(wp), PUBLIC ::   rn_bits_erosion_fraction        !: Fraction of erosion melt flux to divert to bergy bits 
     126   REAL(wp), PUBLIC ::   rn_sicn_shift                   !: Shift of sea-ice concentration in erosion flux modulation (0<sicn_shift<1) 
     127   LOGICAL , PUBLIC ::   ln_operator_splitting           !: Use first order operator splitting for thermodynamics 
     128   LOGICAL , PUBLIC ::   ln_passive_mode                 !: iceberg - ocean decoupling 
     129   LOGICAL , PUBLIC ::   ln_time_average_weight          !: Time average the weight on the ocean    !!gm I don't understand that ! 
     130   REAL(wp), PUBLIC ::   rn_speed_limit                  !: CFL speed limit for a berg 
    125131   ! 
    126132   !                                     ! Mass thresholds between iceberg classes [kg] 
    127    REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_initial_mass      = (/8.8e07, 4.1e08, 3.3e09, 1.8e10, 3.8e10,   & 
    128       &                                                                7.5e10, 1.2e11, 2.2e11, 3.9e11, 7.4e11/) 
    129    !                                     ! Fraction of calving to apply to this class [non-dim] 
    130    REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_distribution      = (/0.25  , 0.12  , 0.15  , 0.18  , 0.12  ,   & 
    131       &                                                                0.07  , 0.03  , 0.03  , 0.03  , 0.02  /) 
    132    !                                     ! Ratio between effective and real iceberg mass (non-dim) 
    133    REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_mass_scaling      = (/2000. ,  200. ,   50. ,   20. ,   10. ,   & 
    134       &                                                                   5. ,    2. ,    1. ,    1. ,    1. /) 
    135    !                                     ! Total thickness of newly calved bergs [m] 
    136    REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_initial_thickness = (/  40. ,   67. ,  133. ,  175. ,  250. ,   & 
    137       &                                                                 250. ,  250. ,  250. ,  250. ,  250./) 
    138  
    139    ! Single instance of an icebergs type initialised in icebergs_init and updated in icebergs_run 
     133   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_initial_mass      ! Fraction of calving to apply to this class [non-dim] 
     134   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_distribution      ! Ratio between effective and real iceberg mass (non-dim) 
     135   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_mass_scaling      ! Total thickness of newly calved bergs [m] 
     136   REAL(wp), DIMENSION(nclasses), PUBLIC ::   rn_initial_thickness !  Single instance of an icebergs type initialised in icebergs_init and updated in icebergs_run 
    140137   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   src_calving, src_calving_hflx    !: accumulate input ice 
    141138   INTEGER , PUBLIC             , SAVE                     ::   numicb                           !: iceberg IO 
     
    168165      ! 
    169166      icb_alloc = 0 
    170       ALLOCATE( berg_grid                      ,                                               & 
     167!!      ALLOCATE( berg_grid                      ,                                               & 
     168      ALLOCATE(                                                                                & 
    171169         &      berg_grid%calving    (jpi,jpj) , berg_grid%calving_hflx (jpi,jpj)          ,   & 
    172170         &      berg_grid%stored_heat(jpi,jpj) , berg_grid%floating_melt(jpi,jpj)          ,   & 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/ICB/icbini.F90

    r3785 r4147  
    3535   PUBLIC   icb_init  ! routine called in nemogcm.F90 module 
    3636 
    37    CHARACTER(len=100) ::   cn_dir = './'   ! Root directory for location of icb files 
     37   CHARACTER(len=100) ::   cn_dir          ! Root directory for location of icb files 
    3838   TYPE(FLD_N)        ::   sn_icb          ! information about the calving file to be read 
    3939 
     
    344344      !!---------------------------------------------------------------------- 
    345345      INTEGER  ::   jn      ! dummy loop indices 
     346      INTEGER  ::   ios     ! Local integer output status for namelist read 
    346347      REAL(wp) ::   zfact   ! local scalar 
    347348      ! 
     
    354355      !!---------------------------------------------------------------------- 
    355356 
    356       ! (NB: frequency positive => hours, negative => months) 
    357       !            !   file     ! frequency !  variable  ! time intep !  clim  ! 'yearly' or ! weights  ! rotation   ! 
    358       !            !   name     !  (hours)  !   name     !   (T/F)    !  (T/F) !  'monthly'  ! filename ! pairs      ! 
    359       sn_icb = FLD_N( 'calving' ,    -1     , 'calving'  ,  .TRUE.    , .TRUE. ,   'yearly'  , ''       , ''         ) 
    360  
    361       REWIND( numnam )              ! Namelist namrun : iceberg parameters 
    362       READ  ( numnam, namberg ) 
    363        
     357#if !defined key_agrif 
     358      REWIND( numnam_ref )              ! Namelist namberg in reference namelist : Iceberg parameters 
     359      READ  ( numnam_ref, namberg, IOSTAT = ios, ERR = 901) 
     360901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namberg in reference namelist', lwp ) 
     361      REWIND( numnam_cfg )              ! Namelist namberg in configuration namelist : Iceberg parameters 
     362      READ  ( numnam_cfg, namberg, IOSTAT = ios, ERR = 902 ) 
     363902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namberg in configuration namelist', lwp ) 
     364      WRITE ( numond, namberg ) 
     365#else 
     366      IF(lwp) THEN 
     367         WRITE(numout,*) 
     368         WRITE(numout,*) 'icbini :   AGRIF is not compatible with namelist namberg :  ' 
     369         WRITE(numout,*) '         definition of rn_initial_mass(nclasses) with nclasses as PARAMETER ' 
     370         WRITE(numout,*) ' namelist namberg not read' 
     371      ENDIF 
     372      ln_icebergs = .false.       
     373#endif    
    364374      IF( .NOT. ln_icebergs ) THEN   ! no icebergs 
    365375         IF(lwp) THEN 
    366376            WRITE(numout,*) 
    367             WRITE(numout,*) 'icb_nam :  ln_icebergs = F , NO icebergs used' 
     377            WRITE(numout,*) 'icbini :   Namelist namberg ln_icebergs = F , NO icebergs used' 
    368378            WRITE(numout,*) '~~~~~~~~ ' 
    369379         ENDIF 
Note: See TracChangeset for help on using the changeset viewer.