Changeset 1691 for trunk/LMDZ.VENUS


Ignore:
Timestamp:
Apr 10, 2017, 11:14:59 AM (8 years ago)
Author:
slebonnois
Message:

SL: corrections after testing of cloud microphysics in 1D

Location:
trunk/LMDZ.VENUS/libf/phyvenus
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/chemparam_mod.F90

    r1661 r1691  
    8888!     radius R_MEDIAN en m (donc *e-6 pour microns)
    8989       
    90         R_MEDIAN(:,:,:)=0.0E+0             ! Geometric Average Radius
     90        R_MEDIAN(:,:,:)=0.0E+0           ! Geometric Average Radius
    9191        STDDEV(:,:,:)=0.0E+0             ! Geometric Std Deviation
    9292        K_MASS(:,:,:)=0.0E+0             ! Coeff multimodal
     
    892892  real    :: trac(nlon,nlev,nqtot) ! traceur ( en vmr)
    893893
    894   integer :: i
    895   real    :: trac1d(nlev,2) ! traceur lu ( en vmr)
     894!  integer :: i
     895!  real    :: trac1d(nlev,2) ! traceur lu ( en vmr)
    896896 
    897897! lecture d'un fichier texte contenant les profils de trac1d(:1) = H2O et trac1d(:,2) = H2SO4
    898 
    899   DO i=1,nlon
    900      trac(i,:,i_h2o) = trac1d(:,1)
    901      trac(i,:,i_h2so4) = trac1d(:,2)
    902   ENDDO
    903 
     898!  DO i=1,nlon
     899!     trac(i,:,i_h2o) = trac1d(:,1)
     900!     trac(i,:,i_h2so4) = trac1d(:,2)
     901!  ENDDO
     902
     903!  intitialisation profils altitude H2O et H2SO4
     904!  profil H2O initial vap+liq == que vap
     905   trac(:,1:24,i_h2o) = 30.E-6 !
     906   trac(:,25:50,i_h2o) = 1.E-6 !
     907
     908   trac(:,:,i_h2so4) = 3.E-9 ! Limite sup Sandor 2012
     909   trac(:,23:50,i_h2so4) = 2.E-6 ! Profil H2SO4 initial => vap+liq
    904910
    905911  END SUBROUTINE vapors4muphy_ini
  • trunk/LMDZ.VENUS/libf/phyvenus/dyn1d/rcm1d.F

    r1621 r1691  
    194194      READ(unit,*) lati(1)
    195195      PRINT *,lati(1)
     196      lati(1)=lati(1)*pi/180.  ! must be in radians.
    196197      long(1)=0.E+0
    197198
     
    206207      cufi(1)=1.E+0
    207208      cvfi(1)=1.E+0
     209
     210      call ini_cpdet
    208211
    209212c Ehouarn: iniphysiq requires arrays related to (3D) dynamics grid,
     
    220223     &            rad,g,r,cpp,1)
    221224
    222       call ini_cpdet
    223 
    224225c   le geopotentiel au sol est inutile en 1D car tout est controle
    225226c   par la pression de surface --->
     
    348349      solsw(1)    = 0.
    349350      sollw(1)    = 0.
    350       fder(1)      = 0.
     351      fder(1)     = 0.
    351352      radsol(1)   = 0.
    352353     
  • trunk/LMDZ.VENUS/libf/phyvenus/physiq_mod.F

    r1687 r1691  
    18701870      CALL send_xios_field("fluxec",flux_ec)
    18711871
    1872 c plusieurs traceurs  !!!outputs in [vmr]
     1872c When using tracers
    18731873      IF (iflag_trac.eq.1) THEN
    1874          DO iq=1,nqmax
     1874c photochemical compounds  !!!outputs in [vmr]
     1875         DO iq=1,nqmax-nmicro
    18751876       CALL send_xios_field(tname(iq),qx(:,:,iq)*mmean(:,:)/M_tr(iq))
    18761877         ENDDO
Note: See TracChangeset for help on using the changeset viewer.