Ignore:
Timestamp:
Jul 5, 2024, 4:38:48 PM (2 months ago)
Author:
Sebastien Nguyen
Message:

include ISO keys in pbl_surface and associated routines in phylmd

File:
1 edited

Legend:

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

    r4526 r5022  
    2121       tsurf_new, dflux_s, dflux_l, lmt_bils, &
    2222       flux_u1, flux_v1, delta_sst, delta_sal, ds_ns, dt_ns, dter, dser, &
    23        dt_ds, tkt, tks, taur, sss)
     23       dt_ds, tkt, tks, taur, sss &
     24#ifdef ISO
     25        &       ,xtprecip_rain, xtprecip_snow,xtspechum,Roce, &
     26        &       xtsnow,xtevap,h1 &
     27#endif               
     28        &       )
    2429
    2530    use albedo, only: alboc, alboc_cd
     
    3136    USE ocean_cpl_mod, ONLY    : ocean_cpl_noice
    3237    USE indice_sol_mod, ONLY : nbsrf, is_oce
     38#ifdef ISO
     39    USE infotrac_phy, ONLY : ntraciso=>ntiso,niso
     40#ifdef ISOVERIF
     41    USE isotopes_mod, ONLY: iso_eau,ridicule
     42    USE isotopes_verif_mod
     43#endif
     44#endif
    3345    USE limit_read_mod
    34     use config_ocean_skin_m, only: activate_ocean_skin
     46    USE config_ocean_skin_m, ONLY: activate_ocean_skin
    3547    !
    3648    ! This subroutine will make a call to ocean_XXX_noice according to the ocean mode (force,
     
    6880    REAL, DIMENSION(klon), INTENT(IN)        :: rugoro
    6981    REAL, DIMENSION(klon,nbsrf), INTENT(IN)  :: pctsrf
     82#ifdef ISO
     83    REAL, DIMENSION(ntraciso,klon), INTENT(IN) :: xtprecip_rain, xtprecip_snow
     84    REAL, DIMENSION(ntraciso,klon), INTENT(IN) :: xtspechum
     85#endif
    7086
    7187    ! In/Output variables
     
    7591    REAL, DIMENSION(klon), INTENT(INOUT)     :: agesno
    7692    REAL, DIMENSION(klon), INTENT(inOUT)     :: z0h
     93#ifdef ISO
     94    REAL, DIMENSION(niso,klon), INTENT(IN)   :: xtsnow
     95    REAL, DIMENSION(niso,klon), INTENT(INOUT):: Roce 
     96#endif
    7797
    7898    REAL, intent(inout):: delta_sst(:) ! (knon)
     
    136156    ! size klon because of the coupling machinery.)
    137157
     158#ifdef ISO
     159    REAL, DIMENSION(ntraciso,klon), INTENT(out) :: xtevap ! isotopes in surface evaporation flux
     160    REAL, DIMENSION(klon), INTENT(out)          :: h1 ! just a diagnostic, not useful for the simulation   
     161#endif
     162
    138163    ! Local variables
    139164    !*************************************************************************
     
    146171    REAL, DIMENSION(klon) :: precip_totsnow
    147172    CHARACTER(len=20),PARAMETER :: modname="surf_ocean"
    148     real rhoa(knon) ! density of moist air  (kg / m3)
     173    REAL rhoa(knon) ! density of moist air  (kg / m3)
    149174    REAL sens_prec_liq(knon)
    150175
    151176    REAL t_int(knon) ! ocean-air interface temperature, in K
    152     real s_int(knon) ! ocean-air interface salinity, in ppt
     177    REAL s_int(knon) ! ocean-air interface salinity, in ppt
    153178
    154179    !**************************************************************************
    155180
     181#ifdef ISO
     182#ifdef ISOVERIF
     183    DO i = 1, knon
     184      IF (iso_eau > 0) THEN         
     185        CALL iso_verif_egalite_choix(xtspechum(iso_eau,i), &
     186     &          spechum(i),'surf_ocean_mod 117', &
     187     &          errmax,errmaxrel)         
     188        CALL iso_verif_egalite_choix(xtsnow(iso_eau,i), &
     189     &          snow(i),'surf_ocean_mod 127', &
     190     &          errmax,errmaxrel)
     191      ENDIF !IF (iso_eau > 0) then
     192    ENDDO !DO i=1,klon
     193#endif     
     194#endif
    156195
    157196    !******************************************************************************
     
    230269            radsol, snow, agesno, &
    231270            qsurf, evap, fluxsens, fluxlat, flux_u1, flux_v1, &
    232             tsurf_new, dflux_s, dflux_l, sens_prec_liq, rhoa)
     271            tsurf_new, dflux_s, dflux_l, sens_prec_liq, rhoa &
     272#ifdef ISO
     273            ,xtprecip_rain, xtprecip_snow, xtspechum,Roce,rlat, &
     274            xtsnow,xtevap,h1 & 
     275#endif           
     276            )
    233277    END SELECT
    234278
Note: See TracChangeset for help on using the changeset viewer.