Changeset 11266
- Timestamp:
- 2019-07-15T12:09:30+02:00 (5 years ago)
- Location:
- NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbc_oce.F90
r11182 r11266 153 153 !! Cool-skin/Warm-layer 154 154 !!---------------------------------------------------------------------- 155 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tsk !: sea-surface skin temperature out of the cool-skin/warm-layer parameterization [Celsius]155 REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: tsk !: sea-surface skin temperature (used if ln_skin==.true.) [K] !LB 156 156 157 157 -
NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk.F90
r11217 r11266 346 346 CALL fld_read( kt, nn_fsbc, sf ) ! input fields provided at the current time-step 347 347 ! 348 ! ! compute the surface ocean fluxes using bulk formulea 349 IF( MOD( kt - 1, nn_fsbc ) == 0 ) CALL blk_oce( kt, sf, sst_m, ssu_m, ssv_m ) 348 IF( kt == nit000 ) tsk(:,:) = sst_m(:,:)*tmask(:,:,1) ! no previous estimate of skin temperature => using bulk SST 349 ! 350 IF( MOD( kt - 1, nn_fsbc ) == 0 ) CALL blk_oce( kt, sf, sst_m, ssu_m, ssv_m ) ! compute the surface ocean fluxes using bulk formulea 350 351 351 352 #if defined key_cice … … 493 494 CALL turb_coare ( rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm, & ! COARE v3.0 494 495 & Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce, & 495 & Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1)) 496 & Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1), & 497 & Tsk_b=tsk(:,:) ) 496 498 497 499 CASE( np_ECMWF ) 498 500 CALL turb_ecmwf ( rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm, & ! ECMWF 499 501 & Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce, & 500 & Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1)) 501 502 & Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1), & 503 & Tsk_b=tsk(:,:) ) 504 502 505 CASE DEFAULT 503 506 CALL ctl_stop( 'STOP', 'sbc_oce: unsuported bulk formula selection for "ln_skin==.true."' ) … … 515 518 END WHERE 516 519 517 !LB: Update of tsk, the officialarray for skin temperature520 !LB: Update of tsk, the "official" array for skin temperature 518 521 tsk(:,:) = zst(:,:) 519 522 -
NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_algo_coare.F90
r11215 r11266 57 57 & Cd, Ch, Ce, t_zu, q_zu, U_blk, & 58 58 & Cdn, Chn, Cen, & 59 & Qsw, rad_lw, slp 59 & Qsw, rad_lw, slp, Tsk_b ) 60 60 !!---------------------------------------------------------------------- 61 61 !! *** ROUTINE turb_coare *** … … 81 81 !! INPUT/OUTPUT: 82 82 !! ------------- 83 !! * T_s : SST or skin temperature [K] 83 !! * T_s : always "bulk SST" as input [K] 84 !! -> unchanged "bulk SST" as output if CSWL not used [K] 85 !! -> skin temperature as output if CSWL used [K] 86 !! 84 87 !! * q_s : SSQ aka saturation specific humidity at temp. T_s [kg/kg] 85 88 !! -> doesn't need to be given a value if skin temp computed (in case l_use_skin=True) … … 91 94 !! * rad_lw : downwelling longwave radiation at the surface (>0) [W/m^2] 92 95 !! * slp : sea-level pressure [Pa] 96 !! * Tsk_b : estimate of skin temperature at previous time-step [K] 93 97 !! 94 98 !! OUTPUT : … … 122 126 REAL(wp), INTENT(in ), OPTIONAL, DIMENSION(jpi,jpj) :: rad_lw ! [W/m^2] 123 127 REAL(wp), INTENT(in ), OPTIONAL, DIMENSION(jpi,jpj) :: slp ! [Pa] 128 REAL(wp), INTENT(in ), OPTIONAL, DIMENSION(jpi,jpj) :: Tsk_b ! [Pa] 124 129 ! 125 130 INTEGER :: j_itt … … 152 157 153 158 !! Initialization for cool skin: 159 zsst = T_s ! save the bulk SST 154 160 IF( l_use_skin ) THEN 155 zsst = T_s ! save the bulk SST 156 T_s = T_s - 0.25 ! First guess of correction 161 ! First guess for skin temperature: 162 IF( PRESENT(Tsk_b) ) THEN 163 T_s = Tsk_b 164 ELSE 165 T_s = T_s - 0.25 ! sst - 0.25 166 END IF 157 167 q_s = rdct_qsat_salt*q_sat(MAX(T_s, 200._wp), slp) ! First guess of q_s 158 168 END IF … … 202 212 q_star = dq_zu*ztmp0 203 213 204 ! What 's needto be done if zt /= zu:214 ! What needs to be done if zt /= zu: 205 215 IF( .NOT. l_zt_equal_zu ) THEN 206 216 !! First update of values at zu (or zt for wind) … … 275 285 ztmp1 = U_blk*MAX(rho_air(t_zu, q_zu, slp), 1._wp) ! rho*U10 276 286 ztmp2 = T_s*T_s 277 ztmp1 = ztmp1 * ( Ce*rLevap*(q_zu - q_s) + Ch*rCp_dry*(t_zu - T_s) ) & ! Total turb. heat flux 278 & + (rad_lw - emiss_w*stefan*ztmp2*ztmp2) ! Net longwave flux 287 ztmp1 = ztmp1 * ( Ce*L_vap(T_s)*(q_zu - q_s) + Ch*cp_air(q_zu)*(t_zu - T_s) ) & ! Total turb. heat flux 288 & + rad_lw - emiss_w*stefan*ztmp2*ztmp2 ! Net longwave flux 289 !! => "ztmp1" is the net non-solar surface heat flux ! 279 290 !! Updating the values of the skin temperature T_s and q_s : 280 291 CALL CSWL_ECMWF( Qsw, ztmp1, u_star, zsst, T_s ) ! yes ECMWF, because more advanced than COARE (warm-layer added!) -
NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_algo_ecmwf.F90
r11215 r11266 63 63 & Cd, Ch, Ce, t_zu, q_zu, U_blk, & 64 64 & Cdn, Chn, Cen, & 65 & Qsw, rad_lw, slp 65 & Qsw, rad_lw, slp, Tsk_b ) 66 66 !!---------------------------------------------------------------------------------- 67 67 !! *** ROUTINE turb_ecmwf *** … … 87 87 !! INPUT/OUTPUT: 88 88 !! ------------- 89 !! * T_s : SST or skin temperature [K] 89 !! * T_s : always "bulk SST" as input [K] 90 !! -> unchanged "bulk SST" as output if CSWL not used [K] 91 !! -> skin temperature as output if CSWL used [K] 92 !! 90 93 !! * q_s : SSQ aka saturation specific humidity at temp. T_s [kg/kg] 91 94 !! -> doesn't need to be given a value if skin temp computed (in case l_use_skin=True) … … 97 100 !! * rad_lw : downwelling longwave radiation at the surface (>0) [W/m^2] 98 101 !! * slp : sea-level pressure [Pa] 102 !! * Tsk_b : estimate of skin temperature at previous time-step [K] 99 103 !! 100 104 !! OUTPUT : … … 128 132 REAL(wp), INTENT(in ), OPTIONAL, DIMENSION(jpi,jpj) :: rad_lw ! [W/m^2] 129 133 REAL(wp), INTENT(in ), OPTIONAL, DIMENSION(jpi,jpj) :: slp ! [Pa] 134 REAL(wp), INTENT(in ), OPTIONAL, DIMENSION(jpi,jpj) :: Tsk_b ! [Pa] 130 135 ! 131 136 INTEGER :: j_itt … … 156 161 ! 157 162 l_zt_equal_zu = .FALSE. 158 IF( ABS(zu - zt) < 0.01 ) l_zt_equal_zu = .TRUE. ! testing "zu == zt" is risky with double precision163 IF( ABS(zu - zt) < 0.01_wp ) l_zt_equal_zu = .TRUE. ! testing "zu == zt" is risky with double precision 159 164 160 165 !! Initialization for cool skin: 166 zsst = T_s ! save the bulk SST 161 167 IF( l_use_skin ) THEN 162 zsst = T_s ! save the bulk SST 163 T_s = T_s - 0.25 ! First guess of correction 168 ! First guess for skin temperature: 169 IF( PRESENT(Tsk_b) ) THEN 170 T_s = Tsk_b 171 ELSE 172 T_s = T_s - 0.25 ! sst - 0.25 173 END IF 164 174 q_s = rdct_qsat_salt*q_sat(MAX(T_s, 200._wp), slp) ! First guess of q_s 165 175 END IF … … 209 219 q_star = dq_zu*ztmp0 210 220 211 ! What 's needto be done if zt /= zu:221 ! What needs to be done if zt /= zu: 212 222 IF( .NOT. l_zt_equal_zu ) THEN 213 223 !! First update of values at zu (or zt for wind) … … 304 314 ztmp1 = U_blk*MAX(rho_air(t_zu, q_zu, slp), 1._wp) ! rho*U10 305 315 ztmp2 = T_s*T_s 306 ztmp1 = ztmp1 * ( Ce*rLevap*(q_zu - q_s) + Ch*rCp_dry*(t_zu - T_s) ) & ! Total turb. heat flux 307 & + (rad_lw - emiss_w*stefan*ztmp2*ztmp2) ! Net longwave flux 316 ztmp1 = ztmp1 * ( Ce*L_vap(T_s)*(q_zu - q_s) + Ch*cp_air(q_zu)*(t_zu - T_s) ) & ! Total turb. heat flux 317 & + rad_lw - emiss_w*stefan*ztmp2*ztmp2 ! Net longwave flux 318 !! => "ztmp1" is the net non-solar surface heat flux ! 308 319 !! Updating the values of the skin temperature T_s and q_s : 309 320 CALL CSWL_ECMWF( Qsw, ztmp1, u_star, zsst, T_s ) -
NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_phy.F90
r11209 r11266 219 219 zqa = (1._wp + rctv0*pqa(ji,jj)) 220 220 ! 221 One_on_L(ji,jj) = grav*vkarmn*(pts(ji,jj) + rctv0*ptha(ji,jj)*pqs(ji,jj)) & 221 ! The main concern is to know whether, the vertical turbulent flux of virtual temperature, < u' theta_v' > is estimated with: 222 ! a/ -u* [ theta* (1 + 0.61 q) + 0.61 theta q* ] => this is the one that seems correct! chose this one! 223 ! or 224 ! b/ -u* [ theta* + 0.61 theta q* ] 225 ! 226 One_on_L(ji,jj) = grav*vkarmn*( pts(ji,jj)*zqa + rctv0*ptha(ji,jj)*pqs(ji,jj) ) & 222 227 & / MAX( pus(ji,jj)*pus(ji,jj)*ptha(ji,jj)*zqa , 1.E-9_wp ) 223 228 ! -
NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_skin.F90
r11182 r11266 34 34 IMPLICIT NONE 35 35 PRIVATE 36 37 PUBLIC :: CSWL_ECMWF ! called by sbcblk_algo_ *.F9036 37 PUBLIC :: CSWL_ECMWF ! called by sbcblk_algo_coare.F90 and sbcblk_algo_ecmwf.F90 38 38 39 39 !! Cool-Skin / Warm-Layer related parameters: 40 REAL(wp), PARAMETER :: rdt0 = 3600.*1.5 !: time step40 !LB: we use "rdt" instead !!! REAL(wp), PARAMETER :: rdt0 = 3600.*1.5 !: time step 41 41 REAL(wp), PARAMETER :: rd0 = 3. !: Depth scale [m], "d" in Eq.11 (Zeng & Beljaars 2005) 42 42 REAL(wp), PARAMETER :: rNu0 = 0.5 !: Nu (exponent of temperature profile) Eq.11 … … 162 162 IF( nbi > 1 ) THEN 163 163 !! Itterating for warm-layer solution 164 zdt = rdt 0/REAL(nbi)164 zdt = rdt/REAL(nbi) 165 165 rmult = 1._wp 166 166 ELSE
Note: See TracChangeset
for help on using the changeset viewer.