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

Changeset 8847


Ignore:
Timestamp:
2017-11-29T14:27:57+01:00 (6 years ago)
Author:
alexwestmohc
Message:

Implementing new logicals to control coupling:

ln_meto_cpl - .TRUE. if Met Office style coupling is being used, i.e. if the
surface exchange is in the atmosphere. .FALSE. by default

nn_cats_cpl - the number of sea ice categories over which the coupling is being
carried out. 5 by default

In addition, the calculation of meltpond area, depth, top layer ice/snow temp
and sea surface freezing temperature has been corrected to be appropriate to LIM
variable names.

Location:
branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/CONFIG/SHARED/namelist_ref

    r8796 r8847  
    188188   ln_cpl      = .false.   !  atmosphere coupled   formulation          ( requires key_oasis3 ) 
    189189   ln_mixcpl   = .false.   !  forced-coupled mixed formulation          ( requires key_oasis3 ) 
     190   ln_meto_cpl = .false.   !  Met Office coupling formulation, with surface exchange carried out in atmosphere (requires key_oasis3) 
    190191   nn_components = 0       !  configuration of the opa-sas OASIS coupling 
    191192                           !  =0 no opa-sas OASIS coupling: default single executable configuration 
     
    308309   ln_usecplmask = .false. !  use a coupling mask file to merge data received from several models 
    309310   !                       !   -> file cplmask.nc with the float variable called cplmask (jpi,jpj,nn_cplmodel) 
     311   nn_cats_cpl   =     5   !  Number of sea ice categories over which coupling is to be carried out 
    310312/ 
    311313!----------------------------------------------------------------------- 
  • branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/LIM_SRC_3/iceforcing.F90

    r8796 r8847  
    294294      CASE( -1  ) 
    295295         IF(lwp) WRITE(numout,*) '   ESIM: use per-category fluxes (nn_iceflx = -1) ' 
    296          !IF( ln_cpl )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for ESIM in coupled mode must be 0 or 2' ) 
     296         IF( (ln_cpl) .AND. (.NOT. ln_meto_cpl) )   CALL ctl_stop( 'ice_thd_init : the chosen nn_iceflx for ESIM in coupled mode must be 0 or 2' ) 
    297297      CASE(  0  ) 
    298298         IF(lwp) WRITE(numout,*) '   ESIM: use average per-category fluxes (nn_iceflx = 0) ' 
  • branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r8804 r8847  
    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             !: sea surface freezing temperature 
     72   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sstfrz       !: wind speed module at T-point                 [m/s] 
    7373   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tsfc_ice           !: sea ice surface skin temperature (on categories) 
    74    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ttlyr_ice          !: sea ice top layer temperature (on categories) 
    75    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_p, ht_p          ! Meltpond fraction and depth 
    7674#endif 
    7775 
     
    136134         &      qemp_ice(jpi,jpj)     , qevap_ice(jpi,jpj,jpl) , qemp_oce (jpi,jpj) ,   & 
    137135         &      qns_oce (jpi,jpj)     , qsr_oce  (jpi,jpj)     , emp_oce (jpi,jpj)  ,   & 
    138          &      emp_ice(jpi,jpj)      , sstfrz (jpi, jpj) , tsfc_ice(jpi,jpj,jpl), & 
    139          &      ttlyr_ice(jpi,jpj,jpl), a_p(jpi,jpj,jpl),    & 
    140          &      ht_p(jpi,jpj,jpl),      STAT= ierr(2) ) 
     136         &      emp_ice(jpi,jpj)      , tsfc_ice(jpi,jpj,jpl)  , sstfrz(jpi,jpj), & 
     137         STAT= ierr(2) ) 
    141138#endif 
    142139 
  • branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_oce.F90

    r8738 r8847  
    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/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r8825 r8847  
    158158   INTEGER, PARAMETER ::   jpsnd      = 38   ! total number of fields sent  
    159159 
     160   INTEGER :: nn_cats_cpl   ! number of sea ice categories over which the coupling is carried out 
     161 
    160162   !                                  !!** namelist namsbc_cpl ** 
    161163   TYPE ::   FLD_C                     !    
     
    251253         &                  sn_rcv_wdrag, sn_rcv_qns  , sn_rcv_emp   , sn_rcv_rnf   , sn_rcv_cal   ,   & 
    252254         &                  sn_rcv_iceflx,sn_rcv_co2  , nn_cplmodel  , ln_usecplmask, sn_rcv_mslp  ,   & 
    253          &                  sn_rcv_icb , sn_rcv_isf, ln_iceshelf_init_atmos 
     255         &                  sn_rcv_icb , sn_rcv_isf, ln_iceshelf_init_atmos,        nn_cats_cpl   
    254256 
    255257      !!--------------------------------------------------------------------- 
     
    279281 
    280282      !!!!! Getting NEMO4-LIM working at the Met Office: Hardcode number of ice cats to 5 during the initialisation 
    281       jpl = 5 
     283      jpl = nn_cats_cpl 
    282284      !!!!! 
    283285 
     
    331333         WRITE(numout,*)'  nn_cplmodel                         = ', nn_cplmodel 
    332334         WRITE(numout,*)'  ln_usecplmask                       = ', ln_usecplmask 
     335         WRITE(numout,*)'  nn_cats_cpl                         = ', nn_cats_cpl 
    333336      ENDIF 
    334337 
     
    521524      ! non solar sensitivity mandatory for LIM ice model 
    522525 
    523       !!!!! Getting NEMO4-LIM working at Met Office: Disable this check because we don't need dqnsdt for JULES-style coupling 
    524       !IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. k_ice /= 0 .AND. k_ice /= 3 .AND. nn_components /= jp_iam_sas ) & 
    525       !   CALL ctl_stop( 'sbc_cpl_init: sn_rcv_dqnsdt%cldes must be coupled in namsbc_cpl namelist' ) 
    526       !!!!! 
     526      IF (.NOT. ln_meto_cpl) THEN 
     527         IF( TRIM( sn_rcv_dqnsdt%cldes ) == 'none' .AND. k_ice /= 0 .AND. k_ice /= 3 .AND. nn_components /= jp_iam_sas) & 
     528            CALL ctl_stop( 'sbc_cpl_init: sn_rcv_dqnsdt%cldes must be coupled in namsbc_cpl namelist' ) 
     529      ENDIF 
    527530 
    528531      ! non solar sensitivity mandatory for mixed oce-ice solar radiation coupling technique 
     
    18391842            ENDIF 
    18401843 
    1841             !!!!! Getting NEMO4-LIM to work at the Met Office: Semi-implicit coupling 
    1842             evap_ice (:,:,:) = evap_ice (:,:,:) * a_i(:,:,:) 
    1843             !!!!! 
    1844  
    18451844            devap_ice(:,:,jl) = zdevap_ice(:,:) 
    18461845         ENDDO 
     
    21102109      ENDIF 
    21112110       
    2112       !                                                      ! ========================= ! 
    2113       SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) )             !    topmelt and botmelt    ! 
    2114       !                                                      ! ========================= ! 
    2115       CASE ('coupled') 
    2116          qml_ice(:,:,:)=frcv(jpr_topm)%z3(:,:,:) * a_i(:,:,:) 
    2117          qcn_ice(:,:,:)=frcv(jpr_botm)%z3(:,:,:) * a_i(:,:,:) 
    2118  
    2119          !!!!! Getting NEMO4-LIM to work at Met Office: Semi-implicit coupling 
    2120          qml_ice(:,:,:)=qml_ice(:,:,:) * a_i(:,:,:) 
    2121          qcn_ice(:,:,:)=qcn_ice(:,:,:) * a_i(:,:,:) 
    2122       END SELECT 
     2111      IF( ln_meto_cpl ) THEN 
     2112         !                                                      ! ========================= ! 
     2113         SELECT CASE( TRIM( sn_rcv_iceflx%cldes ) )             !    topmelt and botmelt    ! 
     2114         !                                                      ! ========================= ! 
     2115         CASE ('coupled') 
     2116            qml_ice(:,:,:)=frcv(jpr_topm)%z3(:,:,:) * a_i(:,:,:) 
     2117            qcn_ice(:,:,:)=frcv(jpr_botm)%z3(:,:,:) * a_i(:,:,:) 
     2118         END SELECT 
     2119      ENDIF 
    21232120 
    21242121      ! --- Transmitted shortwave radiation (W/m2) --- ! 
     
    22742271         SELECT CASE( sn_snd_ttilyr%cldes) 
    22752272         CASE ('weighted ice') 
    2276             ttlyr_ice(:,:,:) = t1_ice(:,:,:) + rt0 
    2277             ztmp3(:,:,1:jpl) = ttlyr_ice(:,:,1:jpl) * a_i(:,:,1:jpl)  
     2273            ztmp3(:,:,1:jpl) = t1_ice(:,:,1:jpl) * a_i(:,:,1:jpl)  
    22782274         CASE default                     ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_ttilyr%cldes' ) 
    22792275         END SELECT 
     
    23962392      ENDIF 
    23972393 
    2398       !!!!! Getting NEMO4-LIM to work 
    2399       !!!!! Temporary code while we're not modelling meltponds 
    2400       a_p(:,:,1:jpl) = 0.0 
    2401       ht_p(:,:,1:jpl) = 0.0 
    2402  
    24032394      !  
    24042395      ! Send meltpond fields   
     
    24082399            SELECT CASE( sn_snd_mpnd%clcat )   
    24092400            CASE( 'yes' )   
    2410                ztmp3(:,:,1:jpl) =  a_p(:,:,1:jpl) * a_i(:,:,1:jpl)   
    2411                ztmp4(:,:,1:jpl) =  ht_p(:,:,1:jpl) * a_i(:,:,1:jpl)   
     2401               ztmp3(:,:,1:jpl) =  a_ip(:,:,1:jpl) 
     2402               ztmp4(:,:,1:jpl) =  v_ip(:,:,1:jpl)   
    24122403            CASE( 'no' )   
    24132404               ztmp3(:,:,:) = 0.0   
    24142405               ztmp4(:,:,:) = 0.0   
    24152406               DO jl=1,jpl   
    2416                  ztmp3(:,:,1) = ztmp3(:,:,1) + a_p(:,:,jpl) * a_i(:,:,jpl)   
    2417                  ztmp4(:,:,1) = ztmp4(:,:,1) + ht_p(:,:,jpl) * a_i(:,:,jpl)  
     2407                 ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip(:,:,jpl)   
     2408                 ztmp4(:,:,1) = ztmp4(:,:,1) + v_ip(:,:,jpl)  
    24182409               ENDDO   
    24192410            CASE default    ;   CALL ctl_stop( 'sbc_cpl_mpd: wrong definition of sn_snd_mpnd%clcat' )   
    24202411            END SELECT   
    2421          CASE( 'ice only' )      
    2422             ztmp3(:,:,1:jpl) = a_p(:,:,1:jpl)   
    2423             ztmp4(:,:,1:jpl) = ht_p(:,:,1:jpl)   
     2412         CASE( 'default' )    ;   CALL ctl_stop( 'sbc_cpl_mpd: wrong definition of sn_snd_mpnd%cldes' )      
    24242413         END SELECT   
    24252414         IF( ssnd(jps_a_p)%laction )   CALL cpl_snd( jps_a_p, isec, ztmp3, info )      
     
    27692758      IF( ssnd(jps_taum  )%laction )  CALL cpl_snd( jps_taum  , isec, RESHAPE ( taum, (/jpi,jpj,1/) ), info ) 
    27702759 
    2771       ztmp1(:,:) = sstfrz(:,:) + rt0 
     2760      CALL eos_fzp(tsn(:,:,1,jp_sal), sstfrz) 
     2761      ztmp1(:,:) = sstfrz(:,:) 
    27722762      IF( ssnd(jps_sstfrz)%laction )  CALL cpl_snd( jps_sstfrz, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info) 
    27732763 
  • branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

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