Changeset 1816


Ignore:
Timestamp:
Jul 25, 2013, 10:33:44 AM (11 years ago)
Author:
idelkadi
Message:

Inclusion of the convective scale velocity w* for tracers
Concerns : hbtm.F, pbl_surface_mod.F90,
physiq.F, phys_output_ctrlout_mod.F90, phys_output_write_mod.F90

Location:
LMDZ5/trunk/libf/phylmd
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/hbtm.F

    r1279 r1816  
    44
    55      SUBROUTINE HBTM(knon, paprs, pplay,
    6      .                t2m,t10m,q2m,q10m,ustar,
     6     .                t2m,t10m,q2m,q10m,ustar,wstar,
    77     .                flux_t,flux_q,u,v,t,q,
    88     .                pblh,cape,EauLiq,ctei,pblT,
     
    5454      REAL q2m(klon), q10m(klon) ! q a 2 et 10m
    5555      REAL ustar(klon)
     56      REAL wstar(klon)       ! w*, convective velocity scale
    5657      REAL paprs(klon,klev+1) ! pression a inter-couche (Pa)
    5758      REAL pplay(klon,klev)   ! pression au milieu de couche (Pa)
     
    158159      REAL fak1(klon)       ! k*ustar*pblh
    159160      REAL fak2(klon)       ! k*wm*pblh
    160       REAL fak3(klon)       ! fakn*wstr/wm
     161      REAL fak3(klon)       ! fakn*wstar/wm
    161162      REAL pblk(klon)       ! level eddy diffusivity for momentum
    162163      REAL pr(klon)         ! Prandtl number for eddy diffusivities
     
    164165      REAL zh(klon)         ! zmzp / pblh
    165166      REAL zzh(klon)        ! (1-(zmzp/pblh))**2
    166       REAL wstr(klon)       ! w*, convective velocity scale
    167167      REAL zm(klon)         ! current level height
    168168      REAL zp(klon)         ! current level height + one level up
     
    625625          wm(i)      = ustar(i)*phiminv(i)
    626626          fak2(i)    = wm(i)*pblh(i)*vk
    627           wstr(i)    = (heatv(i)*RG*pblh(i)/zxt)**onet
    628           fak3(i)    = fakn*wstr(i)/wm(i)
     627          wstar(i)    = (heatv(i)*RG*pblh(i)/zxt)**onet
     628          fak3(i)    = fakn*wstar(i)/wm(i)
    629629        ENDIF
    630630c Computes Theta_e for thermal (all cases : to be modified)
  • LMDZ5/trunk/libf/phylmd/pbl_surface_mod.F90

    r1787 r1816  
    174174       t,         q,         u,        v,             &
    175175       pplay,     paprs,     pctsrf,                  &
    176        ts,        alb1,      alb2,ustar, u10m, v10m, &
     176       ts,        alb1, alb2,ustar, u10m, v10m,wstar, &
    177177       lwdown_m,  cdragh,    cdragm,   zu1,    zv1,   &
    178178       alb1_m,    alb2_m,    zxsens,   zxevap,        &
     
    294294    REAL, DIMENSION(klon, nbsrf), INTENT(INOUT)     :: alb2    ! albedo in near infra-red SW interval
    295295    REAL, DIMENSION(klon, nbsrf), INTENT(INOUT)     :: ustar   ! u* (m/s)
     296    REAL, DIMENSION(klon, nbsrf+1), INTENT(INOUT)   :: wstar   ! w* (m/s)
    296297    REAL, DIMENSION(klon, nbsrf), INTENT(INOUT)     :: u10m    ! u speed at 10m
    297298    REAL, DIMENSION(klon, nbsrf), INTENT(INOUT)     :: v10m    ! v speed at 10m
     
    406407    REAL, DIMENSION(klon)              :: yt2m, yq2m, yu10m
    407408    REAL, DIMENSION(klon)              :: yustar
     409    REAL, DIMENSION(klon)              :: ywstar
    408410    REAL, DIMENSION(klon)              :: ywindsp
    409411    REAL, DIMENSION(klon)              :: yt10m, yq10m
     
    10651067       q2m(:,nsrf)    = 0.
    10661068       ustar(:,nsrf)   = 0.
     1069       wstar(:,nsrf)   = 0.
    10671070       u10m(:,nsrf)   = 0.
    10681071       v10m(:,nsrf)   = 0.
     
    11451148
    11461149!   print*,'OK pbl 5'
    1147        CALL HBTM(knon, ypaprs, ypplay, &
    1148             yt2m,yt10m,yq2m,yq10m,yustar, &
     1150       CALL hbtm(knon, ypaprs, ypplay, &
     1151            yt2m,yt10m,yq2m,yq10m,yustar,ywstar, &
    11491152            y_flux_t,y_flux_q,yu,yv,yt,yq, &
    11501153            ypblh,ycapCL,yoliqCL,ycteiCL,ypblT, &
     
    11541157          i = ni(j)
    11551158          pblh(i,nsrf)   = ypblh(j)
     1159          wstar(i,nsrf)  = ywstar(j)
    11561160          plcl(i,nsrf)   = ylcl(j)
    11571161          capCL(i,nsrf)  = ycapCL(j)
     
    12151219    s_therm(:) = 0.0 ; s_trmb1(:) = 0.0
    12161220    s_trmb2(:) = 0.0 ; s_trmb3(:) = 0.0
     1221    wstar(:,is_ave)=0.
    12171222   
    12181223!   print*,'OK pbl 9'
     
    12331238          zq2m(i)  = zq2m(i)  + q2m(i,nsrf)  * pctsrf(i,nsrf)
    12341239          zustar(i) = zustar(i) + ustar(i,nsrf) * pctsrf(i,nsrf)
     1240          wstar(i,is_ave)=wstar(i,is_ave)+wstar(i,nsrf)*pctsrf(i,nsrf)
    12351241          zu10m(i) = zu10m(i) + u10m(i,nsrf) * pctsrf(i,nsrf)
    12361242          zv10m(i) = zv10m(i) + v10m(i,nsrf) * pctsrf(i,nsrf)
  • LMDZ5/trunk/libf/phylmd/phys_output_ctrlout_mod.F90

    r1813 r1816  
    9393      ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_sic', &
    9494      "Friction velocity "//clnsurf(4),"m/s", (/ ('', i=1, 6) /)) /)
     95
     96  TYPE(ctrl_out), SAVE, DIMENSION(5) :: o_wstar         = (/ &
     97      ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'wstar_ter', &
     98      "Friction velocity "//clnsurf(1),"m/s", (/ ('', i=1, 6) /)), &
     99      ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'wstar_lic', &
     100      "Friction velocity "//clnsurf(2),"m/s", (/ ('', i=1, 6) /)), &
     101      ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'wstar_oce', &
     102      "Friction velocity "//clnsurf(3),"m/s", (/ ('', i=1, 6) /)), &
     103      ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'wstar_sic', &
     104      "Friction velocity "//clnsurf(4),"m/s", (/ ('', i=1, 6) /)), &
     105      ctrl_out((/ 5, 5, 10, 10, 10, 10 /),'wstar', &
     106      "w* convective velocity "//clnsurf(4),"m/s", (/ ('', i=1, 6) /)) /)
    95107
    96108  TYPE(ctrl_out), SAVE, DIMENSION(4) :: o_u10m_srf     = (/ &
  • LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90

    r1813 r1816  
    319319
    320320      ENDDO
     321      DO nsrf=1,nbsrf+1
     322         CALL histwrite_phy(o_wstar(nsrf), wstar(1 : klon, nsrf))
     323      ENDDO
     324
    321325      CALL histwrite_phy(o_cdrm, cdragm)
    322326      CALL histwrite_phy(o_cdrh, cdragh)
  • LMDZ5/trunk/libf/phylmd/physiq.F

    r1813 r1816  
    19991999     e     t_seri,    q_seri,    u_seri,  v_seri,   
    20002000     e     pplay,     paprs,     pctsrf,           
    2001      +     ftsol,     falb1,     falb2,   ustar, u10m,   v10m,
     2001     +     ftsol,falb1,falb2,ustar,u10m,v10m,wstar,
    20022002     s     sollwdown, cdragh,    cdragm,  u1,    v1,
    20032003     s     albsol1,   albsol2,   sens,    evap, 
     
    36403640       END IF
    36413641
    3642       wstar=0. ! FH 2013/07/22 a corriger des que dans pbl_surface_mod
    36433642      call phytrac (
    36443643     I     itap,     days_elapsed+1,    jH_cur,   debut,
Note: See TracChangeset for help on using the changeset viewer.