Changeset 2907 for LMDZ5/branches


Ignore:
Timestamp:
Jun 9, 2017, 4:56:43 PM (7 years ago)
Author:
acozic
Message:

Add some modification to fit with recent version of model Inca

Location:
LMDZ5/branches/IPSLCM5A2.1/libf/phylmd
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/phys_output_mod.F90

    r2551 r2907  
    4646    USE mod_grid_phy_lmdz, only: klon_glo,nbp_lon,nbp_lat
    4747    USE print_control_mod, ONLY: prt_level,lunout
    48     USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs
     48    USE vertical_layers_mod, ONLY: ap,bp,preff,presnivs, Ahyb, Bhyb
    4949    USE time_phylmdz_mod, ONLY: day_ini, itau_phy, start_time, annee_ref, day_ref
    5050#ifdef CPP_XIOS
     
    9595    INTEGER                               :: idayref
    9696    REAL                                  :: zjulian_start, zjulian
    97     REAL, DIMENSION(klev)                 :: Ahyb, Bhyb, Alt
     97    REAL, DIMENSION(klev)                 :: Alt
    9898    CHARACTER(LEN=4), DIMENSION(nlevSTD)  :: clevSTD
    9999    REAL, DIMENSION(nlevSTD)              :: rlevSTD
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/physiq_mod.F90

    r2618 r2907  
    223223    use FLOTT_GWD_rando_m, only: FLOTT_GWD_rando
    224224    use ACAMA_GWD_rando_m, only: ACAMA_GWD_rando
    225 
     225    USE vertical_layers_mod, only : Ahyb, Bhyb
    226226    IMPLICIT none
    227227    !>======================================================================
     
    10761076    INTEGER :: nbtr_tmp ! Number of tracer inside concvl
    10771077    REAL, dimension(klon,klev) :: sh_in ! Specific humidity entering in phytrac
     1078    REAL, dimension(klon,klev) :: ch_in ! Condensed humidity entering in phytrac (eau liquide)
    10781079    integer iostat
    10791080
     
    15841585               start_time, &
    15851586               itau_phy, &
     1587               date0, &
    15861588               io_lon, &
    15871589               io_lat)
     
    37543756               (kdlon,kflev,dist, rmu0, fract, solaire, &
    37553757               paprs, pplay,zxtsol,albsol1, albsol2, t_seri,q_seri, &
    3756                wo(:, :, 1), &
     3758               size(wo,3), wo(:, :, 1), &
    37573759               cldfrarad, cldemirad, cldtaurad, &
    37583760               heat,heat0,cool,cool0,albpla, &
     
    42624264    ELSE
    42634265       sh_in(:,:) = qx(:,:,ivap)
     4266       ch_in(:,:) = qx(:,:,iliq)
    42644267    END IF
    42654268
     
    42764279         frac_impa,frac_nucl, beta_prec_fisrt,beta_prec, &
    42774280         presnivs, pphis,     pphi,     albsol1, &
    4278          sh_in,    rhcl,      cldfra,   rneb, &
     4281         sh_in,    ch_in,  rhcl,      cldfra,   rneb, &
    42794282         diafra,   cldliq,    itop_con, ibas_con, &
    42804283         pmflxr,   pmflxs,    prfl,     psfl, &
     
    44134416            pphi, &
    44144417            pphis, &
    4415             zx_rh)
     4418            zx_rh, &
     4419            Ahyb, Bhyb)
    44164420
    44174421       CALL VTe(VTinca)
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/phytrac_mod.F90

    r2394 r2907  
    6666       frac_impa,frac_nucl,beta_fisrt,beta_v1,        &
    6767       presnivs,  pphis,    pphi,     albsol,         &
    68        sh,        rh,       cldfra,   rneb,           &
     68       sh,        ch, rh,       cldfra,   rneb,           &
    6969       diafra,    cldliq,   itop_con, ibas_con,       &
    7070       pmflxr,    pmflxs,   prfl,     psfl,           &
     
    131131    REAL,DIMENSION(klon,klev),INTENT(IN)   :: sh      ! humidite specifique
    132132    REAL,DIMENSION(klon,klev),INTENT(IN)   :: rh      ! humidite relative
     133    REAL,DIMENSION(klon,klev),INTENT(IN)   :: ch      ! eau liquide
    133134    REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour chaque inter-couche (en Pa)
    134135    REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
     
    575576            pdtphys,  t_seri,   paprs,          pplay,     &
    576577            pmfu,     upwd,     ftsol,  pctsrf, pphis,     &
    577             pphi,     albsol,   sh,             rh,        &
     578            pphi,     albsol,   sh,             ch, rh,        &
    578579            cldfra,   rneb,     diafra,         cldliq,    &
    579580            itop_con, ibas_con, pmflxr,         pmflxs,    &
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/tracinca_mod.F90

    r2609 r2907  
    3636       pdtphys,  t_seri,   paprs,          pplay,     &
    3737       pmfu,     upwd,     ftsol,  pctsrf, pphis,     &
    38        pphi,     albsol,   sh,             rh,        &
     38       pphi,     albsol,   sh,             ch, rh,    &
    3939       cldfra,   rneb,     diafra,         cldliq,    &
    4040       itop_con, ibas_con, pmflxr,         pmflxs,    &
     
    7676    REAL,DIMENSION(klon,klev),INTENT(IN)   :: t_seri  ! Temperature
    7777    REAL,DIMENSION(klon,klev),INTENT(IN)   :: sh      ! humidite specifique
     78    REAL,DIMENSION(klon,klev),INTENT(IN)   :: ch      ! eau liquide
    7879    REAL,DIMENSION(klon,klev),INTENT(IN)   :: rh      ! humidite relative
    7980    REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs   ! pression pour chaque inter-couche (en Pa)
     
    185186         t_seri,     & !tfld
    186187         sh,         & !sh
     188         ch,         & !ql
    187189         rh,         & !rh
    188190         nbp_lon,    & !nx
  • LMDZ5/branches/IPSLCM5A2.1/libf/phylmd/vertical_layers_mod.F90

    r2315 r2907  
    1515   
    1616!$OMP THREADPRIVATE(preff,scaleheight,ap,bp,presnivs,pseudoalt)
    17 
     17   REAL, SAVE, ALLOCATABLE :: Ahyb(:), Bhyb(:)
     18!$OMP THREADPRIVATE(Ahyb, Bhyb)
    1819
    1920CONTAINS
     
    3435    ALLOCATE(presnivs(nlayer))
    3536    ALLOCATE(pseudoalt(nlayer))
    36  
     37    ALLOCATE(Ahyb(nlayer))
     38    ALLOCATE(Bhyb(nlayer))
     39
     40
    3741    preff = preff_
    3842    scaleheight=scaleheight_
Note: See TracChangeset for help on using the changeset viewer.