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

Ignore:
Timestamp:
2016-05-03T14:28:12+02:00 (8 years ago)
Author:
timgraham
Message:

First attempt at merging in science changes from GO6 package branch at v3.6 stable (Note-namelists not yet dealt with)

File:
1 edited

Legend:

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

    r6503 r6507  
    1313   USE dom_oce         ! ocean space and time domain 
    1414   USE domvvl 
    15    USE phycst, only : rcp, rau0, r1_rau0, rhosn, rhoic 
     15   USE eosbn2, only : eos_fzp ! Function to calculate freezing point of seawater 
     16   USE phycst, only : rcp, rau0, r1_rau0, rhosn, rhoic, rt0 
    1617   USE in_out_manager  ! I/O manager 
    1718   USE iom, ONLY : iom_put,iom_use              ! I/O manager library !!Joakim edit 
     
    3536   USE ice_gather_scatter 
    3637   USE ice_calendar, only: dt 
     38# if defined key_cice4 
    3739   USE ice_state, only: aice,aicen,uvel,vvel,vsno,vsnon,vice,vicen 
    38 # if defined key_cice4 
    3940   USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow,  & 
    4041                strocnxT,strocnyT,                               &  
     
    4344                flatn_f,fsurfn_f,fcondtopn_f,                    & 
    4445                uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl,   & 
    45                 swvdr,swvdf,swidr,swidf 
     46                swvdr,swvdf,swidr,swidf,Tf 
    4647   USE ice_therm_vertical, only: calc_Tsfc 
    4748#else 
     49   USE ice_state, only: aice,aicen,uvel,nt_hpnd,trcrn,vvel,vsno,& 
     50                vsnon,vice,vicen,nt_Tsfc 
    4851   USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow,  & 
    4952                strocnxT,strocnyT,                               &  
    50                 sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_ai,     & 
    51                 fresh_ai,fhocn_ai,fswthru_ai,frzmlt,          & 
     53                sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_ai,      & 
     54                fresh_ai,fhocn_ai,fswthru_ai,frzmlt,             & 
    5255                flatn_f,fsurfn_f,fcondtopn_f,                    & 
    5356                uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl,   & 
    54                 swvdr,swvdf,swidr,swidf 
    55    USE ice_therm_shared, only: calc_Tsfc 
     57                swvdr,swvdf,swidr,swidf,Tf,                      & 
     58                !! When using NEMO with CICE, this change requires use of  
     59                !! one of the following two CICE branches: 
     60                !! - at CICE5.0,   hadax/r1015_GSI8_with_GSI7 
     61                !! - at CICE5.1.2, hadax/vn5.1.2_GSI8 
     62                keffn_top,Tn_top 
     63 
     64   USE ice_therm_shared, only: calc_Tsfc, heat_capacity 
     65   USE ice_shortwave, only: apeffn 
    5666#endif 
    5767   USE ice_forcing, only: frcvdr,frcvdf,frcidr,frcidf 
     
    162172      REAL(wp), DIMENSION(:,:), POINTER :: ztmp1, ztmp2 
    163173      REAL(wp) ::   zcoefu, zcoefv, zcoeff            ! local scalar 
     174      REAL(wp), DIMENSION(:,:,:), POINTER :: ztfrz3d 
    164175      INTEGER  ::   ji, jj, jl, jk                    ! dummy loop indices 
    165176      !!--------------------------------------------------------------------- 
     
    173184      ji_off = INT ( (jpiglo - nx_global) / 2 ) 
    174185      jj_off = INT ( (jpjglo - ny_global) / 2 ) 
    175  
    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 
    184186 
    185187! Initialize CICE 
     
    199201 
    200202! 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' ) 
     203      IF( sbc_ice_alloc()      /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_alloc : unable to allocate arrays' ) 
    202204      IF( sbc_ice_cice_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate cice arrays' ) 
    203205 
    204 ! Ensure ocean temperatures are nowhere below freezing if not a NEMO restart 
     206      ! Ensure that no temperature points are below freezing if not a NEMO restart 
    205207      IF( .NOT. ln_rstart ) THEN 
    206          tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),Tocnfrz) 
     208         CALL wrk_alloc( jpi,jpj,jpk, ztfrz3d )  
     209         DO jk=1,jpk 
     210             CALL eos_fzp( tsn(:,:,jk,jp_sal), ztfrz3d(:,:,jk), 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      CALL  eos_fzp(sss_m(:,:), sstfrz(:,:), 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 
     
    345363         CALL nemo2cice(ztmp,stray,'F', -1. ) 
    346364 
     365 
     366! Alex West: From configuration GSI8 onwards, when NEMO is used with CICE in 
     367! HadGEM3 the 'time-travelling ice' coupling approach is used, whereby  
     368! atmosphere-ice fluxes are passed as pseudo-local values, formed by dividing 
     369! gridbox mean fluxes in the UM by future ice concentration obtained through   
     370! OASIS.  This allows for a much more realistic apportionment of energy through 
     371! the ice - and conserves energy. 
     372! Therefore the fluxes are now divided by ice concentration in the coupled 
     373! formulation (jp_purecpl) as well as for jp_flx.  This NEMO branch should only 
     374! be used at UM10.2 onwards (unless an explicit GSI8 UM branch is included), at 
     375! which point the GSI8 UM changes were committed. 
     376 
    347377! Surface downward latent heat flux (CI_5) 
    348378         IF (ksbc == jp_flx) THEN 
     
    350380               ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl) 
    351381            ENDDO 
     382         ELSE IF (ksbc == jp_purecpl) THEN 
     383            DO jl=1,ncat 
     384               ztmpn(:,:,jl)=qla_ice(:,:,jl)*a_i(:,:,jl) 
     385            ENDDO 
    352386         ELSE 
    353 ! emp_ice is set in sbc_cpl_ice_flx as sublimation-snow 
    354             qla_ice(:,:,1)= - ( emp_ice(:,:)+sprecip(:,:) ) * Lsub 
    355 ! End of temporary code 
    356             DO jj=1,jpj 
    357                DO ji=1,jpi 
    358                   IF (fr_i(ji,jj).eq.0.0) THEN 
    359                      DO jl=1,ncat 
    360                         ztmpn(ji,jj,jl)=0.0 
    361                      ENDDO 
    362                      ! This will then be conserved in CICE 
    363                      ztmpn(ji,jj,1)=qla_ice(ji,jj,1) 
    364                   ELSE 
    365                      DO jl=1,ncat 
    366                         ztmpn(ji,jj,jl)=qla_ice(ji,jj,1)*a_i(ji,jj,jl)/fr_i(ji,jj) 
    367                      ENDDO 
    368                   ENDIF 
    369                ENDDO 
    370             ENDDO 
     387           !In coupled mode - qla_ice calculated in sbc_cpl for each category 
     388           ztmpn(:,:,1:ncat)=qla_ice(:,:,1:ncat) 
    371389         ENDIF 
     390 
    372391         DO jl=1,ncat 
    373392            CALL nemo2cice(ztmpn(:,:,jl),flatn_f(:,:,jl,:),'T', 1. ) 
     
    375394! GBM conductive flux through ice (CI_6) 
    376395!  Convert to GBM 
    377             IF (ksbc == jp_flx) THEN 
     396            IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    378397               ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl) 
    379398            ELSE 
     
    384403! GBM surface heat flux (CI_7) 
    385404!  Convert to GBM 
    386             IF (ksbc == jp_flx) THEN 
     405            IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 
    387406               ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl)  
    388407            ELSE 
     
    456475      CALL nemo2cice(sss_m,sss,'T', 1. ) 
    457476 
     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 
     483 
    458484! x comp and y comp of surface ocean current 
    459485! U point to F point 
     
    730756         CALL cice2nemo(vicen(:,:,jl,:),ht_i(:,:,jl),'T', 1. ) 
    731757      ENDDO 
     758 
     759#if ! defined key_cice4 
     760! Meltpond fraction and depth 
     761      DO jl = 1,ncat 
     762         CALL cice2nemo(apeffn(:,:,jl,:),a_p(:,:,jl),'T', 1. ) 
     763         CALL cice2nemo(trcrn(:,:,nt_hpnd,jl,:),ht_p(:,:,jl),'T', 1. ) 
     764      ENDDO 
     765#endif 
     766 
     767 
     768! If using multilayers thermodynamics in CICE then get top layer temperature 
     769! and effective conductivity        
     770!! When using NEMO with CICE, this change requires use of  
     771!! one of the following two CICE branches: 
     772!! - at CICE5.0,   hadax/r1015_GSI8_with_GSI7 
     773!! - at CICE5.1.2, hadax/vn5.1.2_GSI8 
     774      IF (heat_capacity) THEN 
     775         DO jl = 1,ncat 
     776            CALL cice2nemo(Tn_top(:,:,jl,:),tn_ice(:,:,jl),'T', 1. ) 
     777            CALL cice2nemo(keffn_top(:,:,jl,:),kn_ice(:,:,jl),'T', 1. ) 
     778         ENDDO 
     779! Convert surface temperature to Kelvin 
     780         tn_ice(:,:,:)=tn_ice(:,:,:)+rt0 
     781      ELSE 
     782         tn_ice(:,:,:) = 0.0 
     783         kn_ice(:,:,:) = 0.0 
     784      ENDIF        
     785 
    732786      ! 
    733787      IF( nn_timing == 1 )  CALL timing_stop('cice_sbc_hadgam') 
Note: See TracChangeset for help on using the changeset viewer.