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

Ignore:
Timestamp:
2016-04-20T11:42:09+02:00 (8 years ago)
Author:
davestorkey
Message:

Commit changes from dev_r5518_coupling_GSI7_GSI8_landice and its ancestor branch dev_r5518_CICE_coupling_GSI7_GSI8.
Custom merge into /branches/UKMO/dev_r5518_GO6_package/NEMOGCM: r6023 cf. r5668 of /branches/UKMO/dev_r5518_coupling_GSI7_GSI8_landice/NEMOGCM@6487

Custom merge into /branches/UKMO/dev_r5518_GO6_package/NEMOGCM: r5668 cf. r5662 of /branches/UKMO/dev_r5518_CICE_coupling_GSI7_GSI8/NEMOGCM@6487

File:
1 edited

Legend:

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

    r6486 r6488  
    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 
    163       REAL(wp) ::   zcoefu, zcoefv, zcoeff            ! local scalar 
     173      REAL(wp), DIMENSION(:,:,:), POINTER :: ztfrz3d 
    164174      INTEGER  ::   ji, jj, jl, jk                    ! dummy loop indices 
    165175      !!--------------------------------------------------------------------- 
     
    174184      jj_off = INT ( (jpjglo - ny_global) / 2 ) 
    175185 
    176 #if defined key_nemocice_decomp 
    177       ! Pass initial SST from NEMO to CICE so ice is initialised correctly if 
    178       ! there is no restart file. 
    179       ! Values from a CICE restart file would overwrite this 
    180       IF ( .NOT. ln_rstart ) THEN     
    181          CALL nemo2cice( tsn(:,:,1,jp_tem) , sst , 'T' , 1.)  
    182       ENDIF   
    183 #endif 
    184  
    185 ! Initialize CICE 
     186      ! Initialize CICE 
    186187      CALL CICE_Initialize 
    187188 
    188 ! Do some CICE consistency checks 
     189      ! Do some CICE consistency checks 
    189190      IF ( (ksbc == jp_flx) .OR. (ksbc == jp_purecpl) ) THEN 
    190191         IF ( calc_strair .OR. calc_Tsfc ) THEN 
     
    198199 
    199200 
    200 ! allocate sbc_ice and sbc_cice arrays 
    201       IF( sbc_ice_alloc()      /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate arrays' ) 
     201      ! allocate sbc_ice and sbc_cice arrays 
     202      IF( sbc_ice_alloc()      /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_alloc : unable to allocate arrays' ) 
    202203      IF( sbc_ice_cice_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate cice arrays' ) 
    203204 
    204 ! Ensure ocean temperatures are nowhere below freezing if not a NEMO restart 
     205      ! Ensure that no temperature points are below freezing if not a NEMO restart 
    205206      IF( .NOT. ln_rstart ) THEN 
    206          tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),Tocnfrz) 
     207 
     208         CALL wrk_alloc( jpi,jpj,jpk, ztfrz3d )  
     209         DO jk=1,jpk 
     210            ztfrz3d(:,:,jk) = eos_fzp( tsn(:,:,jk,jp_sal), fsdept_n(:,:,jk) ) 
     211         ENDDO 
     212         tsn(:,:,:,jp_tem) = MAX( tsn(:,:,:,jp_tem), ztfrz3d ) 
    207213         tsb(:,:,:,jp_tem) = tsn(:,:,:,jp_tem) 
    208       ENDIF 
    209  
    210       fr_iu(:,:)=0.0 
    211       fr_iv(:,:)=0.0 
     214         CALL wrk_dealloc( jpi,jpj,jpk, ztfrz3d )  
     215 
     216#if defined key_nemocice_decomp 
     217         ! Pass initial SST from NEMO to CICE so ice is initialised correctly if 
     218         ! there is no restart file. 
     219         ! Values from a CICE restart file would overwrite this 
     220         CALL nemo2cice( tsn(:,:,1,jp_tem) , sst , 'T' , 1.)  
     221#endif 
     222 
     223      ENDIF   
     224 
     225      ! calculate surface freezing temperature and send to CICE 
     226      sstfrz(:,:) = eos_fzp(sss_m(:,:), fsdept_n(:,:,1))  
     227      CALL nemo2cice(sstfrz,Tf, 'T', 1. ) 
    212228 
    213229      CALL cice2nemo(aice,fr_i, 'T', 1. ) 
     
    220236! T point to U point 
    221237! T point to V point 
     238      fr_iu(:,:)=0.0 
     239      fr_iv(:,:)=0.0 
    222240      DO jj=1,jpjm1 
    223241         DO ji=1,jpim1 
     
    343361         CALL nemo2cice(ztmp,stray,'F', -1. ) 
    344362 
     363 
     364! Alex West: From configuration GSI8 onwards, when NEMO is used with CICE in 
     365! HadGEM3 the 'time-travelling ice' coupling approach is used, whereby  
     366! atmosphere-ice fluxes are passed as pseudo-local values, formed by dividing 
     367! gridbox mean fluxes in the UM by future ice concentration obtained through   
     368! OASIS.  This allows for a much more realistic apportionment of energy through 
     369! the ice - and conserves energy. 
     370! Therefore the fluxes are now divided by ice concentration in the coupled 
     371! formulation (jp_purecpl) as well as for jp_flx.  This NEMO branch should only 
     372! be used at UM10.2 onwards (unless an explicit GSI8 UM branch is included), at 
     373! which point the GSI8 UM changes were committed. 
     374 
    345375! Surface downward latent heat flux (CI_5) 
    346376         IF (ksbc == jp_flx) THEN 
     
    348378               ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl) 
    349379            ENDDO 
    350          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 
     380         ELSE IF (ksbc == jp_purecpl) THEN 
     381            DO jl=1,ncat 
     382               ztmpn(:,:,jl)=qla_ice(:,:,jl)*a_i(:,:,jl) 
    368383            ENDDO 
     384    ELSE 
     385           !In coupled mode - qla_ice calculated in sbc_cpl for each category 
     386           ztmpn(:,:,1:ncat)=qla_ice(:,:,1:ncat) 
    369387         ENDIF 
     388 
    370389         DO jl=1,ncat 
    371390            CALL nemo2cice(ztmpn(:,:,jl),flatn_f(:,:,jl,:),'T', 1. ) 
     
    373392! GBM conductive flux through ice (CI_6) 
    374393!  Convert to GBM 
    375             IF (ksbc == jp_flx) THEN 
     394            IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    376395               ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl) 
    377396            ELSE 
     
    382401! GBM surface heat flux (CI_7) 
    383402!  Convert to GBM 
    384             IF (ksbc == jp_flx) THEN 
     403            IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    385404               ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl)  
    386405            ELSE 
     
    442461      CALL nemo2cice(ztmp,frain,'T', 1. )  
    443462 
     463! Recalculate freezing temperature and send to CICE  
     464      sstfrz(:,:)=eos_fzp(sss_m(:,:), fsdept_n(:,:,1))  
     465      CALL nemo2cice(sstfrz,Tf,'T', 1. ) 
     466 
    444467! Freezing/melting potential 
    445468! 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. ) 
     469      nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:)*(sstfrz(:,:)-sst_m(:,:))/(2.0*dt)  
     470      CALL nemo2cice(nfrzmlt,frzmlt,'T', 1. ) 
    450471 
    451472! SST  and SSS 
     
    453474      CALL nemo2cice(sst_m,sst,'T', 1. ) 
    454475      CALL nemo2cice(sss_m,sss,'T', 1. ) 
     476 
     477      IF( ksbc == jp_purecpl ) THEN 
     478! Sea ice surface skin temperature 
     479         DO jl=1,ncat 
     480           CALL nemo2cice(tsfc_ice(:,:,jl), trcrn(:,:,nt_tsfc,jl,:),'T',1.) 
     481         ENDDO  
     482      ENDIF 
    455483 
    456484! x comp and y comp of surface ocean current 
     
    730758         CALL cice2nemo(vicen(:,:,jl,:),ht_i(:,:,jl),'T', 1. ) 
    731759      ENDDO 
     760 
     761#if ! defined key_cice4 
     762! Meltpond fraction and depth 
     763      DO jl = 1,ncat 
     764         CALL cice2nemo(apeffn(:,:,jl,:),a_p(:,:,jl),'T', 1. ) 
     765         CALL cice2nemo(trcrn(:,:,nt_hpnd,jl,:),ht_p(:,:,jl),'T', 1. ) 
     766      ENDDO 
     767#endif 
     768 
     769 
     770! If using multilayers thermodynamics in CICE then get top layer temperature 
     771! and effective conductivity        
     772!! When using NEMO with CICE, this change requires use of  
     773!! one of the following two CICE branches: 
     774!! - at CICE5.0,   hadax/r1015_GSI8_with_GSI7 
     775!! - at CICE5.1.2, hadax/vn5.1.2_GSI8 
     776      IF (heat_capacity) THEN 
     777         DO jl = 1,ncat 
     778            CALL cice2nemo(Tn_top(:,:,jl,:),tn_ice(:,:,jl),'T', 1. ) 
     779            CALL cice2nemo(keffn_top(:,:,jl,:),kn_ice(:,:,jl),'T', 1. ) 
     780         ENDDO 
     781! Convert surface temperature to Kelvin 
     782         tn_ice(:,:,:)=tn_ice(:,:,:)+rt0 
     783      ELSE 
     784         tn_ice(:,:,:) = 0.0 
     785         kn_ice(:,:,:) = 0.0 
     786      ENDIF        
     787 
    732788      ! 
    733789      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_hadgam') 
Note: See TracChangeset for help on using the changeset viewer.