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 8933 for branches/2017/dev_CNRS_2017/NEMOGCM/NEMO – NEMO

Ignore:
Timestamp:
2017-12-07T12:14:23+01:00 (6 years ago)
Author:
clem
Message:

dev_CNRS_2017: raw commit of the Met-Office specifics for coupling with their Earth system model. It is not yet tested and debuging is expected

Location:
branches/2017/dev_CNRS_2017/NEMOGCM/NEMO
Files:
11 edited

Legend:

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

    r8930 r8933  
    313313   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d     !: maximum ice concentration 2d array 
    314314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ftr_ice        !: transmitted solar radiation under ice 
     315   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t1_ice         !: temperature of the first layer (Jules coupling) [K] 
     316   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   cnd_ice        !: effective conductivity at the top of ice/snow (Jules coupling) [W.m-2.K-1] 
    315317 
    316318   !!---------------------------------------------------------------------- 
     
    325327   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_su      !: Sea-Ice Surface Temperature (K) 
    326328   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   s_i       !: Sea-Ice Bulk salinity (ppt) 
    327    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sv_i     !: Sea-Ice Bulk salinity times volume per area (ppt.m) 
     329   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sv_i      !: Sea-Ice Bulk salinity times volume per area (ppt.m) 
    328330   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   o_i       !: Sea-Ice Age (s) 
    329331   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   oa_i      !: Sea-Ice Age times ice area (s) 
     
    364366   !! * Old values of global variables 
    365367   !!---------------------------------------------------------------------- 
    366    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, h_s_b, h_i_b  !: snow and ice volumes/thickness 
    367    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, sv_i_b, oa_i_b        !: 
     368   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, h_s_b, h_i_b    !: snow and ice volumes/thickness 
     369   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, sv_i_b, oa_i_b         !: 
    368370   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                         !: snow heat content 
    369371   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                         !: ice temperatures 
     
    449451      ! * Ice global state variables 
    450452      ii = ii + 1 
    451       ALLOCATE( ftr_ice(jpi,jpj,jpl) ,                                                 & 
    452          &      h_i   (jpi,jpj,jpl) , a_i   (jpi,jpj,jpl) , v_i  (jpi,jpj,jpl) ,     & 
    453          &      v_s    (jpi,jpj,jpl) , h_s  (jpi,jpj,jpl) , t_su  (jpi,jpj,jpl) ,     & 
    454          &      s_i   (jpi,jpj,jpl) , sv_i (jpi,jpj,jpl) , o_i  (jpi,jpj,jpl) ,     & 
    455          &      oa_i   (jpi,jpj,jpl) , bv_i  (jpi,jpj,jpl) ,  STAT=ierr(ii) ) 
    456       ii = ii + 1 
    457       ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) ,                                       & 
    458          &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , at_i (jpi,jpj) , ato_i(jpi,jpj) ,     & 
    459          &      et_i (jpi,jpj) , et_s (jpi,jpj) , tm_i (jpi,jpj) , bvm_i(jpi,jpj) ,     & 
    460          &      sm_i (jpi,jpj) , tm_su(jpi,jpj) , hm_i(jpi,jpj) , hm_s(jpi,jpj) ,     & 
    461          &      om_i (jpi,jpj) , tau_icebfr(jpi,jpj)                              , STAT=ierr(ii) ) 
     453      ALLOCATE( ftr_ice(jpi,jpj,jpl) , cnd_ice(jpi,jpj,jpl) , t1_ice(jpi,jpj,jpl) , & 
     454         &      h_i (jpi,jpj,jpl) , a_i (jpi,jpj,jpl) , v_i (jpi,jpj,jpl) ,     & 
     455         &      v_s (jpi,jpj,jpl) , h_s (jpi,jpj,jpl) , t_su(jpi,jpj,jpl) ,     & 
     456         &      s_i (jpi,jpj,jpl) , sv_i(jpi,jpj,jpl) , o_i (jpi,jpj,jpl) ,     & 
     457         &      oa_i(jpi,jpj,jpl) , bv_i(jpi,jpj,jpl) ,  STAT=ierr(ii) ) 
     458      ii = ii + 1 
     459      ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) ,                                      & 
     460         &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , at_i(jpi,jpj) , ato_i(jpi,jpj) ,     & 
     461         &      et_i (jpi,jpj) , et_s (jpi,jpj) , tm_i(jpi,jpj) , bvm_i(jpi,jpj) ,     & 
     462         &      sm_i (jpi,jpj) , tm_su(jpi,jpj) , hm_i(jpi,jpj) , hm_s (jpi,jpj) ,     & 
     463         &      om_i (jpi,jpj) , tau_icebfr(jpi,jpj)                             , STAT=ierr(ii) ) 
    462464      ii = ii + 1 
    463465      ALLOCATE( t_s(jpi,jpj,nlay_s,jpl) , e_s(jpi,jpj,nlay_s,jpl) , STAT=ierr(ii) ) 
     
    466468 
    467469      ii = ii + 1 
    468       ALLOCATE( a_ip(jpi,jpj,jpl) , v_ip(jpi,jpj,jpl) , a_ip_frac(jpi,jpj,jpl) , & 
    469          &      h_ip(jpi,jpj,jpl) , STAT = ierr(ii) ) 
     470      ALLOCATE( a_ip(jpi,jpj,jpl) , v_ip(jpi,jpj,jpl) , a_ip_frac(jpi,jpj,jpl) , h_ip(jpi,jpj,jpl) , STAT = ierr(ii) ) 
    470471      ii = ii + 1 
    471472      ALLOCATE( at_ip(jpi,jpj) , vt_ip(jpi,jpj) , STAT = ierr(ii) ) 
     
    473474      ! * Old values of global variables 
    474475      ii = ii + 1 
    475       ALLOCATE( v_s_b  (jpi,jpj,jpl) , v_i_b  (jpi,jpj,jpl) , h_s_b(jpi,jpj,jpl)        , h_i_b(jpi,jpj,jpl)        ,   & 
    476          &      a_i_b  (jpi,jpj,jpl) , sv_i_b(jpi,jpj,jpl) , e_i_b (jpi,jpj,nlay_i,jpl) , e_s_b (jpi,jpj,nlay_s,jpl) ,   & 
    477          &      oa_i_b (jpi,jpj,jpl)                                                     , STAT=ierr(ii) ) 
     476      ALLOCATE( v_s_b  (jpi,jpj,jpl) , v_i_b (jpi,jpj,jpl) , h_s_b(jpi,jpj,jpl)        , h_i_b(jpi,jpj,jpl)        ,   & 
     477         &      a_i_b  (jpi,jpj,jpl) , sv_i_b(jpi,jpj,jpl) , e_i_b(jpi,jpj,nlay_i,jpl) , e_s_b(jpi,jpj,nlay_s,jpl) ,   & 
     478         &      oa_i_b (jpi,jpj,jpl)                                                   , STAT=ierr(ii) ) 
    478479      ii = ii + 1 
    479480      ALLOCATE( u_ice_b(jpi,jpj) , v_ice_b(jpi,jpj) , at_i_b(jpi,jpj) , STAT=ierr(ii) ) 
     
    491492      ! * SIMIP diagnostics 
    492493      ii = ii + 1 
    493       ALLOCATE( t_si (jpi,jpj,jpl)    , tm_si(jpi,jpj)        ,    &  
    494                 diag_fc_bo(jpi,jpj)   , diag_fc_su(jpi,jpj)   ,    & 
    495                 STAT = ierr(ii) ) 
     494      ALLOCATE( t_si (jpi,jpj,jpl) , tm_si(jpi,jpj) , diag_fc_bo(jpi,jpj) , diag_fc_su(jpi,jpj) , STAT = ierr(ii) ) 
    496495 
    497496      ice_alloc = MAXVAL( ierr(:) ) 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3/ice1d.F90

    r8882 r8933  
    3838    
    3939   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   qml_ice_1d     !: heat available for snow / ice surface melting [W/m2]  
    40    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   qcn_ice_1d     !: heat available for snow / ice surface sublimation¬ [W/m2]  
    41    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   qsr_ice_tr_1d  !: solar flux transmitted below the ice surface¬ [W/m2]  
     40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   qcn_ice_1d     !: heat available for snow / ice surface sublimation [W/m2]  
     41   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   qsr_ice_tr_1d  !: solar flux transmitted below the ice surface [W/m2]  
     42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   t1_ice_1d      !: temperature of the 1st layer (Jules coupling) [K] 
     43   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   cnd_ice_1d     !: conductivity at the top of ice/snow (Jules coupling) [W/K/m2] 
    4244 
    4345   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hfx_sum_1d 
     
    176178 
    177179      ii = 1 
    178       ALLOCATE( nptidx   (jpij) ,   & 
    179          &      qlead_1d (jpij) , ftr_ice_1d(jpij) , qsr_ice_1d (jpij) ,   & 
    180          &      qns_ice_1d(jpij)  ,   & 
    181          &      qml_ice_1d(jpij), qcn_ice_1d(jpij) , qsr_ice_tr_1d(jpij) , & 
    182          &      t_bo_1d   (jpij) ,                                         & 
    183          &      hfx_sum_1d(jpij) , hfx_bom_1d(jpij) ,hfx_bog_1d(jpij) ,    &  
    184          &      hfx_dif_1d(jpij) , hfx_opw_1d(jpij) ,hfx_dyn_1d(jpij) ,    & 
     180      ALLOCATE( nptidx    (jpij) ,   & 
     181         &      qlead_1d  (jpij) , ftr_ice_1d(jpij) , qsr_ice_1d (jpij) ,   & 
     182         &      qns_ice_1d(jpij) ,   & 
     183         &      qml_ice_1d(jpij) , qcn_ice_1d(jpij) , qsr_ice_tr_1d(jpij) , & 
     184         &      cnd_ice_1d(jpij) , t1_ice_1d(jpij)  , t_bo_1d   (jpij) ,      & 
     185         &      hfx_sum_1d(jpij) , hfx_bom_1d(jpij) , hfx_bog_1d(jpij) ,    &  
     186         &      hfx_dif_1d(jpij) , hfx_opw_1d(jpij) , hfx_dyn_1d(jpij) ,    & 
    185187         &      rn_amax_1d(jpij) ,                                         & 
    186188         &      hfx_thd_1d(jpij) , hfx_spr_1d(jpij) ,                      & 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3/iceistate.F90

    r8885 r8933  
    354354         ! 
    355355         tn_ice (:,:,:) = t_su (:,:,:) 
    356          ! 
     356         t1_ice (:,:,:) = t_i (:,:,1,:)   ! initialisation of 1st layer temp for coupled simu 
     357         cnd_ice(:,:,:) = 0._wp           ! initialisation of the effective conductivity at the top of ice/snow (Jules coupling) 
     358 
    357359         ! Melt pond volume and fraction 
    358360         IF ( ln_pnd_CST .OR. ln_pnd_H12 ) THEN   ;   zfac = 1._wp 
     
    388390            END DO 
    389391         END DO 
    390          ! 
     392 
     393         tn_ice (:,:,:) = t_i (:,:,1,:) 
     394         t1_ice (:,:,:) = t_i (:,:,1,:)   ! initialisation of 1st layer temp for coupled simu 
     395         cnd_ice(:,:,:) = 0._wp           ! initialisation of the effective conductivity at the top of ice/snow (Jules coupling) 
     396          
    391397         a_ip(:,:,:)      = 0._wp 
    392398         v_ip(:,:,:)      = 0._wp 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3/icerst.F90

    r8882 r8933  
    1919   USE ice            ! sea-ice variables 
    2020   USE dom_oce        ! ocean domain 
    21    USE sbc_oce , ONLY : nn_fsbc 
     21   USE sbc_oce , ONLY : nn_fsbc, ln_meto_cpl 
    2222   USE icectl 
    2323   ! 
     
    129129      CALL iom_rstput( iter, nitrst, numriw, 'a_i' , a_i  ) 
    130130      CALL iom_rstput( iter, nitrst, numriw, 't_su', t_su ) 
    131       ! 
    132131      ! Melt ponds 
    133132      CALL iom_rstput( iter, nitrst, numriw, 'a_ip', a_ip ) 
    134133      CALL iom_rstput( iter, nitrst, numriw, 'v_ip', v_ip ) 
    135       ! 
    136134!!gm dangerous !!!!!  ===>>>> better reading writing all snow layers ! 
    137135      ! Snow enthalpy (1st snow layer only) 
    138136      z3d = e_s(:,:,1,:) 
    139137      CALL iom_rstput( iter, nitrst, numriw, 'tempt_sl1' , z3d ) 
    140       ! 
    141138      ! Ice enthalpy (all ice layers) 
    142139      DO jk = 1, nlay_i  
     
    146143         CALL iom_rstput( iter, nitrst, numriw, znam , z3d ) 
    147144      END DO 
    148       ! 
    149145      ! ice velocity 
    150146      CALL iom_rstput( iter, nitrst, numriw, 'u_ice', u_ice ) ! u_ice 
    151147      CALL iom_rstput( iter, nitrst, numriw, 'v_ice', v_ice ) ! v_ice 
    152        
     148      ! fields needed for Jules coupling 
     149      IF (ln_meto_cpl) THEN 
     150         CALL iom_rstput( iter, nitrst, numriw, 'cnd_ice', cnd_ice ) 
     151         CALL iom_rstput( iter, nitrst, numriw, 't1_ice' , t1_ice  ) 
     152      ENDIF 
     153      ! 
     154 
    153155      ! close restart file 
    154156      ! ------------------ 
     
    207209      CALL iom_get( numrir, jpdom_autoglo, 'a_i' , a_i  ) 
    208210      CALL iom_get( numrir, jpdom_autoglo, 't_su', t_su ) 
    209       ! 
    210211      ! Melt ponds 
    211212      id1 = iom_varid( numrir, 'a_ip_htc01' , ldstop = .FALSE. ) 
     
    218219         v_ip(:,:,:) = 0._wp 
    219220      ENDIF 
    220       ! 
    221221!!gm dangerous !!!!!  ===>>>> better reading writing all snow layers ! 
    222222      ! Snow enthalpy (1st snow layer only) 
    223223      CALL iom_get( numrir, jpdom_autoglo, 'tempt_sl1' , z3d ) 
    224224      e_s(:,:,1,:) = z3d 
    225       ! 
    226225      ! Ice enthalpy (all ice layers) 
    227226      DO jk = 1, nlay_i  
     
    231230         e_i(:,:,jk,:) = z3d(:,:,:) 
    232231      END DO 
    233       ! 
    234232      ! ice velocity 
    235233      CALL iom_get( numrir, jpdom_autoglo, 'u_ice', u_ice ) 
    236234      CALL iom_get( numrir, jpdom_autoglo, 'v_ice', v_ice ) 
     235      ! fields needed for Jules coupling 
     236      IF (ln_meto_cpl) THEN 
     237         CALL iom_get( numrir, jpdom_autoglo, 'cnd_ice', cnd_ice ) 
     238         CALL iom_get( numrir, jpdom_autoglo, 't1_ice' , t1_ice  ) 
     239      ENDIF 
    237240 
    238241   END SUBROUTINE ice_rst_read 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3/icestp.F90

    r8882 r8933  
    319319         IF(lwp) WRITE(numout,*) '   nn_monocat forced to 0 as jpl>1, i.e. multi-category case is chosen' 
    320320      ENDIF 
     321      ! 
     322     IF( ln_cpl .AND. nn_cats_cpl /= 1 .AND. nn_cats_cpl /= jpl ) THEN 
     323        CALL ctl_stop( 'STOP', 'par_init: in coupled mode, nn_cats_cpl should be either 1 or jpl' ) 
     324     ENDIF 
    321325!     IF ( jpl == 1 .AND. nn_monocat == 0 ) THEN 
    322326!        CALL ctl_stop( 'STOP', 'par_init : if jpl=1 then nn_monocat should be between 1 and 4' ) 
     
    410414 
    411415      ! SIMIP diagnostics 
    412       diag_fc_bo(:,:)    = 0._wp ; diag_fc_su(:,:)    = 0._wp 
    413  
    414       tau_icebfr(:,:) = 0._wp; ! landfast ice param only (clem: important to keep the init here) 
     416      diag_fc_bo(:,:) = 0._wp ; diag_fc_su(:,:) = 0._wp 
     417 
     418      tau_icebfr(:,:)   = 0._wp   ! landfast ice param only (clem: important to keep the init here) 
     419      cnd_ice   (:,:,:) = 0._wp   ! initialisation of the effective conductivity at the top of ice/snow (Jules coupling) 
    415420       
    416421   END SUBROUTINE diag_set0 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3/icethd.F90

    r8882 r8933  
    527527         CALL tab_1d_2d( npti, nptidx(1:npti), qns_ice_1d(1:npti), qns_ice(:,:,kl) ) 
    528528         CALL tab_1d_2d( npti, nptidx(1:npti), ftr_ice_1d(1:npti), ftr_ice(:,:,kl) ) 
    529          ! 
     529         ! effective conductivity and 1st layer temperature (for Jules coupling) 
     530         CALL tab_1d_2d( npti, nptidx(1:npti), cnd_ice_1d(1:npti), cnd_ice(:,:,kl) ) 
     531         CALL tab_1d_2d( npti, nptidx(1:npti), t1_ice_1d (1:npti), t1_ice (:,:,kl) ) 
    530532         ! SIMIP diagnostics          
    531533         CALL tab_1d_2d( npti, nptidx(1:npti), t_si_1d      (1:npti), t_si(:,:,kl) ) 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/LIM_SRC_3/icethd_zdf.F90

    r8882 r8933  
    840840 
    841841      IF ( ( k_jules == np_zdf_jules_OFF ) .OR. ( k_jules == np_zdf_jules_RCV ) ) THEN ! OFF 
    842        
     842          
    843843         CALL ice_thd_enmelt        
    844  
     844          
    845845         !     zhfx_err = correction on the diagnosed heat flux due to non-convergence of the algorithm used to solve heat equation 
    846846         DO ji = 1, npti 
    847847            zdq = - zq_ini(ji) + ( SUM( e_i_1d(ji,1:nlay_i) ) * h_i_1d(ji) * r1_nlay_i +  & 
    848848               &                   SUM( e_s_1d(ji,1:nlay_s) ) * h_s_1d(ji) * r1_nlay_s ) 
    849                 
     849             
    850850            IF ( ( k_jules == np_zdf_jules_OFF ) ) THEN 
    851851                
    852                   IF( t_su_1d(ji) < rt0 ) THEN  ! case T_su < 0degC 
    853                      zhfx_err = ( qns_ice_1d(ji) + qsr_ice_1d(ji)    - zradtr_i(ji,nlay_i) - fc_bo_i(ji) + zdq * r1_rdtice ) * a_i_1d(ji)  
    854                   ELSE                          ! case T_su = 0degC 
    855                      zhfx_err = ( fc_su(ji)      + qsr_ice_tr_1d(ji) - zradtr_i(ji,nlay_i) - fc_bo_i(ji) + zdq * r1_rdtice ) * a_i_1d(ji) 
    856                   ENDIF 
    857              
     852               IF( t_su_1d(ji) < rt0 ) THEN  ! case T_su < 0degC 
     853                  zhfx_err = ( qns_ice_1d(ji) + qsr_ice_1d(ji)    - zradtr_i(ji,nlay_i) - fc_bo_i(ji) + zdq * r1_rdtice )*a_i_1d(ji) 
     854               ELSE                          ! case T_su = 0degC 
     855                  zhfx_err = ( fc_su(ji)      + qsr_ice_tr_1d(ji) - zradtr_i(ji,nlay_i) - fc_bo_i(ji) + zdq * r1_rdtice )*a_i_1d(ji) 
     856               ENDIF 
     857                
    858858            ELSE ! RCV CASE 
    859859             
     
    892892      ! 11) Jules coupling: reset inner snow and ice temperatures, update conduction fluxes 
    893893      !--------------------------------------------------------------------------------------- 
     894      ! effective conductivity and 1st layer temperature (Jules coupling) 
     895      DO ji = 1, npti 
     896         IF (h_s_1d(ji) > 0.1 ) THEN  
     897             cnd_ice_1d(ji) = 2._wp * zkappa_s(ji,0) 
     898         ELSE 
     899             IF (h_i_1d(ji) > 0.1 ) THEN 
     900                 cnd_ice_1d(ji) = 2._wp * zkappa_i(ji,0) 
     901             ELSE 
     902                 cnd_ice_1d(ji) = 2._wp * ztcond_i(ji,0) / 0.1 
     903             ENDIF 
     904         ENDIF 
     905         t1_ice_1d (ji) = ( isnow(ji) * t_s_1d  (ji,1) + ( 1._wp - isnow(ji) ) * t_i_1d  (ji,1) ) 
     906      END DO 
    894907      ! 
    895908      IF ( k_jules == np_zdf_jules_SND ) THEN   ! --- Jules coupling in "SND" mode 
    896909         ! 
    897910         ! Restore temperatures to their initial values 
    898          t_s_1d(1:npti,:)        = ztsold (1:npti,:) 
    899          t_i_1d(1:npti,:)        = ztiold (1:npti,:) 
    900          qcn_ice_1d(1:npti)      = fc_su(1:npti) 
     911         t_s_1d    (1:npti,:) = ztsold(1:npti,:) 
     912         t_i_1d    (1:npti,:) = ztiold(1:npti,:) 
     913         qcn_ice_1d(1:npti)   = fc_su (1:npti) 
    901914         !   
    902915      ENDIF 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r8882 r8933  
    7070   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   emp_oce        !: evap - precip over ocean                 [kg/m2/s] 
    7171   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndm_ice       !: wind speed module at T-point                 [m/s] 
     72   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sstfrz         !: wind speed module at T-point                 [m/s] 
     73   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tsfc_ice       !: sea ice surface skin temperature (on categories) 
    7274#endif 
    7375 
     
    123125 
    124126#if defined key_lim3 
    125       ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice (jpi,jpj,jpl) ,     & 
    126          &      qla_ice (jpi,jpj,jpl) , dqla_ice(jpi,jpj,jpl) ,     & 
    127          &      dqns_ice(jpi,jpj,jpl) , tn_ice  (jpi,jpj,jpl)  , alb_ice (jpi,jpj,jpl) ,   & 
    128          &      qml_ice(jpi,jpj,jpl)  , qcn_ice(jpi,jpj,jpl)   , qsr_ice_tr(jpi,jpj,jpl),  & 
    129          &      utau_ice(jpi,jpj)     , vtau_ice(jpi,jpj)     , wndm_ice(jpi,jpj)     ,   & 
    130          &      evap_ice(jpi,jpj,jpl) , devap_ice(jpi,jpj,jpl) , qprec_ice(jpi,jpj) ,   & 
    131          &      qemp_ice(jpi,jpj)     , qevap_ice(jpi,jpj,jpl) , qemp_oce (jpi,jpj) ,   & 
    132          &      qns_oce (jpi,jpj)     , qsr_oce  (jpi,jpj)     , emp_oce (jpi,jpj)  ,   & 
    133          &      emp_ice(jpi,jpj)      , STAT= ierr(2) ) 
     127      ALLOCATE( qns_ice (jpi,jpj,jpl) , qsr_ice  (jpi,jpj,jpl) ,     & 
     128         &      qla_ice (jpi,jpj,jpl) , dqla_ice (jpi,jpj,jpl) ,     & 
     129         &      dqns_ice(jpi,jpj,jpl) , tn_ice   (jpi,jpj,jpl) , alb_ice  (jpi,jpj,jpl) ,   & 
     130         &      qml_ice (jpi,jpj,jpl) , qcn_ice  (jpi,jpj,jpl) , qsr_ice_tr(jpi,jpj,jpl) ,   & 
     131         &      utau_ice(jpi,jpj)     , vtau_ice (jpi,jpj)     , wndm_ice  (jpi,jpj)     ,   & 
     132         &      evap_ice(jpi,jpj,jpl) , devap_ice(jpi,jpj,jpl) , qprec_ice (jpi,jpj)    ,   & 
     133         &      qemp_ice(jpi,jpj)     , qevap_ice(jpi,jpj,jpl) , qemp_oce  (jpi,jpj)    ,   & 
     134         &      qns_oce (jpi,jpj)     , qsr_oce  (jpi,jpj)     , emp_oce   (jpi,jpj)     ,   & 
     135         &      emp_ice (jpi,jpj)     , tsfc_ice (jpi,jpj,jpl) , sstfrz    (jpi,jpj)     , STAT= ierr(2) ) 
    134136#endif 
    135137 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r8882 r8933  
    4141   LOGICAL , PUBLIC ::   ln_cpl         !: ocean-atmosphere coupled formulation 
    4242   LOGICAL , PUBLIC ::   ln_mixcpl      !: ocean-atmosphere forced-coupled mixed formulation 
     43   LOGICAL , PUBLIC ::   ln_meto_cpl    !: Met Office coupling formulation, with surface exchange carried out in atmosphere 
    4344   LOGICAL , PUBLIC ::   ln_dm2dc       !: Daily mean to Diurnal Cycle short wave (qsr) 
    4445   LOGICAL , PUBLIC ::   ln_rnf         !: runoffs / runoff mouths 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r8882 r8933  
    114114   INTEGER, PARAMETER ::   jpr_isf    = 52 
    115115   INTEGER, PARAMETER ::   jpr_icb    = 53 
    116  
    117    INTEGER, PARAMETER ::   jprcv      = 53   ! total number of fields received   
     116   INTEGER, PARAMETER ::   jpr_ts_ice = 54   ! Sea ice surface temp 
     117 
     118   INTEGER, PARAMETER ::   jprcv      = 55   ! total number of fields received   
    118119 
    119120   INTEGER, PARAMETER ::   jps_fice   =  1   ! ice fraction sent to the atmosphere 
     
    149150   INTEGER, PARAMETER ::   jps_ocyw   = 31   ! currents on grid 2 
    150151   INTEGER, PARAMETER ::   jps_wlev   = 32   ! water level  
    151    INTEGER, PARAMETER ::   jpsnd      = 32   ! total number of fields sent  
     152   INTEGER, PARAMETER ::   jps_fice1  = 33   ! first-order ice concentration (for semi-implicit coupling of atmos-ice fluxes) 
     153   INTEGER, PARAMETER ::   jps_a_p    = 34   ! meltpond area 
     154   INTEGER, PARAMETER ::   jps_ht_p   = 35   ! meltpond thickness 
     155   INTEGER, PARAMETER ::   jps_kice   = 36   ! sea ice effective conductivity 
     156   INTEGER, PARAMETER ::   jps_sstfrz = 37   ! sea surface freezing temperature 
     157   INTEGER, PARAMETER ::   jps_ttilyr = 38   ! sea ice top layer temp 
     158 
     159   INTEGER, PARAMETER ::   jpsnd      = 38   ! total number of fields sent  
     160 
     161   INTEGER :: nn_cats_cpl   ! number of sea ice categories over which the coupling is carried out 
    152162 
    153163   !                                  !!** namelist namsbc_cpl ** 
     
    160170   END TYPE FLD_C 
    161171   !                                   ! Send to the atmosphere   
    162    TYPE(FLD_C) ::   sn_snd_temp, sn_snd_alb, sn_snd_thick, sn_snd_crt, sn_snd_co2                         
     172   TYPE(FLD_C) ::   sn_snd_temp  , sn_snd_alb , sn_snd_thick, sn_snd_crt   , sn_snd_co2,  & 
     173      &             sn_snd_thick1, sn_snd_cond, sn_snd_mpnd , sn_snd_sstfrz, sn_snd_ttilyr          
    163174   !                                   ! Received from the atmosphere 
    164    TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_dqnsdt, sn_rcv_qsr, sn_rcv_qns, sn_rcv_emp, sn_rcv_rnf 
     175   TYPE(FLD_C) ::   sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau, sn_rcv_dqnsdt, sn_rcv_qsr,  & 
     176      &             sn_rcv_qns , sn_rcv_emp   , sn_rcv_rnf, sn_rcv_ts_ice 
    165177   TYPE(FLD_C) ::   sn_rcv_cal, sn_rcv_iceflx, sn_rcv_co2, sn_rcv_mslp, sn_rcv_icb, sn_rcv_isf                               
    166178   ! Send to waves  
     
    183195   REAL(wp) ::   r1_grau              ! = 1.e0 / (grav * rau0)  
    184196 
    185    INTEGER , ALLOCATABLE, SAVE, DIMENSION(    :) ::   nrcvinfo           ! OASIS info argument 
     197   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:) ::   nrcvinfo           ! OASIS info argument 
    186198 
    187199   !! Substitution 
     
    236248      REAL(wp), POINTER, DIMENSION(:,:) ::   zacs, zaos 
    237249      !! 
    238       NAMELIST/namsbc_cpl/  sn_snd_temp , sn_snd_alb  , sn_snd_thick , sn_snd_crt   , sn_snd_co2,      &  
    239          &                  sn_rcv_w10m, sn_rcv_taumod, sn_rcv_tau   , sn_rcv_dqnsdt, sn_rcv_qsr,      &  
    240          &                  sn_snd_ifrac, sn_snd_crtw , sn_snd_wlev  , sn_rcv_hsig  , sn_rcv_phioc ,   &  
    241          &                  sn_rcv_sdrfx, sn_rcv_sdrfy, sn_rcv_wper  , sn_rcv_wnum  , sn_rcv_wstrf ,   & 
    242          &                  sn_rcv_wdrag, sn_rcv_qns  , sn_rcv_emp   , sn_rcv_rnf   , sn_rcv_cal   ,   & 
    243          &                  sn_rcv_iceflx,sn_rcv_co2  , nn_cplmodel  , ln_usecplmask, sn_rcv_mslp ,   & 
    244          &                  sn_rcv_icb , sn_rcv_isf 
     250      NAMELIST/namsbc_cpl/  sn_snd_temp  , sn_snd_alb   , sn_snd_thick, sn_snd_crt   , sn_snd_co2  ,   &  
     251         &                  sn_rcv_w10m  , sn_rcv_taumod, sn_rcv_tau  , sn_rcv_dqnsdt, sn_rcv_qsr  ,   &  
     252         &                  sn_snd_ifrac , sn_snd_crtw  , sn_snd_wlev , sn_rcv_hsig  , sn_rcv_phioc,   &  
     253         &                  sn_rcv_sdrfx , sn_rcv_sdrfy , sn_rcv_wper , sn_rcv_wnum  , sn_rcv_wstrf,   & 
     254         &                  sn_rcv_wdrag , sn_rcv_qns   , sn_rcv_emp  , sn_rcv_rnf   , sn_rcv_cal  ,   & 
     255         &                  sn_rcv_iceflx, sn_rcv_co2   , nn_cplmodel , ln_usecplmask, sn_rcv_mslp ,   & 
     256         &                  sn_rcv_icb   , sn_rcv_isf   , nn_cats_cpl   
    245257 
    246258      !!--------------------------------------------------------------------- 
     
    249261      ! 
    250262      CALL wrk_alloc( jpi,jpj,   zacs, zaos ) 
     263 
     264      IF( ln_meto_cpl ) THEN 
     265         tsfc_ice(:,:,:) = 0.0 
     266         a_ip    (:,:,:) = 0.0 
     267         v_ip    (:,:,:) = 0.0 
     268         t1_ice  (:,:,:) = rt0 
     269         cnd_ice (:,:,:) = 0.0 
     270         sstfrz  (:,:)   = 0.0 
     271      ENDIF 
    251272 
    252273      ! ================================ ! 
     
    294315         WRITE(numout,*)'      Stress frac adsorbed by waves   = ', TRIM(sn_rcv_wstrf%cldes ), ' (', TRIM(sn_rcv_wstrf%clcat ), ')'  
    295316         WRITE(numout,*)'      Neutral surf drag coefficient   = ', TRIM(sn_rcv_wdrag%cldes ), ' (', TRIM(sn_rcv_wdrag%clcat ), ')'  
     317         WRITE(numout,*)'      Sea ice surface skin temperature= ', TRIM(sn_rcv_ts_ice%cldes), ' (', TRIM(sn_rcv_ts_ice%clcat), ')'  
    296318         WRITE(numout,*)'  sent fields (multiple ice categories)' 
    297319         WRITE(numout,*)'      surface temperature             = ', TRIM(sn_snd_temp%cldes  ), ' (', TRIM(sn_snd_temp%clcat  ), ')' 
     320         WRITE(numout,*)'      top ice layer temperature       = ', TRIM(sn_snd_ttilyr%cldes), ' (', TRIM(sn_snd_ttilyr%clcat), ')' 
    298321         WRITE(numout,*)'      albedo                          = ', TRIM(sn_snd_alb%cldes   ), ' (', TRIM(sn_snd_alb%clcat   ), ')' 
    299322         WRITE(numout,*)'      ice/snow thickness              = ', TRIM(sn_snd_thick%cldes ), ' (', TRIM(sn_snd_thick%clcat ), ')' 
     
    304327         WRITE(numout,*)'                      - mesh          = ', sn_snd_crt%clvgrd 
    305328         WRITE(numout,*)'      oce co2 flux                    = ', TRIM(sn_snd_co2%cldes   ), ' (', TRIM(sn_snd_co2%clcat   ), ')' 
     329         WRITE(numout,*)'      ice effective conductivity      = ', TRIM(sn_snd_cond%cldes  ), ' (', TRIM(sn_snd_cond%clcat  ), ')' 
     330         WRITE(numout,*)'      meltponds fraction and depth    = ', TRIM(sn_snd_mpnd%cldes  ), ' (', TRIM(sn_snd_mpnd%clcat  ), ')' 
     331         WRITE(numout,*)'      sea surface freezing temp       = ', TRIM(sn_snd_sstfrz%cldes), ' (', TRIM(sn_snd_sstfrz%clcat), ')' 
    306332         WRITE(numout,*)'      water level                     = ', TRIM(sn_snd_wlev%cldes  ), ' (', TRIM(sn_snd_wlev%clcat  ), ')'  
    307333         WRITE(numout,*)'      mean sea level pressure         = ', TRIM(sn_rcv_mslp%cldes  ), ' (', TRIM(sn_rcv_mslp%clcat  ), ')'  
     
    312338         WRITE(numout,*)'  nn_cplmodel                         = ', nn_cplmodel 
    313339         WRITE(numout,*)'  ln_usecplmask                       = ', ln_usecplmask 
     340         WRITE(numout,*)'  nn_cats_cpl                         = ', nn_cats_cpl 
    314341      ENDIF 
    315342 
     
    501528      ! 
    502529      ! non solar sensitivity mandatory for LIM ice model 
    503       IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. k_ice /= 0 .AND. k_ice /= 3 .AND. nn_components /= jp_iam_sas ) & 
    504          CALL ctl_stop( 'sbc_cpl_init: sn_rcv_dqnsdt%cldes must be coupled in namsbc_cpl namelist' ) 
     530      IF (.NOT. ln_meto_cpl) THEN 
     531         IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. k_ice /= 0 .AND. k_ice /= 3 .AND. nn_components /= jp_iam_sas )  & 
     532            &   CALL ctl_stop( 'sbc_cpl_init: sn_rcv_dqnsdt%cldes must be coupled in namsbc_cpl namelist' ) 
     533      ENDIF 
     534 
    505535      ! non solar sensitivity mandatory for mixed oce-ice solar radiation coupling technique 
    506536      IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. TRIM( sn_rcv_qns%cldes ) == 'mixed oce-ice' ) & 
     
    547577         srcv(jpr_topm:jpr_botm)%laction = .TRUE. 
    548578      ENDIF 
     579      !                                                      ! ----------------------------- ! 
     580 
     581      !!!!! To get NEMO4-LIM working at Met Office 
     582      srcv(jpr_ts_ice)%clname = 'OTsfIce' 
     583      IF ( TRIM( sn_rcv_ts_ice%cldes ) == 'ice' )   srcv(jpr_ts_ice)%laction = .TRUE. 
     584      IF ( TRIM( sn_rcv_ts_ice%clcat ) == 'yes' )   srcv(jpr_ts_ice)%nct     = nn_cats_cpl 
     585      IF ( TRIM( sn_rcv_emp%clcat    ) == 'yes' )   srcv(jpr_ievp)%nct       = nn_cats_cpl 
     586      !!!!! 
     587 
    549588      !                                                      ! ------------------------- ! 
    550589      !                                                      !      Wave breaking        !     
     
    707746      !                                                      !    Surface temperature    ! 
    708747      !                                                      ! ------------------------- ! 
    709       ssnd(jps_toce)%clname = 'O_SSTSST' 
    710       ssnd(jps_tice)%clname = 'O_TepIce' 
    711       ssnd(jps_tmix)%clname = 'O_TepMix' 
     748      ssnd(jps_toce)%clname   = 'O_SSTSST' 
     749      ssnd(jps_tice)%clname   = 'O_TepIce' 
     750      ssnd(jps_ttilyr)%clname = 'O_TtiLyr' 
     751      ssnd(jps_tmix)%clname   = 'O_TepMix' 
    712752      SELECT CASE( TRIM( sn_snd_temp%cldes ) ) 
    713753      CASE( 'none'                                 )       ! nothing to do 
    714754      CASE( 'oce only'                             )   ;   ssnd( jps_toce )%laction = .TRUE. 
    715       CASE( 'oce and ice' , 'weighted oce and ice' ) 
     755      CASE( 'oce and ice' , 'weighted oce and ice' , 'oce and weighted ice' ) 
    716756         ssnd( (/jps_toce, jps_tice/) )%laction = .TRUE. 
    717757         IF ( TRIM( sn_snd_temp%clcat ) == 'yes' )  ssnd(jps_tice)%nct = jpl 
     
    744784      !                                                      !  Ice fraction & Thickness !  
    745785      !                                                      ! ------------------------- ! 
    746       ssnd(jps_fice)%clname = 'OIceFrc' 
     786      ssnd(jps_fice)%clname  = 'OIceFrc' 
    747787      ssnd(jps_ficet)%clname = 'OIceFrcT'  
    748       ssnd(jps_hice)%clname = 'OIceTck' 
    749       ssnd(jps_hsnw)%clname = 'OSnwTck' 
     788      ssnd(jps_hice)%clname  = 'OIceTck' 
     789      ssnd(jps_a_p)%clname   = 'OPndFrc' 
     790      ssnd(jps_ht_p)%clname  = 'OPndTck' 
     791      ssnd(jps_hsnw)%clname  = 'OSnwTck' 
     792      ssnd(jps_fice1)%clname = 'OIceFrd' 
    750793      IF( k_ice /= 0 ) THEN 
    751794         ssnd(jps_fice)%laction = .TRUE.                  ! if ice treated in the ocean (even in climato case) 
     795         ssnd(jps_fice1)%laction = .TRUE.                 ! First-order regridded ice concentration, to be used 
     796                                                          ! producing atmos-to-ice fluxes 
    752797! Currently no namelist entry to determine sending of multi-category ice fraction so use the thickness entry for now 
    753          IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_fice)%nct = jpl 
     798         IF ( TRIM( sn_snd_thick%clcat  ) == 'yes' ) ssnd(jps_fice)%nct = jpl 
     799         IF ( TRIM( sn_snd_thick1%clcat ) == 'yes' ) ssnd(jps_fice1)%nct = jpl 
    754800      ENDIF 
    755801       
     
    769815      END SELECT 
    770816 
     817      !                                                      ! ------------------------- !  
     818      !                                                      ! Ice Meltponds             !  
     819      !                                                      ! ------------------------- !  
     820 
     821 
     822      !!!!! Getting NEMO4-LIM to work at Met Office 
     823      ssnd(jps_a_p)%clname = 'OPndFrc'     
     824      ssnd(jps_ht_p)%clname = 'OPndTck'     
     825      SELECT CASE ( TRIM( sn_snd_mpnd%cldes ) )  
     826      CASE ( 'none' )  
     827         ssnd(jps_a_p)%laction = .FALSE.  
     828         ssnd(jps_ht_p)%laction = .FALSE.  
     829      CASE ( 'ice only' )   
     830         ssnd(jps_a_p)%laction = .TRUE.  
     831         ssnd(jps_ht_p)%laction = .TRUE.  
     832         IF ( TRIM( sn_snd_mpnd%clcat ) == 'yes' ) THEN  
     833            ssnd(jps_a_p)%nct = nn_cats_cpl  
     834            ssnd(jps_ht_p)%nct = nn_cats_cpl  
     835         ELSE  
     836            IF ( jpl > 1 ) THEN  
     837               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_mpnd%cldes if not exchanging category fields' )  
     838            ENDIF  
     839         ENDIF  
     840      CASE ( 'weighted ice' )   
     841         ssnd(jps_a_p)%laction = .TRUE.  
     842         ssnd(jps_ht_p)%laction = .TRUE.  
     843         IF ( TRIM( sn_snd_mpnd%clcat ) == 'yes' ) THEN  
     844            ssnd(jps_a_p)%nct = nn_cats_cpl   
     845            ssnd(jps_ht_p)%nct = nn_cats_cpl   
     846         ENDIF  
     847      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_mpnd%cldes; '//sn_snd_mpnd%cldes )  
     848      END SELECT  
     849      !!!!! 
     850  
    771851      !                                                      ! ------------------------- ! 
    772852      !                                                      !      Surface current      ! 
     
    818898      !                                                      ! ------------------------- ! 
    819899      ssnd(jps_co2)%clname = 'O_CO2FLX' ;  IF( TRIM(sn_snd_co2%cldes) == 'coupled' )    ssnd(jps_co2 )%laction = .TRUE. 
    820  
     900      !  
     901       
     902      !!!!! Getting NEMO4-LIM to work at the Met Office 
     903      !                                                      ! ------------------------- !  
     904      !                                                      ! Sea surface freezing temp !  
     905      !                                                      ! ------------------------- !  
     906      ssnd(jps_sstfrz)%clname = 'O_SSTFrz' ; IF( TRIM(sn_snd_sstfrz%cldes) == 'coupled' )  ssnd(jps_sstfrz)%laction = .TRUE.  
     907      !!!!! 
     908 
     909      !  
     910      !                                                      ! ------------------------- !  
     911      !                                                      !    Ice conductivity       !  
     912      !                                                      ! ------------------------- !  
     913      ! Note that ultimately we will move to passing an ocean effective conductivity as well so there  
     914      ! will be some changes to the parts of the code which currently relate only to ice conductivity  
     915 
     916      ssnd(jps_ttilyr )%clname = 'O_TtiLyr'  
     917      SELECT CASE ( TRIM( sn_snd_ttilyr%cldes ) )  
     918      CASE ( 'none' )  
     919         ssnd(jps_ttilyr)%laction = .FALSE.  
     920      CASE ( 'ice only' )  
     921         ssnd(jps_ttilyr)%laction = .TRUE.  
     922         IF ( TRIM( sn_snd_ttilyr%clcat ) == 'yes' ) THEN  
     923            ssnd(jps_ttilyr)%nct = nn_cats_cpl  
     924         ELSE  
     925            IF ( nn_cats_cpl > 1 ) THEN  
     926               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_ttilyr%cldes if not exchanging category fields' )  
     927            ENDIF  
     928         ENDIF  
     929      CASE ( 'weighted ice' )  
     930         ssnd(jps_ttilyr)%laction = .TRUE.  
     931         IF ( TRIM( sn_snd_ttilyr%clcat ) == 'yes' ) ssnd(jps_ttilyr)%nct = nn_cats_cpl  
     932      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_ttilyr%cldes;'//sn_snd_ttilyr%cldes )  
     933      END SELECT  
     934 
     935      ssnd(jps_kice )%clname = 'OIceKn'  
     936      SELECT CASE ( TRIM( sn_snd_cond%cldes ) )  
     937      CASE ( 'none' )  
     938         ssnd(jps_kice)%laction = .FALSE.  
     939      CASE ( 'ice only' )  
     940         ssnd(jps_kice)%laction = .TRUE.  
     941         IF ( TRIM( sn_snd_cond%clcat ) == 'yes' ) THEN  
     942            ssnd(jps_kice)%nct = nn_cats_cpl  
     943         ELSE  
     944            IF ( nn_cats_cpl > 1 ) THEN  
     945               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_cond%cldes if not exchanging category fields' )  
     946            ENDIF  
     947         ENDIF  
     948      CASE ( 'weighted ice' )  
     949         ssnd(jps_kice)%laction = .TRUE.  
     950         IF ( TRIM( sn_snd_cond%clcat ) == 'yes' ) ssnd(jps_kice)%nct = nn_cats_cpl  
     951      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_cond%cldes;'//sn_snd_cond%cldes )  
     952      END SELECT  
     953      !  
     954        
    821955      !                                                      ! ------------------------- !  
    822956      !                                                      !     Sea surface height    !  
     
    11261260      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1) 
    11271261      !  
     1262 
     1263      !!!!! Getting NEMO4-LIM to work at the Met Office 
     1264      !  ! Sea ice surface skin temp:  
     1265      IF( srcv(jpr_ts_ice)%laction ) THEN  
     1266        DO jn = 1, jpl  
     1267          DO jj = 1, jpj  
     1268            DO ji = 1, jpi  
     1269              IF (frcv(jpr_ts_ice)%z3(ji,jj,jn) > 0.0) THEN  
     1270                tsfc_ice(ji,jj,jn) = 0.0  
     1271              ELSE IF (frcv(jpr_ts_ice)%z3(ji,jj,jn) < -60.0) THEN  
     1272                tsfc_ice(ji,jj,jn) = -60.0  
     1273              ELSE  
     1274                tsfc_ice(ji,jj,jn) = frcv(jpr_ts_ice)%z3(ji,jj,jn)  
     1275              ENDIF  
     1276            END DO  
     1277          END DO  
     1278        END DO  
     1279      ENDIF  
     1280      !!!!! 
     1281 
     1282 
    11281283      !                                                      ! ========================= !  
    11291284      !                                                      ! Mean Sea Level Pressure   !   (taum)  
     
    15841739      REAL(wp) ::   ztri         ! local scalar 
    15851740      REAL(wp), DIMENSION(jpi,jpj)     ::   zcptn, zcptrain, zcptsnw, ziceld, zmsk, zsnw 
    1586       REAL(wp), DIMENSION(jpi,jpj)     ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip  , zevap_oce, zevap_ice, zdevap_ice 
     1741      REAL(wp), DIMENSION(jpi,jpj)     ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip  , zevap_oce, zdevap_ice 
    15871742      REAL(wp), DIMENSION(jpi,jpj)     ::   zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice 
    1588       REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice    !!gm , zfrqsr_tr_i 
     1743      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice, zevap_ice    !!gm , zfrqsr_tr_i 
    15891744      !!---------------------------------------------------------------------- 
    15901745      ! 
     
    16281783 
    16291784      ! --- evaporation over ice (kg/m2/s) --- ! 
    1630       zevap_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) 
     1785      DO jl=1,jpl 
     1786         IF (sn_rcv_emp%clcat == 'yes') THEN   ;   zevap_ice(:,:,jl) = frcv(jpr_ievp)%z3(:,:,jl) 
     1787         ELSE                                  ;   zevap_ice(:,:,jl) = frcv(jpr_ievp)%z3(:,:,1 )   ;   ENDIF 
     1788      ENDDO 
     1789 
    16311790      ! since the sensitivity of evap to temperature (devap/dT) is not prescribed by the atmosphere, we set it to 0 
    16321791      ! therefore, sublimation is not redistributed over the ice categories when no subgrid scale fluxes are provided by atm. 
     
    16561815         tprecip(:,:) = tprecip(:,:) * xcplmask(:,:,0) + ztprecip(:,:) * zmsk(:,:) 
    16571816         DO jl = 1, jpl 
    1658             evap_ice (:,:,jl) = evap_ice (:,:,jl) * xcplmask(:,:,0) + zevap_ice (:,:) * zmsk(:,:) 
    1659             devap_ice(:,:,jl) = devap_ice(:,:,jl) * xcplmask(:,:,0) + zdevap_ice(:,:) * zmsk(:,:) 
     1817            evap_ice (:,:,jl) = evap_ice (:,:,jl) * xcplmask(:,:,0) + zevap_ice (:,:,jl) * zmsk(:,:) 
     1818            devap_ice(:,:,jl) = devap_ice(:,:,jl) * xcplmask(:,:,0) + zdevap_ice(:,:)    * zmsk(:,:) 
    16601819         END DO 
    16611820      ELSE 
    1662          emp_tot(:,:) = zemp_tot(:,:) 
    1663          emp_ice(:,:) = zemp_ice(:,:) 
    1664          emp_oce(:,:) = zemp_oce(:,:)      
    1665          sprecip(:,:) = zsprecip(:,:) 
    1666          tprecip(:,:) = ztprecip(:,:) 
     1821         emp_tot (:,:)   = zemp_tot (:,:) 
     1822         emp_ice (:,:)   = zemp_ice (:,:) 
     1823         emp_oce (:,:)   = zemp_oce (:,:)      
     1824         sprecip (:,:)   = zsprecip (:,:) 
     1825         tprecip (:,:)   = ztprecip (:,:) 
     1826         evap_ice(:,:,:) = zevap_ice(:,:,:) 
    16671827         DO jl = 1, jpl 
    1668             evap_ice (:,:,jl) = zevap_ice (:,:) 
    16691828            devap_ice(:,:,jl) = zdevap_ice(:,:) 
    16701829         END DO 
     
    19342093         dqns_ice(:,:,:) = zdqns_ice(:,:,:) 
    19352094      ENDIF 
    1936  
    1937       !                                                      ! ========================= ! 
    1938       SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) )             !    topmelt and botmelt    ! 
    1939       !                                                      ! ========================= ! 
    1940       CASE ('coupled') 
    1941          topmelt(:,:,:)=frcv(jpr_topm)%z3(:,:,:) 
    1942          botmelt(:,:,:)=frcv(jpr_botm)%z3(:,:,:) 
    1943       END SELECT 
     2095       
     2096      IF( ln_meto_cpl ) THEN 
     2097         !                                                      ! ========================= ! 
     2098         SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) )             !    topmelt and botmelt    ! 
     2099         !                                                      ! ========================= ! 
     2100         CASE ('coupled') 
     2101            qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) * a_i(:,:,:) 
     2102            qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:) * a_i(:,:,:) 
     2103         END SELECT 
     2104      ENDIF 
     2105 
    19442106 
    19452107#if defined key_lim3 
     
    19502112      CASE( np_jules_OFF    )       !==  No Jules coupler  ==! 
    19512113         ! 
    1952 !!gm         ! former coding was     
    1953 !!gm         ! Coupled case: since cloud cover is not received from atmosphere  
    1954 !!gm         !               ===> used prescribed cloud fraction representative for polar oceans in summer (0.81) 
    1955 !!gm         !     fr1_i0(:,:) = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice ) 
    1956 !!gm         !     fr2_i0(:,:) = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice ) 
    1957 !!gm          
    1958 !!gm         ! to retrieve that coding, we needed to access h_i & h_s from here 
    1959 !!gm         ! we could even retrieve cloud fraction from the coupler 
    1960 !!gm         ! 
    1961 !!gm         zfrqsr_tr_i(:,:,:) = 0._wp   !   surface transmission parameter 
    1962 !!gm         ! 
    1963 !!gm         DO jl = 1, jpl 
    1964 !!gm            DO jj = 1 , jpj 
    1965 !!gm               DO ji = 1, jpi 
    1966 !!gm                  !              !--- surface transmission parameter (Grenfell Maykut 77) --- ! 
    1967 !!gm                  zfrqsr_tr_i(ji,jj,jl) = 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice  
    1968 !!gm                  ! 
    1969 !!gm                  !              ! --- influence of snow and thin ice --- ! 
    1970 !!gm                  IF ( phs(ji,jj,jl) >= 0.0_wp )   zfrqsr_tr_i(ji,jj,jl) = 0._wp   !   snow fully opaque 
    1971 !!gm                  IF ( phi(ji,jj,jl) <= 0.1_wp )   zfrqsr_tr_i(ji,jj,jl) = 1._wp   !   thin ice transmits all solar radiation 
    1972 !!gm               END DO 
    1973 !!gm            END DO 
    1974 !!gm         END DO 
    1975 !!gm         ! 
    1976 !!gm         qsr_ice_tr(:,:,:) =   zfrqsr_tr_i(:,:,:) * qsr_ice(:,:,:)               !   transmitted solar radiation  
    1977 !!gm         ! 
    1978 !!gm better coding of the above calculation: 
    1979          ! 
    19802114         !                    ! ===> used prescribed cloud fraction representative for polar oceans in summer (0.81) 
    19812115         ztri = 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice    ! surface transmission parameter (Grenfell Maykut 77) 
     
    19842118         WHERE( phs(:,:,:) >= 0.0_wp )   qsr_ice_tr(:,:,:) = 0._wp            ! snow fully opaque 
    19852119         WHERE( phi(:,:,:) <= 0.1_wp )   qsr_ice_tr(:,:,:) = qsr_ice(:,:,:)   ! thin ice transmits all solar radiation 
    1986 !!gm end 
    19872120         !      
    19882121      CASE( np_jules_ACTIVE )       !==  Jules coupler is active  ==! 
     
    20642197               CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' ) 
    20652198               END SELECT 
     2199            CASE( 'oce and weighted ice')    ;   ztmp1(:,:) =   tsn(:,:,1,jp_tem) + rt0   
     2200               SELECT CASE( sn_snd_temp%clcat )  
     2201               CASE( 'yes' )     
     2202                  ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl) * a_i(:,:,1:jpl)  
     2203               CASE( 'no' )  
     2204                  ztmp3(:,:,:) = 0.0  
     2205                  DO jl=1,jpl  
     2206                     ztmp3(:,:,1) = ztmp3(:,:,1) + tn_ice(:,:,jl) * a_i(:,:,jl)  
     2207                  ENDDO  
     2208               CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' )  
     2209               END SELECT  
    20662210            CASE( 'mixed oce-ice'        )    
    20672211               ztmp1(:,:) = ( ztmp1(:,:) + rt0 ) * zfr_l(:,:)  
     
    20762220         IF( ssnd(jps_tmix)%laction )   CALL cpl_snd( jps_tmix, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
    20772221      ENDIF 
     2222 
     2223      !!!!! Getting NEMO4-LIM working at Met Office 
     2224      ! Top layer ice temperature 
     2225      IF( ssnd(jps_ttilyr)%laction) THEN 
     2226         SELECT CASE( sn_snd_ttilyr%cldes) 
     2227         CASE ('weighted ice') 
     2228            ztmp3(:,:,1:jpl) = t1_ice(:,:,1:jpl) * a_i(:,:,1:jpl)  
     2229         CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_ttilyr%cldes' ) 
     2230         END SELECT 
     2231         IF( ssnd(jps_ttilyr)%laction )   CALL cpl_snd( jps_ttilyr, isec, ztmp3, info ) 
     2232      ENDIF 
     2233      !!!!! 
     2234 
     2235 
    20782236      !                                                      ! ------------------------- ! 
    20792237      !                                                      !           Albedo          ! 
     
    21342292         END SELECT 
    21352293         IF( ssnd(jps_fice)%laction )   CALL cpl_snd( jps_fice, isec, ztmp3, info ) 
     2294      ENDIF 
     2295 
     2296      IF( ssnd(jps_fice1)%laction ) THEN 
     2297         SELECT CASE( sn_snd_thick1%clcat ) 
     2298         CASE( 'yes' )   ;   ztmp3(:,:,1:jpl) =  a_i(:,:,1:jpl) 
     2299         CASE( 'no'  )   ;   ztmp3(:,:,1    ) = fr_i(:,:      ) 
     2300         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick1%clcat' ) 
     2301         END SELECT 
     2302         CALL cpl_snd( jps_fice1, isec, ztmp3, info ) 
    21362303      ENDIF 
    21372304       
     
    21792346         IF( ssnd(jps_hsnw)%laction )   CALL cpl_snd( jps_hsnw, isec, ztmp4, info ) 
    21802347      ENDIF 
     2348 
     2349      ! NEMO4 - Jules coupling - Met Office 
     2350      ! Send meltpond fields   
     2351      IF( ssnd(jps_a_p)%laction .OR. ssnd(jps_ht_p)%laction ) THEN  
     2352         SELECT CASE( sn_snd_mpnd%cldes)   
     2353         CASE( 'ice only' )   
     2354            SELECT CASE( sn_snd_mpnd%clcat )   
     2355            CASE( 'yes' )   
     2356               ztmp3(:,:,1:jpl) =  a_ip(:,:,1:jpl) 
     2357               ztmp4(:,:,1:jpl) =  v_ip(:,:,1:jpl)   
     2358            CASE( 'no' )   
     2359               ztmp3(:,:,:) = 0.0   
     2360               ztmp4(:,:,:) = 0.0   
     2361               DO jl=1,jpl   
     2362                 ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip(:,:,jpl)   
     2363                 ztmp4(:,:,1) = ztmp4(:,:,1) + v_ip(:,:,jpl)  
     2364               ENDDO   
     2365            CASE default    ;   CALL ctl_stop( 'sbc_cpl_mpd: wrong definition of sn_snd_mpnd%clcat' )   
     2366            END SELECT   
     2367         CASE( 'default' )    ;   CALL ctl_stop( 'sbc_cpl_mpd: wrong definition of sn_snd_mpnd%cldes' )      
     2368         END SELECT   
     2369         IF( ssnd(jps_a_p)%laction )   CALL cpl_snd( jps_a_p, isec, ztmp3, info )      
     2370         IF( ssnd(jps_ht_p)%laction )   CALL cpl_snd( jps_ht_p, isec, ztmp4, info )      
     2371         !  
     2372         ! Send ice effective conductivity  
     2373         SELECT CASE( sn_snd_cond%cldes)  
     2374         CASE( 'weighted ice' )     
     2375            SELECT CASE( sn_snd_cond%clcat )  
     2376            CASE( 'yes' )     
     2377                  ztmp3(:,:,1:jpl) =  cnd_ice(:,:,1:jpl) * a_i(:,:,1:jpl)  
     2378            CASE( 'no' )  
     2379               ztmp3(:,:,:) = 0.0  
     2380               DO jl=1,jpl  
     2381                 ztmp3(:,:,1) = ztmp3(:,:,1) + cnd_ice(:,:,jl) * a_i(:,:,jl)  
     2382               ENDDO  
     2383            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_cond%clcat' )  
     2384            END SELECT  
     2385         CASE( 'ice only' )     
     2386           ztmp3(:,:,1:jpl) = cnd_ice(:,:,1:jpl)  
     2387         END SELECT  
     2388         IF( ssnd(jps_kice)%laction )   CALL cpl_snd( jps_kice, isec, ztmp3, info )  
     2389      ENDIF  
     2390      !    
     2391      !!!!! 
     2392 
     2393 
    21812394      !                                                      ! ------------------------- ! 
    21822395      !                                                      !  CO2 flux from PISCES     !  
     
    25002713      IF( ssnd(jps_taum  )%laction )  CALL cpl_snd( jps_taum  , isec, RESHAPE ( taum, (/jpi,jpj,1/) ), info ) 
    25012714 
     2715      ! NEMO4 - Jules coupling - Met Office 
     2716      CALL eos_fzp(tsn(:,:,1,jp_sal), sstfrz) 
     2717      ztmp1(:,:) = sstfrz(:,:) + rt0 
     2718      IF( ssnd(jps_sstfrz)%laction )  CALL cpl_snd( jps_sstfrz, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info) 
     2719 
    25022720      CALL wrk_dealloc( jpi,jpj,       zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 ) 
    25032721      CALL wrk_dealloc( jpi,jpj,jpl,   ztmp3, ztmp4 ) 
  • branches/2017/dev_CNRS_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r8885 r8933  
    9292      NAMELIST/namsbc/ nn_fsbc  ,                                                    & 
    9393         &             ln_usr   , ln_flx   , ln_blk       ,                          & 
    94          &             ln_cpl   , ln_mixcpl, nn_components,                          & 
     94         &             ln_cpl   , ln_mixcpl, ln_meto_cpl  , nn_components,           & 
    9595         &             nn_ice   , ln_ice_embd,                                       & 
    9696         &             ln_traqsr, ln_dm2dc ,                                         & 
     
    138138         WRITE(numout,*) '         mixed forced-coupled     formulation       ln_mixcpl     = ', ln_mixcpl 
    139139!!gm  lk_oasis is controlled by key_oasis3  ===>>>  It shoud be removed from the namelist  
     140         WRITE(numout,*) '         Met Office coupling specifics              ln_meto_cpl   = ', ln_meto_cpl 
    140141         WRITE(numout,*) '         OASIS coupling (with atm or sas)           lk_oasis      = ', lk_oasis 
    141142         WRITE(numout,*) '         components of your executable              nn_components = ', nn_components 
Note: See TracChangeset for help on using the changeset viewer.