Ignore:
Timestamp:
Feb 22, 2021, 12:44:07 PM (4 years ago)
Author:
dcugnet
Message:

Update the branch to the current trunk.

Location:
LMDZ6/branches/LMDZ-tracers
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ-tracers

  • LMDZ6/branches/LMDZ-tracers/libf/phylmd/surf_ocean_mod.F90

    r3395 r3851  
    2020       z0m, z0h, SFRWL, alb_dir_new, alb_dif_new, evap, fluxsens, fluxlat, &
    2121       tsurf_new, dflux_s, dflux_l, lmt_bils, &
    22        flux_u1, flux_v1)
     22       flux_u1, flux_v1, delta_sst, delta_sal, ds_ns, dt_ns, dter, dser, tkt, tks, &
     23       taur, sss)
    2324
    2425    use albedo, only: alboc, alboc_cd
     26    use bulk_flux_m, only: bulk_flux
    2527    USE dimphy, ONLY: klon, zmasq
    2628    USE surface_data, ONLY     : type_ocean
     
    3032    USE indice_sol_mod, ONLY : nbsrf, is_oce
    3133    USE limit_read_mod
     34    use config_ocean_skin_m, only: activate_ocean_skin
    3235    !
    3336    ! This subroutine will make a call to ocean_XXX_noice according to the ocean mode (force,
     
    5053    REAL, DIMENSION(klon), INTENT(IN)        :: lwnet  ! net longwave radiation at surface 
    5154    REAL, DIMENSION(klon), INTENT(IN)        :: alb1   ! albedo in visible SW interval
    52     REAL, DIMENSION(klon), INTENT(IN)        :: windsp
     55    REAL, DIMENSION(klon), INTENT(IN)        :: windsp ! wind at 10 m, in m s-1
    5356    REAL, DIMENSION(klon), INTENT(IN)        :: rmu0 
    5457    REAL, DIMENSION(klon), INTENT(IN)        :: fder
    55     REAL, DIMENSION(klon), INTENT(IN)        :: tsurf_in
     58    REAL, INTENT(IN):: tsurf_in(klon) ! defined only for subscripts 1:knon
    5659    REAL, DIMENSION(klon), INTENT(IN)        :: p1lay,z1lay ! pression (Pa) et altitude (m) du premier niveau
    5760    REAL, DIMENSION(klon), INTENT(IN)        :: cdragh
     
    7376    REAL, DIMENSION(klon), INTENT(inOUT):: z0h
    7477
     78    REAL, intent(inout):: delta_sst(:) ! (knon)
     79    ! Ocean-air interface temperature minus bulk SST, in K. Defined
     80    ! only if activate_ocean_skin >= 1.
     81
     82    real, intent(inout):: delta_sal(:) ! (knon)
     83    ! Ocean-air interface salinity minus bulk salinity, in ppt. Defined
     84    ! only if activate_ocean_skin >= 1.
     85
     86    REAL, intent(inout):: ds_ns(:) ! (knon)
     87    ! "delta salinity near surface". Salinity variation in the
     88    ! near-surface turbulent layer. That is subskin salinity minus
     89    ! foundation salinity. In ppt.
     90
     91    REAL, intent(inout):: dt_ns(:) ! (knon)
     92    ! "delta temperature near surface". Temperature variation in the
     93    ! near-surface turbulent layer. That is subskin temperature
     94    ! minus foundation temperature. (Can be negative.) In K.
     95
    7596    ! Output variables
    76     !******************************************************************************
     97    !**************************************************************************
    7798    REAL, DIMENSION(klon), INTENT(OUT)       :: z0m
    7899    !albedo SB >>>
     
    83104    !albedo SB <<<     
    84105    REAL, DIMENSION(klon), INTENT(OUT)       :: evap, fluxsens, fluxlat
    85     REAL, DIMENSION(klon), INTENT(OUT)       :: tsurf_new
     106    REAL, INTENT(OUT):: tsurf_new(klon) ! sea surface temperature, in K
    86107    REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l     
    87108    REAL, DIMENSION(klon), INTENT(OUT)       :: lmt_bils
    88109    REAL, DIMENSION(klon), INTENT(OUT)       :: flux_u1, flux_v1
    89110
     111    REAL, intent(out):: dter(:) ! (knon)
     112    ! Temperature variation in the diffusive microlayer, that is
     113    ! ocean-air interface temperature minus subskin temperature. In
     114    ! K.
     115
     116    REAL, intent(out):: dser(:) ! (knon)
     117    ! Salinity variation in the diffusive microlayer, that is
     118    ! ocean-air interface salinity minus subskin salinity. In ppt.
     119
     120    REAL, intent(out):: tkt(:) ! (knon)
     121    ! épaisseur (m) de la couche de diffusion thermique (microlayer)
     122    ! cool skin thickness
     123
     124    REAL, intent(out):: tks(:) ! (knon)
     125    ! épaisseur (m) de la couche de diffusion de masse (microlayer)
     126
     127    REAL, intent(out):: taur(:) ! (knon)
     128    ! momentum flux due to rain, in Pa
     129
     130    real, intent(out):: sss(:) ! (klon)
     131    ! Bulk salinity of the surface layer of the ocean, in ppt. (Only
     132    ! defined for subscripts 1:knon, but we have to declare it with
     133    ! size klon because of the coupling machinery.)
     134
    90135    ! Local variables
    91     !******************************************************************************
     136    !*************************************************************************
    92137    INTEGER               :: i, k
    93138    REAL                  :: tmp
     
    97142    REAL, DIMENSION(klon) :: cdragq ! Cdrag pour l'evaporation
    98143    CHARACTER(len=20),PARAMETER :: modname="surf_ocean"
    99 
    100     ! End definition
    101     !******************************************************************************
     144    real rhoa(knon) ! density of moist air  (kg / m3)
     145    REAL sens_prec_liq(knon)
     146
     147    REAL t_int(knon) ! ocean-air interface temperature, in K
     148    real s_int(knon) ! ocean-air interface salinity, in ppt
     149
     150    !**************************************************************************
    102151
    103152
     
    126175    ENDIF
    127176
    128 
     177    rhoa = PS(:KNON) / (Rd * temp_air(:knon) * (1. + retv * spechum(:knon)))
    129178    !******************************************************************************
    130179    ! Switch according to type of ocean (couple, slab or forced)
     
    139188            AcoefH, AcoefQ, BcoefH, BcoefQ, &
    140189            AcoefU, AcoefV, BcoefU, BcoefV, &
    141             ps, u1, v1, gustiness, &
     190            ps, u1, v1, gustiness, tsurf_in, &
    142191            radsol, snow, agesno, &
    143192            qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    144             tsurf_new, dflux_s, dflux_l)
     193            tsurf_new, dflux_s, dflux_l, sens_prec_liq, sss, delta_sal, rhoa, &
     194            delta_sst)
    145195
    146196    CASE('slab')
     
    162212            AcoefH, AcoefQ, BcoefH, BcoefQ, &
    163213            AcoefU, AcoefV, BcoefU, BcoefV, &
    164             ps, u1, v1, gustiness, &
     214            ps, u1, v1, gustiness, tsurf_in, &
    165215            radsol, snow, agesno, &
    166216            qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    167             tsurf_new, dflux_s, dflux_l)
     217            tsurf_new, dflux_s, dflux_l, sens_prec_liq, rhoa)
    168218    END SELECT
    169219
     
    268318       CALL abort_physic(modname,'version non prevue',1)
    269319    ENDIF
    270     !
    271     !******************************************************************************
     320
     321    if (activate_ocean_skin >= 1) then
     322       if (type_ocean /= 'couple') sss(:knon) = 35.
     323       call bulk_flux(tkt, tks, taur, dter, dser, t_int, s_int, ds_ns, dt_ns, &
     324            u = windsp(:knon), t_ocean_1 = tsurf_new(:knon), s1 = sss(:knon), &
     325            rain = precip_rain(:knon) + precip_snow(:knon), &
     326            hf = - fluxsens(:knon), hlb = - fluxlat(:knon), &
     327            rnl = - lwnet(:knon), &
     328            tau = sqrt(flux_u1(:knon)**2 + flux_v1(:knon)**2), rhoa = rhoa, &
     329            xlv = [(rlvtt, i = 1, knon)], rf = - sens_prec_liq, dtime = dtime, &
     330            rns = swnet(:knon))
     331       delta_sst = t_int - tsurf_new(:knon)
     332       delta_sal = s_int - sss(:knon)
     333       if (activate_ocean_skin >= 2) tsurf_new(:knon) = t_int
     334    end if
     335   
    272336  END SUBROUTINE surf_ocean
    273   !******************************************************************************
     337  !****************************************************************************
    274338  !
    275339END MODULE surf_ocean_mod
Note: See TracChangeset for help on using the changeset viewer.