Changeset 4374


Ignore:
Timestamp:
Dec 12, 2022, 10:11:56 PM (18 months ago)
Author:
lguez
Message:

Report modifications from phylmd into phylmdiso

Report modifications of revision 4370 from phylmd into phylmdiso.

Location:
LMDZ6/trunk/libf/phylmdiso
Files:
6 edited

Legend:

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

    r4285 r4374  
    406406#endif
    407407    USE ioipsl_getin_p_mod, ONLY : getin_p
    408     use phys_state_var_mod, only: ds_ns, dt_ns, delta_sst, delta_sal, zsig, zmea
    409     use phys_output_var_mod, only: dter, dser, tkt, tks, taur, sss
     408    use phys_state_var_mod, only: ds_ns, dt_ns, delta_sst, delta_sal, dter, &
     409         dser, dt_ds, zsig, zmea
     410    use phys_output_var_mod, only: tkt, tks, taur, sss
    410411#ifdef CPP_XIOS
    411412    USE wxios, ONLY: missing_val
     
    10291030    ! Martin
    10301031
    1031     REAL, DIMENSION(klon):: ydelta_sst, ydelta_sal, yds_ns, ydt_ns, ydter, ydser, &
    1032          ytkt, ytks, ytaur, ysss
    1033     ! compression of delta_sst, delta_sal, ds_ns, dt_ns, dter, dser, tkt, tks,
    1034     ! taur, sss on ocean points
     1032    REAL, DIMENSION(klon):: ydelta_sst, ydelta_sal, yds_ns, ydt_ns, ydter, &
     1033         ydser, ydt_ds, ytkt, ytks, ytaur, ysss
     1034    ! compression of delta_sst, delta_sal, ds_ns, dt_ns, dter, dser,
     1035    ! dt_ds, tkt, tks, taur, sss on ocean points
    10351036
    10361037#ifdef ISO
     
    18131814             ydelta_sal(:knon) = delta_sal(ni(:knon))
    18141815             ydelta_sst(:knon) = delta_sst(ni(:knon))
     1816             ydter(:knon) = dter(ni(:knon))
     1817             ydser(:knon) = dser(ni(:knon))
     1818             ydt_ds(:knon) = dt_ds(ni(:knon))
    18151819          end if
    18161820         
     
    24622466               y_flux_u1, y_flux_v1, ydelta_sst(:knon), ydelta_sal(:knon), &
    24632467               yds_ns(:knon), ydt_ns(:knon), ydter(:knon), ydser(:knon), &
    2464                ytkt(:knon), ytks(:knon), ytaur(:knon), ysss &
     2468               ydt_ds(:knon), ytkt(:knon), ytks(:knon), ytaur(:knon), ysss &
    24652469#ifdef ISO
    24662470         &      ,yxtrain_f, yxtsnow_f,yxt1,Roce, &
     
    33943398          taur(ni(:knon)) = ytaur(:knon)
    33953399          sss(ni(:knon)) = ysss(:knon)
     3400
     3401          if (activate_ocean_skin == 2 .and. type_ocean == "couple") then
     3402             dt_ds = missing_val
     3403             dt_ds(ni(:knon)) = ydt_ds(:knon)
     3404          end if
    33963405       end if
    33973406
     
    41314140
    41324141    USE indice_sol_mod
    4133     use phys_state_var_mod, only: delta_sal, ds_ns, dt_ns, delta_sst
     4142    use phys_state_var_mod, only: delta_sal, ds_ns, dt_ns, delta_sst, dter, &
     4143         dser, dt_ds
    41344144    use config_ocean_skin_m, only: activate_ocean_skin
    41354145
     
    42374247                         delta_sal(i) = 0.
    42384248                         delta_sst(i) = 0.
     4249                         dter(i) = 0.
     4250                         dser(i) = 0.
     4251                         dt_ds(i) = 0.
    42394252                      end if
    42404253                     
  • LMDZ6/trunk/libf/phylmdiso/phyetat0_mod.F90

    r4367 r4374  
    3535#endif
    3636       zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl, u10m, v10m, treedrg, &
    37        ale_wake, ale_bl_stat, ds_ns, dt_ns, delta_sst, delta_sal, ratqs_inter
     37       ale_wake, ale_bl_stat, ds_ns, dt_ns, delta_sst, delta_sal, dter, dser, &
     38       dt_ds, ratqs_inter
    3839!FC
    3940  USE geometry_mod,     ONLY: longitude_deg, latitude_deg
     
    599600        found = phyetat0_get(delta_sst, "delta_SST", &
    600601             "ocean-air interface temperature minus bulk SST", 0.)
     602        found = phyetat0_get(dter, "dter", &
     603             "ocean-air interface temperature minus subskin temperature", 0.)
     604        found = phyetat0_get(dser, "dser", &
     605             "ocean-air interface salinity minus subskin salinity", 0.)
     606        found = phyetat0_get(dt_ds, "dt_ds", "(tks / tkt) * dTer", 0.)
     607
     608        where (pctsrf(:, is_oce) == 0.)
     609           delta_sst = missing_val
     610           delta_sal = missing_val
     611           dter = missing_val
     612           dser = missing_val
     613           dt_ds = missing_val
     614        end where
    601615     end if
    602616     
  • LMDZ6/trunk/libf/phylmdiso/phyredem.F90

    r4298 r4374  
    3030                                du_gwd_rando, du_gwd_front, u10m, v10m, &
    3131                                treedrg, solswfdiff, delta_sal, ds_ns, dt_ns, &
    32                                 delta_sst, ratqs_inter
     32                                delta_sst, ratqs_inter, dter, dser, dt_ds
    3333#ifdef ISO
    3434  USE phys_state_var_mod, ONLY: xtsol, fxtevap,xtrain_fall, xtsnow_fall,     &
     
    399399          CALL put_field(pass, "delta_SST", &
    400400               "ocean-air interface temperature minus bulk SST", delta_sst)
     401          CALL put_field(pass, "dter", &
     402               "ocean-air interface temperature minus subskin temperature", &
     403               dter)
     404          CALL put_field(pass, "dser", &
     405               "ocean-air interface salinity minus subskin salinity", dser)
     406          CALL put_field(pass, "dt_ds", &
     407               "(tks / tkt) * dTer", dt_ds)
    401408       end if
    402409       
  • LMDZ6/trunk/libf/phylmdiso/phys_output_var_mod.F90

    r3940 r4374  
    135135  ! Ocean-atmosphere interface, subskin ocean and near-surface ocean:
    136136 
    137   REAL, ALLOCATABLE, SAVE:: dter(:)
    138   ! Temperature variation in the diffusive microlayer, that is
    139   ! ocean-air interface temperature minus subskin temperature. In K.
    140      
    141   REAL, SAVE, ALLOCATABLE:: dser(:)
    142   ! Temperature variation in the diffusive microlayer, that is
    143   ! subskin temperature minus ocean-air interface temperature. In K.
    144 
    145   REAL, SAVE, ALLOCATABLE:: tkt(:)
     137  REAL, SAVE, ALLOCATABLE:: tkt(:) ! (klon)
    146138  ! épaisseur (m) de la couche de diffusion thermique (microlayer)
    147139  ! cool skin thickness
    148140
    149   REAL, SAVE, ALLOCATABLE:: tks(:)
     141  REAL, SAVE, ALLOCATABLE:: tks(:) ! (klon)
    150142  ! épaisseur (m) de la couche de diffusion de masse (microlayer)
    151143 
    152   REAL, SAVE, ALLOCATABLE:: taur(:) ! momentum flux due to rain, in Pa
    153 
    154   REAL, SAVE, ALLOCATABLE:: sss(:)
     144  REAL, SAVE, ALLOCATABLE:: taur(:) ! (klon) momentum flux due to rain, in Pa
     145
     146  REAL, SAVE, ALLOCATABLE:: sss(:) ! (klon)
    155147  ! bulk salinity of the surface layer of the ocean, in ppt
    156148 
    157   !$OMP THREADPRIVATE(dter, dser, tkt, tks, taur, sss)
     149  !$OMP THREADPRIVATE(tkt, tks, taur, sss)
    158150
    159151CONTAINS
     
    216208    IF (ok_gwd_rando) allocate(zustr_gwd_rando(klon), zvstr_gwd_rando(klon))
    217209
    218     if (activate_ocean_skin >= 1) allocate(dter(klon), dser(klon), tkt(klon), &
    219          tks(klon), taur(klon), sss(klon))
     210    if (activate_ocean_skin >= 1) allocate(tkt(klon), tks(klon), taur(klon), &
     211         sss(klon))
    220212
    221213  END SUBROUTINE phys_output_var_init
  • LMDZ6/trunk/libf/phylmdiso/surf_ocean_mod.F90

    r4143 r4374  
    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, delta_sst, delta_sal, ds_ns, dt_ns, dter, dser, tkt, tks, &
    23        taur, sss &
     22       flux_u1, flux_v1, delta_sst, delta_sal, ds_ns, dt_ns, dter, dser, &
     23       dt_ds, tkt, tks, taur, sss &
    2424#ifdef ISO
    2525        &       ,xtprecip_rain, xtprecip_snow,xtspechum,Roce, &
     
    114114    ! minus foundation temperature. (Can be negative.) In K.
    115115
     116    REAL, intent(inout):: dter(:) ! (knon)
     117    ! Temperature variation in the diffusive microlayer, that is
     118    ! ocean-air interface temperature minus subskin temperature. In
     119    ! K.
     120
     121    REAL, intent(inout):: dser(:) ! (knon)
     122    ! Salinity variation in the diffusive microlayer, that is
     123    ! ocean-air interface salinity minus subskin salinity. In ppt.
     124
     125    real, intent(inout):: dt_ds(:) ! (knon)
     126    ! (tks / tkt) * dTer, in K
     127
    116128    ! Output variables
    117129    !**************************************************************************
     
    129141    REAL, DIMENSION(klon), INTENT(OUT)       :: flux_u1, flux_v1
    130142
    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 
    140143    REAL, intent(out):: tkt(:) ! (knon)
    141144    ! épaisseur (m) de la couche de diffusion thermique (microlayer)
     
    152155    ! defined for subscripts 1:knon, but we have to declare it with
    153156    ! size klon because of the coupling machinery.)
     157
    154158#ifdef ISO
    155159    REAL, DIMENSION(ntraciso,klon), INTENT(out)        :: xtevap ! isotopes in surface evaporation flux
     
    172176    real s_int(knon) ! ocean-air interface salinity, in ppt
    173177
    174     !******************************************************************************
     178    !**************************************************************************
    175179
    176180#ifdef ISO
     
    213217    ENDIF
    214218
    215 
    216219    rhoa = PS(:KNON) / (Rd * temp_air(:knon) * (1. + retv * spechum(:knon)))
    217 
    218220    !******************************************************************************
    219221    ! Switch according to type of ocean (couple, slab or forced)
     
    232234            qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    233235            tsurf_new, dflux_s, dflux_l, sens_prec_liq, sss, delta_sal, rhoa, &
    234             delta_sst)
     236            delta_sst, dTer, dSer, dt_ds)
    235237
    236238    CASE('slab')
     
    376378       delta_sst = t_int - tsurf_new(:knon)
    377379       delta_sal = s_int - sss(:knon)
    378        if (activate_ocean_skin >= 2) tsurf_new(:knon) = t_int
     380
     381       if (activate_ocean_skin == 2) then
     382          tsurf_new(:knon) = t_int
     383          if (type_ocean == 'couple') dt_ds = (tks / tkt) * dter
     384       end if
    379385    end if
    380 
     386   
    381387  END SUBROUTINE surf_ocean
    382388  !****************************************************************************
  • LMDZ6/trunk/libf/phylmdiso/wake.F90

    r4143 r4374  
    25502550    d_deltaqw, sigmaw, d_sigmaw, alpha)
    25512551  ! ------------------------------------------------------
    2552   ! Dtermination du coefficient alpha tel que les tendances
     2552  ! D\'etermination du coefficient alpha tel que les tendances
    25532553  ! corriges alpha*d_G, pour toutes les grandeurs G, correspondent
    25542554  ! a une humidite positive dans la zone (x) et dans la zone (w).
Note: See TracChangeset for help on using the changeset viewer.