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 5663 for branches/UKMO/dev_r5518_CICE_coupling_GSI7_GSI8/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90 – NEMO

Ignore:
Timestamp:
2015-08-03T15:53:06+02:00 (9 years ago)
Author:
dancopsey
Message:

Merged in Alex West's GSI8 changes from eld259:/data/local/hadax/FCM_working/NEMO/Multilayers/NEMO3.6_stable/UKMO1_CICE_coupling_GSI7_GSI8

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_CICE_coupling_GSI7_GSI8/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90

    r5662 r5663  
    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 
     
    161171      INTEGER, INTENT( in  ) ::   ksbc                ! surface forcing type 
    162172      REAL(wp), DIMENSION(:,:), POINTER :: ztmp1, ztmp2 
     173      REAL(wp), DIMENSION(:,:,:), POINTER :: ztfrz3d 
    163174      REAL(wp) ::   zcoefu, zcoefv, zcoeff            ! local scalar 
    164175      INTEGER  ::   ji, jj, jl, jk                    ! dummy loop indices 
     
    173184      ji_off = INT ( (jpiglo - nx_global) / 2 ) 
    174185      jj_off = INT ( (jpjglo - ny_global) / 2 ) 
     186 
     187      ! Set freezing temperatures and ensure consistencey between NEMO and CICE 
     188      CALL wrk_alloc( jpi,jpj,jpk, ztfrz3d )  
     189      DO jk=1,jpk 
     190         ztfrz3d(:,:,jk) = eos_fzp( tsn(:,:,jk,jp_sal), fsdept_n(:,:,jk) ) 
     191      ENDDO 
     192 
     193      !Ensure that no temperature points are below freezing if not a NEMO restart 
     194      IF( .NOT. ln_rstart ) THEN 
     195         tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),ztfrz3d) 
     196         tsb(:,:,:,jp_tem) = tsn(:,:,:,jp_tem) 
     197      ENDIF 
    175198 
    176199#if defined key_nemocice_decomp 
     
    202225      IF( sbc_ice_cice_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate cice arrays' ) 
    203226 
    204 ! Ensure ocean temperatures are nowhere below freezing if not a NEMO restart 
    205       IF( .NOT. ln_rstart ) THEN 
    206          tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),Tocnfrz) 
    207          tsb(:,:,:,jp_tem) = tsn(:,:,:,jp_tem) 
    208       ENDIF 
     227      ! Populate the surface freezing temperature array 
     228      sstfrz(:,:)=ztfrz3d(:,:,1) 
    209229 
    210230      fr_iu(:,:)=0.0 
     
    283303  
    284304      CALL wrk_dealloc( jpi,jpj, ztmp1, ztmp2 ) 
     305      CALL wrk_dealloc( jpi,jpj,jpk, ztfrz3d )  
    285306      ! 
    286307      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_init') 
     
    343364         CALL nemo2cice(ztmp,stray,'F', -1. ) 
    344365 
     366 
     367! Alex West: From configuration GSI8 onwards, when NEMO is used with CICE in 
     368! HadGEM3 the 'time-travelling ice' coupling approach is used, whereby  
     369! atmosphere-ice fluxes are passed as pseudo-local values, formed by dividing 
     370! gridbox mean fluxes in the UM by future ice concentration obtained through   
     371! OASIS.  This allows for a much more realistic apportionment of energy through 
     372! the ice - and conserves energy. 
     373! Therefore the fluxes are now divided by ice concentration in the coupled 
     374! formulation (jp_purecpl) as well as for jp_flx.  This NEMO branch should only 
     375! be used at UM10.2 onwards (unless an explicit GSI8 UM branch is included), at 
     376! which point the GSI8 UM changes were committed. 
     377 
    345378! Surface downward latent heat flux (CI_5) 
    346          IF (ksbc == jp_flx) THEN 
     379         IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    347380            DO jl=1,ncat 
    348381               ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl) 
    349382            ENDDO 
    350383         ELSE 
    351 ! emp_ice is set in sbc_cpl_ice_flx as sublimation-snow 
    352             qla_ice(:,:,1)= - ( emp_ice(:,:)+sprecip(:,:) ) * Lsub 
    353 ! End of temporary code 
    354             DO jj=1,jpj 
    355                DO ji=1,jpi 
    356                   IF (fr_i(ji,jj).eq.0.0) THEN 
    357                      DO jl=1,ncat 
    358                         ztmpn(ji,jj,jl)=0.0 
    359                      ENDDO 
    360                      ! This will then be conserved in CICE 
    361                      ztmpn(ji,jj,1)=qla_ice(ji,jj,1) 
    362                   ELSE 
    363                      DO jl=1,ncat 
    364                         ztmpn(ji,jj,jl)=qla_ice(ji,jj,1)*a_i(ji,jj,jl)/fr_i(ji,jj) 
    365                      ENDDO 
    366                   ENDIF 
    367                ENDDO 
    368             ENDDO 
     384           !In coupled mode - qla_ice calculated in sbc_cpl for each category 
     385           ztmpn(:,:,1:ncat)=qla_ice(:,:,1:ncat) 
    369386         ENDIF 
     387 
    370388         DO jl=1,ncat 
    371389            CALL nemo2cice(ztmpn(:,:,jl),flatn_f(:,:,jl,:),'T', 1. ) 
     
    373391! GBM conductive flux through ice (CI_6) 
    374392!  Convert to GBM 
    375             IF (ksbc == jp_flx) THEN 
     393            IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    376394               ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl) 
    377395            ELSE 
     
    382400! GBM surface heat flux (CI_7) 
    383401!  Convert to GBM 
    384             IF (ksbc == jp_flx) THEN 
     402            IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    385403               ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl)  
    386404            ELSE 
     
    442460      CALL nemo2cice(ztmp,frain,'T', 1. )  
    443461 
     462! Recalculate freezing temperature and send to CICE  
     463      sstfrz(:,:)=eos_fzp(sss_m(:,:), fsdept_n(:,:,1))  
     464      CALL nemo2cice(sstfrz,Tf,'T', 1. ) 
     465 
    444466! Freezing/melting potential 
    445467! Calculated over NEMO leapfrog timestep (hence 2*dt) 
    446       nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:)*(Tocnfrz-sst_m(:,:))/(2.0*dt) 
    447  
    448       ztmp(:,:) = nfrzmlt(:,:) 
    449       CALL nemo2cice(ztmp,frzmlt,'T', 1. ) 
     468      nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:)*(sstfrz(:,:)-sst_m(:,:))/(2.0*dt)  
     469      CALL nemo2cice(nfrzmlt,frzmlt,'T', 1. ) 
    450470 
    451471! SST  and SSS 
     
    453473      CALL nemo2cice(sst_m,sst,'T', 1. ) 
    454474      CALL nemo2cice(sss_m,sss,'T', 1. ) 
     475 
     476! Sea ice surface skin temperature 
     477      DO jl=1,ncat 
     478        CALL nemo2cice(tsfc_ice(:,:,jl), trcrn(:,:,nt_tsfc,jl,:),'T',1.) 
     479      ENDDO  
    455480 
    456481! x comp and y comp of surface ocean current 
     
    730755         CALL cice2nemo(vicen(:,:,jl,:),ht_i(:,:,jl),'T', 1. ) 
    731756      ENDDO 
     757 
     758#if ! defined key_cice4 
     759! Meltpond fraction and depth 
     760      DO jl = 1,ncat 
     761         CALL cice2nemo(apeffn(:,:,jl,:),a_p(:,:,jl),'T', 1. ) 
     762         CALL cice2nemo(trcrn(:,:,nt_hpnd,jl,:),ht_p(:,:,jl),'T', 1. ) 
     763      ENDDO 
     764#endif 
     765 
     766 
     767! If using multilayers thermodynamics in CICE then get top layer temperature 
     768! and effective conductivity        
     769!! When using NEMO with CICE, this change requires use of  
     770!! one of the following two CICE branches: 
     771!! - at CICE5.0,   hadax/r1015_GSI8_with_GSI7 
     772!! - at CICE5.1.2, hadax/vn5.1.2_GSI8 
     773      IF (heat_capacity) THEN 
     774         DO jl = 1,ncat 
     775            CALL cice2nemo(Tn_top(:,:,jl,:),tn_ice(:,:,jl),'T', 1. ) 
     776            CALL cice2nemo(keffn_top(:,:,jl,:),kn_ice(:,:,jl),'T', 1. ) 
     777         ENDDO 
     778! Convert surface temperature to Kelvin 
     779         tn_ice(:,:,:)=tn_ice(:,:,:)+rt0 
     780      ELSE 
     781         tn_ice(:,:,:) = 0.0 
     782         kn_ice(:,:,:) = 0.0 
     783      ENDIF        
     784 
    732785      ! 
    733786      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_hadgam') 
Note: See TracChangeset for help on using the changeset viewer.