Changeset 1305 for trunk/LMDZ.VENUS/libf


Ignore:
Timestamp:
Jul 8, 2014, 2:21:53 PM (10 years ago)
Author:
slebonnois
Message:

SL: VENUS PHOTOCHEMISTRY. Needs Lapack (see arch files...)

Location:
trunk/LMDZ.VENUS/libf/phyvenus
Files:
5 added
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/clesphys.h

    r1160 r1305  
    1111       LOGICAL ok_orodr,ok_orolf,ok_gw_nonoro
    1212       LOGICAL ok_kzmin
     13       LOGICAL ok_cloud, ok_chem, reinit_trac, ok_sedim
    1314       INTEGER nbapp_rad, nbapp_chim, iflag_con, iflag_ajs
    14        INTEGER lev_histhf, lev_histday, lev_histmth
     15       INTEGER lev_histins, lev_histday, lev_histmth
    1516       INTEGER tr_scheme
    1617       REAL    ecriphy
     
    1920       REAL    ksta, inertie
    2021
    21        COMMON/clesphys_l/cycle_diurne, soil_model,                      &
    22      &     ok_orodr, ok_orolf, ok_gw_nonoro, ok_kzmin
     22       COMMON/clesphys_l/ cycle_diurne, soil_model,                     &
     23     &     ok_orodr, ok_orolf, ok_gw_nonoro, ok_kzmin,                  &
     24     &     ok_cloud, ok_chem, reinit_trac, ok_sedim
    2325
    24        COMMON/clesphys_i/nbapp_rad, nbapp_chim,                         &
     26       COMMON/clesphys_i/ nbapp_rad, nbapp_chim,                        &
    2527     &     iflag_con, iflag_ajs,                                        &
    26      &     lev_histhf, lev_histday, lev_histmth, tr_scheme
     28     &     lev_histins, lev_histday, lev_histmth, tr_scheme
    2729
    28        COMMON/clesphys_r/ecriphy, solaire, z0, lmixmin,                 &
     30       COMMON/clesphys_r/ ecriphy, solaire, z0, lmixmin,                &
    2931     &     ksta, inertie
    3032
  • trunk/LMDZ.VENUS/libf/phyvenus/conf_phys.F90

    r1160 r1305  
    191191!
    192192!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     193! PARAMETER FOR THE PLANETARY BOUNDARY LAYER AND SOIL
     194!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     195!
     196!Config Key  = iflag_pbl
     197!Config Desc =
     198!Config Def  = 1
     199!Config Help =
     200!
     201! 2   = calculs Cd et K simples pour VENUS :
     202!       parametres = z0, lmixmin, ksta (en dur: umin2,ric,cepdu2,karman)
     203! 1   = calculs Cd et K issus LMDZ Terre
     204!       parametres = ksta, ok_kzmin (et plein d'autres en dur...)
     205! 6-9 = schema des thermiques Fred
     206  iflag_pbl = 1
     207  call getin('iflag_pbl',iflag_pbl)
     208
     209!
     210!Config Key  = ksta
     211!Config Desc =
     212!Config Def  = 1.0e-7
     213!Config Help =
     214!
     215  ksta = 1.0e-7
     216  call getin('ksta',ksta)
     217
     218!
     219!Config Key  = z0
     220!Config Desc =
     221!Config Def  = 1.0e-2
     222!Config Help =
     223!
     224  z0 = 1.0e-2
     225  call getin('z0',z0)
     226
     227!
     228!Config Key  = lmixmin
     229!Config Desc =
     230!Config Def  = 35.
     231!Config Help =
     232!
     233  lmixmin = 35.
     234  call getin('lmixmin',lmixmin)
     235
     236!
     237!Config Key  = ok_kzmin
     238!Config Desc =
     239!Config Def  = .false.
     240!Config Help =
     241!
     242  ok_kzmin = .false.
     243  call getin('ok_kzmin',ok_kzmin)
     244
     245
     246!Config Key  = iflag_ajs
     247!Config Desc =
     248!Config Def  = 0
     249!Config Help =
     250!
     251  iflag_ajs = 1
     252  call getin('iflag_ajs',iflag_ajs)
     253
     254!
     255!Config Key  = inertie
     256!Config Desc =
     257!Config Def  = 2000.
     258!Config Help =
     259!
     260  inertie = 2000.
     261  call getin('inertie',inertie)
     262!
     263!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     264! PARAMETER FOR THE OUTPUT LEVELS
     265!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     266!
     267!Config Key  = lev_histins
     268!Config Desc =
     269!Config Def  = 0
     270!Config Help =
     271!
     272  lev_histins = 0
     273  call getin('lev_histins',lev_histins)
     274
     275!
     276!Config Key  = lev_histday
     277!Config Desc =
     278!Config Def  = 1
     279!Config Help =
     280!
     281  lev_histday = 1
     282  call getin('lev_histday',lev_histday)
     283
     284!
     285!Config Key  = lev_histmth
     286!Config Desc =
     287!Config Def  = 2
     288!Config Help =
     289!
     290  lev_histmth = 2
     291  call getin('lev_histmth',lev_histmth)
     292
     293
     294!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    193295! PARAMETER FOR THE TRACERS
    194296!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    206308!       However, the variable 'source' could be used in physiq
    207309!       so the call to phytrac_emiss could be to initialise it.
    208 ! 3   = Full chemistry
    209 !       To be added by Aurelien
     310! 3   = Full chemistry and/or clouds => phytrac_chimie
     311!       Need ok_chem or ok_cloud
    210312  tr_scheme = 0
    211313  call getin('tr_scheme',tr_scheme)
    212314
    213315!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    214 ! PARAMETER FOR THE PLANETARY BOUNDARY LAYER AND SOIL
    215 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    216 !
    217 !Config Key  = iflag_pbl
    218 !Config Desc =
    219 !Config Def  = 1
    220 !Config Help =
    221 !
    222 ! 2   = calculs Cd et K simples pour VENUS :
    223 !       parametres = z0, lmixmin, ksta (en dur: umin2,ric,cepdu2,karman)
    224 ! 1   = calculs Cd et K issus LMDZ Terre
    225 !       parametres = ksta, ok_kzmin (et plein d'autres en dur...)
    226 ! 6-9 = schema des thermiques Fred
    227   iflag_pbl = 1
    228   call getin('iflag_pbl',iflag_pbl)
    229 
    230 !
    231 !Config Key  = ksta
    232 !Config Desc =
    233 !Config Def  = 1.0e-7
    234 !Config Help =
    235 !
    236   ksta = 1.0e-7
    237   call getin('ksta',ksta)
    238 
    239 !
    240 !Config Key  = z0
    241 !Config Desc =
    242 !Config Def  = 1.0e-2
    243 !Config Help =
    244 !
    245   z0 = 1.0e-2
    246   call getin('z0',z0)
    247 
    248 !
    249 !Config Key  = lmixmin
    250 !Config Desc =
    251 !Config Def  = 35.
    252 !Config Help =
    253 !
    254   lmixmin = 35.
    255   call getin('lmixmin',lmixmin)
    256 
    257 !
    258 !Config Key  = ok_kzmin
    259 !Config Desc =
    260 !Config Def  = .false.
    261 !Config Help =
    262 !
    263   ok_kzmin = .false.
    264   call getin('ok_kzmin',ok_kzmin)
    265 
    266 
    267 !Config Key  = iflag_ajs
    268 !Config Desc =
    269 !Config Def  = 0
    270 !Config Help =
    271 !
    272   iflag_ajs = 1
    273   call getin('iflag_ajs',iflag_ajs)
    274 
    275 !
    276 !Config Key  = inertie
    277 !Config Desc =
    278 !Config Def  = 2000.
    279 !Config Help =
    280 !
    281   inertie = 2000.
    282   call getin('inertie',inertie)
    283 !
    284 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    285 ! PARAMETER FOR THE OUTPUT LEVELS
    286 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    287 !
    288 !Config Key  = lev_histhf
    289 !Config Desc =
    290 !Config Def  = 0
    291 !Config Help =
    292 !
    293   lev_histhf = 0
    294   call getin('lev_histhf',lev_histhf)
    295 
    296 !
    297 !Config Key  = lev_histday
    298 !Config Desc =
    299 !Config Def  = 1
    300 !Config Help =
    301 !
    302   lev_histday = 1
    303   call getin('lev_histday',lev_histday)
    304 
    305 !
    306 !Config Key  = lev_histmth
    307 !Config Desc =
    308 !Config Def  = 2
    309 !Config Help =
    310 !
    311   lev_histmth = 2
    312   call getin('lev_histmth',lev_histmth)
    313 
     316!   PARAMETRES DE LA CHIMIE/NUAGE dans physiq.def
     317!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     318
     319!
     320!Config Key  = reinit_trac
     321!Config Desc = 
     322!Config Def  = .FALSE.
     323!Config Help =
     324!
     325  reinit_trac = .FALSE.
     326  call getin('reinit_trac',reinit_trac)
     327 
     328!
     329!Config Key  = ok_cloud
     330!Config Desc = 
     331!Config Def  = .FALSE.
     332!Config Help =
     333!
     334  ok_cloud = .FALSE.
     335  call getin('ok_cloud',ok_cloud)
     336
     337!
     338!Config Key  = ok_chem
     339!Config Desc = 
     340!Config Def  = .FALSE.
     341!Config Help =
     342!
     343  ok_chem = .FALSE.
     344  call getin('ok_chem',ok_chem)
     345
     346  if (((tr_scheme.ne.3).and.(ok_chem.or.ok_cloud)).or. &
     347      ((tr_scheme.eq.3).and.(.not.ok_chem.and..not.ok_cloud))) then
     348    write(*,*) "Attention, incoherence :"
     349    write(*,*) "tr_scheme=",tr_scheme," / ok_chem=",ok_chem, &
     350                                     " / ok_cloud=",ok_cloud
     351    write(*,*) "Verifier votre physiq.def"
     352    stop
     353  endif
     354
     355!
     356!Config Key  = ok_sedim
     357!Config Desc = 
     358!Config Def  = .FALSE.
     359!Config Help =
     360!
     361  ok_sedim = .FALSE.
     362  call getin('ok_sedim',ok_sedim)
     363 
    314364!
    315365!
     
    352402  write(numout,*)' inertie = ', inertie
    353403  write(numout,*)' iflag_ajs = ', iflag_ajs
    354   write(numout,*)' lev_histhf = ',lev_histhf
     404  write(numout,*)' lev_histins = ',lev_histins
    355405  write(numout,*)' lev_histday = ',lev_histday
    356406  write(numout,*)' lev_histmth = ',lev_histmth
     407  write(numout,*)' reinit_trac = ',reinit_trac
     408  write(numout,*)' ok_cloud = ',ok_cloud
     409  write(numout,*)' ok_chem = ',ok_chem
     410  write(numout,*)' ok_sedim = ',ok_sedim
    357411
    358412  return
  • trunk/LMDZ.VENUS/libf/phyvenus/ini_histins.h

    r902 r1305  
    1818
    1919c-------------------------------------------------------
    20       IF(lev_histday.GE.1) THEN
     20      IF(lev_histins.GE.1) THEN
    2121c
    2222ccccccccccccc 2D fields, basics
     
    5454c    .                "ins(X)", zsto,zout)
    5555c
    56       ENDIF !lev_histday.GE.1
    57 c
    58 c-------------------------------------------------------
    59       IF(lev_histday.GE.2) THEN
     56      ENDIF !lev_histins.GE.1
     57c
     58c-------------------------------------------------------
     59      IF(lev_histins.GE.2) THEN
    6060c
    6161ccccccccccccc 3D fields, basics
     
    102102c
    103103c plusieurs traceurs
    104           if (iflag_trac.eq.1) THEN
     104         if (iflag_trac.eq.1) THEN
    105105            DO iq=1,nqmax
    106106             IF (iq.LE.99) THEN
    107107          WRITE(str2,'(i2.2)') iq
    108           CALL histdef(nid_ins, tname(iq), ttext(iq), "ppm",
     108          CALL histdef(nid_ins, tname(iq), ttext(iq), "vmr",
    109109     .                iim,jj_nb,nhori, klev,1,klev,nvert, 32,
    110110     .                "ins(X)", zsto,zout)
     
    114114             ENDIF
    115115            ENDDO
    116           endif
     116         endif
    117117c
    118118         CALL histdef(nid_ins, "tops", "Solar rad. at TOA", "W/m2",
     
    120120     .                "ins(X)", zsto,zout)
    121121c
    122       ENDIF !lev_histday.GE.2
    123 c
    124 c-------------------------------------------------------
    125       IF(lev_histday.GE.3) THEN
     122         if (ok_cloud) THEN
     123          CALL histdef(nid_ins, "NBRTOT", "Nbr total droplet", "#/cm3",
     124     .                iim,jj_nb,nhori, klev,1,klev, nvert, 32,
     125     .                "ins(X)", zsto,zout)
     126          CALL histdef(nid_ins, "WH2SO4", "Weight fraction H2SO4",
     127     .     "fraction",iim,jj_nb,nhori, klev,1,klev, nvert, 32,
     128     .                "ins(X)", zsto,zout)
     129          CALL histdef(nid_ins, "R_MEDIAN",
     130     .     "Median radius fo log normal distribution" ,
     131     .     "fraction",iim,jj_nb,nhori, klev,1,klev, nvert, 32,
     132     .                "ins(X)", zsto,zout)
     133          CALL histdef(nid_ins, "STDDEV",
     134     .     "Std Deviation for lor normaldistribution",
     135     .     "fraction",iim,jj_nb,nhori, klev,1,klev, nvert, 32,
     136     .                "ins(X)", zsto,zout)
     137          CALL histdef(nid_ins, "rho_droplet", "density cloud droplet",
     138     .       "kg.m-3",iim,jj_nb,nhori, klev,1,klev, nvert, 32,
     139     .                "ins(X)", zsto,zout)
     140         endif
     141
     142         if (ok_sedim) THEN
     143          CALL histdef(nid_ins,"d_tr_sed_H2SO4","H2SO4 mmr from sedim",
     144     .        "kg/kg",iim,jj_nb,nhori, klev,1,klev, nvert, 32,
     145     .                "ins(X)", zsto,zout)
     146          CALL histdef(nid_ins,"d_tr_sed_H2O", "H2O mmr from sedim",
     147     .        "kg/kg",iim,jj_nb,nhori, klev,1,klev, nvert, 32,
     148     .                "ins(X)", zsto,zout)
     149          CALL histdef(nid_ins, "F_sedim", "tendency from sedim",
     150     .   "kg.m-2.s-1",iim,jj_nb,nhori, klev,1,klev, nvert, 32,
     151     .                "ins(X)", zsto,zout)
     152         endif
     153
     154      ENDIF !lev_histins.GE.2
     155c
     156c-------------------------------------------------------
     157      IF(lev_histins.GE.3) THEN
    126158c
    127159cccccccccccccccccc  Radiative transfer
     
    167199c    .                32, "ins(X)", zsto,zout)
    168200c
    169       ENDIF !lev_histday.GE.3
    170 c
    171 c-------------------------------------------------------
    172       IF(lev_histday.GE.4) THEN
     201      ENDIF !lev_histins.GE.3
     202c
     203c-------------------------------------------------------
     204      IF(lev_histins.GE.4) THEN
    173205c
    174206         CALL histdef(nid_ins, "dtdyn", "Dynamics dT", "K/s",
     
    216248c    .                "ins(X)", zsto,zout)
    217249c
    218       ENDIF !lev_histday.GE.4
    219 c
    220 c-------------------------------------------------------
    221       IF(lev_histday.GE.5) THEN
     250      ENDIF !lev_histins.GE.4
     251c
     252c-------------------------------------------------------
     253      IF(lev_histins.GE.5) THEN
    222254c
    223255c        call histdef(nid_ins, "taux",
     
    239271c    .                "ins(X)", zsto,zout)
    240272c
    241       ENDIF !lev_histday.GE.5
     273      ENDIF !lev_histins.GE.5
    242274c-------------------------------------------------------
    243275c
  • trunk/LMDZ.VENUS/libf/phyvenus/physiq.F

    r1301 r1305  
    5656      USE ioipsl
    5757!      USE histcom ! not needed; histcom is included in ioipsl
     58      USE chemparam_mod
    5859      USE infotrac
    5960      USE control_mod
     
    6566      USE iophy
    6667      use cpdet_mod, only: cpdet, t2tpot
     68      use ieee_arithmetic
    6769      IMPLICIT none
    6870c======================================================================
     
    198200      REAL uq(klon) ! integr. verticale du transport zonal de l'eau
    199201c
     202      REAL Fsedim(klon,klev+1)  ! Flux de sedimentation (kg.m-2)
    200203
    201204c======================================================================
     
    285288      REAL u_seri(klon,klev), v_seri(klon,klev)
    286289c
    287       REAL tr_seri(klon,klev,nqmax)
    288       REAL d_tr(klon,klev,nqmax)
     290      REAL :: tr_seri(klon,klev,nqmax)
     291      REAL :: d_tr(klon,klev,nqmax)
     292
     293c Variables tendance sedimentation
     294
     295      REAL :: d_tr_sed(klon,klev,2)
     296      REAL :: d_tr_ssed(klon)
    289297c
    290298c pour ioipsl
     
    530538      ENDDO
    531539
     540c---------
     541c       Ecriture fichier initialisation
     542c       PRINT*,'Ecriture Initial_State.csv'
     543c       OPEN(88,file='Trac_Point.csv',
     544c     & form='formatted')
     545c---------
     546     
     547c---------
     548c       Initialisation des parametres des nuages
     549c===============================================
     550     
     551      if ((nlon .EQ. 1) .AND. ok_cloud) then
     552        PRINT*,'Open profile_cloud_parameters.csv'
     553        OPEN(66,file='profile_cloud_parameters.csv',
     554     &   form='formatted')
     555      endif
     556
     557      if ((nlon .EQ. 1) .AND. ok_sedim) then
     558        PRINT*,'Open profile_cloud_sedim.csv'
     559        OPEN(77,file='profile_cloud_sedim.csv',
     560     &   form='formatted')
     561      endif
     562           
     563      if ((nlon .GT. 1) .AND. ok_chem) then
     564c !!! DONC 3D !!!
     565        CALL chemparam_ini()
     566      endif
    532567         
     568      if ((nlon .GT. 1) .AND. ok_cloud) then
     569c !!! DONC 3D !!!
     570        CALL cloud_ini(nlon,nlev)
     571      endif
     572       
    533573      ENDIF ! debut
    534574c====================================================================
     
    704744       if (tr_scheme.eq.1) then
    705745! Case 1: pseudo-chemistry with relaxation toward fixed profile
     746
    706747         call phytrac_relax (debut,lafin,nqmax,
    707748     I                   nlon,nlev,dtime,pplay,
     
    713754! However, the variable 'source' could be used in physiq
    714755! so the call to phytrac_emiss could be to initialise it.
     756
    715757         call phytrac_emiss ( (rjourvrai+gmtime)*RDAY,
    716758     I                   debut,lafin,nqmax,
     
    718760     I                   rlatd,rlond,
    719761     O                   tr_seri)
    720        elseif (tr_scheme.eq.3) then
    721 ! Case 3: Full chemistry
    722 !        call phytrac_chem ( ?? )
    723          print*,"Chemistry not yet implemented..."
    724          print*,"See Aurelien Stolzenbach"
    725        endif
    726       endif
     762
     763       elseif (tr_scheme.eq.3) then  ! identical to ok_chem.or.ok_cloud
     764! Case 3: Full chemistry and/or clouds
     765
     766         call phytrac_chimie(                 
     767     I             debut,
     768     I             gmtime,
     769     I             nqmax,
     770     I             nlon,
     771     I             rlatd,
     772     I             rlond,
     773     I             nlev,
     774     I             dtime,
     775     I             t_seri,pplay,
     776     O             tr_seri,
     777     O             NBRTOT,
     778     O             WH2SO4,
     779     O             rho_droplet)
     780
     781c        CALL WriteField_phy('Pression',pplay,nlev)
     782c        CALL WriteField_phy('PressionBnd',paprs,nlev+1)
     783c        CALL WriteField_phy('Temp',t_seri,nlev)
     784c        IF (ok_cloud) THEN
     785c          CALL WriteField_phy('NBRTOT',NBRTOT,nlev)
     786c        ENDIF
     787c        CALL WriteField_phy('SAl',tr_seri(:,:,i_h2so4liq),nlev)
     788c        CALL WriteField_phy('SAg',tr_seri(:,:,i_h2so4),nlev)
     789
     790         if (ok_sedim) then
     791
     792           CALL new_cloud_sedim(
     793     I               klon,
     794     I               nlev,
     795     I               dtime,
     796     I               pplay,
     797     I               paprs,
     798     I               t_seri,
     799     I               WH2SO4,
     800     I               tr_seri,
     801     I               nqmax,
     802     I               NBRTOT,
     803     I               rho_droplet,
     804     O               Fsedim,
     805     O               d_tr_sed,
     806     O               d_tr_ssed)
     807
     808          DO k = 1, klev
     809           DO i = 1, klon
     810     
     811c        WRITE(88,"(11(e15.8,','))") pplay(5,25),
     812c     &  t_seri(5,25),tr_seri(5,25,i_h2oliq),
     813c     &  tr_seri(5,25,i_h2o),tr_seri(5,25,i_h2so4liq),
     814c     &  tr_seri(5,25,i_h2so4),NBRTOT(5,25),WH2SO4(5,25),
     815c     &  Fsedim(5,25),d_tr_sed(5,25,1),d_tr_sed(5,25,2)
     816
     817c--------------------
     818c   Ce test est necessaire pour eviter Xliq=NaN   
     819        IF (ieee_is_nan(d_tr_sed(i,k,1)).OR.
     820     &  ieee_is_nan(d_tr_sed(i,k,2))) THEN
     821        PRINT*,'sedim NaN PROBLEM'
     822        PRINT*,'d_tr_sed Nan?',d_tr_sed(i,k,:),'Temp',t_seri(i,k)
     823        PRINT*,'lat-lon',i,'level',k,'dtime',dtime
     824        PRINT*,'NBRTOT',NBRTOT(i,k),'F_sed',Fsedim(i,k)
     825        PRINT*,'==============================================='
     826                d_tr_sed(i,k,:)=0.
     827        ENDIF
     828c--------------------
     829
     830        tr_seri(i,k,i_h2so4liq) = tr_seri(i,k,i_h2so4liq)+
     831     &                            d_tr_sed(i,k,1)
     832        tr_seri(i,k,i_h2oliq)   = tr_seri(i,k,i_h2oliq)+
     833     &                            d_tr_sed(i,k,2)
     834        d_tr_sed(i,k,:) = d_tr_sed(i,k,:) / dtime
     835        Fsedim(i,k)     = Fsedim(i,k) / dtime
     836     
     837           ENDDO
     838          ENDDO
     839     
     840        Fsedim(:,klev+1) = 0.
     841
     842         endif ! ok_sedim
     843
     844       endif   ! tr_scheme
     845      endif    ! iflag_trac
    727846
    728847c
  • trunk/LMDZ.VENUS/libf/phyvenus/phytrac_emiss.F

    r1301 r1305  
    7676
    7777      integer,parameter :: nbsrc=2,nblat=5,nblon=4
    78       integer,parameter :: Nemiss=1   ! duree emission (Ed)
     78!     integer,parameter :: Nemiss=1   ! duree emission (Ed)
    7979      integer,save :: Nemiss(nbsrc)      ! duration emission (Ed)
    8080      real,save :: source_volcan(nbsrc)  ! flux emission (kg/s)
  • trunk/LMDZ.VENUS/libf/phyvenus/rcm1d.F

    r1301 r1305  
    55      use comgeomphy
    66      USE phys_state_var_mod
     7      use chemparam_mod
    78      use cpdet_mod, only: ini_cpdet
    89      use moyzon_mod, only: tmoy
     
    308309        ENDDO
    309310      ENDDO
     311
     312c FULL CHEMISTRY !! AJOUTER INIT AURELIEN...
     313C Faudrait lire les cles avant pour mettre ca en option....
     314c ou alors mettre ca dans physiq
    310315
    311316c    Initialisation des parametres d'oro
  • trunk/LMDZ.VENUS/libf/phyvenus/write_histins.h

    r1301 r1305  
    77
    88c-------------------------------------------------------
    9       IF(lev_histday.GE.1) THEN
     9      IF(lev_histins.GE.1) THEN
    1010
    1111ccccccccccccc 2D fields, basics
     
    2121c     call histwrite_phy(nid_ins,.false.,"cdragm",itau_w,cdragm)
    2222
    23       ENDIF !lev_histday.GE.1
     23      ENDIF !lev_histins.GE.1
    2424
    2525c-------------------------------------------------------
    26       IF(lev_histday.GE.2) THEN
     26      IF(lev_histins.GE.2) THEN
    2727
    2828ccccccccccccc 3D fields, basics
     
    5151      call histwrite_phy(nid_ins,.false.,"tops",itau_w,topsw)
    5252
    53       ENDIF !lev_histday.GE.2
     53      if (ok_cloud) THEN
     54       call histwrite_phy(nid_ins,.false.,"NBRTOT",itau_w,NBRTOT)
     55       call histwrite_phy(nid_ins,.false.,"WH2SO4",itau_w,WH2SO4)
     56       call histwrite_phy(nid_ins,.false.,"R_MEDIAN",itau_w,R_MEDIAN)
     57       call histwrite_phy(nid_ins,.false.,"STDDEV",itau_w,STDDEV)
     58       call histwrite_phy(nid_ins,.false.,"rho_droplet",
     59     &                              itau_w,rho_droplet)
     60      endif
     61
     62      if (ok_sedim) THEN     
     63       call histwrite_phy(nid_ins,.false.,"d_tr_sed_H2SO4",
     64     &                              itau_w,d_tr_sed(:,:,1))
     65       call histwrite_phy(nid_ins,.false.,"d_tr_sed_H2O",
     66     &                              itau_w,d_tr_sed(:,:,2))
     67       call histwrite_phy(nid_ins,.false.,"F_sedim",itau_w,Fsedim)
     68      endif           
     69
     70      ENDIF !lev_histins.GE.2
    5471
    5572c-------------------------------------------------------
    56       IF(lev_histday.GE.3) THEN
     73      IF(lev_histins.GE.3) THEN
    5774
    5875cccccccccccccccccc  Radiative transfer
     
    7390c     call histwrite_phy(nid_ins,.false.,"fluxec",itau_w,flux_ec)
    7491
    75       ENDIF !lev_histday.GE.3
     92      ENDIF !lev_histins.GE.3
    7693
    7794c-------------------------------------------------------
    78       IF(lev_histday.GE.4) THEN
     95      IF(lev_histins.GE.4) THEN
    7996
    8097c en K/s     
     
    102119c     call histwrite_phy(nid_ins,.false.,"dvvdf",itau_w,-1.*d_v_vdf)
    103120
    104       ENDIF !lev_histday.GE.4
     121      ENDIF !lev_histins.GE.4
    105122
    106123c-------------------------------------------------------
    107       IF(lev_histday.GE.5) THEN
     124      IF(lev_histins.GE.5) THEN
    108125
    109126c     call histwrite_phy(nid_ins,.false.,"taux_",itau_w,fluxu)
     
    112129c     call histwrite_phy(nid_ins,.false.,"cdrh",itau_w,cdragh)
    113130
    114       ENDIF !lev_histday.GE.5
     131      ENDIF !lev_histins.GE.5
    115132c-------------------------------------------------------
    116133
Note: See TracChangeset for help on using the changeset viewer.