Changeset 10940
- Timestamp:
- 2019-05-07T16:28:11+02:00 (4 years ago)
- Location:
- branches/UKMO/dev_r5518_GO6_fix_zemp_ice_8615/NEMOGCM/NEMO/OPA_SRC/SBC
- Files:
-
- 3 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/UKMO/dev_r5518_GO6_fix_zemp_ice_8615/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_ice.F90
r8400 r10940 124 124 #if defined key_lim2 || defined key_cice 125 125 ! already defined in ice.F90 for LIM3 126 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: a_i 126 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: a_i ! Sea ice fraction on categories 127 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: a_i_last_couple ! Sea ice fraction on categories at the last coupling point 127 128 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: ht_i, ht_s 128 129 #endif -
branches/UKMO/dev_r5518_GO6_fix_zemp_ice_8615/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90
r10738 r10940 54 54 USE lib_fortran, ONLY: glob_sum 55 55 56 #if defined key_oasis3 57 USE mod_oasis, ONLY : OASIS_Sent, OASIS_ToRest, OASIS_SentOut, OASIS_ToRestOut 58 #else 59 INTEGER :: OASIS_Sent = -1 60 INTEGER :: OASIS_SentOut = -1 61 INTEGER :: OASIS_ToRest = -1 62 INTEGER :: OASIS_ToRestOut = -1 63 #endif 64 56 65 IMPLICIT NONE 57 66 PRIVATE … … 200 209 !! *** FUNCTION sbc_cpl_alloc *** 201 210 !!---------------------------------------------------------------------- 202 INTEGER :: ierr( 3)211 INTEGER :: ierr(4) 203 212 !!---------------------------------------------------------------------- 204 213 ierr(:) = 0 … … 212 221 ! Hardwire only two models as nn_cplmodel has not been read in 213 222 ! from the namelist yet. 214 ALLOCATE( xcplmask(jpi,jpj,0:2) , STAT=ierr(3) ) 223 ALLOCATE( xcplmask(jpi,jpj,0:2) , STAT=ierr(3) ) 224 #if defined key_cice 225 ALLOCATE( a_i_last_couple(jpi,jpj,jpl) , STAT=ierr(4) ) 226 #endif 215 227 ! 216 228 sbc_cpl_alloc = MAXVAL( ierr ) … … 1760 1772 zemp_ice(:,:) = - frcv(jpr_snow)%z3(:,:,1) * zicefr(:,:) 1761 1773 DO jl=1,jpl 1762 zemp_ice(:,: ) = zemp_ice(:,:) + frcv(jpr_ievp)%z3(:,:,jl) * a_i (:,:,jl)1774 zemp_ice(:,: ) = zemp_ice(:,:) + frcv(jpr_ievp)%z3(:,:,jl) * a_i_last_couple(:,:,jl) 1763 1775 ENDDO 1764 1776 ! latent heat coupled for each category in CICE … … 2269 2281 END SELECT 2270 2282 IF( ssnd(jps_fice)%laction ) CALL cpl_snd( jps_fice, isec, ztmp3, info ) 2283 2284 ! If this coupling was successful then save ice fraction for use between coupling points. 2285 ! This is needed for some calculations where the ice fraction at the last coupling point 2286 ! is needed. 2287 IF( info == OASIS_Sent .OR. info == OASIS_ToRest .OR. & 2288 & info == OASIS_SentOut .OR. info == OASIS_ToRestOut ) THEN 2289 IF ( sn_snd_thick%clcat == 'yes' ) THEN 2290 a_i_last_couple(:,:,:) = a_i(:,:,:) 2291 ENDIF 2292 ENDIF 2293 2271 2294 ENDIF 2272 2295 -
branches/UKMO/dev_r5518_GO6_fix_zemp_ice_8615/NEMOGCM/NEMO/OPA_SRC/SBC/sbcice_cice.F90
r8400 r10940 395 395 ELSE IF (ksbc == jp_purecpl) THEN 396 396 DO jl=1,ncat 397 ztmpn(:,:,jl)=qla_ice(:,:,jl)*a_i (:,:,jl)397 ztmpn(:,:,jl)=qla_ice(:,:,jl)*a_i_last_couple(:,:,jl) 398 398 ENDDO 399 399 ELSE … … 408 408 ! Convert to GBM 409 409 IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 410 ztmp(:,:) = botmelt(:,:,jl)*a_i (:,:,jl)410 ztmp(:,:) = botmelt(:,:,jl)*a_i_last_couple(:,:,jl) 411 411 ELSE 412 412 ztmp(:,:) = botmelt(:,:,jl) … … 417 417 ! Convert to GBM 418 418 IF (ksbc == jp_flx .OR. ksbc == jp_purecpl) THEN 419 ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i (:,:,jl)419 ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i_last_couple(:,:,jl) 420 420 ELSE 421 421 ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))
Note: See TracChangeset
for help on using the changeset viewer.