Ignore:
Timestamp:
Jun 15, 2021, 1:18:14 PM (3 years ago)
Author:
crisi
Message:

replace files by symbloic liks from phylmdiso towards phylmd.
Many files at once

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/surf_ocean_mod.F90

    r3927 r3940  
    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#ifdef ISO
    2425        &       ,xtprecip_rain, xtprecip_snow,xtspechum,Roce, &
     
    2829
    2930    use albedo, only: alboc, alboc_cd
     31    use bulk_flux_m, only: bulk_flux
    3032    USE dimphy, ONLY: klon, zmasq
    3133    USE surface_data, ONLY     : type_ocean
     
    4244#endif
    4345    USE limit_read_mod
     46    use config_ocean_skin_m, only: activate_ocean_skin
    4447    !
    4548    ! This subroutine will make a call to ocean_XXX_noice according to the ocean mode (force,
     
    6265    REAL, DIMENSION(klon), INTENT(IN)        :: lwnet  ! net longwave radiation at surface 
    6366    REAL, DIMENSION(klon), INTENT(IN)        :: alb1   ! albedo in visible SW interval
    64     REAL, DIMENSION(klon), INTENT(IN)        :: windsp
     67    REAL, DIMENSION(klon), INTENT(IN)        :: windsp ! wind at 10 m, in m s-1
    6568    REAL, DIMENSION(klon), INTENT(IN)        :: rmu0 
    6669    REAL, DIMENSION(klon), INTENT(IN)        :: fder
    67     REAL, DIMENSION(klon), INTENT(IN)        :: tsurf_in
     70    REAL, DIMENSION(klon), INTENT(IN)        :: tsurf_in     ! defined only for subscripts 1:knon
    6871    REAL, DIMENSION(klon), INTENT(IN)        :: p1lay,z1lay ! pression (Pa) et altitude (m) du premier niveau
    6972    REAL, DIMENSION(klon), INTENT(IN)        :: cdragh
     
    8790    REAL, DIMENSION(klon), INTENT(INOUT)     :: qsurf
    8891    REAL, DIMENSION(klon), INTENT(INOUT)     :: agesno
     92    REAL, DIMENSION(klon), INTENT(inOUT)     :: z0h
    8993#ifdef ISO
    9094    REAL, DIMENSION(niso,klon), INTENT(IN)        :: xtsnow
    9195    REAL, DIMENSION(niso,klon), INTENT(INOUT)        :: Roce 
    9296#endif
    93     REAL, DIMENSION(klon), INTENT(inOUT):: z0h
     97
     98    REAL, intent(inout):: delta_sst(:) ! (knon)
     99    ! Ocean-air interface temperature minus bulk SST, in K. Defined
     100    ! only if activate_ocean_skin >= 1.
     101
     102    real, intent(inout):: delta_sal(:) ! (knon)
     103    ! Ocean-air interface salinity minus bulk salinity, in ppt. Defined
     104    ! only if activate_ocean_skin >= 1.
     105
     106    REAL, intent(inout):: ds_ns(:) ! (knon)
     107    ! "delta salinity near surface". Salinity variation in the
     108    ! near-surface turbulent layer. That is subskin salinity minus
     109    ! foundation salinity. In ppt.
     110
     111    REAL, intent(inout):: dt_ns(:) ! (knon)
     112    ! "delta temperature near surface". Temperature variation in the
     113    ! near-surface turbulent layer. That is subskin temperature
     114    ! minus foundation temperature. (Can be negative.) In K.
    94115
    95116    ! Output variables
    96     !******************************************************************************
     117    !**************************************************************************
    97118    REAL, DIMENSION(klon), INTENT(OUT)       :: z0m
    98119    !albedo SB >>>
    99     !    REAL, DIMENSION(klon), INTENT(OUT)       :: alb1_new  ! new albedo in visible SW interval
    100     !    REAL, DIMENSION(klon), INTENT(OUT)       :: alb2_new  ! new albedo in near IR interval
    101     REAL, DIMENSION(6), INTENT(IN)          :: SFRWL
    102     REAL, DIMENSION(klon,nsw), INTENT(OUT)       :: alb_dir_new,alb_dif_new
     120    !    REAL, DIMENSION(klon), INTENT(OUT)  :: alb1_new  ! new albedo in visible SW interval
     121    !    REAL, DIMENSION(klon), INTENT(OUT)  :: alb2_new  ! new albedo in near IR interval
     122    REAL, DIMENSION(6), INTENT(IN)           :: SFRWL
     123    REAL, DIMENSION(klon,nsw), INTENT(OUT)   :: alb_dir_new,alb_dif_new
    103124    !albedo SB <<<     
    104125    REAL, DIMENSION(klon), INTENT(OUT)       :: evap, fluxsens, fluxlat
    105     REAL, DIMENSION(klon), INTENT(OUT)       :: tsurf_new
     126    REAL, DIMENSION(klon), INTENT(OUT)       :: tsurf_new    ! sea surface temperature, in K
    106127    REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l     
    107128    REAL, DIMENSION(klon), INTENT(OUT)       :: lmt_bils
    108129    REAL, DIMENSION(klon), INTENT(OUT)       :: flux_u1, flux_v1
     130
     131    REAL, intent(out):: dter(:) ! (knon)
     132    ! Temperature variation in the diffusive microlayer, that is
     133    ! ocean-air interface temperature minus subskin temperature. In
     134    ! K.
     135
     136    REAL, intent(out):: dser(:) ! (knon)
     137    ! Salinity variation in the diffusive microlayer, that is
     138    ! ocean-air interface salinity minus subskin salinity. In ppt.
     139
     140    REAL, intent(out):: tkt(:) ! (knon)
     141    ! épaisseur (m) de la couche de diffusion thermique (microlayer)
     142    ! cool skin thickness
     143
     144    REAL, intent(out):: tks(:) ! (knon)
     145    ! épaisseur (m) de la couche de diffusion de masse (microlayer)
     146
     147    REAL, intent(out):: taur(:) ! (knon)
     148    ! momentum flux due to rain, in Pa
     149
     150    real, intent(out):: sss(:) ! (klon)
     151    ! Bulk salinity of the surface layer of the ocean, in ppt. (Only
     152    ! defined for subscripts 1:knon, but we have to declare it with
     153    ! size klon because of the coupling machinery.)
    109154#ifdef ISO
    110155    REAL, DIMENSION(ntraciso,klon), INTENT(out)        :: xtevap ! isotopes in surface evaporation flux
     
    113158
    114159    ! Local variables
    115     !******************************************************************************
     160    !*************************************************************************
    116161    INTEGER               :: i, k
    117162    REAL                  :: tmp
     
    121166    REAL, DIMENSION(klon) :: cdragq ! Cdrag pour l'evaporation
    122167    CHARACTER(len=20),PARAMETER :: modname="surf_ocean"
    123 
    124     ! End definition
     168    real rhoa(knon) ! density of moist air  (kg / m3)
     169    REAL sens_prec_liq(knon)
     170
     171    REAL t_int(knon) ! ocean-air interface temperature, in K
     172    real s_int(knon) ! ocean-air interface salinity, in ppt
     173
    125174    !******************************************************************************
    126175
     
    165214
    166215
     216    rhoa = PS(:KNON) / (Rd * temp_air(:knon) * (1. + retv * spechum(:knon)))
     217
    167218    !******************************************************************************
    168219    ! Switch according to type of ocean (couple, slab or forced)
     
    177228            AcoefH, AcoefQ, BcoefH, BcoefQ, &
    178229            AcoefU, AcoefV, BcoefU, BcoefV, &
    179             ps, u1, v1, gustiness, &
     230            ps, u1, v1, gustiness, tsurf_in, &
    180231            radsol, snow, agesno, &
    181232            qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    182             tsurf_new, dflux_s, dflux_l)
     233            tsurf_new, dflux_s, dflux_l, sens_prec_liq, sss, delta_sal, rhoa, &
     234            delta_sst)
    183235
    184236    CASE('slab')
     
    200252            AcoefH, AcoefQ, BcoefH, BcoefQ, &
    201253            AcoefU, AcoefV, BcoefU, BcoefV, &
    202             ps, u1, v1, gustiness, &
     254            ps, u1, v1, gustiness, tsurf_in, &
    203255            radsol, snow, agesno, &
    204256            qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    205             tsurf_new, dflux_s, dflux_l &
     257            tsurf_new, dflux_s, dflux_l, sens_prec_liq, rhoa &
    206258#ifdef ISO
    207259            ,xtprecip_rain, xtprecip_snow, xtspechum,Roce,rlat, &
     
    311363       CALL abort_physic(modname,'version non prevue',1)
    312364    ENDIF
    313     !
    314     !******************************************************************************
     365
     366    if (activate_ocean_skin >= 1) then
     367       if (type_ocean /= 'couple') sss(:knon) = 35.
     368       call bulk_flux(tkt, tks, taur, dter, dser, t_int, s_int, ds_ns, dt_ns, &
     369            u = windsp(:knon), t_ocean_1 = tsurf_new(:knon), s1 = sss(:knon), &
     370            rain = precip_rain(:knon) + precip_snow(:knon), &
     371            hf = - fluxsens(:knon), hlb = - fluxlat(:knon), &
     372            rnl = - lwnet(:knon), &
     373            tau = sqrt(flux_u1(:knon)**2 + flux_v1(:knon)**2), rhoa = rhoa, &
     374            xlv = [(rlvtt, i = 1, knon)], rf = - sens_prec_liq, dtime = dtime, &
     375            rns = swnet(:knon))
     376       delta_sst = t_int - tsurf_new(:knon)
     377       delta_sal = s_int - sss(:knon)
     378       if (activate_ocean_skin >= 2) tsurf_new(:knon) = t_int
     379    end if
     380
    315381  END SUBROUTINE surf_ocean
    316   !******************************************************************************
     382  !****************************************************************************
    317383  !
    318384END MODULE surf_ocean_mod
Note: See TracChangeset for help on using the changeset viewer.