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 10534 for NEMO/trunk – NEMO

Changeset 10534 for NEMO/trunk


Ignore:
Timestamp:
2019-01-16T17:49:45+01:00 (5 years ago)
Author:
clem
Message:

change some more names in the ice

Location:
NEMO/trunk
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/cfgs/SHARED/namelist_ice_ref

    r10532 r10534  
    119119                                      !     = 1  Average N(cat) fluxes then redistribute over the N(cat) ice using T-ice and albedo sensitivity 
    120120                                      !     = 2  Redistribute a single flux over categories 
    121    nice_jules       = 0               !  Jules coupling (0=OFF, 1=EMULATED, 2=ACTIVE) 
     121   ln_cndflx        = .false.         !  Use conduction flux as surface boundary conditions (i.e. for Jules coupling) 
     122      ln_cndemulate = .false.         !     emulate conduction flux (if not provided in the inputs) 
    122123/ 
    123124!------------------------------------------------------------------------------ 
  • NEMO/trunk/src/ICE/ice.F90

    r10532 r10534  
    160160   !                                      !   = 1  Average N(cat) fluxes then redistribute over the N(cat) ice using T-ice and albedo sensitivity 
    161161   !                                      !   = 2  Redistribute a single flux over categories 
    162    INTEGER , PUBLIC            ::   nice_jules           !: Choice of jules coupling  
    163    INTEGER , PUBLIC, PARAMETER ::   np_jules_OFF    = 0  !: no Jules coupling (ice thermodynamics forced via qsr and qns) 
    164    INTEGER , PUBLIC, PARAMETER ::   np_jules_EMULE  = 1  !: emulated Jules coupling via icethd_zdf.F90 (BL99) (1st round compute qcn and qsr_tr, 2nd round use it) 
    165    INTEGER , PUBLIC, PARAMETER ::   np_jules_ACTIVE = 2  !: active Jules coupling                      (SM0L) (compute qcn and qsr_tr via sbcblk.F90 or sbccpl.F90) 
     162   LOGICAL , PUBLIC ::   ln_cndflx        !: use conduction flux as surface boundary condition (instead of qsr and qns)  
     163   LOGICAL , PUBLIC ::   ln_cndemulate    !: emulate conduction flux (if not provided)  
     164   !                                      ! Conduction flux as surface forcing or not 
     165   INTEGER, PUBLIC, PARAMETER ::   np_cnd_OFF = 0  !: no forcing from conduction flux (ice thermodynamics forced via qsr and qns) 
     166   INTEGER, PUBLIC, PARAMETER ::   np_cnd_ON  = 1  !: forcing from conduction flux (SM0L) (compute qcn and qsr_tr via sbcblk.F90 or sbccpl.F90) 
     167   INTEGER, PUBLIC, PARAMETER ::   np_cnd_EMU = 2  !: emulate conduction flux via icethd_zdf.F90 (BL99) (1st round compute qcn and qsr_tr, 2nd round use it) 
    166168 
    167169   !                                     !!** ice-vertical diffusion namelist (namthd_zdf) ** 
     
    281283   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d     !: maximum ice concentration 2d array 
    282284   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qtr_ice_bot    !: transmitted solar radiation under ice 
    283    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t1_ice         !: temperature of the first layer (Jules coupling) [K] 
    284    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   cnd_ice        !: effective conductivity at the top of ice/snow (Jules coupling) [W.m-2.K-1] 
     285   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t1_ice         !: temperature of the first layer                (ln_cndflx=T) [K] 
     286   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   cnd_ice        !: effective conductivity at the top of ice/snow (ln_cndflx=T) [W.m-2.K-1] 
    285287 
    286288   !!---------------------------------------------------------------------- 
  • NEMO/trunk/src/ICE/ice1d.F90

    r10425 r10534  
    4141   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   qcn_ice_1d     !: heat available for snow / ice surface sublimation [W/m2]  
    4242   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   qtr_ice_top_1d !: solar flux transmitted below the ice surface [W/m2]  
    43    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   t1_ice_1d      !: temperature of the 1st layer (Jules coupling) [K] 
    44    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   cnd_ice_1d     !: conductivity at the top of ice/snow (Jules coupling) [W/K/m2] 
     43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   t1_ice_1d      !: temperature of the 1st layer        (ln_cndflx=T) [K] 
     44   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   cnd_ice_1d     !: conductivity at the top of ice/snow (ln_cndflx=T) [W/K/m2] 
    4545 
    4646   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hfx_sum_1d 
  • NEMO/trunk/src/ICE/iceforcing.F90

    r10531 r10534  
    143143         IF( ln_mixcpl        )   CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su, phs=h_s, phi=h_i ) 
    144144         IF( nn_flxdist /= -1 )   CALL ice_flx_dist   ( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_flxdist ) 
    145          SELECT CASE( nice_jules ) 
    146          CASE( np_jules_ACTIVE )  !    compute conduction flux and surface temperature (as in Jules surface module) 
    147                                   CALL blk_ice_qcn    ( ln_virtual_itd, t_su, t_bo, h_s, h_i ) 
    148          END SELECT 
     145         !                        !    compute conduction flux and surface temperature (as in Jules surface module) 
     146         IF( ln_cndflx .AND. .NOT.ln_cndemulate ) & 
     147            &                     CALL blk_ice_qcn    ( ln_virtual_itd, t_su, t_bo, h_s, h_i ) 
    149148      CASE ( jp_purecpl )         !--- coupled formulation 
    150149                                  CALL sbc_cpl_ice_flx( picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su, phs=h_s, phi=h_i ) 
     
    169168 
    170169 
    171    SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_iceflx ) 
     170   SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_flxdist ) 
    172171      !!------------------------------------------------------------------- 
    173172      !!                  ***  ROUTINE ice_flx_dist  *** 
     
    178177      !! ** Method  :   average then redistribute 
    179178      !! 
    180       !! ** Action  :   depends on k_iceflx 
     179      !! ** Action  :   depends on k_flxdist 
    181180      !!                = -1  Do nothing (needs N(cat) fluxes) 
    182181      !!                =  0  Average N(cat) fluxes then apply the average over the N(cat) ice  
     
    185184      !!                =  2  Redistribute a single flux over categories 
    186185      !!------------------------------------------------------------------- 
    187       INTEGER                   , INTENT(in   ) ::   k_iceflx   ! redistributor 
     186      INTEGER                   , INTENT(in   ) ::   k_flxdist  ! redistributor 
    188187      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   ptn_ice    ! ice surface temperature 
    189188      REAL(wp), DIMENSION(:,:,:), INTENT(in   ) ::   palb_ice   ! ice albedo 
     
    211210      END WHERE 
    212211       
    213       SELECT CASE( k_iceflx )       !==  averaged on all ice categories  ==! 
     212      SELECT CASE( k_flxdist )       !==  averaged on all ice categories  ==! 
    214213      ! 
    215214      CASE( 0 , 1 ) 
     
    234233      END SELECT 
    235234      ! 
    236       SELECT CASE( k_iceflx )       !==  redistribution on all ice categories  ==! 
     235      SELECT CASE( k_flxdist )       !==  redistribution on all ice categories  ==! 
    237236      ! 
    238237      CASE( 1 , 2 ) 
     
    268267      INTEGER ::   ios, ioptio   ! Local integer 
    269268      !! 
    270       NAMELIST/namforcing/ rn_cio, rn_blow_s, nn_flxdist, nice_jules 
     269      NAMELIST/namforcing/ rn_cio, rn_blow_s, nn_flxdist, ln_cndflx, ln_cndemulate 
    271270      !!------------------------------------------------------------------- 
    272271      ! 
     
    284283         WRITE(numout,*) '~~~~~~~~~~~~~~~~' 
    285284         WRITE(numout,*) '   Namelist namforcing:' 
    286          WRITE(numout,*) '      drag coefficient for oceanic stress              rn_cio     = ', rn_cio 
    287          WRITE(numout,*) '      coefficient for ice-lead partition of snowfall   rn_blow_s  = ', rn_blow_s 
    288          WRITE(numout,*) '      Multicategory heat flux formulation              nn_flxdist = ', nn_flxdist 
    289          WRITE(numout,*) '      Jules coupling (0=no, 1=emulated, 2=active)      nice_jules = ', nice_jules 
     285         WRITE(numout,*) '      drag coefficient for oceanic stress              rn_cio        = ', rn_cio 
     286         WRITE(numout,*) '      coefficient for ice-lead partition of snowfall   rn_blow_s     = ', rn_blow_s 
     287         WRITE(numout,*) '      Multicategory heat flux formulation              nn_flxdist    = ', nn_flxdist 
     288         WRITE(numout,*) '      Use conduction flux as surface condition         ln_cndflx     = ', ln_cndflx 
     289         WRITE(numout,*) '         emulate conduction flux                       ln_cndemulate = ', ln_cndemulate 
    290290      ENDIF 
    291291      ! 
  • NEMO/trunk/src/ICE/iceistate.F90

    r10527 r10534  
    112112      DO jl = 1, jpl 
    113113         t_su   (:,:,jl) = rt0 * tmask(:,:,1)  ! temp at the surface 
    114          cnd_ice(:,:,jl) = 0._wp               ! initialisation of the effective conductivity at the top of ice/snow (Jules coupling) 
     114         cnd_ice(:,:,jl) = 0._wp               ! initialisation of the effective conductivity at the top of ice/snow (ln_cndflx=T) 
    115115      END DO 
    116116      ! 
  • NEMO/trunk/src/ICE/icestp.F90

    r10531 r10534  
    432432 
    433433      tau_icebfr(:,:)   = 0._wp   ! landfast ice param only (clem: important to keep the init here) 
    434       cnd_ice   (:,:,:) = 0._wp   ! initialisation: effective conductivity at the top of ice/snow (Jules coupling) 
     434      cnd_ice   (:,:,:) = 0._wp   ! initialisation: effective conductivity at the top of ice/snow (ln_cndflx=T) 
    435435      qtr_ice_bot(:,:,:) = 0._wp  ! initialization: part of solar radiation transmitted through the ice needed at least for outputs 
    436436      ! 
  • NEMO/trunk/src/ICE/icethd.F90

    r10531 r10534  
    504504         CALL tab_1d_2d( npti, nptidx(1:npti), qns_ice_1d    (1:npti), qns_ice    (:,:,kl) ) 
    505505         CALL tab_1d_2d( npti, nptidx(1:npti), qtr_ice_bot_1d(1:npti), qtr_ice_bot(:,:,kl) ) 
    506          ! effective conductivity and 1st layer temperature (for Jules coupling) 
     506         ! effective conductivity and 1st layer temperature (ln_cndflx=T) 
    507507         CALL tab_1d_2d( npti, nptidx(1:npti), cnd_ice_1d(1:npti), cnd_ice(:,:,kl) ) 
    508508         CALL tab_1d_2d( npti, nptidx(1:npti), t1_ice_1d (1:npti), t1_ice (:,:,kl) ) 
  • NEMO/trunk/src/ICE/icethd_dh.F90

    r10069 r10534  
    126126      !                       ! Available heat for surface and bottom ablation ! 
    127127      !                       ! ============================================== ! 
    128       SELECT CASE( nice_jules ) 
    129128      ! 
    130       CASE( np_jules_ACTIVE ) 
     129      IF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN 
    131130         ! 
    132131         DO ji = 1, npti 
     
    134133         END DO 
    135134         ! 
    136       CASE( np_jules_OFF , np_jules_EMULE ) 
     135      ELSE 
    137136         ! 
    138137         DO ji = 1, npti 
     
    142141         END DO 
    143142         ! 
    144       END SELECT 
     143      ENDIF 
    145144      ! 
    146145      DO ji = 1, npti 
  • NEMO/trunk/src/ICE/icethd_zdf.F90

    r10069 r10534  
    5757      CASE( np_BL99 )               ! BL99 solver ! 
    5858         !                          !-------------! 
    59          SELECT CASE( nice_jules ) 
    60          !                         ! No Jules coupler ==> default option 
    61          CASE( np_jules_OFF    )   ;   CALL ice_thd_zdf_BL99 ( np_jules_OFF    ) 
    62          ! 
    63          !                         ! Jules coupler is emulated => 1st call to get the needed fields (conduction...) 
    64          !                                                        2nd call to use these fields to calculate heat diffusion    
    65          CASE( np_jules_EMULE  )   ;   CALL ice_thd_zdf_BL99 ( np_jules_EMULE  ) 
    66                                        CALL ice_thd_zdf_BL99 ( np_jules_ACTIVE ) 
    67          ! 
    68          !                         ! Jules coupler is active ==> Met Office default option 
    69          CASE( np_jules_ACTIVE )   ;   CALL ice_thd_zdf_BL99 ( np_jules_ACTIVE ) 
    70          ! 
    71          END SELECT 
     59         IF( .NOT.ln_cndflx ) THEN                           ! No conduction flux ==> default option 
     60            CALL ice_thd_zdf_BL99( np_cnd_OFF ) 
     61         ELSEIF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN   ! Conduction flux as surface boundary condition ==> Met Office default option 
     62            CALL ice_thd_zdf_BL99( np_cnd_ON  ) 
     63         ELSEIF( ln_cndflx .AND.      ln_cndemulate ) THEN   ! Conduction flux is emulated  
     64            CALL ice_thd_zdf_BL99( np_cnd_EMU ) 
     65            CALL ice_thd_zdf_BL99( np_cnd_ON  ) 
     66         ENDIF 
    7267         ! 
    7368      END SELECT 
  • NEMO/trunk/src/ICE/icethd_zdf_bl99.F90

    r10531 r10534  
    3636CONTAINS 
    3737 
    38    SUBROUTINE ice_thd_zdf_BL99( k_jules ) 
     38   SUBROUTINE ice_thd_zdf_BL99( k_cnd ) 
    3939      !!------------------------------------------------------------------- 
    4040      !!                ***  ROUTINE ice_thd_zdf_BL99  *** 
     
    7373      !!           total ice/snow thickness         : h_i_1d, h_s_1d 
    7474      !!------------------------------------------------------------------- 
    75       INTEGER, INTENT(in) ::   k_jules     ! Jules coupling (0=OFF, 1=EMULATED, 2=ACTIVE) 
     75      INTEGER, INTENT(in) ::   k_cnd     ! conduction flux (off, on, emulated) 
    7676      ! 
    7777      INTEGER ::   ji, jk         ! spatial loop index 
     
    164164      ! 
    165165      ! Store initial temperatures and non solar heat fluxes 
    166       IF( k_jules == np_jules_OFF .OR. k_jules == np_jules_EMULE ) THEN 
     166      IF( k_cnd == np_cnd_OFF .OR. k_cnd == np_cnd_EMU ) THEN 
    167167         ! 
    168168         ztsub      (1:npti) = t_su_1d(1:npti)                          ! surface temperature at iteration n-1 
     
    332332         !----------------------------------------! 
    333333         !                                        ! 
    334          !   JULES COUPLING IS OFF OR EMULATED    ! 
     334         !   Conduction flux is off or emulated   ! 
    335335         !                                        ! 
    336336         !----------------------------------------! 
    337337         ! 
    338          IF( k_jules == np_jules_OFF .OR. k_jules == np_jules_EMULE ) THEN 
     338         IF( k_cnd == np_cnd_OFF .OR. k_cnd == np_cnd_EMU ) THEN 
    339339            ! 
    340340            ! ==> The original BL99 temperature computation is used 
     
    581581         !----------------------------------------! 
    582582         !                                        ! 
    583          !      JULES COUPLING IS ACTIVE          ! 
     583         !      Conduction flux is on             ! 
    584584         !                                        ! 
    585585         !----------------------------------------! 
    586586         ! 
    587          ELSEIF( k_jules == np_jules_ACTIVE ) THEN 
     587         ELSEIF( k_cnd == np_cnd_ON ) THEN 
    588588            ! 
    589589            ! ==> we use a modified BL99 solver with conduction flux (qcn_ice) as forcing term 
     
    754754            END DO 
    755755 
    756          ENDIF ! k_jules 
     756         ENDIF ! k_cnd 
    757757          
    758758      END DO  ! End of the do while iterative procedure 
     
    781781      ! --- Diagnose the heat loss due to changing non-solar / conduction flux --- ! 
    782782      ! 
    783       IF( k_jules == np_jules_OFF .OR. k_jules == np_jules_EMULE ) THEN 
     783      IF( k_cnd == np_cnd_OFF .OR. k_cnd == np_cnd_EMU ) THEN 
    784784         ! 
    785785         DO ji = 1, npti 
     
    787787         END DO 
    788788         ! 
    789       ELSEIF( k_jules == np_jules_ACTIVE ) THEN 
     789      ELSEIF( k_cnd == np_cnd_ON ) THEN 
    790790         ! 
    791791         DO ji = 1, npti 
     
    798798      ! --- Diagnose the heat loss due to non-fully converged temperature solution (should not be above 10-4 W-m2) --- ! 
    799799      ! 
    800       IF( k_jules == np_jules_OFF .OR. k_jules == np_jules_ACTIVE ) THEN 
     800      IF( k_cnd == np_cnd_OFF .OR. k_cnd == np_cnd_ON ) THEN 
    801801          
    802802         CALL ice_var_enthalpy        
     
    807807               &                   SUM( e_s_1d(ji,1:nlay_s) ) * h_s_1d(ji) * r1_nlay_s ) 
    808808             
    809             IF( k_jules == np_jules_OFF ) THEN 
     809            IF( k_cnd == np_cnd_OFF ) THEN 
    810810                
    811811               IF( t_su_1d(ji) < rt0 ) THEN  ! case T_su < 0degC 
     
    817817               ENDIF 
    818818                
    819             ELSEIF( k_jules == np_jules_ACTIVE ) THEN 
     819            ELSEIF( k_cnd == np_cnd_ON ) THEN 
    820820             
    821821               zhfx_err    = ( qcn_ice_top_1d(ji) + qtr_ice_top_1d(ji) - zradtr_i(ji,nlay_i) - qcn_ice_bot_1d(ji)  & 
     
    834834      ENDIF 
    835835      ! 
    836       !--------------------------------------------------------------------------------------- 
    837       ! 11) Jules coupling: reset inner snow and ice temperatures, update conduction fluxes 
    838       !--------------------------------------------------------------------------------------- 
     836      !-------------------------------------------------------------------- 
     837      ! 11) reset inner snow and ice temperatures, update conduction fluxes 
     838      !-------------------------------------------------------------------- 
    839839      ! effective conductivity and 1st layer temperature (needed by Met Office) 
    840840      DO ji = 1, npti 
     
    851851      END DO 
    852852      ! 
    853       IF( k_jules == np_jules_EMULE ) THEN 
     853      IF( k_cnd == np_cnd_EMU ) THEN 
    854854         ! Restore temperatures to their initial values 
    855855         t_s_1d    (1:npti,:) = ztsold        (1:npti,:) 
  • NEMO/trunk/src/OCE/SBC/sbcblk.F90

    r10531 r10534  
    1717   !!                 !                        ==> based on AeroBulk (http://aerobulk.sourceforge.net/) 
    1818   !!            4.0  !  2016-10  (G. Madec)  introduce a sbc_blk_init routine 
    19    !!            4.0  !  2016-10  (M. Vancoppenolle)  Introduce Jules emulator (M. Vancoppenolle)  
     19   !!            4.0  !  2016-10  (M. Vancoppenolle)  Introduce conduction flux emulator (M. Vancoppenolle)  
    2020   !!---------------------------------------------------------------------- 
    2121 
     
    3131   !!   blk_ice_tau   : provide the air-ice stress 
    3232   !!   blk_ice_flx   : provide the heat and mass fluxes at air-ice interface 
    33    !!   blk_ice_qcn   : provide ice surface temperature and snow/ice conduction flux (emulating JULES coupler) 
     33   !!   blk_ice_qcn   : provide ice surface temperature and snow/ice conduction flux (emulating conduction flux) 
    3434   !!   Cdn10_Lupkes2012 : Lupkes et al. (2012) air-ice drag 
    3535   !!   Cdn10_Lupkes2015 : Lupkes et al. (2015) air-ice drag  
     
    688688   !!   blk_ice_tau : provide the air-ice stress 
    689689   !!   blk_ice_flx : provide the heat and mass fluxes at air-ice interface 
    690    !!   blk_ice_qcn : provide ice surface temperature and snow/ice conduction flux (emulating JULES coupler) 
     690   !!   blk_ice_qcn : provide ice surface temperature and snow/ice conduction flux (emulating conduction flux) 
    691691   !!   Cdn10_Lupkes2012 : Lupkes et al. (2012) air-ice drag 
    692692   !!   Cdn10_Lupkes2015 : Lupkes et al. (2015) air-ice drag  
     
    932932      !! ** Purpose :   Compute surface temperature and snow/ice conduction flux 
    933933      !!                to force sea ice / snow thermodynamics 
    934       !!                in the case JULES coupler is emulated 
     934      !!                in the case conduction flux is emulated 
    935935      !!                 
    936936      !! ** Method  :   compute surface energy balance assuming neglecting heat storage 
  • NEMO/trunk/src/OCE/SBC/sbccpl.F90

    r10425 r10534  
    20122012      !                                                      !      Transmitted Qsr      !   [W/m2] 
    20132013      !                                                      ! ========================= ! 
    2014       SELECT CASE( nice_jules ) 
    2015       CASE( np_jules_OFF    )       !==  No Jules coupler  ==! 
     2014      IF( .NOT.ln_cndflx ) THEN                              !==  No conduction flux as surface forcing  ==! 
    20162015         ! 
    20172016         !                    ! ===> used prescribed cloud fraction representative for polar oceans in summer (0.81) 
     
    20222021         WHERE( phi(:,:,:) <= 0.1_wp )   qtr_ice_top(:,:,:) = qsr_ice(:,:,:)   ! thin ice transmits all solar radiation 
    20232022         !      
    2024       CASE( np_jules_ACTIVE )       !==  Jules coupler is active  ==! 
     2023      ELSEIF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN      !==  conduction flux as surface forcing  ==! 
    20252024         ! 
    20262025         !                    ! ===> here we must receive the qtr_ice_top array from the coupler 
     
    20282027         qtr_ice_top(:,:,:) = 0._wp 
    20292028         ! 
    2030       END SELECT 
     2029      ENDIF 
    20312030      ! 
    20322031#endif 
Note: See TracChangeset for help on using the changeset viewer.