Changeset 3489


Ignore:
Timestamp:
Apr 26, 2019, 5:50:39 PM (5 years ago)
Author:
musat
Message:

Ajout bornage a 2m

Location:
LMDZ6/trunk/libf/phylmd
Files:
1 added
3 edited

Legend:

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

    r3439 r3489  
    380380      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: t2m_min_mon, t2m_max_mon
    381381!$OMP THREADPRIVATE(t2m_min_mon, t2m_max_mon)
     382      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: zq2m_cor, zt2m_cor
     383!$OMP THREADPRIVATE(zq2m_cor, zt2m_cor)
     384      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: zu10m_cor, zv10m_cor
     385!$OMP THREADPRIVATE(zu10m_cor, zv10m_cor)
     386      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: zrh2m_cor, zqsat2m_cor
     387!$OMP THREADPRIVATE(zrh2m_cor, zqsat2m_cor)
    382388      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: weak_inversion
    383389!$OMP THREADPRIVATE(weak_inversion)
     
    752758      ALLOCATE(zt2m_min_mon(klon), zt2m_max_mon(klon))
    753759      ALLOCATE(t2m_min_mon(klon), t2m_max_mon(klon))
     760      ALLOCATE(zq2m_cor(klon), zt2m_cor(klon), zu10m_cor(klon), zv10m_cor(klon))
     761      ALLOCATE(zrh2m_cor(klon), zqsat2m_cor(klon))
    754762      ALLOCATE(sens(klon), flwp(klon), fiwp(klon))
    755763      ALLOCATE(alp_bl_conv(klon), alp_bl_det(klon))
     
    10461054      DEALLOCATE(zt2m_min_mon, zt2m_max_mon)
    10471055      DEALLOCATE(t2m_min_mon, t2m_max_mon)
     1056      DEALLOCATE(zq2m_cor, zt2m_cor, zu10m_cor, zv10m_cor)
     1057      DEALLOCATE(zrh2m_cor, zqsat2m_cor)
    10481058      DEALLOCATE(sens, flwp, fiwp)
    10491059      DEALLOCATE(alp_bl_conv,alp_bl_det)
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r3480 r3489  
    249249
    250250    USE phys_local_var_mod, ONLY: zxfluxlat, slp, ptstar, pt0, zxtsol, zt2m, &
     251         zt2m_cor,zq2m_cor,zu10m_cor,zv10m_cor, zrh2m_cor, zqsat2m_cor, &
    251252         t2m_min_mon, t2m_max_mon, evap, &
    252253         l_mixmin,l_mix, &
     
    665666       CALL histwrite_phy(o_slp, slp)
    666667       CALL histwrite_phy(o_tsol, zxtsol)
    667        CALL histwrite_phy(o_t2m, zt2m)
    668        CALL histwrite_phy(o_t2m_min, zt2m)
    669        CALL histwrite_phy(o_t2m_max, zt2m)
     668       CALL histwrite_phy(o_t2m, zt2m_cor)
     669       CALL histwrite_phy(o_t2m_min, zt2m_cor)
     670       CALL histwrite_phy(o_t2m_max, zt2m_cor)
    670671       CALL histwrite_phy(o_t2m_max_mon, t2m_max_mon)
    671672       CALL histwrite_phy(o_t2m_min_mon, t2m_min_mon)
     
    673674       IF (vars_defined) THEN
    674675          DO i=1, klon
    675              zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
     676             zx_tmp_fi2d(i)=SQRT(zu10m_cor(i)*zu10m_cor(i)+zv10m_cor(i)*zv10m_cor(i))
    676677          ENDDO
    677678       ENDIF
     
    680681       IF (vars_defined) THEN
    681682          DO i=1, klon
    682              zx_tmp_fi2d(i)=SQRT(zu10m(i)*zu10m(i)+zv10m(i)*zv10m(i))
     683             zx_tmp_fi2d(i)=SQRT(zu10m_cor(i)*zu10m_cor(i)+zv10m_cor(i)*zv10m_cor(i))
    683684          ENDDO
    684685       ENDIF
     
    693694       ENDIF
    694695       CALL histwrite_phy(o_sicf, zx_tmp_fi2d)
    695        CALL histwrite_phy(o_q2m, zq2m)
     696       CALL histwrite_phy(o_q2m, zq2m_cor)
    696697       CALL histwrite_phy(o_ustar, zustar)
    697        CALL histwrite_phy(o_u10m, zu10m)
    698        CALL histwrite_phy(o_v10m, zv10m)
     698       CALL histwrite_phy(o_u10m, zu10m_cor)
     699       CALL histwrite_phy(o_v10m, zv10m_cor)
    699700
    700701       IF (vars_defined) THEN
     
    13301331!       CALL histwrite_phy(o_rh2m_max, zx_tmp_fi2d)
    13311332
    1332        CALL histwrite_phy(o_qsat2m, qsat2m)
     1333       CALL histwrite_phy(o_qsat2m, zqsat2m_cor)
    13331334       CALL histwrite_phy(o_tpot, tpot)
    13341335       CALL histwrite_phy(o_tpote, tpote)
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r3480 r3489  
    117117       zustar, zu10m, zv10m, rh2m, qsat2m, &
    118118       zq2m, zt2m, weak_inversion, &
     119       zq2m_cor,zt2m_cor,zu10m_cor,zv10m_cor, & ! pour corriger d'un bug
     120       zrh2m_cor,zqsat2m_cor, &
    119121       zt2m_min_mon, zt2m_max_mon,   &         ! pour calcul_divers.h
    120122       t2m_min_mon, t2m_max_mon,  &            ! pour calcul_divers.h
     
    593595                                                        ! gust-front in the grid cell.
    594596    !$OMP THREADPRIVATE(iflag_alp_wk_cond)
     597
     598    INTEGER,  SAVE               :: iflag_bug_t2m_ipslcm61=0 !
     599    !$OMP THREADPRIVATE(iflag_bug_t2m_ipslcm61)
     600    INTEGER,  SAVE               :: iflag_bug_t2m_stab_ipslcm61=1 !
     601    !$OMP THREADPRIVATE(iflag_bug_t2m_stab_ipslcm61)
     602
    595603    REAL t_w(klon,klev),q_w(klon,klev) ! temperature and moisture profiles in the wake region
    596604    REAL t_x(klon,klev),q_x(klon,klev) ! temperature and moisture profiles in the off-wake region
     
    12951303       tau_gl=86400.*tau_gl
    12961304       WRITE(lunout,*) 'debut physiq_mod tau_gl=',tau_gl
     1305
     1306       iflag_bug_t2m_ipslcm61 = 0
     1307       CALL getin_p('iflag_bug_t2m_ipslcm61', iflag_bug_t2m_ipslcm61)
     1308       iflag_bug_t2m_stab_ipslcm61 = 0
     1309       CALL getin_p('iflag_bug_t2m_stab_ipslcm61', iflag_bug_t2m_stab_ipslcm61)
    12971310
    12981311       CALL getin_p('iflag_alp_wk_cond', iflag_alp_wk_cond)
     
    24582471       ENDIF
    24592472
     2473!add limitation for t,q at and wind at 10m
     2474        if ( iflag_bug_t2m_ipslcm61 == 0 ) THEN
     2475          CALL borne_var_surf( klon,klev,nbsrf,                 &
     2476            iflag_bug_t2m_stab_ipslcm61,                        &
     2477            t_seri(:,1),q_seri(:,1),u_seri(:,1),v_seri(:,1),    &
     2478            ftsol,zxqsurf,pctsrf,paprs,                         &
     2479            t2m, q2m, u10m, v10m,                               &
     2480            zt2m_cor, zq2m_cor, zu10m_cor, zv10m_cor,           &
     2481            zrh2m_cor, zqsat2m_cor)
     2482        ELSE
     2483          zt2m_cor(:)=zt2m(:)
     2484          zq2m_cor(:)=zq2m(:)
     2485          zu10m_cor(:)=zu10m(:)
     2486          zv10m_cor(:)=zv10m(:)
     2487        ENDIF
    24602488
    24612489       !---------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.