Changeset 3962 for LMDZ6/trunk/libf


Ignore:
Timestamp:
Jul 18, 2021, 11:33:55 AM (3 years ago)
Author:
crisi
Message:

fix de isotopic test. Update in pbl_surface_mod.F90 to add the new arguments defined in wx_pbl_var_mod in a recent comission by Jean-Yves

File:
1 edited

Legend:

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

    r3940 r3962  
    11!
    2 ! $Id: pbl_surface_mod.F90 3906 2021-05-19 10:35:18Z jyg $
     2! $Id: pbl_surface_mod.F90 3956 2021-07-06 07:16:14Z jyg $
    33!
    44MODULE pbl_surface_mod
     
    805805    REAL, DIMENSION(klon, klev)        :: zxfluxu_x, zxfluxv_x, zxfluxu_w, zxfluxv_w
    806806    REAL                               :: zx_qs_surf, zcor_surf, zdelta_surf
    807     REAL, DIMENSION(klon)              :: ytsurf_th, yqsatsurf
    808807!jyg<
    809808    REAL, DIMENSION(klon)              :: ybeta
     
    969968    REAL, PARAMETER                    :: facteur=2./sqrt(3.14)
    970969    REAL, PARAMETER                    :: inertia=2000.
    971     REAL, DIMENSION(klon)              :: ytsurf_th_x,ytsurf_th_w,yqsatsurf_x,yqsatsurf_w
    972970    REAL, DIMENSION(klon)              :: ydtsurf_th
    973971    REAL                               :: zdelta_surf_x,zdelta_surf_w,zx_qs_surf_x,zx_qs_surf_w
     
    10511049!!jyg      iflag_split = mod(iflag_pbl_split,2)
    10521050!!jyg      iflag_split = mod(iflag_pbl_split,10)
     1051!
     1052! Flags controlling the splitting of the turbulent boundary layer:
     1053!   iflag_split_ref = 0  ==> no splitting
     1054!                   = 1  ==> splitting without coupling with surface temperature
     1055!                   = 2  ==> splitting with coupling with surface temperature over land
     1056!                   = 3  ==> splitting over ocean; no splitting over land
     1057!   iflag_split: actual flag controlling the splitting.
     1058!   iflag_split = iflag_split_ref outside the sub-surface loop
     1059!               = iflag_split_ref if iflag_split_ref = 0, 1, or 2
     1060!               = 0 over land  if iflga_split_ref = 3
     1061!               = 1 over ocean if iflga_split_ref = 3
     1062
    10531063      iflag_split_ref = mod(iflag_pbl_split,10)
     1064      iflag_split = iflag_split_ref
    10541065
    10551066#ifdef ISO     
     
    12431254!!! jyg le 10/02/2012
    12441255    rh2m_x(:) = 0. ; qsat2m_x(:) = 0. ; rh2m_w(:) = 0. ; qsat2m_w(:) = 0.
    1245 !!!
    12461256
    12471257! 2b) Initialization of all local variables that will be compressed later
     
    18131823!****************************************************************************************
    18141824
     1825
    18151826!!! jyg le 07/02/2012
    18161827       IF (iflag_split .eq.0) THEN
     
    21952206                         AcoefU_x, AcoefU_w, AcoefV_x, AcoefV_w, &
    21962207                         BcoefH_x, BcoefH_w, BcoefQ_x, BcoefQ_w, &
    2197                          BcoefU_x, BcoefU_w, BcoefV_x, BcoefV_w  &
     2208                         BcoefU_x, BcoefU_w, BcoefV_x, BcoefV_w, &
     2209                         Kech_h_x, Kech_h_w, Kech_h  &
    21982210                         )
    21992211         CALL wx_pbl_prelim_beta(knon, dtime, ywake_s, ybeta,  &
     
    27982810         print*,'Chx,Chw,Ch', ycdragh_x(j), ycdragh_w(j), ycdragh(j)
    27992811         print*,'Khx,Khw,Kh', Kech_h_x(j), Kech_h_w(j), Kech_h(j)
    2800 !         print*,'tsurf_x,tsurf_w,tsurf,t1', ytsurf_th_x(j), ytsurf_th_w(j), ytsurf_th(j), yt(j,1)
    2801          print*,'tsurf_x,t1x,tsurf_w,t1w,tsurf,t1,t1_ancien', &
    2802  &               ytsurf_th_x(j), yt_x(j,1), ytsurf_th_w(j), yt_w(j,1), ytsurf_th(j), yt(j,1),t(j,1)
    2803          print*,'qsatsurf,qsatsurf_x,qsatsurf_w', yqsatsurf(j), yqsatsurf_x(j), yqsatsurf_w(j)
     2812         print*,'t1x, t1w, t1, t1_ancien', &
     2813 &               yt_x(j,1), yt_w(j,1),  yt(j,1), t(j,1)
    28042814         print*,'delta_coef,delta_flux,delta_tsurf,tau', delta_coef(j), y_delta_flux_t1(j), y_delta_tsurf(j), tau_eq(j)
    28052815        ENDDO
     
    28082818         print*,'fluxT_x, fluxT_w, y_flux_t1, fluxQ_x, fluxQ_w, yfluxlat, wakes' &
    28092819 &             , y_flux_t1_x(j), y_flux_t1_w(j), y_flux_t1(j), y_flux_q1_x(j)*RLVTT, y_flux_q1_w(j)*RLVTT, yfluxlat(j), ywake_s(j)
    2810          print*,'beta,ytsurf_new,yqsatsurf', ybeta(j), ytsurf_new(j), yqsatsurf(j)
    2811          print*,'inertia,facteur,cstar', inertia, facteur,wake_cstar(j)
     2820         print*,'beta, ytsurf_new ', ybeta(j), ytsurf_new(j)
     2821         print*,'inertia, facteur, cstar', inertia, facteur,wake_cstar(j)
    28122822        ENDDO
    28132823       ENDIF  ! (prt_level >=10)
     
    37273737!****************************************************************************************
    37283738    ENDDO loop_nbsrf
     3739!
     3740!----------------------------------------------------------------------------------------
     3741!   Reset iflag_split
     3742!
     3743   iflag_split=iflag_split_ref
    37293744
    37303745#ifdef ISO
Note: See TracChangeset for help on using the changeset viewer.