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

Changeset 6368


Ignore:
Timestamp:
2016-03-08T10:13:34+01:00 (8 years ago)
Author:
frrh
Message:

Add missing revision from dev_r5518_fix_global_ice. Our merge should have
started from 6340.

Location:
branches/UKMO/dev_r5518_debug_isf_restart/NEMOGCM/NEMO/OPA_SRC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_debug_isf_restart/NEMOGCM/NEMO/OPA_SRC/DOM/phycst.F90

    r6366 r6368  
    6868   REAL(wp), PUBLIC ::   rcdsn    =    0.31_wp       !: thermal conductivity of snow 
    6969   REAL(wp), PUBLIC ::   cpic     = 2067.0_wp        !: specific heat for ice  
     70#if defined key_cice 
     71   REAL(wp), PUBLIC ::   lsub     =    2.835e+6_wp   !: pure ice latent heat of sublimation                   [J/kg] 
     72#else 
    7073   REAL(wp), PUBLIC ::   lsub     =    2.834e+6_wp   !: pure ice latent heat of sublimation                   [J/kg] 
     74#endif 
    7175   REAL(wp), PUBLIC ::   lfus     =    0.334e+6_wp   !: latent heat of fusion of fresh ice                    [J/kg] 
    7276   REAL(wp), PUBLIC ::   tmut     =    0.054_wp      !: decrease of seawater meltpoint with salinity 
  • branches/UKMO/dev_r5518_debug_isf_restart/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90

    r6366 r6368  
    101101   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iu              !: ice fraction at NEMO U point 
    102102   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fr_iv              !: ice fraction at NEMO V point 
    103     
     103   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sstfrz             !: sea surface freezing temperature 
     104   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tsfc_ice           !: sea-ice surface skin temperature (on categories) 
     105   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   kn_ice             !: sea-ice surface layer thermal conductivity (on cats) 
     106 
    104107   ! variables used in the coupled interface 
    105108   INTEGER , PUBLIC, PARAMETER ::   jpl = ncat 
    106109   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice          ! jpi, jpj 
     110   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::  a_p, ht_p ! Meltpond fraction and depth 
    107111#endif 
    108112    
     
    152156 
    153157#if defined key_cice 
    154       ALLOCATE( qla_ice(jpi,jpj,1)    , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , & 
     158      ALLOCATE( qla_ice(jpi,jpj,ncat) , qlw_ice(jpi,jpj,1)    , qsr_ice(jpi,jpj,1)    , & 
    155159                wndi_ice(jpi,jpj)     , tatm_ice(jpi,jpj)     , qatm_ice(jpi,jpj)     , & 
    156160                wndj_ice(jpi,jpj)     , nfrzmlt(jpi,jpj)      , ss_iou(jpi,jpj)       , & 
    157161                ss_iov(jpi,jpj)       , fr_iu(jpi,jpj)        , fr_iv(jpi,jpj)        , & 
    158162                a_i(jpi,jpj,ncat)     , topmelt(jpi,jpj,ncat) , botmelt(jpi,jpj,ncat) , & 
    159                 STAT= ierr(1) ) 
    160       IF( ln_cpl )   ALLOCATE( u_ice(jpi,jpj)        , fr1_i0(jpi,jpj)       , tn_ice (jpi,jpj,1)    , & 
     163                sstfrz(jpi,jpj)       , STAT= ierr(1) ) 
     164   ! Alex West: Allocating tn_ice with 5 categories.  When NEMO is used with CICE, this variable 
     165   ! represents top layer ice temperature, which is multi-category. 
     166      IF( ln_cpl )   ALLOCATE( u_ice(jpi,jpj)        , fr1_i0(jpi,jpj)       , tn_ice (jpi,jpj,jpl)  , & 
    161167         &                     v_ice(jpi,jpj)        , fr2_i0(jpi,jpj)       , alb_ice(jpi,jpj,1)    , & 
    162168         &                     emp_ice(jpi,jpj)      , qns_ice(jpi,jpj,1)    , dqns_ice(jpi,jpj,1)   , & 
    163          &                     STAT= ierr(2) ) 
     169         &                     a_p(jpi,jpj,jpl)      , ht_p(jpi,jpj,jpl)     , tsfc_ice(jpi,jpj,jpl) , & 
     170         &                     kn_ice(jpi,jpj,jpl) ,    STAT=ierr(2) ) 
    164171       
    165172#endif 
  • branches/UKMO/dev_r5518_debug_isf_restart/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r6367 r6368  
    4646   USE p4zflx, ONLY : oce_co2 
    4747#endif 
    48 #if defined key_cice 
    49    USE ice_domain_size, only: ncat 
    50 #endif 
    5148#if defined key_lim3 
    5249   USE limthd_dh       ! for CALL lim_thd_snwblow 
     
    139136   INTEGER, PARAMETER ::   jps_e3t1st = 27            ! first level depth (vvl) 
    140137   INTEGER, PARAMETER ::   jps_fraqsr = 28            ! fraction of solar net radiation absorbed in the first ocean level 
    141    INTEGER, PARAMETER ::   jpsnd      = 28            ! total number of fields sended 
     138   INTEGER, PARAMETER ::   jps_a_p    = 29            ! meltpond fraction   
     139   INTEGER, PARAMETER ::   jps_ht_p   = 30            ! meltpond depth (m)  
     140   INTEGER, PARAMETER ::   jps_kice   = 31            ! ice surface layer thermal conductivity 
     141   INTEGER, PARAMETER ::   jps_sstfrz = 32            ! sea-surface freezing temperature 
     142   INTEGER, PARAMETER ::   jps_fice1  = 33            ! first-order ice concentration (for time-travelling ice coupling) 
     143   INTEGER, PARAMETER ::   jpsnd      = 33            ! total number of fields sended 
    142144 
    143145   !                                                         !!** namelist namsbc_cpl ** 
     
    150152   END TYPE FLD_C 
    151153   ! Send to the atmosphere                           ! 
    152    TYPE(FLD_C) ::   sn_snd_temp, sn_snd_alb, sn_snd_thick, sn_snd_crt, sn_snd_co2                         
     154   TYPE(FLD_C) ::   sn_snd_temp, sn_snd_alb, sn_snd_thick, sn_snd_crt, sn_snd_co2, sn_snd_cond, sn_snd_mpnd, sn_snd_sstfrz, sn_snd_thick1 
     155 
    153156   ! Received from the atmosphere                     ! 
    154157   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 
     
    278281         WRITE(numout,*)'                      - mesh          = ', sn_snd_crt%clvgrd 
    279282         WRITE(numout,*)'      oce co2 flux                    = ', TRIM(sn_snd_co2%cldes   ), ' (', TRIM(sn_snd_co2%clcat   ), ')' 
     283         WRITE(numout,*)'      ice effective conductivity      = ', TRIM(sn_snd_cond%cldes   ), ' (', TRIM(sn_snd_cond%clcat   ), ')' 
     284         WRITE(numout,*)'      meltponds fraction & depth      = ', TRIM(sn_snd_mpnd%cldes  ), ' (', TRIM(sn_snd_mpnd%clcat   ), ')' 
     285         WRITE(numout,*)'      sea surface freezing temp       = ', TRIM(sn_snd_sstfrz%cldes   ), ' (', TRIM(sn_snd_sstfrz%clcat   ), ')' 
     286 
    280287         WRITE(numout,*)'  nn_cplmodel                         = ', nn_cplmodel 
    281288         WRITE(numout,*)'  ln_usecplmask                       = ', ln_usecplmask 
     
    396403      srcv(jpr_snow)%clname = 'OTotSnow'      ! Snow = solid precipitation 
    397404      srcv(jpr_tevp)%clname = 'OTotEvap'      ! total evaporation (over oce + ice sublimation) 
    398       srcv(jpr_ievp)%clname = 'OIceEvap'      ! evaporation over ice = sublimation 
     405      srcv(jpr_ievp)%clname = 'OIceEvp'      ! evaporation over ice = sublimation 
    399406      srcv(jpr_sbpr)%clname = 'OSubMPre'      ! sublimation - liquid precipitation - solid precipitation  
    400407      srcv(jpr_semp)%clname = 'OISubMSn'      ! ice solid water budget = sublimation - solid precipitation 
     
    409416      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_emp%cldes' ) 
    410417      END SELECT 
    411  
     418      !Set the number of categories for coupling of sublimation 
     419      IF ( TRIM( sn_rcv_emp%clcat ) == 'yes' ) srcv(jpr_ievp)%nct = jpl 
     420      ! 
    412421      !                                                      ! ------------------------- ! 
    413422      !                                                      !     Runoffs & Calving     !    
     
    499508         srcv(jpr_topm:jpr_botm)%laction = .TRUE. 
    500509      ENDIF 
     510       
     511#if defined key_cice && ! defined key_cice4 
     512      !                                                      ! ----------------------------- ! 
     513      !                                                      !  sea-ice skin temperature     !    
     514      !                                                      !  used in meltpond scheme      ! 
     515      !                                                      !  May be calculated in Atm     ! 
     516      !                                                      ! ----------------------------- ! 
     517      srcv(jpr_ts_ice)%clname = 'OTsfIce' 
     518      IF ( TRIM( sn_rcv_ts_ice%cldes ) == 'ice' ) srcv(jpr_ts_ice)%laction = .TRUE. 
     519      IF ( TRIM( sn_rcv_ts_ice%clcat ) == 'yes' ) srcv(jpr_ts_ice)%nct = jpl 
     520      !TODO: Should there be a consistency check here? 
     521#endif 
     522 
    501523      !                                                      ! ------------------------------- ! 
    502524      !                                                      !   OPA-SAS coupling - rcv by opa !    
     
    616638      !                                                      ! ------------------------- ! 
    617639      ssnd(jps_toce)%clname = 'O_SSTSST' 
    618       ssnd(jps_tice)%clname = 'O_TepIce' 
     640      ssnd(jps_tice)%clname = 'OTepIce' 
    619641      ssnd(jps_tmix)%clname = 'O_TepMix' 
    620642      SELECT CASE( TRIM( sn_snd_temp%cldes ) ) 
    621643      CASE( 'none'                                 )       ! nothing to do 
    622644      CASE( 'oce only'                             )   ;   ssnd( jps_toce )%laction = .TRUE. 
    623       CASE( 'oce and ice' , 'weighted oce and ice' ) 
     645      CASE( 'oce and ice' , 'weighted oce and ice' , 'oce and weighted ice') 
    624646         ssnd( (/jps_toce, jps_tice/) )%laction = .TRUE. 
    625647         IF ( TRIM( sn_snd_temp%clcat ) == 'yes' )  ssnd(jps_tice)%nct = jpl 
     
    650672 
    651673      !                                                      ! ------------------------- ! 
    652       !                                                      !  Ice fraction & Thickness !  
     674      !                                                      !  Ice fraction & Thickness  
    653675      !                                                      ! ------------------------- ! 
    654676      ssnd(jps_fice)%clname = 'OIceFrc' 
    655677      ssnd(jps_hice)%clname = 'OIceTck' 
    656678      ssnd(jps_hsnw)%clname = 'OSnwTck' 
     679      ssnd(jps_a_p)%clname  = 'OPndFrc' 
     680      ssnd(jps_ht_p)%clname = 'OPndTck' 
     681      ssnd(jps_fice1)%clname = 'OIceFrd' 
    657682      IF( k_ice /= 0 ) THEN 
    658683         ssnd(jps_fice)%laction = .TRUE.                  ! if ice treated in the ocean (even in climato case) 
     684         ssnd(jps_fice1)%laction = .TRUE.                 ! First-order regridded ice concentration, to be used 
     685                                                     ! in producing atmos-to-ice fluxes 
    659686! Currently no namelist entry to determine sending of multi-category ice fraction so use the thickness entry for now 
    660687         IF ( TRIM( sn_snd_thick%clcat ) == 'yes' ) ssnd(jps_fice)%nct = jpl 
     688         IF ( TRIM( sn_snd_thick1%clcat ) == 'yes' ) ssnd(jps_fice1)%nct = jpl 
    661689      ENDIF 
    662690       
     
    673701      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_thick%cldes' ) 
    674702      END SELECT 
     703 
     704      !                                                      ! ------------------------- ! 
     705      !                                                      ! Ice Meltponds             ! 
     706      !                                                      ! ------------------------- ! 
     707#if defined key_cice && ! defined key_cice4 
     708      ! Meltponds only CICE5  
     709      ssnd(jps_a_p)%clname = 'OPndFrc'    
     710      ssnd(jps_ht_p)%clname = 'OPndTck'    
     711      SELECT CASE ( TRIM( sn_snd_mpnd%cldes ) ) 
     712      CASE ( 'none' ) 
     713         ssnd(jps_a_p)%laction = .FALSE. 
     714         ssnd(jps_ht_p)%laction = .FALSE. 
     715      CASE ( 'ice only' )  
     716         ssnd(jps_a_p)%laction = .TRUE. 
     717         ssnd(jps_ht_p)%laction = .TRUE. 
     718         IF ( TRIM( sn_snd_mpnd%clcat ) == 'yes' ) THEN 
     719            ssnd(jps_a_p)%nct = jpl 
     720            ssnd(jps_ht_p)%nct = jpl 
     721         ELSE 
     722            IF ( jpl > 1 ) THEN 
     723               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_mpnd%cldes if not exchanging category fields' ) 
     724            ENDIF 
     725         ENDIF 
     726      CASE ( 'weighted ice' )  
     727         ssnd(jps_a_p)%laction = .TRUE. 
     728         ssnd(jps_ht_p)%laction = .TRUE. 
     729         IF ( TRIM( sn_snd_mpnd%clcat ) == 'yes' ) THEN 
     730            ssnd(jps_a_p)%nct = jpl  
     731            ssnd(jps_ht_p)%nct = jpl  
     732         ENDIF 
     733      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_mpnd%cldes' ) 
     734      END SELECT 
     735#else 
     736      IF( TRIM( sn_snd_mpnd%cldes /= 'none' ) THEN 
     737         CALL ctl_stop('Meltponds can only be used with CICEv5') 
     738      ENDIF 
     739#endif 
    675740 
    676741      !                                                      ! ------------------------- ! 
     
    705770      !                                                      ! ------------------------- ! 
    706771      ssnd(jps_co2)%clname = 'O_CO2FLX' ;  IF( TRIM(sn_snd_co2%cldes) == 'coupled' )    ssnd(jps_co2 )%laction = .TRUE. 
     772      ! 
     773       
     774      !                                                      ! ------------------------- ! 
     775      !                                                      ! Sea surface freezing temp ! 
     776      !                                                      ! ------------------------- ! 
     777      ssnd(jps_sstfrz)%clname = 'O_SSTFrz' ; IF( TRIM(sn_snd_sstfrz%cldes) == 'coupled' )  ssnd(jps_sstfrz)%laction = .TRUE. 
     778      ! 
     779      !                                                      ! ------------------------- ! 
     780      !                                                      !    Ice conductivity       ! 
     781      !                                                      ! ------------------------- ! 
     782      ! Note that ultimately we will move to passing an ocean effective conductivity as well so there 
     783      ! will be some changes to the parts of the code which currently relate only to ice conductivity 
     784      ssnd(jps_kice )%clname = 'OIceKn' 
     785      SELECT CASE ( TRIM( sn_snd_cond%cldes ) ) 
     786      CASE ( 'none' ) 
     787         ssnd(jps_kice)%laction = .FALSE. 
     788      CASE ( 'ice only' ) 
     789         ssnd(jps_kice)%laction = .TRUE. 
     790         IF ( TRIM( sn_snd_cond%clcat ) == 'yes' ) THEN 
     791            ssnd(jps_kice)%nct = jpl 
     792         ELSE 
     793            IF ( jpl > 1 ) THEN 
     794               CALL ctl_stop( 'sbc_cpl_init: use weighted ice option for sn_snd_cond%cldes if not exchanging category fields' ) 
     795            ENDIF 
     796         ENDIF 
     797      CASE ( 'weighted ice' ) 
     798         ssnd(jps_kice)%laction = .TRUE. 
     799         IF ( TRIM( sn_snd_cond%clcat ) == 'yes' ) ssnd(jps_kice)%nct = jpl 
     800      CASE default   ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_snd_cond%cldes' ) 
     801      END SELECT 
     802      ! 
     803       
    707804 
    708805      !                                                      ! ------------------------------- ! 
     
    882979      !! 
    883980      LOGICAL  ::   llnewtx, llnewtau      ! update wind stress components and module?? 
    884       INTEGER  ::   ji, jj, jn             ! dummy loop indices 
     981      INTEGER  ::   ji, jj, jl, jn         ! dummy loop indices 
    885982      INTEGER  ::   isec                   ! number of seconds since nit000 (assuming rdttra did not change since nit000) 
    886983      REAL(wp) ::   zcumulneg, zcumulpos   ! temporary scalars      
     
    10371134      !                                                      ! ================== ! 
    10381135      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1) 
     1136#endif 
     1137 
     1138#if defined key_cice && ! defined key_cice4 
     1139      !  ! Sea ice surface skin temp: 
     1140      IF( srcv(jpr_ts_ice)%laction ) THEN 
     1141        DO jl = 1, jpl 
     1142          DO jj = 1, jpj 
     1143            DO ji = 1, jpi 
     1144              IF (frcv(jpr_ts_ice)%z3(ji,jj,jl) > 0.0) THEN 
     1145                tsfc_ice(ji,jj,jl) = 0.0 
     1146              ELSE IF (frcv(jpr_ts_ice)%z3(ji,jj,jl) < -60.0) THEN 
     1147                tsfc_ice(ji,jj,jl) = -60.0 
     1148              ELSE 
     1149                tsfc_ice(ji,jj,jl) = frcv(jpr_ts_ice)%z3(ji,jj,jl) 
     1150              ENDIF 
     1151            END DO 
     1152          END DO 
     1153        END DO 
     1154      ENDIF 
    10391155#endif 
    10401156 
     
    15091625         zsprecip(:,:) = frcv(jpr_snow)%z3(:,:,1)                  ! May need to ensure positive here 
    15101626         ztprecip(:,:) = frcv(jpr_rain)%z3(:,:,1) + zsprecip(:,:)  ! May need to ensure positive here 
    1511          zemp_tot(:,:) = frcv(jpr_tevp)%z3(:,:,1) - ztprecip(:,:) 
     1627         zemp_tot(:,:) = frcv(jpr_tevp)%z3(:,:,1) - ztprecip(:,:)          
     1628#if defined key_cice 
     1629         IF ( TRIM(sn_rcv_emp%clcat) == 'yes' ) THEN 
     1630            ! zemp_ice is the sum of frcv(jpr_ievp)%z3(:,:,1) over all layers - snow 
     1631            zemp_ice(:,:) = - frcv(jpr_snow)%z3(:,:,1) 
     1632            DO jl=1,jpl 
     1633               zemp_ice(:,:   ) = zemp_ice(:,:) + frcv(jpr_ievp)%z3(:,:,jl) 
     1634            ENDDO 
     1635            ! latent heat coupled for each category in CICE 
     1636            qla_ice(:,:,1:jpl) = - frcv(jpr_ievp)%z3(:,:,1:jpl) * lsub 
     1637         ELSE 
     1638            ! If CICE has multicategories it still expects coupling fields for 
     1639            ! each even if we treat as a single field 
     1640            ! The latent heat flux is split between the ice categories according 
     1641            ! to the fraction of the ice in each category 
     1642            zemp_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1) 
     1643            WHERE ( zicefr(:,:) /= 0._wp )  
     1644               ztmp(:,:) = 1./zicefr(:,:) 
     1645            ELSEWHERE  
     1646               ztmp(:,:) = 0.e0 
     1647            END WHERE   
     1648            DO jl=1,jpl 
     1649               qla_ice(:,:,jl) = - a_i(:,:,jl) * ztmp(:,:) * frcv(jpr_ievp)%z3(:,:,1) * lsub  
     1650            END DO 
     1651            WHERE ( zicefr(:,:) == 0._wp )  qla_ice(:,:,1) = -frcv(jpr_ievp)%z3(:,:,1) * lsub  
     1652         ENDIF 
     1653#else          
    15121654         zemp_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1) 
     1655#endif                   
    15131656            CALL iom_put( 'rain'         , frcv(jpr_rain)%z3(:,:,1)              )   ! liquid precipitation  
    15141657         IF( iom_use('hflx_rain_cea') )   & 
     
    18642007               CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' ) 
    18652008               END SELECT 
     2009            CASE( 'oce and weighted ice' )   ;   ztmp1(:,:) =   tsn(:,:,1,jp_tem) + rt0  
     2010               SELECT CASE( sn_snd_temp%clcat ) 
     2011               CASE( 'yes' )    
     2012           ztmp3(:,:,1:jpl) = tn_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
     2013               CASE( 'no' ) 
     2014           ztmp3(:,:,:) = 0.0 
     2015           DO jl=1,jpl 
     2016                     ztmp3(:,:,1) = ztmp3(:,:,1) + tn_ice(:,:,jl) * a_i(:,:,jl) 
     2017           ENDDO 
     2018               CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' ) 
     2019               END SELECT 
    18662020            CASE( 'mixed oce-ice'        )    
    18672021               ztmp1(:,:) = ( ztmp1(:,:) + rt0 ) * zfr_l(:,:)  
     
    19052059         END SELECT 
    19062060         IF( ssnd(jps_fice)%laction )   CALL cpl_snd( jps_fice, isec, ztmp3, info ) 
     2061      ENDIF 
     2062       
     2063      ! Send ice fraction field (first order interpolation), for weighting UM fluxes to be passed to NEMO 
     2064      IF (ssnd(jps_fice1)%laction) THEN 
     2065         SELECT CASE (sn_snd_thick1%clcat) 
     2066         CASE( 'yes' )   ;   ztmp3(:,:,1:jpl) =  a_i(:,:,1:jpl) 
     2067         CASE( 'no' )    ;   ztmp3(:,:,1) = fr_i(:,:) 
     2068         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick1%clcat' ) 
     2069    END SELECT 
     2070         CALL cpl_snd (jps_fice1, isec, ztmp3, info) 
    19072071      ENDIF 
    19082072       
     
    19502114         IF( ssnd(jps_hsnw)%laction )   CALL cpl_snd( jps_hsnw, isec, ztmp4, info ) 
    19512115      ENDIF 
     2116      ! 
     2117      ! Send meltpond fields  
     2118      IF( ssnd(jps_a_p)%laction .OR. ssnd(jps_ht_p)%laction ) THEN 
     2119         SELECT CASE( sn_snd_mpnd%cldes)  
     2120         CASE( 'weighted ice' )  
     2121            SELECT CASE( sn_snd_mpnd%clcat )  
     2122            CASE( 'yes' )  
     2123               ztmp3(:,:,1:jpl) =  a_p(:,:,1:jpl) * a_i(:,:,1:jpl)  
     2124               ztmp4(:,:,1:jpl) =  ht_p(:,:,1:jpl) * a_i(:,:,1:jpl)  
     2125            CASE( 'no' )  
     2126               ztmp3(:,:,:) = 0.0  
     2127               ztmp4(:,:,:) = 0.0  
     2128               DO jl=1,jpl  
     2129                 ztmp3(:,:,1) = ztmp3(:,:,1) + a_p(:,:,jpl) * a_i(:,:,jpl)  
     2130                 ztmp4(:,:,1) = ztmp4(:,:,1) + ht_p(:,:,jpl) * a_i(:,:,jpl)  
     2131               ENDDO  
     2132            CASE default    ;   CALL ctl_stop( 'sbc_cpl_mpd: wrong definition of sn_snd_mpnd%clcat' )  
     2133            END SELECT  
     2134         CASE( 'ice only' )     
     2135            ztmp3(:,:,1:jpl) = a_p(:,:,1:jpl)  
     2136            ztmp4(:,:,1:jpl) = ht_p(:,:,1:jpl)  
     2137         END SELECT  
     2138         IF( ssnd(jps_a_p)%laction )   CALL cpl_snd( jps_a_p, isec, ztmp3, info )     
     2139         IF( ssnd(jps_ht_p)%laction )   CALL cpl_snd( jps_ht_p, isec, ztmp4, info )     
     2140         ! 
     2141         ! Send ice effective conductivity 
     2142         SELECT CASE( sn_snd_cond%cldes) 
     2143         CASE( 'weighted ice' )    
     2144            SELECT CASE( sn_snd_cond%clcat ) 
     2145            CASE( 'yes' )    
     2146               ztmp3(:,:,1:jpl) =  kn_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
     2147            CASE( 'no' ) 
     2148               ztmp3(:,:,:) = 0.0 
     2149               DO jl=1,jpl 
     2150                 ztmp3(:,:,1) = ztmp3(:,:,1) + kn_ice(:,:,jl) * a_i(:,:,jl) 
     2151               ENDDO 
     2152            CASE default                  ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_cond%clcat' ) 
     2153            END SELECT 
     2154         CASE( 'ice only' )    
     2155           ztmp3(:,:,1:jpl) = kn_ice(:,:,1:jpl) 
     2156         END SELECT 
     2157         IF( ssnd(jps_kice)%laction )   CALL cpl_snd( jps_kice, isec, ztmp3, info ) 
     2158      ENDIF 
     2159      ! 
    19522160      ! 
    19532161#if defined key_cpl_carbon_cycle 
     
    21292337      IF( ssnd(jps_rnf   )%laction )  CALL cpl_snd( jps_rnf   , isec, RESHAPE ( rnf , (/jpi,jpj,1/) ), info ) 
    21302338      IF( ssnd(jps_taum  )%laction )  CALL cpl_snd( jps_taum  , isec, RESHAPE ( taum, (/jpi,jpj,1/) ), info ) 
    2131  
     2339       
     2340      ztmp1(:,:) = sstfrz(:,:) + rt0 
     2341      IF( ssnd(jps_sstfrz)%laction )  CALL cpl_snd( jps_sstfrz, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info ) 
     2342      ! 
    21322343      CALL wrk_dealloc( jpi,jpj, zfr_l, ztmp1, ztmp2, zotx1, zoty1, zotz1, zitx1, zity1, zitz1 ) 
    21332344      CALL wrk_dealloc( jpi,jpj,jpl, ztmp3, ztmp4 ) 
  • branches/UKMO/dev_r5518_debug_isf_restart/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r6367 r6368  
    1515   USE dom_oce         ! ocean space and time domain 
    1616   USE domvvl 
    17    USE phycst, only : rcp, rau0, r1_rau0, rhosn, rhoic 
     17   USE eosbn2, only : eos_fzp ! Function to calculate freezing point of seawater 
     18   USE phycst, only : rcp, rau0, r1_rau0, rhosn, rhoic, rt0 
    1819   USE in_out_manager  ! I/O manager 
    1920   USE iom, ONLY : iom_put,iom_use              ! I/O manager library !!Joakim edit 
     
    3738   USE ice_gather_scatter 
    3839   USE ice_calendar, only: dt 
     40# if defined key_cice4 
    3941   USE ice_state, only: aice,aicen,uvel,vvel,vsno,vsnon,vice,vicen 
    40 # if defined key_cice4 
    4142   USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow,  & 
    4243                strocnxT,strocnyT,                               &  
     
    4546                flatn_f,fsurfn_f,fcondtopn_f,                    & 
    4647                uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl,   & 
    47                 swvdr,swvdf,swidr,swidf 
     48                swvdr,swvdf,swidr,swidf,Tf 
    4849   USE ice_therm_vertical, only: calc_Tsfc 
    4950#else 
     51   USE ice_state, only: aice,aicen,uvel,nt_hpnd,trcrn,vvel,vsno,& 
     52                vsnon,vice,vicen,nt_Tsfc 
    5053   USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow,  & 
    5154                strocnxT,strocnyT,                               &  
    52                 sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_ai,     & 
    53                 fresh_ai,fhocn_ai,fswthru_ai,frzmlt,          & 
     55                sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_ai,      & 
     56                fresh_ai,fhocn_ai,fswthru_ai,frzmlt,             & 
    5457                flatn_f,fsurfn_f,fcondtopn_f,                    & 
    5558                uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl,   & 
    56                 swvdr,swvdf,swidr,swidf 
    57    USE ice_therm_shared, only: calc_Tsfc 
     59                swvdr,swvdf,swidr,swidf,Tf,                      & 
     60      !! When using NEMO with CICE, this change requires use of  
     61      !! one of the following two CICE branches: 
     62      !! - at CICE5.0,   hadax/r1015_GSI8_with_GSI7 
     63      !! - at CICE5.1.2, hadax/vn5.1.2_GSI8 
     64                keffn_top,Tn_top 
     65 
     66   USE ice_therm_shared, only: calc_Tsfc, heat_capacity 
     67   USE ice_shortwave, only: apeffn 
    5868#endif 
    5969   USE ice_forcing, only: frcvdr,frcvdf,frcidr,frcidf 
     
    291301  
    292302      CALL wrk_dealloc( jpi,jpj, ztmp1, ztmp2 ) 
     303      CALL wrk_dealloc( jpi,jpj,jpk, ztfrz3d )  
    293304      ! 
    294305      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_init') 
     
    351362         CALL nemo2cice(ztmp,stray,'F', -1. ) 
    352363 
     364 
     365! Alex West: From configuration GSI8 onwards, when NEMO is used with CICE in 
     366! HadGEM3 the 'time-travelling ice' coupling approach is used, whereby  
     367! atmosphere-ice fluxes are passed as pseudo-local values, formed by dividing 
     368! gridbox mean fluxes in the UM by future ice concentration obtained through   
     369! OASIS.  This allows for a much more realistic apportionment of energy through 
     370! the ice - and conserves energy. 
     371! Therefore the fluxes are now divided by ice concentration in the coupled 
     372! formulation (jp_purecpl) as well as for jp_flx.  This NEMO branch should only 
     373! be used at UM10.2 onwards (unless an explicit GSI8 UM branch is included), at 
     374! which point the GSI8 UM changes were committed. 
     375 
    353376! Surface downward latent heat flux (CI_5) 
    354          IF (ksbc == jp_flx) THEN 
     377         IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    355378            DO jl=1,ncat 
    356379               ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl) 
     
    364387           ztmpn(:,:,1:ncat)=qla_ice(:,:,1:ncat) 
    365388         ENDIF 
     389 
    366390         DO jl=1,ncat 
    367391            CALL nemo2cice(ztmpn(:,:,jl),flatn_f(:,:,jl,:),'T', 1. ) 
     
    369393! GBM conductive flux through ice (CI_6) 
    370394!  Convert to GBM 
    371             IF (ksbc == jp_flx) THEN 
     395            IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    372396               ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl) 
    373397            ELSE 
     
    378402! GBM surface heat flux (CI_7) 
    379403!  Convert to GBM 
    380             IF (ksbc == jp_flx) THEN 
     404            IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    381405               ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl)  
    382406            ELSE 
     
    438462      CALL nemo2cice(ztmp,frain,'T', 1. )  
    439463 
     464! Recalculate freezing temperature and send to CICE  
     465      sstfrz(:,:)=eos_fzp(sss_m(:,:), fsdept_n(:,:,1))  
     466      CALL nemo2cice(sstfrz,Tf,'T', 1. ) 
     467 
    440468! Freezing/melting potential 
    441469! Calculated over NEMO leapfrog timestep (hence 2*dt) 
    442       nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:)*(Tocnfrz-sst_m(:,:))/(2.0*dt) 
    443  
    444       ztmp(:,:) = nfrzmlt(:,:) 
    445       CALL nemo2cice(ztmp,frzmlt,'T', 1. ) 
     470      nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:)*(sstfrz(:,:)-sst_m(:,:))/(2.0*dt)  
     471      CALL nemo2cice(nfrzmlt,frzmlt,'T', 1. ) 
    446472 
    447473! SST  and SSS 
     
    733759         CALL cice2nemo(vicen(:,:,jl,:),ht_i(:,:,jl),'T', 1. ) 
    734760      ENDDO 
     761 
     762#if ! defined key_cice4 
     763! Meltpond fraction and depth 
     764      DO jl = 1,ncat 
     765         CALL cice2nemo(apeffn(:,:,jl,:),a_p(:,:,jl),'T', 1. ) 
     766         CALL cice2nemo(trcrn(:,:,nt_hpnd,jl,:),ht_p(:,:,jl),'T', 1. ) 
     767      ENDDO 
     768#endif 
     769 
     770 
     771! If using multilayers thermodynamics in CICE then get top layer temperature 
     772! and effective conductivity        
     773!! When using NEMO with CICE, this change requires use of  
     774!! one of the following two CICE branches: 
     775!! - at CICE5.0,   hadax/r1015_GSI8_with_GSI7 
     776!! - at CICE5.1.2, hadax/vn5.1.2_GSI8 
     777      IF (heat_capacity) THEN 
     778         DO jl = 1,ncat 
     779            CALL cice2nemo(Tn_top(:,:,jl,:),tn_ice(:,:,jl),'T', 1. ) 
     780            CALL cice2nemo(keffn_top(:,:,jl,:),kn_ice(:,:,jl),'T', 1. ) 
     781         ENDDO 
     782! Convert surface temperature to Kelvin 
     783         tn_ice(:,:,:)=tn_ice(:,:,:)+rt0 
     784      ELSE 
     785         tn_ice(:,:,:) = 0.0 
     786         kn_ice(:,:,:) = 0.0 
     787      ENDIF        
     788 
    735789      ! 
    736790      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_hadgam') 
Note: See TracChangeset for help on using the changeset viewer.