Changeset 9500
- Timestamp:
- 2018-04-23T16:40:35+02:00 (5 years ago)
- Location:
- branches/UKMO/dev_merge_2017_CICE_interface/NEMOGCM/NEMO/OPA_SRC
- Files:
-
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/UKMO/dev_merge_2017_CICE_interface/NEMOGCM/NEMO/OPA_SRC/LBC/mppini.F90
r9499 r9500 30 30 USE ioipsl ! I/O IPSL library 31 31 USE in_out_manager ! I/O Manager 32 #if defined key_nemocice_decomp 33 USE ice_domain_size, only: nx_global, ny_global 34 #endif 32 35 33 36 IMPLICIT NONE -
branches/UKMO/dev_merge_2017_CICE_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90
r9499 r9500 88 88 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fr_iu !: ice fraction at NEMO U point 89 89 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: fr_iv !: ice fraction at NEMO V point 90 90 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: sstfrz !: sea surface freezing temperature 91 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tsfc_ice !: sea-ice surface skin temperature (on categories) 92 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: kn_ice !: sea-ice surface layer thermal conductivity (on cats) 93 91 94 ! variables used in the coupled interface 92 95 INTEGER , PUBLIC, PARAMETER :: jpl = ncat 93 96 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: u_ice, v_ice ! jpi, jpj 97 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: a_p, ht_p ! Meltpond fraction and depth 98 99 ! 100 101 ! 102 #if defined key_asminc 103 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: ndaice_da !: NEMO fresh water flux to ocean due to data assim 104 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: nfresh_da !: NEMO salt flux to ocean due to data assim 105 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: nfsalt_da !: NEMO ice concentration change/second from data assim 106 #endif 107 94 108 95 109 ! already defined in ice.F90 for LIM3 -
branches/UKMO/dev_merge_2017_CICE_interface/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90
r9499 r9500 13 13 USE dom_oce ! ocean space and time domain 14 14 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 16 17 USE in_out_manager ! I/O manager 17 18 USE iom, ONLY : iom_put,iom_use ! I/O manager library !!Joakim edit … … 33 34 USE ice_gather_scatter 34 35 USE ice_calendar, only: dt 36 # if defined key_cice4 35 37 USE ice_state, only: aice,aicen,uvel,vvel,vsno,vsnon,vice,vicen 36 # if defined key_cice437 38 USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow, & 38 39 strocnxT,strocnyT, & … … 41 42 flatn_f,fsurfn_f,fcondtopn_f, & 42 43 uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl, & 43 swvdr,swvdf,swidr,swidf 44 swvdr,swvdf,swidr,swidf,Tf 44 45 USE ice_therm_vertical, only: calc_Tsfc 45 46 #else 47 USE ice_state, only: aice,aicen,uvel,nt_hpnd,trcrn,vvel,vsno,& 48 vsnon,vice,vicen,nt_Tsfc 46 49 USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow, & 47 50 strocnxT,strocnyT, & 48 sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_ai, &49 fresh_ai,fhocn_ai,fswthru_ai,frzmlt, &51 sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_ai, & 52 fresh_ai,fhocn_ai,fswthru_ai,frzmlt, & 50 53 flatn_f,fsurfn_f,fcondtopn_f, & 54 #ifdef key_asminc 55 daice_da,fresh_da,fsalt_da, & 56 #endif 51 57 uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl, & 52 swvdr,swvdf,swidr,swidf 53 USE ice_therm_shared, only: calc_Tsfc 58 swvdr,swvdf,swidr,swidf,Tf, & 59 !! When using NEMO with CICE, this change requires use of 60 !! one of the following two CICE branches: 61 !! - at CICE5.0, hadax/r1015_GSI8_with_GSI7 62 !! - at CICE5.1.2, hadax/vn5.1.2_GSI8 63 keffn_top,Tn_top 64 65 USE ice_therm_shared, only: calc_Tsfc, heat_capacity 66 USE ice_shortwave, only: apeffn 54 67 #endif 55 68 USE ice_forcing, only: frcvdr,frcvdf,frcidr,frcidf … … 155 168 INTEGER, INTENT( in ) :: ksbc ! surface forcing type 156 169 REAL(wp), DIMENSION(jpi,jpj) :: ztmp1, ztmp2 157 REAL(wp) :: zcoefu, zcoefv, zcoeff ! local scalar170 REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztfrz3d 158 171 INTEGER :: ji, jj, jl, jk ! dummy loop indices 159 172 !!--------------------------------------------------------------------- … … 164 177 jj_off = INT ( (jpjglo - ny_global) / 2 ) 165 178 166 #if defined key_nemocice_decomp 167 ! Pass initial SST from NEMO to CICE so ice is initialised correctly if 168 ! there is no restart file. 169 ! Values from a CICE restart file would overwrite this 170 IF ( .NOT. ln_rstart ) THEN 171 CALL nemo2cice( tsn(:,:,1,jp_tem) , sst , 'T' , 1.) 172 ENDIF 173 #endif 174 175 ! Initialize CICE 179 ! Initialize CICE 176 180 CALL CICE_Initialize 177 181 178 ! Do some CICE consistency checks182 ! Do some CICE consistency checks 179 183 IF ( (ksbc == jp_flx) .OR. (ksbc == jp_purecpl) ) THEN 180 184 IF ( calc_strair .OR. calc_Tsfc ) THEN … … 188 192 189 193 190 ! allocate sbc_ice and sbc_cice arrays191 IF( sbc_ice_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_ice_ cice_alloc : unable to allocate arrays' )194 ! allocate sbc_ice and sbc_cice arrays 195 IF( sbc_ice_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_ice_alloc : unable to allocate arrays' ) 192 196 IF( sbc_ice_cice_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate cice arrays' ) 193 197 194 ! Ensure ocean temperatures are nowhere below freezing if not a NEMO restart198 ! Ensure that no temperature points are below freezing if not a NEMO restart 195 199 IF( .NOT. ln_rstart ) THEN 196 tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),Tocnfrz) 200 201 DO jk=1,jpk 202 CALL eos_fzp( tsn(:,:,jk,jp_sal), ztfrz3d(:,:,jk), gdept_n(:,:,jk) ) 203 ENDDO 204 tsn(:,:,:,jp_tem) = MAX( tsn(:,:,:,jp_tem), ztfrz3d ) 197 205 tsb(:,:,:,jp_tem) = tsn(:,:,:,jp_tem) 198 ENDIF 199 200 fr_iu(:,:)=0.0 201 fr_iv(:,:)=0.0 206 207 #if defined key_nemocice_decomp 208 ! Pass initial SST from NEMO to CICE so ice is initialised correctly if 209 ! there is no restart file. 210 ! Values from a CICE restart file would overwrite this 211 CALL nemo2cice( tsn(:,:,1,jp_tem) , sst , 'T' , 1.) 212 #endif 213 214 ENDIF 215 216 ! calculate surface freezing temperature and send to CICE 217 CALL eos_fzp(sss_m(:,:), sstfrz(:,:), gdept_n(:,:,1)) 218 CALL nemo2cice(sstfrz,Tf, 'T', 1. ) 202 219 203 220 CALL cice2nemo(aice,fr_i, 'T', 1. ) … … 210 227 ! T point to U point 211 228 ! T point to V point 229 fr_iu(:,:)=0.0 230 fr_iv(:,:)=0.0 212 231 DO jj=1,jpjm1 213 232 DO ji=1,jpim1 … … 268 287 ENDIF 269 288 ENDIF 270 ! 289 290 #if defined key_asminc 291 ! Initialize fresh water and salt fluxes from data assim 292 ! and data assimilation index to cice 293 nfresh_da(:,:) = 0.0 294 nfsalt_da(:,:) = 0.0 295 ndaice_da(:,:) = 0.0 296 #endif 297 ! 298 ! In coupled mode get extra fields from CICE for passing back to atmosphere 299 300 IF ( ksbc == jp_purecpl ) CALL cice_sbc_hadgam(nit000) 301 ! 271 302 END SUBROUTINE cice_sbc_init 272 303 … … 321 352 CALL nemo2cice(ztmp,stray,'F', -1. ) 322 353 354 355 ! Alex West: From configuration GSI8 onwards, when NEMO is used with CICE in 356 ! HadGEM3 the 'time-travelling ice' coupling approach is used, whereby 357 ! atmosphere-ice fluxes are passed as pseudo-local values, formed by dividing 358 ! gridbox mean fluxes in the UM by future ice concentration obtained through 359 ! OASIS. This allows for a much more realistic apportionment of energy through 360 ! the ice - and conserves energy. 361 ! Therefore the fluxes are now divided by ice concentration in the coupled 362 ! formulation (jp_purecpl) as well as for jp_flx. This NEMO branch should only 363 ! be used at UM10.2 onwards (unless an explicit GSI8 UM branch is included), at 364 ! which point the GSI8 UM changes were committed. 365 323 366 ! Surface downward latent heat flux (CI_5) 324 367 IF (ksbc == jp_flx) THEN … … 326 369 ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl) 327 370 ENDDO 328 ELSE 329 ! emp_ice is set in sbc_cpl_ice_flx as sublimation-snow 330 qla_ice(:,:,1)= - ( emp_ice(:,:)+sprecip(:,:) ) * Lsub 331 ! End of temporary code 332 DO jj=1,jpj 333 DO ji=1,jpi 334 IF (fr_i(ji,jj).eq.0.0) THEN 335 DO jl=1,ncat 336 ztmpn(ji,jj,jl)=0.0 337 ENDDO 338 ! This will then be conserved in CICE 339 ztmpn(ji,jj,1)=qla_ice(ji,jj,1) 340 ELSE 341 DO jl=1,ncat 342 ztmpn(ji,jj,jl)=qla_ice(ji,jj,1)*a_i(ji,jj,jl)/fr_i(ji,jj) 343 ENDDO 344 ENDIF 345 ENDDO 371 ELSE IF (ksbc == jp_purecpl) THEN 372 DO jl=1,ncat 373 ztmpn(:,:,jl)=qla_ice(:,:,jl)*a_i(:,:,jl) 346 374 ENDDO 375 ELSE 376 !In coupled mode - qla_ice calculated in sbc_cpl for each category 377 ztmpn(:,:,1:ncat)=qla_ice(:,:,1:ncat) 347 378 ENDIF 379 348 380 DO jl=1,ncat 349 381 CALL nemo2cice(ztmpn(:,:,jl),flatn_f(:,:,jl,:),'T', 1. ) … … 351 383 ! GBM conductive flux through ice (CI_6) 352 384 ! Convert to GBM 353 IF (ksbc == jp_flx ) THEN385 IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 354 386 ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl) 355 387 ELSE … … 360 392 ! GBM surface heat flux (CI_7) 361 393 ! Convert to GBM 362 IF (ksbc == jp_flx ) THEN394 IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 363 395 ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl) 364 396 ELSE … … 409 441 ENDIF 410 442 443 #if defined key_asminc 444 !Ice concentration change (from assimilation) 445 ztmp(:,:)=ndaice_da(:,:)*tmask(:,:,1) 446 Call nemo2cice(ztmp,daice_da,'T', 1. ) 447 #endif 448 411 449 ! Snowfall 412 450 ! Ensure fsnow is positive (as in CICE routine prepare_forcing) … … 420 458 CALL nemo2cice(ztmp,frain,'T', 1. ) 421 459 460 ! Recalculate freezing temperature and send to CICE 461 CALL eos_fzp(sss_m(:,:), sstfrz(:,:), gdept_n(:,:,1)) 462 CALL nemo2cice(sstfrz,Tf,'T', 1. ) 463 422 464 ! Freezing/melting potential 423 465 ! Calculated over NEMO leapfrog timestep (hence 2*dt) 424 nfrzmlt(:,:) = rau0 * rcp * e3t_m(:,:) * ( Tocnfrz-sst_m(:,:) ) / ( 2.0*dt ) 425 426 ztmp(:,:) = nfrzmlt(:,:) 427 CALL nemo2cice(ztmp,frzmlt,'T', 1. ) 466 nfrzmlt(:,:)=rau0*rcp*e3t_m(:,:)*(sstfrz(:,:)-sst_m(:,:))/(2.0*dt) 467 CALL nemo2cice(nfrzmlt,frzmlt,'T', 1. ) 428 468 429 469 ! SST and SSS … … 431 471 CALL nemo2cice(sst_m,sst,'T', 1. ) 432 472 CALL nemo2cice(sss_m,sss,'T', 1. ) 473 474 IF( ksbc == jp_purecpl ) THEN 475 ! Sea ice surface skin temperature 476 DO jl=1,ncat 477 CALL nemo2cice(tsfc_ice(:,:,jl), trcrn(:,:,nt_tsfc,jl,:),'T',1.) 478 ENDDO 479 ENDIF 433 480 434 481 ! x comp and y comp of surface ocean current … … 663 710 INTEGER :: ierror 664 711 !!--------------------------------------------------------------------- 665 ! 666 IF( kt == nit000 ) THEN 667 IF(lwp) WRITE(numout,*)'cice_sbc_hadgam' 668 IF( sbc_cpl_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' ) 669 ENDIF 670 712 #if defined key_asminc 713 ! Import fresh water and salt flux due to seaice da 714 CALL cice2nemo(fresh_da, nfresh_da,'T',1.0) 715 CALL cice2nemo(fsalt_da, nfsalt_da,'T',1.0) 716 #endif 717 718 ! 671 719 ! ! =========================== ! 672 720 ! ! Prepare Coupling fields ! … … 686 734 CALL cice2nemo( vicen(:,:,jl,:), h_i(:,:,jl),'T', 1. ) 687 735 END DO 736 737 #if ! defined key_cice4 738 ! Meltpond fraction and depth 739 DO jl = 1,ncat 740 CALL cice2nemo(apeffn(:,:,jl,:),a_p(:,:,jl),'T', 1. ) 741 CALL cice2nemo(trcrn(:,:,nt_hpnd,jl,:),ht_p(:,:,jl),'T', 1. ) 742 ENDDO 743 #endif 744 745 746 ! If using multilayers thermodynamics in CICE then get top layer temperature 747 ! and effective conductivity 748 !! When using NEMO with CICE, this change requires use of 749 !! one of the following two CICE branches: 750 !! - at CICE5.0, hadax/r1015_GSI8_with_GSI7 751 !! - at CICE5.1.2, hadax/vn5.1.2_GSI8 752 IF (heat_capacity) THEN 753 DO jl = 1,ncat 754 CALL cice2nemo(Tn_top(:,:,jl,:),tn_ice(:,:,jl),'T', 1. ) 755 CALL cice2nemo(keffn_top(:,:,jl,:),kn_ice(:,:,jl),'T', 1. ) 756 ENDDO 757 ! Convert surface temperature to Kelvin 758 tn_ice(:,:,:)=tn_ice(:,:,:)+rt0 759 ELSE 760 tn_ice(:,:,:) = 0.0 761 kn_ice(:,:,:) = 0.0 762 ENDIF 763 688 764 ! 689 765 END SUBROUTINE cice_sbc_hadgam
Note: See TracChangeset
for help on using the changeset viewer.