Ignore:
Timestamp:
Feb 1, 2021, 3:30:57 PM (3 years ago)
Author:
lguez
Message:

Merge Ocean_skin branch back into trunk

Location:
LMDZ6/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk

  • LMDZ6/trunk/libf/phylmd/ocean_cpl_mod.F90

    r3102 r3815  
    5252       AcoefH, AcoefQ, BcoefH, BcoefQ, &
    5353       AcoefU, AcoefV, BcoefU, BcoefV, &
    54        ps, u1, v1, gustiness, &
     54       ps, u1, v1, gustiness, tsurf_in, &
    5555       radsol, snow, agesno, &
    5656       qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    57        tsurf_new, dflux_s, dflux_l)
     57       tsurf_new, dflux_s, dflux_l, sens_prec_liq, sss, delta_sal, rhoa, &
     58       delta_sst)
    5859
    5960!
     
    6364!
    6465    USE dimphy,           ONLY : klon
    65     USE cpl_mod
    6666    USE calcul_fluxs_mod
    6767    USE indice_sol_mod
    6868    USE phys_output_var_mod, ONLY : sens_prec_liq_o, sens_prec_sol_o, lat_prec_liq_o, lat_prec_sol_o
    69     USE cpl_mod,             ONLY : gath2cpl
     69    USE cpl_mod, ONLY : gath2cpl, cpl_receive_ocean_fields, &
     70         cpl_send_ocean_fields
     71    use config_ocean_skin_m, only: activate_ocean_skin
    7072
    7173    INCLUDE "YOMCST.h"
     
    9092    REAL, DIMENSION(klon), INTENT(IN)        :: ps
    9193    REAL, DIMENSION(klon), INTENT(IN)        :: u1, v1, gustiness
     94    REAL, INTENT(IN) :: tsurf_in(:) ! (klon)
     95
     96    real, intent(in):: delta_sal(:) ! (knon)
     97    ! ocean-air interface salinity minus bulk salinity, in ppt
     98
     99    real, intent(in):: rhoa(:) ! (knon) density of moist air  (kg / m3)
     100
     101    REAL, intent(in):: delta_sst(:) ! (knon)
     102    ! Ocean-air interface temperature minus bulk SST, in K. Defined
     103    ! only if activate_ocean_skin >= 1.
    92104
    93105! In/Output arguments
     
    104116    REAL, DIMENSION(klon), INTENT(OUT)       :: tsurf_new
    105117    REAL, DIMENSION(klon), INTENT(OUT)       :: dflux_s, dflux_l     
     118    REAL, intent(out):: sens_prec_liq(:) ! (knon)
     119
     120    REAL, INTENT(OUT):: sss(:) ! (klon)
     121    ! bulk salinity of the surface layer of the ocean, in ppt
    106122 
    107123
     
    116132    REAL, DIMENSION(klon) :: u1_lay, v1_lay
    117133    LOGICAL               :: check=.FALSE.
    118     REAL, DIMENSION(klon) :: sens_prec_liq, sens_prec_sol   
     134    REAL sens_prec_sol(knon) 
    119135    REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol   
    120136
     
    128144!
    129145!****************************************************************************************
    130     CALL cpl_receive_ocean_fields(knon, knindex, tsurf_cpl, u0_cpl, v0_cpl)
     146    CALL cpl_receive_ocean_fields(knon, knindex, tsurf_cpl, u0_cpl, v0_cpl, &
     147         sss)
    131148
    132149!****************************************************************************************
     
    138155    dif_grnd = 0.
    139156    agesno(:) = 0.
    140     sens_prec_liq = 0.; sens_prec_sol = 0.; lat_prec_liq = 0.; lat_prec_sol = 0.
     157    lat_prec_liq = 0.; lat_prec_sol = 0.
    141158   
    142159
     
    147164
    148165    CALL calcul_fluxs(knon, is_oce, dtime, &
    149          tsurf_cpl, p1lay, cal, beta, cdragh, cdragq, ps, &
     166         merge(tsurf_in, tsurf_cpl, activate_ocean_skin == 2), p1lay, cal, &
     167         beta, cdragh, cdragq, ps, &
    150168         precip_rain, precip_snow, snow, qsurf,  &
    151169         radsol, dif_grnd, temp_air, spechum, u1_lay, v1_lay, gustiness, &
    152170         f_qsat_oce,AcoefH, AcoefQ, BcoefH, BcoefQ, &
    153171         tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
    154          sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol)
     172         sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, rhoa)
     173
     174    if (activate_ocean_skin == 2) then
     175       ! tsurf_new was set to tsurf_in in calcul_flux, correct it to
     176       ! the new bulk SST tsurf_cpl:
     177       tsurf_new = tsurf_cpl
     178    end if
     179
     180    ! assertion: tsurf_new == tsurf_cpl
     181   
    155182    do j = 1, knon
    156183      i = knindex(j)
     
    189216!****************************************************************************************
    190217
    191     CALL cpl_send_ocean_fields(itime, knon, knindex, &
    192          swnet, lwnet, fluxlat, fluxsens, &
    193          precip_rain, precip_snow, evap, tsurf_new, fder_new, alb1, flux_u1, flux_v1, windsp,&
    194          sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol)
    195    
     218    CALL cpl_send_ocean_fields(itime, knon, knindex, swnet, lwnet, fluxlat, &
     219         fluxsens, precip_rain, precip_snow, evap, tsurf_new, fder_new, alb1, &
     220         flux_u1, flux_v1, windsp, sens_prec_liq, sens_prec_sol, lat_prec_liq, &
     221         lat_prec_sol, delta_sst, delta_sal)
    196222
    197223  END SUBROUTINE ocean_cpl_noice
     
    210236       radsol, snow, qsurf, &
    211237       alb1_new, alb2_new, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    212        tsurf_new, dflux_s, dflux_l)
     238       tsurf_new, dflux_s, dflux_l, rhoa)
    213239!
    214240! This subroutine treats the ocean where there is ice. The subroutine first receives
     
    245271    REAL, DIMENSION(klon), INTENT(IN)        :: u1, v1, gustiness
    246272    REAL, DIMENSION(klon,nbsrf), INTENT(IN)  :: pctsrf
     273    real, intent(in):: rhoa(:) ! (knon) density of moist air  (kg / m3)
    247274
    248275! In/output arguments
     
    272299    REAL, DIMENSION(klon)   :: u0, v0
    273300    REAL, DIMENSION(klon)   :: u1_lay, v1_lay
    274     REAL, DIMENSION(klon) :: sens_prec_liq, sens_prec_sol    
     301    REAL sens_prec_liq(knon), sens_prec_sol(knon)   
    275302    REAL, DIMENSION(klon) :: lat_prec_liq, lat_prec_sol   
    276303
     
    280307    IF (check) WRITE(*,*)'Entering surface_seaice, knon=',knon
    281308
    282     sens_prec_liq = 0.; sens_prec_sol = 0.; lat_prec_liq = 0.; lat_prec_sol = 0.
     309    lat_prec_liq = 0.; lat_prec_sol = 0.
    283310
    284311!****************************************************************************************
     
    313340         f_qsat_oce,AcoefH, AcoefQ, BcoefH, BcoefQ, &
    314341         tsurf_new, evap, fluxlat, fluxsens, dflux_s, dflux_l, &
    315          sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol)
     342         sens_prec_liq, sens_prec_sol, lat_prec_liq, lat_prec_sol, rhoa)
    316343    do j = 1, knon
    317344      i = knindex(j)
Note: See TracChangeset for help on using the changeset viewer.