[3816] | 1 | module Near_Surface_m |
---|
| 2 | |
---|
| 3 | Implicit none |
---|
| 4 | |
---|
| 5 | real, parameter:: depth = 3. |
---|
| 6 | ! diurnal warm layer and fresh water lens depth, in m (Zeng and Beljaars 2005) |
---|
| 7 | |
---|
| 8 | contains |
---|
| 9 | |
---|
| 10 | subroutine near_surface(al, t_subskin, s_subskin, ds_ns, dt_ns, tau, taur, & |
---|
| 11 | hlb, rhoa, xlv, dtime, t_ocean_1, s1, rain, q_pwp) |
---|
| 12 | |
---|
| 13 | ! Hugo Bellenger, 2016 |
---|
| 14 | |
---|
| 15 | use config_ocean_skin_m, only: depth_1 |
---|
| 16 | use const, only: beta, cpw, grav, rhow, von |
---|
| 17 | use Phiw_m, only: Phiw |
---|
| 18 | use therm_expans_m, only: therm_expans |
---|
| 19 | |
---|
| 20 | real, intent(out):: al(:) ! water thermal expansion coefficient (in K-1) |
---|
| 21 | real, intent(out):: t_subskin(:) ! subskin temperature, in K |
---|
| 22 | real, intent(out):: s_subskin(:) ! subskin salinity, in ppt |
---|
| 23 | |
---|
| 24 | real, intent(inout):: ds_ns(:) |
---|
| 25 | ! "delta salinity near surface". Salinity variation in the |
---|
| 26 | ! near-surface turbulent layer. That is subskin salinity minus |
---|
| 27 | ! foundation salinity. In ppt. |
---|
| 28 | |
---|
| 29 | real, intent(inout):: dt_ns(:) |
---|
| 30 | ! "delta temperature near surface". Temperature variation in the |
---|
| 31 | ! near-surface turbulent layer. That is subskin temperature minus |
---|
| 32 | ! foundation temperature. (Can be negative.) In K. |
---|
| 33 | |
---|
| 34 | real, intent(in):: tau(:) |
---|
| 35 | ! wind stress at the surface, turbulent part only, in Pa |
---|
| 36 | |
---|
| 37 | real, intent(in):: taur(:) ! momentum flux due to rainfall, in Pa |
---|
| 38 | real, intent(in):: hlb(:) ! latent heat flux, turbulent part only, in W / m2 |
---|
| 39 | real, intent(in):: rhoa(:) ! density of moist air (kg / m3) |
---|
| 40 | real, intent(in):: xlv(:) ! latent heat of evaporation (J/kg) |
---|
| 41 | real, intent(in):: dtime ! time step (s) |
---|
| 42 | real, intent(in):: t_ocean_1(:) ! input sea temperature, at depth_1, in K |
---|
| 43 | real, intent(in):: S1(:) ! salinity at depth_1, in ppt |
---|
| 44 | real, intent(in):: rain(:) ! rain mass flux, in kg m-2 s-1 |
---|
| 45 | |
---|
| 46 | real, intent(in):: q_pwp(:) |
---|
| 47 | ! net flux absorbed by the warm layer (part of the solar flux |
---|
| 48 | ! absorbed at "depth"), minus surface fluxes, in W m-2 |
---|
| 49 | |
---|
| 50 | ! Local: |
---|
| 51 | |
---|
| 52 | real, parameter:: khor = 1. / 1.5e4 |
---|
| 53 | ! Parameter for the lens spread, in m-1. Inverse of the size of |
---|
| 54 | ! the lens. |
---|
| 55 | |
---|
| 56 | real, parameter:: umax = 15. |
---|
| 57 | real, parameter:: fact = 1. |
---|
| 58 | real buoyf(size(t_ocean_1)) ! buoyancy flux |
---|
| 59 | real usrc(size(t_ocean_1)) |
---|
| 60 | real drho(size(t_ocean_1)) ! rho(- delta) - rho(- d) |
---|
| 61 | real Lmo(size(t_ocean_1)) ! Monin-Obukhov length |
---|
| 62 | |
---|
| 63 | real u(size(t_ocean_1)) |
---|
| 64 | ! Wind speed at 15 m relative to the sea surface, i. e. taking |
---|
| 65 | ! current vector into account. In m s-1. |
---|
| 66 | |
---|
| 67 | real, dimension(size(t_ocean_1)):: At, Bt, As, Bs, correction |
---|
| 68 | |
---|
| 69 | real eta(size(t_ocean_1)) |
---|
| 70 | ! exponent in the function giving T(z) and S(z), equation (11) in |
---|
| 71 | ! Bellenger et al. 2017 JGR |
---|
| 72 | |
---|
| 73 | real t_fnd(size(t_ocean_1)) ! foundation temperature, in K |
---|
| 74 | real s_fnd(size(t_ocean_1)) ! foundation salinity, in ppt |
---|
| 75 | |
---|
| 76 | !---------------------------------------------------------------------- |
---|
| 77 | |
---|
| 78 | ! Temperature and salinity profiles change with wind: |
---|
| 79 | |
---|
| 80 | u = 28. * sqrt(tau / rhoa) |
---|
| 81 | |
---|
| 82 | where (dt_ns < 0.) |
---|
| 83 | where (u >= umax) |
---|
| 84 | eta = 1. / fact |
---|
| 85 | elsewhere (u <= 2.) |
---|
| 86 | eta = 2. / (fact * umax) |
---|
| 87 | elsewhere |
---|
| 88 | ! {u > 2. .and. u < umax} |
---|
| 89 | eta = u / (fact * umax) |
---|
| 90 | end where |
---|
| 91 | elsewhere |
---|
| 92 | eta = 0.3 |
---|
| 93 | end where |
---|
| 94 | |
---|
| 95 | if (depth_1 < depth) then |
---|
| 96 | correction = 1. - (depth_1 / depth)**eta |
---|
| 97 | ! (neglecting microlayer thickness compared to depth_1 and depth) |
---|
| 98 | |
---|
| 99 | t_fnd = t_ocean_1 - dt_ns * correction |
---|
| 100 | s_fnd = s1 - ds_ns * correction |
---|
| 101 | else |
---|
| 102 | t_fnd = t_ocean_1 |
---|
| 103 | s_fnd = s1 |
---|
| 104 | end if |
---|
| 105 | |
---|
| 106 | al = therm_expans(t_fnd) |
---|
| 107 | |
---|
| 108 | ! Bellenger 2017 k0976, equation (13): |
---|
| 109 | buoyf = Al * grav / (rhow * cpw) * q_pwp & |
---|
| 110 | - beta * S_FND * grav * (hlb / xlv - rain) / rhow |
---|
| 111 | |
---|
| 112 | usrc = sqrt((tau + taur) / rhow) |
---|
| 113 | drho = rhow * (- al * dt_ns + beta * ds_ns) |
---|
| 114 | |
---|
| 115 | ! Case of stable stratification and negative flux, Bellenger 2017 |
---|
| 116 | ! k0976, equation (15): |
---|
| 117 | where (buoyf < 0. .and. drho < 0.) |
---|
| 118 | buoyf = sqrt(- eta * grav / (5. * depth * rhow) * drho) * usrc**2 |
---|
| 119 | elsewhere (buoyf == 0.) |
---|
| 120 | buoyf = tiny(0.) |
---|
| 121 | end where |
---|
| 122 | |
---|
| 123 | |
---|
| 124 | Lmo = usrc**3 / (von * buoyf) |
---|
| 125 | |
---|
| 126 | ! Equation (14) for temperature. Implicit scheme for time integration: |
---|
| 127 | ! \Delta T_{i + 1} - \Delta T_i = \delta t (Bt + At \Delta T_{i + 1}) |
---|
| 128 | At = - (eta + 1.) * von * usrc / (depth * Phiw(depth / Lmo)) |
---|
| 129 | |
---|
| 130 | ! Lens horizontal spreading: |
---|
| 131 | where (drho < 0. .and. ds_ns < 0.) At = At & |
---|
| 132 | - (eta + 1.) * khor * sqrt(depth * grav * abs(drho) / rhow) |
---|
| 133 | |
---|
| 134 | Bt = q_pwp / (depth * rhow * cpw * eta / (eta + 1.)) |
---|
| 135 | dt_ns = (dtime * Bt + dt_ns) / (1 - dtime * At) |
---|
| 136 | |
---|
| 137 | ! Equation (14) for salinity: |
---|
| 138 | ! \frac{\partial \Delta S}{\partial t} |
---|
| 139 | ! = (\Delta S + S_\mathrm{fnd}) B_S + A_S \Delta S |
---|
| 140 | As = - (eta + 1.) * von * usrc / (depth * Phiw(depth / Lmo)) |
---|
| 141 | |
---|
| 142 | ! Lens horizontal spreading: |
---|
| 143 | where (drho < 0. .and. ds_ns < 0.) As = As & |
---|
| 144 | - (eta + 1.) * khor * sqrt(depth * grav * abs(drho) / rhow) |
---|
| 145 | |
---|
| 146 | Bs = (hlb / xlv - rain) * (eta + 1.) / (depth * rhow * eta) |
---|
| 147 | |
---|
| 148 | ! Implicit scheme for time integration: |
---|
| 149 | ds_ns = (dtime * Bs * S_fnd + ds_ns) / (1 - dtime * (As + bs)) |
---|
| 150 | |
---|
| 151 | t_subskin = t_fnd + dt_ns |
---|
| 152 | s_subskin = s_fnd + ds_ns |
---|
| 153 | |
---|
| 154 | end subroutine Near_Surface |
---|
| 155 | |
---|
| 156 | end module Near_Surface_m |
---|