Changeset 12811
- Timestamp:
- 2020-04-24T17:20:27+02:00 (3 years ago)
- Location:
- NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl
- Files:
-
- 8 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/ICE/icethd_pnd.F90
r12726 r12811 184 184 h_ip_1d(ji) = 0._wp 185 185 h_il_1d(ji) = 0._wp 186 !187 ! clem: problem with conservation or not ?188 186 ! !--------------------------------! 189 187 ELSE ! Case ice thickness >= rn_himin ! … … 267 265 zhp = ( h_i_1d(ji) * ( rau0 - rhoi ) + h_ip_1d(ji) * ( rau0 - rhow * a_ip_1d(ji) / a_i_1d(ji) ) ) * r1_rau0 268 266 269 ! Calculate the permeability of the ice (Assur 1958 )267 ! Calculate the permeability of the ice (Assur 1958, see Flocco 2010) 270 268 DO jk = 1, nlay_i 271 269 zsbr = - 1.2_wp & 272 270 & - 21.8_wp * ( t_i_1d(ji,jk) - rt0 ) & 273 271 & - 0.919_wp * ( t_i_1d(ji,jk) - rt0 )**2 & 274 & - 0.0178_wp * ( t_i_1d(ji,jk) - rt0 )**3 ! clem: error here the factor was 0.01878 instead of 0.0178 (cf Flocco 2010)272 & - 0.0178_wp * ( t_i_1d(ji,jk) - rt0 )**3 275 273 ztmp(jk) = sz_i_1d(ji,jk) / zsbr 276 274 END DO -
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbc_ice.F90
r12785 r12811 70 70 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: wndm_ice !: wind speed module at T-point [m/s] 71 71 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: sstfrz !: sea surface freezing temperature [degC] 72 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: cloud_fra !: cloud cover [-]73 72 #endif 74 73 … … 100 99 #endif 101 100 102 REAL(wp), PUBLIC, SAVE :: cldf_ice= 0.81 !: cloud fraction over sea ice, summer CLIO value [-]101 REAL(wp), PUBLIC, SAVE :: pp_cldf = 0.81 !: cloud fraction over sea ice, summer CLIO value [-] 103 102 104 103 !! arrays relating to embedding ice in the ocean … … 133 132 & qemp_ice(jpi,jpj) , qevap_ice(jpi,jpj,jpl) , qemp_oce (jpi,jpj) , & 134 133 & qns_oce (jpi,jpj) , qsr_oce (jpi,jpj) , emp_oce (jpi,jpj) , & 135 & emp_ice (jpi,jpj) , sstfrz (jpi,jpj) , cloud_fra (jpi,jpj) ,STAT= ierr(2) )134 & emp_ice (jpi,jpj) , sstfrz (jpi,jpj) , STAT= ierr(2) ) 136 135 #endif 137 136 … … 169 168 LOGICAL , PUBLIC, PARAMETER :: lk_si3 = .FALSE. !: no SI3 ice model 170 169 LOGICAL , PUBLIC, PARAMETER :: lk_cice = .FALSE. !: no CICE ice model 171 REAL(wp) , PUBLIC, PARAMETER :: cldf_ice = 0.81!: cloud fraction over sea ice, summer CLIO value [-]170 REAL(wp) , PUBLIC, PARAMETER :: pp_cldf = 0.81 !: cloud fraction over sea ice, summer CLIO value [-] 172 171 INTEGER , PUBLIC, PARAMETER :: jpl = 1 173 172 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: u_ice, v_ice ! jpi, jpj -
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbc_oce.F90
r12132 r12811 136 136 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: atm_co2 !: atmospheric pCO2 [ppm] 137 137 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: xcplmask !: coupling mask for ln_mixcpl (warning: allocated in sbccpl) 138 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: cloud_fra !: cloud cover (fraction of cloud in a gridcell) [-] 138 139 139 140 !!---------------------------------------------------------------------- … … 178 179 & fwficb (jpi,jpj), fwficb_b(jpi,jpj), STAT=ierr(3) ) 179 180 ! 180 ALLOCATE( tprecip(jpi,jpj) , sprecip (jpi,jpj) , fr_i(jpi,jpj) ,&181 & atm_co2(jpi,jpj) , 182 & ssu_m (jpi,jpj) , sst_m (jpi,jpj) , frq_m(jpi,jpj) ,&183 & ssv_m (jpi,jpj) , sss_m (jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) )181 ALLOCATE( tprecip(jpi,jpj) , sprecip (jpi,jpj) , fr_i(jpi,jpj) , & 182 & atm_co2(jpi,jpj) , cloud_fra(jpi,jpj) , & 183 & ssu_m (jpi,jpj) , sst_m (jpi,jpj) , frq_m(jpi,jpj) , & 184 & ssv_m (jpi,jpj) , sss_m (jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) ) 184 185 ! 185 186 ALLOCATE( e3t_m(jpi,jpj) , STAT=ierr(5) ) -
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbcblk.F90
r12785 r12811 242 242 ENDDO 243 243 ! fill cloud cover array with constant value if "not used" 244 IF( TRIM(sf(jp_cc)%clrootname) == 'NOT USED' ) sf(jp_cc)%fnow(:,:,1) = cldf_ice244 IF( TRIM(sf(jp_cc)%clrootname) == 'NOT USED' ) sf(jp_cc)%fnow(:,:,1) = pp_cldf 245 245 246 246 IF ( ln_wave ) THEN … … 395 395 zst(:,:) = pst(:,:) + rt0 ! convert SST from Celcius to Kelvin (and set minimum value far above 0 K) 396 396 397 ! --- cloud cover --- ! 398 cloud_fra(:,:) = sf(jp_cc)%fnow(:,:,1) 399 397 400 ! ----------------------------------------------------------------------------- ! 398 401 ! 0 Wind components and module at T-point relative to the moving ocean ! … … 914 917 END DO 915 918 916 ! --- cloud cover --- !917 cloud_fra(:,:) = sf(jp_cc)%fnow(:,:,1)918 919 919 ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- ! 920 920 ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:) ! surface transmission when hi>10cm -
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbccpl.F90
r12785 r12811 2100 2100 !!$ cloud_fra(:,:) = frcv(jpr_clfra)*z3(:,:,1) 2101 2101 !!$ END SELECT 2102 zcloud_fra(:,:) = cldf_ice! should be real cloud fraction instead (as in the bulk) but needs to be read from atm.2102 zcloud_fra(:,:) = pp_cldf ! should be real cloud fraction instead (as in the bulk) but needs to be read from atm. 2103 2103 IF( ln_mixcpl ) THEN 2104 2104 cloud_fra(:,:) = cloud_fra(:,:) * xcplmask(:,:,0) + zcloud_fra(:,:)* zmsk(:,:) -
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/tests/ICE_ADV1D/MY_SRC/usrdef_sbc.F90
r10513 r12811 108 108 REAL(wp), DIMENSION(:,:,:), INTENT(in) :: phi ! ice thickness 109 109 !! 110 INTEGER :: jl 110 111 REAL(wp) :: zfr1, zfr2 ! local variables 111 112 REAL(wp), DIMENSION(jpi,jpj) :: zsnw ! snw distribution after wind blowing 113 REAL(wp), DIMENSION(jpi,jpj) :: ztri 112 114 !!--------------------------------------------------------------------- 113 115 ! … … 142 144 143 145 ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- ! 144 zfr1 = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice ) ! transmission when hi>10cm145 z fr2 = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice ) ! zfr2 such that zfr1 + zfr2 to equal 1146 cloud_fra(:,:) = pp_cldf 147 ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:) ! surface transmission when hi>10cm 146 148 ! 147 WHERE ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) < 0.1_wp ) ! linear decrease from hi=0 to 10cm 148 qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( zfr1 + zfr2 * ( 1._wp - phi(:,:,:) * 10._wp ) ) 149 ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp ) ! constant (zfr1) when hi>10cm 150 qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * zfr1 151 ELSEWHERE ! zero when hs>0 152 qtr_ice_top(:,:,:) = 0._wp 153 END WHERE 154 149 DO jl = 1, jpl 150 WHERE ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) < 0.1_wp ) ! linear decrease from hi=0 to 10cm 151 qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) ) 152 ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp ) ! constant (ztri) when hi>10cm 153 qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ztri(:,:) 154 ELSEWHERE ! zero when hs>0 155 qtr_ice_top(:,:,jl) = 0._wp 156 END WHERE 157 ENDDO 158 159 155 160 END SUBROUTINE usrdef_sbc_ice_flx 156 161 -
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/tests/ICE_ADV2D/MY_SRC/usrdef_sbc.F90
r10515 r12811 108 108 REAL(wp), DIMENSION(:,:,:), INTENT(in) :: phi ! ice thickness 109 109 !! 110 INTEGER :: jl 110 111 REAL(wp) :: zfr1, zfr2 ! local variables 111 112 REAL(wp), DIMENSION(jpi,jpj) :: zsnw ! snw distribution after wind blowing 113 REAL(wp), DIMENSION(jpi,jpj) :: ztri 112 114 !!--------------------------------------------------------------------- 113 115 ! … … 142 144 143 145 ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- ! 144 zfr1 = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice ) ! transmission when hi>10cm145 z fr2 = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice ) ! zfr2 such that zfr1 + zfr2 to equal 1146 cloud_fra(:,:) = pp_cldf 147 ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:) ! surface transmission when hi>10cm 146 148 ! 147 WHERE ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) < 0.1_wp ) ! linear decrease from hi=0 to 10cm 148 qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( zfr1 + zfr2 * ( 1._wp - phi(:,:,:) * 10._wp ) ) 149 ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp ) ! constant (zfr1) when hi>10cm 150 qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * zfr1 151 ELSEWHERE ! zero when hs>0 152 qtr_ice_top(:,:,:) = 0._wp 153 END WHERE 154 149 DO jl = 1, jpl 150 WHERE ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) < 0.1_wp ) ! linear decrease from hi=0 to 10cm 151 qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) ) 152 ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp ) ! constant (ztri) when hi>10cm 153 qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ztri(:,:) 154 ELSEWHERE ! zero when hs>0 155 qtr_ice_top(:,:,jl) = 0._wp 156 END WHERE 157 ENDDO 158 159 155 160 END SUBROUTINE usrdef_sbc_ice_flx 156 161 -
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/tests/ICE_AGRIF/MY_SRC/usrdef_sbc.F90
r10516 r12811 108 108 REAL(wp), DIMENSION(:,:,:), INTENT(in) :: phi ! ice thickness 109 109 !! 110 INTEGER :: jl 110 111 REAL(wp) :: zfr1, zfr2 ! local variables 111 112 REAL(wp), DIMENSION(jpi,jpj) :: zsnw ! snw distribution after wind blowing 113 REAL(wp), DIMENSION(jpi,jpj) :: ztri 112 114 !!--------------------------------------------------------------------- 113 115 ! … … 142 144 143 145 ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- ! 144 zfr1 = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice ) ! transmission when hi>10cm145 z fr2 = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice ) ! zfr2 such that zfr1 + zfr2 to equal 1146 cloud_fra(:,:) = pp_cldf 147 ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:) ! surface transmission when hi>10cm 146 148 ! 147 WHERE ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) < 0.1_wp ) ! linear decrease from hi=0 to 10cm 148 qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( zfr1 + zfr2 * ( 1._wp - phi(:,:,:) * 10._wp ) ) 149 ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp ) ! constant (zfr1) when hi>10cm 150 qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * zfr1 151 ELSEWHERE ! zero when hs>0 152 qtr_ice_top(:,:,:) = 0._wp 153 END WHERE 149 DO jl = 1, jpl 150 WHERE ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) < 0.1_wp ) ! linear decrease from hi=0 to 10cm 151 qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) ) 152 ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp ) ! constant (ztri) when hi>10cm 153 qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ztri(:,:) 154 ELSEWHERE ! zero when hs>0 155 qtr_ice_top(:,:,jl) = 0._wp 156 END WHERE 157 ENDDO 154 158 155 159 END SUBROUTINE usrdef_sbc_ice_flx
Note: See TracChangeset
for help on using the changeset viewer.