Ignore:
Timestamp:
Nov 27, 2014, 4:48:31 PM (10 years ago)
Author:
jyg
Message:

1/ Splitting of the boundary layer : the climbing down and up of Pbl_surface is
split between the off-wake and wake regions ; the thermal scheme is applied
only to the off-wake region.
2/ Elimination of wake_scal and calwake_scal.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/phys_local_var_mod.F90

    r2146 r2159  
    4141      REAL, SAVE, ALLOCATABLE :: d_u_ajs(:,:), d_v_ajs(:,:)
    4242      !$OMP THREADPRIVATE(d_u_ajs, d_v_ajs)
     43!nrlmd<
     44      REAL, SAVE, ALLOCATABLE :: d_t_ajs_w(:,:), d_q_ajs_w(:,:)
     45      !$OMP THREADPRIVATE(d_t_ajs_w, d_q_ajs_w)
     46      REAL, SAVE, ALLOCATABLE :: d_t_ajs_x(:,:), d_q_ajs_x(:,:)
     47      !$OMP THREADPRIVATE(d_t_ajs_x, d_q_ajs_x)
     48!>nrlmd
    4349      REAL, SAVE, ALLOCATABLE :: d_t_eva(:,:),d_q_eva(:,:)
    4450      !$OMP THREADPRIVATE(d_t_eva,d_q_eva)
     
    5864      REAL, SAVE, ALLOCATABLE :: d_u_vdf(:,:), d_v_vdf(:,:)
    5965      !$OMP THREADPRIVATE(d_u_vdf, d_v_vdf)
     66!nrlmd+jyg<
     67      REAL, SAVE, ALLOCATABLE :: d_t_vdf_w(:,:), d_q_vdf_w(:,:)
     68      !$OMP THREADPRIVATE( d_t_vdf_w, d_q_vdf_w)
     69      REAL, SAVE, ALLOCATABLE :: d_t_vdf_x(:,:), d_q_vdf_x(:,:)
     70      !$OMP THREADPRIVATE( d_t_vdf_x, d_q_vdf_x)
     71!>nrlmd+jyg
    6072      REAL, SAVE, ALLOCATABLE :: d_t_oro(:,:)
    6173      !$OMP THREADPRIVATE(d_t_oro)
     
    216228!$OMP THREADPRIVATE(toplwad0_aerop, sollwad0_aerop)
    217229
    218 !Ajout de celles nécessaires au phys_output_write_mod
     230!Ajout de celles nécessaires au phys_output_write_mod
    219231      REAL, SAVE, ALLOCATABLE :: slp(:)
    220232!$OMP THREADPRIVATE(slp)
     
    237249      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: s_lcl, s_pblh, s_pblt, s_therm
    238250!$OMP THREADPRIVATE(s_lcl, s_pblh, s_pblt, s_therm)
     251!
     252!nrlmd+jyg<
     253      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: s_pblh_x, s_pblh_w
     254!$OMP THREADPRIVATE(s_pblh_x, s_pblh_w)
     255      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: s_lcl_x, s_lcl_w
     256!$OMP THREADPRIVATE(s_lcl_x, s_lcl_w)
     257!>nrlmd+jyg
     258!
    239259      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: slab_wfbils
    240260!$OMP THREADPRIVATE(slab_wfbils)
     
    247267      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: zxqsurf, rain_lsc
    248268!$OMP THREADPRIVATE(zxqsurf, rain_lsc)
     269!
     270!jyg+nrlmd<
     271!!!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     272!                                                                          c
     273!       Declarations liees a la couche limite differentiee w-x             c
     274!                                                                          c
     275!!!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     276      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: sens_x, sens_w
     277!$OMP THREADPRIVATE(sens_x, sens_w)
     278      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: zxfluxlat_x, zxfluxlat_w
     279!$OMP THREADPRIVATE(zxfluxlat_x, zxfluxlat_w)
     280! Entrées supplémentaires couche-limite
     281      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: t_x, t_w
     282!$OMP THREADPRIVATE(t_x, t_w)
     283      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: q_x, q_w
     284!$OMP THREADPRIVATE(q_x, q_w)
     285! Sorties ferret
     286      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: dtvdf_x, dtvdf_w
     287!$OMP THREADPRIVATE(dtvdf_x, dtvdf_w)
     288      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: dqvdf_x, dqvdf_w
     289!$OMP THREADPRIVATE(dqvdf_x, dqvdf_w)
     290      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: undi_tke, wake_tke
     291!$OMP THREADPRIVATE(undi_tke, wake_tke)
     292! Variables supplémentaires dans physiq.F relative au splitting de la surface
     293      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:,:) :: pbl_tke_input
     294!$OMP THREADPRIVATE(pbl_tke_input)
     295! Entree supplementaire Thermiques :
     296      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: t_therm, q_therm
     297!$OMP THREADPRIVATE(t_therm, q_therm)
     298      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: cdragh_x, cdragh_w
     299!$OMP THREADPRIVATE(cdragh_x, cdragh_w)
     300      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: cdragm_x, cdragm_w
     301!$OMP THREADPRIVATE(cdragm_x, cdragm_w)
     302      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: kh, kh_x, kh_w
     303!$OMP THREADPRIVATE(kh, kh_x, kh_w)
     304!!!
     305!!!ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
     306!>jyg+nrlmd
     307  !
    249308      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: wake_h, wbeff, zmax_th, zq2m, zt2m
    250309!$OMP THREADPRIVATE(wake_h, wbeff, zmax_th, zq2m, zt2m)
     
    335394      allocate(d_t_ajsb(klon,klev),d_q_ajsb(klon,klev))
    336395      allocate(d_t_ajs(klon,klev),d_q_ajs(klon,klev))
     396!nrlmd<
     397      allocate(d_t_ajs_w(klon,klev),d_q_ajs_w(klon,klev))
     398      allocate(d_t_ajs_x(klon,klev),d_q_ajs_x(klon,klev))
     399!>nrlmd
    337400      allocate(d_u_ajs(klon,klev),d_v_ajs(klon,klev))
    338401      allocate(d_t_eva(klon,klev),d_q_eva(klon,klev))
     
    341404      allocate(plul_st(klon),plul_th(klon))
    342405      allocate(d_t_vdf(klon,klev),d_q_vdf(klon,klev),d_t_diss(klon,klev))
     406!nrlmd+jyg<
     407      allocate(d_t_vdf_w(klon,klev),d_q_vdf_w(klon,klev))
     408      allocate(d_t_vdf_x(klon,klev),d_q_vdf_x(klon,klev))
     409!>nrlmd+jyg
    343410      allocate(d_u_vdf(klon,klev),d_v_vdf(klon,klev))
    344411      allocate(d_t_oli(klon,klev),d_t_oro(klon,klev))
     
    380447      allocate(lcc3dcon(klon, klev))
    381448      allocate(lcc3dstra(klon, klev))
    382       allocate(od550aer(klon))   
    383       allocate(od865aer(klon))   
    384       allocate(absvisaer(klon)) 
     449      allocate(od550aer(klon))
     450      allocate(od865aer(klon))
     451      allocate(absvisaer(klon))
    385452      allocate(ec550aer(klon,klev))
    386       allocate(od550lt1aer(klon))               
     453      allocate(od550lt1aer(klon))
    387454      allocate(sconcso4(klon))
    388455      allocate(sconcno3(klon))
     
    423490      ALLOCATE(toplwad0_aerop(klon), sollwad0_aerop(klon))
    424491
    425 ! FH Ajout de celles nécessaires au phys_output_write_mod
     492! FH Ajout de celles nécessaires au phys_output_write_mod
    426493
    427494      ALLOCATE(slp(klon))
     
    435502      ALLOCATE(s_lcl(klon))
    436503      ALLOCATE(s_pblh(klon), s_pblt(klon), s_therm(klon))
     504!
     505!nrlmd+jyg<
     506      ALLOCATE(s_pblh_x(klon), s_pblh_w(klon))
     507      ALLOCATE(s_lcl_x(klon), s_lcl_w(klon))
     508!>nrlmd+jyg
     509!
    437510      ALLOCATE(slab_wfbils(klon), tpot(klon), tpote(klon), ue(klon))
    438511      ALLOCATE(uq(klon), ve(klon), vq(klon), zxffonte(klon))
    439512      ALLOCATE(zxfqcalving(klon), zxfluxlat(klon), zxrugs(klon))
    440513      ALLOCATE(zxtsol(klon), snow_lsc(klon), zxfqfonte(klon), zxqsurf(klon))
    441       ALLOCATE(rain_lsc(klon), wake_h(klon), wbeff(klon), zmax_th(klon))
     514      ALLOCATE(rain_lsc(klon))
     515!
     516      ALLOCATE(sens_x(klon), sens_w(klon))
     517      ALLOCATE(zxfluxlat_x(klon), zxfluxlat_w(klon))
     518      ALLOCATE(t_x(klon,klev), t_w(klon,klev))
     519      ALLOCATE(q_x(klon,klev), q_w(klon,klev))
     520      ALLOCATE(dtvdf_x(klon,klev), dtvdf_w(klon,klev))
     521      ALLOCATE(dqvdf_x(klon,klev), dqvdf_w(klon,klev))
     522      ALLOCATE(undi_tke(klon,klev), wake_tke(klon,klev))
     523      ALLOCATE(pbl_tke_input(klon,klev+1,nbsrf))
     524      ALLOCATE(t_therm(klon,klev), q_therm(klon,klev))
     525      ALLOCATE(cdragh_x(klon), cdragh_w(klon))
     526      ALLOCATE(cdragm_x(klon), cdragm_w(klon))
     527      ALLOCATE(kh(klon), kh_x(klon), kh_w(klon))
     528!
     529      ALLOCATE(wake_h(klon), wbeff(klon), zmax_th(klon))
    442530      ALLOCATE(zq2m(klon), zt2m(klon), weak_inversion(klon))
    443531      ALLOCATE(zt2m_min_mon(klon), zt2m_max_mon(klon))
     
    510598      deallocate(d_t_ajsb,d_q_ajsb)
    511599      deallocate(d_t_ajs,d_q_ajs)
     600!nrlmd<
     601      deallocate(d_t_ajs_w,d_q_ajs_w)
     602      deallocate(d_t_ajs_x,d_q_ajs_x)
     603!>nrlmd
    512604      deallocate(d_u_ajs,d_v_ajs)
    513605      deallocate(d_t_eva,d_q_eva)
     
    516608      deallocate(plul_st,plul_th)
    517609      deallocate(d_t_vdf,d_q_vdf,d_t_diss)
     610!nrlmd+jyg<
     611      deallocate(d_t_vdf_w,d_q_vdf_w)
     612      deallocate(d_t_vdf_x,d_q_vdf_x)
     613!>nrlmd+jyg
    518614      deallocate(d_u_vdf,d_v_vdf)
    519615      deallocate(d_t_oli,d_t_oro)
     
    546642      deallocate(lcc3dcon)
    547643      deallocate(lcc3dstra)
    548       deallocate(od550aer)       
     644      deallocate(od550aer)
    549645      deallocate(od865aer)
    550646      deallocate(absvisaer)
     
    591687      deallocate(toplwad0_aerop, sollwad0_aerop)
    592688
    593 ! FH Ajout de celles nécessaires au phys_output_write_mod
     689! FH Ajout de celles nécessaires au phys_output_write_mod
    594690      DEALLOCATE(slp)
    595691      DEALLOCATE(ale_wake, alp_wake, bils)
     
    600696      DEALLOCATE(prw, zustar, zu10m, zv10m, rh2m, s_lcl)
    601697      DEALLOCATE(s_pblh, s_pblt, s_therm)
     698!
     699!nrlmd+jyg<
     700      DEALLOCATE(s_pblh_x, s_pblh_w)
     701      DEALLOCATE(s_lcl_x, s_lcl_w)
     702!>nrlmd+jyg
     703!
    602704      DEALLOCATE(slab_wfbils, tpot, tpote, ue)
    603705      DEALLOCATE(uq, ve, vq, zxffonte)
    604706      DEALLOCATE(zxfqcalving, zxfluxlat, zxrugs)
    605707      DEALLOCATE(zxtsol, snow_lsc, zxfqfonte, zxqsurf)
    606       DEALLOCATE(rain_lsc, wake_h, wbeff, zmax_th)
     708      DEALLOCATE(rain_lsc)
     709!
     710      DEALLOCATE(sens_x, sens_w)
     711      DEALLOCATE(zxfluxlat_x, zxfluxlat_w)
     712      DEALLOCATE(t_x, t_w)
     713      DEALLOCATE(q_x, q_w)
     714      DEALLOCATE(dtvdf_x, dtvdf_w)
     715      DEALLOCATE(dqvdf_x, dqvdf_w)
     716      DEALLOCATE(undi_tke, wake_tke)
     717      DEALLOCATE(pbl_tke_input)
     718      DEALLOCATE(t_therm, q_therm)
     719      DEALLOCATE(cdragh_x, cdragh_w)
     720      DEALLOCATE(cdragm_x, cdragm_w)
     721      DEALLOCATE(kh, kh_x, kh_w)
     722!
     723      DEALLOCATE(wake_h, wbeff, zmax_th)
    607724      DEALLOCATE(zq2m, zt2m, weak_inversion)
    608725      DEALLOCATE(zt2m_min_mon, zt2m_max_mon)
Note: See TracChangeset for help on using the changeset viewer.