Ignore:
Timestamp:
Feb 17, 2017, 3:44:15 PM (8 years ago)
Author:
jvatant
Message:

Another round of cleaning of dust and dummy tracers
JVO

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/callkeys_mod.F90

    r1648 r1668  
    4545!$OMP THREADPRIVATE(iddist,iaervar,iradia,startype)
    4646
    47       real,save :: topdustref
    4847      real,save :: Fat1AU
    4948      real,save :: stelTbb
    50 !$OMP THREADPRIVATE(topdustref,Fat1AU,stelTbb)
     49!$OMP THREADPRIVATE(Fat1AU,stelTbb)
    5150      real,save :: tplanet
    5251      real,save :: obs_tau_col_tropo
  • trunk/LMDZ.TITAN/libf/phytitan/convadj.F

    r1647 r1668  
    312312            print*,'zh2(ig,:)        = ',zh2(i,l)
    313313         end do
    314 !         do l = 1, nlay
    315 !            print*,'zq(ig,:,vap)     = ',zq(i,l,igcm_h2o_vap)
    316 !         end do
    317 !         do l = 1, nlay
    318 !            print*,'zq2(ig,:,vap)    = ',zq2(i,l,igcm_h2o_vap)
    319 !         end do
    320 !            print*,'zqm(vap)         = ',zqm(igcm_h2o_vap)
    321             print*,'jadrs=',jadrs
     314         print*,'jadrs=',jadrs
    322315
    323316            call abort
  • trunk/LMDZ.TITAN/libf/phytitan/iniaerosol.F

    r1647 r1668  
    1111c   --------
    1212c   Initialization related to aerosols
    13 c   (CO2 aerosols, dust, water, chemical species, ice...)   
     13c   (Chemical species, ice...)   
    1414c
    1515c   author: Laura Kerber, S. Guerlet
  • trunk/LMDZ.TITAN/libf/phytitan/initracer.F

    r1647 r1668  
    88c   --------
    99c   Initialization related to tracer
    10 c   (transported dust, water, chemical species, ice...)
     10c   (chemical species, ice...)
    1111c
    1212c   Name of the tracer
     
    3838c  alpha_lift(nq)  ! saltation vertical flux/horiz flux ratio (m-1)
    3939c  alpha_devil(nq) ! lifting coeeficient by dust devil
    40 c  doubleq           ! if method with mass (iq=1) and number(iq=2) mixing ratio
    41 c  varian            ! Characteristic variance of log-normal distribution
    4240c-----------------------------------------------------------------------
    4341
     
    5351       ALLOCATE(alpha_devil(nq))
    5452       ALLOCATE(qextrhor(nq))
    55        ALLOCATE(igcm_dustbin(nq))
    5653       !! initialization
    5754       alpha_lift(:)=0.
     
    7269      ! 0. initialize tracer indexes to zero:
    7370      ! NB: igcm_* indexes are commons in 'tracer.h'
    74       igcm_co=0
    75       igcm_o=0
    76       igcm_o1d=0
    77       igcm_o2=0
    78       igcm_o3=0
    79       igcm_h=0
    80       igcm_h2=0
    81       igcm_oh=0
    82       igcm_ho2=0
    83       igcm_h2o2=0
    8471      igcm_n2=0
    85       igcm_ar=0
    86       igcm_ar_n2=0
    8772
    8873      write(*,*) 'initracer: noms() ', noms
    8974
    9075
    91       !print*,'Setting dustbin = 0 in initracer.F'
    92       !dustbin=0
     76      ! 1. find chemistry tracers
     77      count = 0.   
    9378
    94       ! 1. find dust tracers
    95       count=0
    96 !      if (dustbin.gt.0) then
    97 !        do iq=1,nq
    98 !          txt=" "
    99 !          write(txt,'(a4,i2.2)')'dust',count+1   
    100 !          if (noms(iq).eq.txt) then
    101 !            count=count+1
    102 !            igcm_dustbin(count)=iq
    103 !            mmol(iq)=100.
    104 !          endif
    105 !        enddo !do iq=1,nq
    106 !      endif ! of if (dustbin.gt.0)
    107 
    108 
    109 !      if (doubleq) then
    110 !        do iq=1,nq
    111 !          if (noms(iq).eq."dust_mass") then
    112 !            igcm_dust_mass=iq
    113 !            count=count+1
    114 !          endif
    115 !          if (noms(iq).eq."dust_number") then
    116 !            igcm_dust_number=iq
    117 !            count=count+1
    118 !          endif
    119 !        enddo
    120 !      endif ! of if (doubleq)
    121       ! 2. find chemistry and water tracers
    122      
     79 
    12380      ! check that we identified all tracers:
    12481      if (count.ne.nq) then
     
    150107      write(*,*) 'alpha_devil = ', alpha_devil
    151108      write(*,*) 'radius  = ', radius
    152 !      if(doubleq) then
    153 !        write(*,*) 'reff_lift (um) =  ', reff_lift
    154 !        write(*,*) 'size distribution variance  = ', varian
    155 !        write(*,*) 'r3n_q , ref_r0 : ', r3n_q , ref_r0
    156 !      end if
     109     
    157110      write(*,*) 'Qext  = ', qext
    158111      write(*,*)
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90

    r1663 r1668  
    2323      USE comgeomfi_h, only: totarea, totarea_planet
    2424      USE tracer_h, only: noms, mmol, radius, qext, &
    25                           alpha_lift, alpha_devil, qextrhor, &
    26                           igcm_dustbin
     25                          alpha_lift, alpha_devil, qextrhor
    2726      use time_phylmdz_mod, only: ecritphy, iphysiq, nday
    2827      use phyredem, only: physdem0, physdem1
     
    316315!$OMP THREADPRIVATE(ztprevious,zuprevious)
    317316
    318       real reff(ngrid,nlayer)                       ! Effective dust radius (used if doubleq=T).
    319317      real vmr(ngrid,nlayer)                        ! volume mixing ratio
    320318      real time_phys
  • trunk/LMDZ.TITAN/libf/phytitan/tracer_h.F90

    r1648 r1668  
    1717       real, DIMENSION(:), ALLOCATABLE :: qextrhor ! Intermediate for computing opt. depth from q
    1818
    19       real varian      ! Characteristic variance of log-normal distribution
    20       real r3n_q     ! used to compute r0 from number and mass mixing ratio
    21       real ref_r0        ! for computing reff=ref_r0*r0 (in log.n. distribution)
    22 !$OMP THREADPRIVATE(noms,mmol,radius,rho_q,qext,alpha_lift,alpha_devil,qextrhor, &
    23         !$OMP varian,r3n_q,ref_r0)
     19!$OMP THREADPRIVATE(noms,mmol,radius,rho_q,qext,alpha_lift,alpha_devil,qextrhor)
    2420
    2521! tracer indexes: these are initialized in initracer and should be 0 if the
    2622!                 corresponding tracer does not exist
    27       ! dust
    28       integer, DIMENSION(:), ALLOCATABLE :: igcm_dustbin ! for dustbin 'dust' tracers
    29       ! dust, special doubleq case
    30       integer :: igcm_dust_mass   ! dust mass mixing ratio (for transported dust)
    31       integer :: igcm_dust_number ! dust number mixing ratio (transported dust)
    3223      ! chemistry:
    33       integer :: igcm_co
    34       integer :: igcm_o
    35       integer :: igcm_o1d
    36       integer :: igcm_o2
    37       integer :: igcm_o3
    38       integer :: igcm_h
    39       integer :: igcm_h2
    40       integer :: igcm_oh
    41       integer :: igcm_ho2
    42       integer :: igcm_h2o2
    4324      integer :: igcm_n2
    44       integer :: igcm_ar
    45       ! other tracers
    46       integer :: igcm_ar_n2 ! for simulations using co2 +neutral gaz
    47 !$OMP THREADPRIVATE(igcm_dustbin,igcm_dust_mass,igcm_dust_number, &
    48         !$OMP igcm_co,igcm_o,igcm_o1d,igcm_o2,igcm_o3,igcm_h,igcm_h2,igcm_oh,       &
    49         !$OMP igcm_ho2,igcm_h2o2,igcm_n2,igcm_ar,igcm_ar_n2)
     25!$OMP THREADPRIVATE(igcm_n2)
    5026
    5127       end module tracer_h
  • trunk/LMDZ.TITAN/libf/phytitan/vdifc.F

    r1647 r1668  
    9797!     variables added for CO2 condensation
    9898!     ------------------------------------
    99       REAL hh                   !, zhcond(ngrid,nlay)
    100 !     REAL latcond,tcond1mb
    101 !     REAL acond,bcond
    102 !     SAVE acond,bcond
    103 !!$OMP THREADPRIVATE(acond,bcond)
    104 !     DATA latcond,tcond1mb/5.9e5,136.27/
     99      REAL hh
    105100
    106101!     Tracers
     
    127122
    128123      IF (firstcall) THEN
    129 !     To compute: Tcond= 1./(bcond-acond*log(.0095*p)) (p in pascal)
    130 !     bcond=1./tcond1mb
    131 !     acond=r/latcond
    132 !     PRINT*,'In vdifc: Tcond(P=1mb)=',tcond1mb,' Lcond=',latcond
    133 !     PRINT*,'          acond,bcond',acond,bcond
    134 
    135124         firstcall=.false.
    136125      ENDIF
Note: See TracChangeset for help on using the changeset viewer.