Changeset 3855 for trunk


Ignore:
Timestamp:
Jul 17, 2025, 4:54:38 PM (7 weeks ago)
Author:
jbclement
Message:

Mars PCM:
"initracer.F" is transformed into "initracer_mod.F90" (explicit module interface + Fortran 90 format).
JBC

Location:
trunk/LMDZ.MARS
Files:
3 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/changelog.txt

    r3854 r3855  
    49214921== 17/07/2025 == JBC
    49224922Addition of a sanity check for the tracers 'ccn_number' and 'ccn_mass' when using the 'microphys' option.
     4923
     4924== 17/07/2025 == JBC
     4925"initracer.F" is transformed into "initracer_mod.F90" (explicit module interface + Fortran 90 format).
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/init_testphys1d_mod.F90

    r3848 r3855  
    4545use comslope_mod,             only: nslope, subslope_dist, ini_comslope_h, end_comslope_h
    4646use co2condens_mod,           only: CO2cond_ps
    47 use callkeys_mod, only: water, photochem, callthermos
    48 use call_dayperi_mod, only: call_dayperi
     47use callkeys_mod,             only: water, photochem, callthermos
     48use call_dayperi_mod,         only: call_dayperi
     49use initracer_mod,            only: initracer
    4950! Mostly for XIOS outputs:
    5051use mod_const_mpi,            only: COMM_LMDZ
  • trunk/LMDZ.MARS/libf/phymars/initracer.F90

    r3854 r3855  
    1       SUBROUTINE initracer(ngrid,nq,qsurf)
    2 
    3        use tracer_mod
    4        use comcstfi_h, only: pi
    5        use dust_param_mod, only: doubleq, submicron, dustbin
    6        use callkeys_mod, only: water, microphys, scavenging, rdstorm,
    7      &                         topflows, photochem, callthermos, hdo,
    8      &                         callnlte, nltemodel, dustinjection,
    9      &                         co2clouds, co2useh2o, meteo_flux
    10        IMPLICIT NONE
    11 c=======================================================================
    12 c   subject:
    13 c   --------
    14 c   Initialization related to tracer
    15 c   (transported dust, water, chemical species, ice...)
    16 c
    17 c   Name of the tracer
    18 c
    19 c   Test of dimension :
    20 c   Initialize tracer related data in tracer_mod, using tracer names provided
    21 c   by the dynamics in "infotrac"
    22 c
    23 c
    24 c   author: F.Forget
    25 c   ------
    26 c    Modifs: Franck Montmessin, Sebastien Lebonnois (june 2003)
    27 c            Ehouarn Millour (oct. 2008) identify tracers by their names
    28 c=======================================================================
    29 
    30 
    31       integer,intent(in) :: ngrid ! number of atmospheric columns
    32       integer,intent(in) :: nq ! number of tracers
    33       real,intent(out) :: qsurf(ngrid,nq) ! tracer on surface (e.g.  kg.m-2)
    34 
    35       integer iq,ig,count
    36       real r0_lift , reff_lift, nueff_lift
    37       real r0_storm,reff_storm
    38 c     Ratio of small over large dust particles (used when both
    39 c       doubleq and the submicron mode are active); In Montmessin
    40 c       et al. (2002), a value of 25 has been deduced;
    41       real, parameter :: popratio = 25.
    42       character(len=30) :: txt ! to store some text
    43       character(len=30), dimension(nq) :: idtracers
    44 
    45 c-----------------------------------------------------------------------
    46 c  radius(nq)      ! aerosol particle radius (m)
    47 c  rho_q(nq)       ! tracer densities (kg.m-3)
    48 c  alpha_lift(nq)  ! saltation vertical flux/horiz flux ratio (m-1)
    49 c  alpha_devil(nq) ! lifting coeeficient by dust devil
    50 c  rho_dust          ! Mars dust density
    51 c  rho_ice           ! Water ice density
    52 c  doubleq           ! if method with mass (iq=1) and number(iq=2) mixing ratio
    53 c  varian            ! Characteristic variance of log-normal distribution
    54 c-----------------------------------------------------------------------
     1MODULE initracer_mod
     2
     3implicit none
     4
     5contains
     6
     7SUBROUTINE initracer(ngrid,nq,qsurf)
     8
     9use tracer_mod
     10use comcstfi_h,     only: pi
     11use dust_param_mod, only: doubleq, submicron, dustbin
     12use callkeys_mod,   only: water, microphys, scavenging, rdstorm, &
     13                          topflows, photochem, callthermos, hdo, &
     14                          callnlte, nltemodel, dustinjection,    &
     15                          co2clouds, co2useh2o, meteo_flux
     16
     17implicit none
     18
     19! == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == =
     20!   subject:
     21!   --------
     22!   Initialization related to tracer
     23!   (transported dust, water, chemical species, ice...)
     24!
     25!   Name of the tracer
     26!
     27!   Test of dimension :
     28!   Initialize tracer related data in tracer_mod, using tracer names provided
     29!   by the dynamics in "infotrac"
     30!
     31!
     32!   author: F.Forget
     33!   ------
     34!    Modifs: Franck Montmessin, Sebastien Lebonnois (june 2003)
     35!            Ehouarn Millour (oct. 2008) identify tracers by their names
     36!            JB Clement (juillet 2025), upgrading to F90 with module
     37! == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == == =
     38
     39
     40integer, intent(in) :: ngrid ! number of atmospheric columns
     41integer, intent(in) :: nq    ! number of tracers
     42real, intent(out) :: qsurf(ngrid,nq) ! tracer on surface (e.g.  kg.m-2)
     43
     44integer :: iq,ig,count
     45real    :: r0_lift, reff_lift, nueff_lift
     46real    :: r0_storm, reff_storm
     47! Ratio of small over large dust particles (used when both
     48!   doubleq and the submicron mode are active); In Montmessin
     49!   et al. (2002), a value of 25 has been deduced;
     50real, parameter                  :: popratio = 25.
     51character(len=30)                :: txt ! to store some text
     52character(len=30), dimension(nq) :: idtracers
     53
     54!-----------------------------------------------------------------------
     55!  radius(nq)      ! aerosol particle radius (m)
     56!  rho_q(nq)       ! tracer densities (kg.m-3)
     57!  alpha_lift(nq)  ! saltation vertical flux/horiz flux ratio (m-1)
     58!  alpha_devil(nq) ! lifting coeeficient by dust devil
     59!  rho_dust          ! Mars dust density
     60!  rho_ice           ! Water ice density
     61!  doubleq           ! if method with mass (iq=1) and number(iq=2) mixing ratio
     62!  varian            ! Characteristic variance of log-normal distribution
     63!-----------------------------------------------------------------------
    5564
    5665! Sanity check: check that we are running with at least 1 tracer:
    57       if (nq<1) then
    58         write(*,*) "initracer error, nq=",nq," must be >=1!"
    59         call abort_physic("initracer","nq<1",1)
    60       endif
    61 c------------------------------------------------------------
    62 c         NAME and molar mass of the tracer
    63 c------------------------------------------------------------
    64    
     66if (nq<1) then
     67    write(*,*) "initracer error, nq=",nq," must be >=1!"
     68    call abort_physic("initracer","nq<1",1)
     69endif
     70!------------------------------------------------------------
     71!         NAME and molar mass of the tracer
     72!------------------------------------------------------------
     73
    6574! Identify tracers by their names: (and set corresponding values of mmol)
    66       ! 0. initialize tracer indexes to zero:
    67       igcm_dustbin(1:nq)=0
    68       igcm_co2_ice=0
    69       igcm_ccnco2_mass=0
    70       igcm_ccnco2_number=0
    71       igcm_ccnco2_meteor_mass=0
    72       igcm_ccnco2_meteor_number=0
    73       igcm_ccnco2_h2o_mass_ice=0
    74       igcm_ccnco2_h2o_mass_ccn=0
    75       igcm_ccnco2_h2o_number=0
    76       igcm_dust_mass=0
    77       igcm_dust_number=0
    78       igcm_ccn_mass=0
    79       igcm_ccn_number=0
    80       igcm_dust_submicron=0
    81       igcm_h2o_vap=0
    82       igcm_h2o_ice=0
    83       igcm_hdo_vap=0
    84       igcm_hdo_ice=0
    85       igcm_stormdust_mass=0
    86       igcm_stormdust_number=0
    87       igcm_topdust_mass=0
    88       igcm_topdust_number=0
    89       igcm_co2=0
    90       igcm_co=0
    91       igcm_o=0
    92       igcm_o1d=0
    93       igcm_o2=0
    94       igcm_o3=0
    95       igcm_h=0
    96       igcm_d=0
    97       igcm_hd=0
    98       igcm_h2=0
    99       igcm_od=0
    100       igcm_do2=0
    101       igcm_hdo2=0
    102       igcm_oh=0
    103       igcm_ho2=0
    104       igcm_h2o2=0
    105       igcm_ch4=0
    106       igcm_n2=0
    107       igcm_ar=0
    108       igcm_ar_n2=0
    109       igcm_n=0
    110       igcm_no=0
    111       igcm_no2=0
    112       igcm_n2d=0
    113       igcm_he=0
    114       igcm_co2plus=0
    115       igcm_oplus=0
    116       igcm_o2plus=0
    117       igcm_coplus=0
    118       igcm_cplus=0
    119       igcm_nplus=0
    120       igcm_noplus=0
    121       igcm_n2plus=0
    122       igcm_hplus=0
    123       igcm_hco2plus=0
    124       igcm_hcoplus=0
    125       igcm_h2oplus=0
    126       igcm_h3oplus=0
    127       igcm_ohplus=0
    128       igcm_elec=0
    129      
    130       ! 1. find dust tracers
    131       count=0
    132       if (dustbin.gt.0) then
    133         do iq=1,nq
    134           txt=" "
    135           write(txt,'(a4,i2.2)')'dust',count+1
    136           if (noms(iq).eq.txt) then
    137             count=count+1
    138             idtracers(count) = txt
    139             igcm_dustbin(count)=iq
    140             mmol(iq)=100.
    141           endif
    142         enddo !do iq=1,nq
    143       endif ! of if (dustbin.gt.0)
    144       if (doubleq) then
    145         do iq=1,nq
    146           if (noms(iq).eq."dust_mass") then
     75! 0. initialize tracer indexes to zero:
     76igcm_dustbin(1:nq)=0
     77igcm_co2_ice=0
     78igcm_ccnco2_mass=0
     79igcm_ccnco2_number=0
     80igcm_ccnco2_meteor_mass=0
     81igcm_ccnco2_meteor_number=0
     82igcm_ccnco2_h2o_mass_ice=0
     83igcm_ccnco2_h2o_mass_ccn=0
     84igcm_ccnco2_h2o_number=0
     85igcm_dust_mass=0
     86igcm_dust_number=0
     87igcm_ccn_mass=0
     88igcm_ccn_number=0
     89igcm_dust_submicron=0
     90igcm_h2o_vap=0
     91igcm_h2o_ice=0
     92igcm_hdo_vap=0
     93igcm_hdo_ice=0
     94igcm_stormdust_mass=0
     95igcm_stormdust_number=0
     96igcm_topdust_mass=0
     97igcm_topdust_number=0
     98igcm_co2=0
     99igcm_co=0
     100igcm_o=0
     101igcm_o1d=0
     102igcm_o2=0
     103igcm_o3=0
     104igcm_h=0
     105igcm_d=0
     106igcm_hd=0
     107igcm_h2=0
     108igcm_od=0
     109igcm_do2=0
     110igcm_hdo2=0
     111igcm_oh=0
     112igcm_ho2=0
     113igcm_h2o2=0
     114igcm_ch4=0
     115igcm_n2=0
     116igcm_ar=0
     117igcm_ar_n2=0
     118igcm_n=0
     119igcm_no=0
     120igcm_no2=0
     121igcm_n2d=0
     122igcm_he=0
     123igcm_co2plus=0
     124igcm_oplus=0
     125igcm_o2plus=0
     126igcm_coplus=0
     127igcm_cplus=0
     128igcm_nplus=0
     129igcm_noplus=0
     130igcm_n2plus=0
     131igcm_hplus=0
     132igcm_hco2plus=0
     133igcm_hcoplus=0
     134igcm_h2oplus=0
     135igcm_h3oplus=0
     136igcm_ohplus=0
     137igcm_elec=0
     138
     139! 1. find dust tracers
     140count=0
     141if (dustbin>0) then
     142    do iq=1,nq
     143        txt=" "
     144        write(txt,'(a4,i2.2)')'dust',count+1
     145        if (noms(iq) == txt) then
     146        count = count + 1
     147        idtracers(count) = txt
     148        igcm_dustbin(count)=iq
     149        mmol(iq)=100.
     150        endif
     151    enddo !do iq=1,nq
     152endif ! of if (dustbin>0)
     153if (doubleq) then
     154    do iq=1,nq
     155        if (noms(iq) == "dust_mass") then
    147156            igcm_dust_mass=iq
    148             count=count+1
     157            count = count + 1
    149158            idtracers(count) = "dust_mass"
    150           endif
    151           if (noms(iq).eq."dust_number") then
     159        endif
     160        if (noms(iq) == "dust_number") then
    152161            igcm_dust_number=iq
    153             count=count+1
     162            count = count + 1
    154163            idtracers(count) = "dust_number"
    155           endif
    156         enddo
    157       endif ! of if (doubleq)
    158       if (microphys) then
    159         do iq=1,nq
    160           if (noms(iq).eq."ccn_mass") then
     164        endif
     165    enddo
     166endif ! of if (doubleq)
     167if (microphys) then
     168    do iq=1,nq
     169        if (noms(iq) == "ccn_mass") then
    161170            igcm_ccn_mass=iq
    162             count=count+1
     171            count = count + 1
    163172            idtracers(count) = "ccn_mass"
    164           endif
    165           if (noms(iq).eq."ccn_number") then
     173        endif
     174        if (noms(iq) == "ccn_number") then
    166175            igcm_ccn_number=iq
    167             count=count+1
     176            count = count + 1
    168177            idtracers(count) = "ccn_number"
    169           endif
    170         enddo
    171       endif ! of if (microphys)
    172       if (submicron) then
    173         do iq=1,nq
    174           if (noms(iq).eq."dust_submicron") then
     178        endif
     179    enddo
     180endif ! of if (microphys)
     181if (submicron) then
     182    do iq=1,nq
     183        if (noms(iq) == "dust_submicron") then
    175184            igcm_dust_submicron=iq
    176185            mmol(iq)=100.
    177             count=count+1
     186            count = count + 1
    178187            idtracers(count) = "dust_submicron"
    179           endif
    180         enddo
    181       endif ! of if (submicron)
    182        if (rdstorm) then
    183         do iq=1,nq
    184           if (noms(iq).eq."stormdust_mass") then
     188        endif
     189    enddo
     190endif ! of if (submicron)
     191if (rdstorm) then
     192    do iq=1,nq
     193        if (noms(iq) == "stormdust_mass") then
    185194            igcm_stormdust_mass=iq
    186             count=count+1
     195            count = count + 1
    187196            idtracers(count) = "stormdust_mass"
    188           endif
    189           if (noms(iq).eq."stormdust_number") then
     197        endif
     198        if (noms(iq) == "stormdust_number") then
    190199            igcm_stormdust_number=iq
    191             count=count+1
     200            count = count + 1
    192201            idtracers(count) = "stormdust_number"
    193           endif
    194         enddo
    195       endif ! of if (rdstorm)
    196        if (topflows) then
    197         do iq=1,nq
    198           if (noms(iq).eq."topdust_mass") then
     202        endif
     203    enddo
     204endif ! of if (rdstorm)
     205if (topflows) then
     206    do iq=1,nq
     207        if (noms(iq) == "topdust_mass") then
    199208            igcm_topdust_mass=iq
    200             count=count+1
     209            count = count + 1
    201210            idtracers(count) = "topdust_mass"
    202           endif
    203           if (noms(iq).eq."topdust_number") then
     211        endif
     212        if (noms(iq) == "topdust_number") then
    204213            igcm_topdust_number=iq
    205             count=count+1
     214            count = count + 1
    206215            idtracers(count) = "topdust_number"
    207           endif
    208         enddo
    209       endif ! of if (topflows)   
    210       ! 2. find chemistry and water tracers
    211       do iq=1,nq
    212         if (noms(iq).eq."co2") then
    213           igcm_co2=iq
    214           mmol(igcm_co2)=44.
    215           count=count+1
    216           idtracers(count) = "co2"
    217         endif
    218         if (noms(iq).eq."co") then
    219           igcm_co=iq
    220           mmol(igcm_co)=28.
    221           count=count+1
    222           idtracers(count) = "co"
    223         endif
    224         if (noms(iq).eq."o") then
    225           igcm_o=iq
    226           mmol(igcm_o)=16.
    227           count=count+1
    228           idtracers(count) = "o"
    229         endif
    230         if (noms(iq).eq."o1d") then
    231           igcm_o1d=iq
    232           mmol(igcm_o1d)=16.
    233           count=count+1
    234           idtracers(count) = "o1d"
    235         endif
    236         if (noms(iq).eq."o2") then
    237           igcm_o2=iq
    238           mmol(igcm_o2)=32.
    239           count=count+1
    240           idtracers(count) = "o2"
    241         endif
    242         if (noms(iq).eq."o3") then
    243           igcm_o3=iq
    244           mmol(igcm_o3)=48.
    245           count=count+1
    246           idtracers(count) = "o3"
    247         endif
    248         if (noms(iq).eq."h") then
    249           igcm_h=iq
    250           mmol(igcm_h)=1.
    251           count=count+1
    252           idtracers(count) = "h"
    253         endif
    254         if (noms(iq).eq."h2") then
    255           igcm_h2=iq
    256           mmol(igcm_h2)=2.
    257           count=count+1
    258           idtracers(count) = "h2"
    259         endif
    260         if (noms(iq).eq."oh") then
    261           igcm_oh=iq
    262           mmol(igcm_oh)=17.
    263           count=count+1
    264           idtracers(count) = "oh"
    265         endif
    266         if (noms(iq).eq."ho2") then
    267           igcm_ho2=iq
    268           mmol(igcm_ho2)=33.
    269           count=count+1
    270           idtracers(count) = "ho2"
    271         endif
    272         if (noms(iq).eq."h2o2") then
    273           igcm_h2o2=iq
    274           mmol(igcm_h2o2)=34.
    275           count=count+1
    276           idtracers(count) = "h2o2"
    277         endif
    278         if (noms(iq).eq."n2") then
    279           igcm_n2=iq
    280           mmol(igcm_n2)=28.
    281           count=count+1
    282           idtracers(count) = "n2"
    283         endif
    284         if (noms(iq).eq."ch4") then
    285           igcm_ch4=iq
    286           mmol(igcm_ch4)=16.
    287           count=count+1
    288           idtracers(count) = "ch4"
    289         endif
    290         if (noms(iq).eq."ar") then
    291           igcm_ar=iq
    292           mmol(igcm_ar)=40.
    293           count=count+1
    294           idtracers(count) = "ar"
    295         endif
    296         if (noms(iq).eq."n") then
    297           igcm_n=iq
    298           mmol(igcm_n)=14.
    299           count=count+1
    300           idtracers(count) = "n"
    301         endif
    302         if (noms(iq).eq."no") then
    303           igcm_no=iq
    304           mmol(igcm_no)=30.
    305           count=count+1
    306           idtracers(count) = "no"
    307         endif
    308         if (noms(iq).eq."no2") then
    309           igcm_no2=iq
    310           mmol(igcm_no2)=46.
    311           count=count+1
    312           idtracers(count) = "no2"
    313         endif
    314         if (noms(iq).eq."n2d") then
    315           igcm_n2d=iq
    316           mmol(igcm_n2d)=28.
    317           count=count+1
    318           idtracers(count) = "n2d"
    319         endif
    320         if (noms(iq).eq."he") then
    321           igcm_he=iq
    322           mmol(igcm_he)=4.
    323           count=count+1
    324           idtracers(count) = "he"
    325         endif
    326         if (noms(iq).eq."co2plus") then
    327           igcm_co2plus=iq
    328           mmol(igcm_co2plus)=44.
    329           count=count+1
    330           idtracers(count) = "co2plus"
    331         endif
    332         if (noms(iq).eq."oplus") then
    333           igcm_oplus=iq
    334           mmol(igcm_oplus)=16.
    335           count=count+1
    336           idtracers(count) = "oplus"
    337         endif
    338         if (noms(iq).eq."o2plus") then
    339           igcm_o2plus=iq
    340           mmol(igcm_o2plus)=32.
    341           count=count+1
    342           idtracers(count) = "o2plus"
    343         endif
    344         if (noms(iq).eq."coplus") then
    345           igcm_coplus=iq
    346           mmol(igcm_coplus)=28.
    347           count=count+1
    348           idtracers(count) = "coplus"
    349         endif
    350         if (noms(iq).eq."cplus") then
    351           igcm_cplus=iq
    352           mmol(igcm_cplus)=12.
    353           count=count+1
    354           idtracers(count) = "cplus"
    355         endif
    356         if (noms(iq).eq."nplus") then
    357           igcm_nplus=iq
    358           mmol(igcm_nplus)=14.
    359           count=count+1
    360           idtracers(count) = "nplus"
    361         endif
    362         if (noms(iq).eq."noplus") then
    363           igcm_noplus=iq
    364           mmol(igcm_noplus)=30.
    365           count=count+1
    366           idtracers(count) = "noplus"
    367         endif
    368         if (noms(iq).eq."n2plus") then
    369           igcm_n2plus=iq
    370           mmol(igcm_n2plus)=28.
    371           count=count+1
    372           idtracers(count) = "n2plus"
    373         endif
    374         if (noms(iq).eq."hplus") then
    375           igcm_hplus=iq
    376           mmol(igcm_hplus)=1.
    377           count=count+1
    378           idtracers(count) = "hplus"
    379         endif
    380         if (noms(iq).eq."hco2plus") then
    381           igcm_hco2plus=iq
    382           mmol(igcm_hco2plus)=45.
    383           count=count+1
    384           idtracers(count) = "hco2plus"
    385         endif
    386         if (noms(iq).eq."hcoplus") then
    387           igcm_hcoplus=iq
    388           mmol(igcm_hcoplus)=29.
    389           count=count+1
    390           idtracers(count) = "hcoplus"
    391         endif
    392         if (noms(iq).eq."h2oplus") then
    393           igcm_h2oplus=iq
    394           mmol(igcm_h2oplus)=18.
    395           count=count+1
    396           idtracers(count) = "h2oplus"
    397         endif
    398         if (noms(iq).eq."h3oplus") then
    399           igcm_h3oplus=iq
    400           mmol(igcm_h3oplus)=19.
    401           count=count+1
    402           idtracers(count) = "h3oplus"
    403         endif
    404         if (noms(iq).eq."ohplus") then
    405           igcm_ohplus=iq
    406           mmol(igcm_ohplus)=17.
    407           count=count+1
    408           idtracers(count) = "ohplus"
    409         endif
    410         if (noms(iq).eq."elec") then
    411           igcm_elec=iq
    412           mmol(igcm_elec)=1./1822.89
    413           count=count+1
    414           idtracers(count) = "elec"
    415         endif
    416         if (noms(iq).eq."h2o_vap") then
    417           igcm_h2o_vap=iq
    418           mmol(igcm_h2o_vap)=18.
    419           count=count+1
    420           idtracers(count) = "h2o_vap"
    421         endif
    422         if (noms(iq).eq."hdo_vap") then
    423           igcm_hdo_vap=iq
    424           mmol(igcm_hdo_vap)=19.
    425           count=count+1
    426           idtracers(count) = "hdo_vap"
    427         endif
    428         if (noms(iq).eq."od") then
    429           igcm_od=iq
    430           mmol(igcm_od)=18.
    431           count=count+1
    432           idtracers(count) = "od"
    433         endif
    434         if (noms(iq).eq."d") then
    435            igcm_d=iq
    436            mmol(igcm_d)=2.
    437            count=count+1
    438            idtracers(count) = "d"
    439         endif
    440         if (noms(iq).eq."hd") then
    441            igcm_hd=iq
    442            mmol(igcm_hd)=3.
    443            count=count+1
    444            idtracers(count) = "hd"
    445         endif
    446         if (noms(iq).eq."do2") then
    447            igcm_do2=iq
    448            mmol(igcm_do2)=34.
    449            count=count+1
    450            idtracers(count) = "do2"
    451         endif
    452         if (noms(iq).eq."hdo2") then
    453            igcm_hdo2=iq
    454            mmol(igcm_hdo2)=35.
    455            count=count+1
    456            idtracers(count) = "hdo2"
    457         endif
    458         if (noms(iq).eq."co2_ice") then
    459           igcm_co2_ice=iq
    460           mmol(igcm_co2_ice)=44.
    461           count=count+1
    462           idtracers(count) = "co2_ice"
    463         endif
    464         if (noms(iq).eq."h2o_ice") then
    465           igcm_h2o_ice=iq
    466           mmol(igcm_h2o_ice)=18.
    467           count=count+1
    468           idtracers(count) = "h2o_ice"
    469         endif
    470         if (noms(iq).eq."hdo_ice") then
    471           igcm_hdo_ice=iq
    472           mmol(igcm_hdo_ice)=19.
    473           count=count+1
    474           idtracers(count) = "hdo_ice"
    475         endif
    476         ! Other stuff: e.g. for simulations using co2 + neutral gaz
    477         if (noms(iq).eq."Ar_N2") then
    478           igcm_ar_n2=iq
    479           mmol(igcm_ar_n2)=30.
    480           count=count+1
    481           idtracers(count) = "Ar_N2"
    482         endif
    483         if (co2clouds) then
    484            if (noms(iq).eq."ccnco2_mass") then
    485               igcm_ccnco2_mass=iq
    486               count=count+1
    487               idtracers(count) = "ccnco2_mass"
    488            endif
    489            if (noms(iq).eq."ccnco2_number") then
    490               igcm_ccnco2_number=iq
    491               count=count+1
    492               idtracers(count) = "ccnco2_number"
    493            endif
    494            if (meteo_flux) then
    495              if (noms(iq).eq."ccnco2_meteor_mass") then
     216        endif
     217    enddo
     218endif ! of if (topflows)
     219! 2. find chemistry and water tracers
     220do iq=1,nq
     221    if (noms(iq) == "co2") then
     222        igcm_co2=iq
     223        mmol(igcm_co2)=44.
     224        count = count + 1
     225        idtracers(count) = "co2"
     226    endif
     227    if (noms(iq) == "co") then
     228        igcm_co=iq
     229        mmol(igcm_co)=28.
     230        count = count + 1
     231        idtracers(count) = "co"
     232    endif
     233    if (noms(iq) == "o") then
     234        igcm_o=iq
     235        mmol(igcm_o)=16.
     236        count = count + 1
     237        idtracers(count) = "o"
     238    endif
     239    if (noms(iq) == "o1d") then
     240        igcm_o1d=iq
     241        mmol(igcm_o1d)=16.
     242        count = count + 1
     243        idtracers(count) = "o1d"
     244    endif
     245    if (noms(iq) == "o2") then
     246        igcm_o2=iq
     247        mmol(igcm_o2)=32.
     248        count = count + 1
     249        idtracers(count) = "o2"
     250    endif
     251    if (noms(iq) == "o3") then
     252        igcm_o3=iq
     253        mmol(igcm_o3)=48.
     254        count = count + 1
     255        idtracers(count) = "o3"
     256    endif
     257    if (noms(iq) == "h") then
     258        igcm_h=iq
     259        mmol(igcm_h)=1.
     260        count = count + 1
     261        idtracers(count) = "h"
     262    endif
     263    if (noms(iq) == "h2") then
     264        igcm_h2=iq
     265        mmol(igcm_h2)=2.
     266        count = count + 1
     267        idtracers(count) = "h2"
     268    endif
     269    if (noms(iq) == "oh") then
     270        igcm_oh=iq
     271        mmol(igcm_oh)=17.
     272        count = count + 1
     273        idtracers(count) = "oh"
     274    endif
     275    if (noms(iq) == "ho2") then
     276        igcm_ho2=iq
     277        mmol(igcm_ho2)=33.
     278        count = count + 1
     279        idtracers(count) = "ho2"
     280    endif
     281    if (noms(iq) == "h2o2") then
     282        igcm_h2o2=iq
     283        mmol(igcm_h2o2)=34.
     284        count = count + 1
     285        idtracers(count) = "h2o2"
     286    endif
     287    if (noms(iq) == "n2") then
     288        igcm_n2=iq
     289        mmol(igcm_n2)=28.
     290        count = count + 1
     291        idtracers(count) = "n2"
     292    endif
     293    if (noms(iq) == "ch4") then
     294        igcm_ch4=iq
     295        mmol(igcm_ch4)=16.
     296        count = count + 1
     297        idtracers(count) = "ch4"
     298    endif
     299    if (noms(iq) == "ar") then
     300        igcm_ar=iq
     301        mmol(igcm_ar)=40.
     302        count = count + 1
     303        idtracers(count) = "ar"
     304    endif
     305    if (noms(iq) == "n") then
     306        igcm_n=iq
     307        mmol(igcm_n)=14.
     308        count = count + 1
     309        idtracers(count) = "n"
     310    endif
     311    if (noms(iq) == "no") then
     312        igcm_no=iq
     313        mmol(igcm_no)=30.
     314        count = count + 1
     315        idtracers(count) = "no"
     316    endif
     317    if (noms(iq) == "no2") then
     318        igcm_no2=iq
     319        mmol(igcm_no2)=46.
     320        count = count + 1
     321        idtracers(count) = "no2"
     322    endif
     323    if (noms(iq) == "n2d") then
     324        igcm_n2d=iq
     325        mmol(igcm_n2d)=28.
     326        count = count + 1
     327        idtracers(count) = "n2d"
     328    endif
     329    if (noms(iq) == "he") then
     330        igcm_he=iq
     331        mmol(igcm_he)=4.
     332        count = count + 1
     333        idtracers(count) = "he"
     334    endif
     335    if (noms(iq) == "co2plus") then
     336        igcm_co2plus=iq
     337        mmol(igcm_co2plus)=44.
     338        count = count + 1
     339        idtracers(count) = "co2plus"
     340    endif
     341    if (noms(iq) == "oplus") then
     342        igcm_oplus=iq
     343        mmol(igcm_oplus)=16.
     344        count = count + 1
     345        idtracers(count) = "oplus"
     346    endif
     347    if (noms(iq) == "o2plus") then
     348        igcm_o2plus=iq
     349        mmol(igcm_o2plus)=32.
     350        count = count + 1
     351        idtracers(count) = "o2plus"
     352    endif
     353    if (noms(iq) == "coplus") then
     354        igcm_coplus=iq
     355        mmol(igcm_coplus)=28.
     356        count = count + 1
     357        idtracers(count) = "coplus"
     358    endif
     359    if (noms(iq) == "cplus") then
     360        igcm_cplus=iq
     361        mmol(igcm_cplus)=12.
     362        count = count + 1
     363        idtracers(count) = "cplus"
     364    endif
     365    if (noms(iq) == "nplus") then
     366        igcm_nplus=iq
     367        mmol(igcm_nplus)=14.
     368        count = count + 1
     369        idtracers(count) = "nplus"
     370    endif
     371    if (noms(iq) == "noplus") then
     372        igcm_noplus=iq
     373        mmol(igcm_noplus)=30.
     374        count = count + 1
     375        idtracers(count) = "noplus"
     376    endif
     377    if (noms(iq) == "n2plus") then
     378        igcm_n2plus=iq
     379        mmol(igcm_n2plus)=28.
     380        count = count + 1
     381        idtracers(count) = "n2plus"
     382    endif
     383    if (noms(iq) == "hplus") then
     384        igcm_hplus=iq
     385        mmol(igcm_hplus)=1.
     386        count = count + 1
     387        idtracers(count) = "hplus"
     388    endif
     389    if (noms(iq) == "hco2plus") then
     390        igcm_hco2plus=iq
     391        mmol(igcm_hco2plus)=45.
     392        count = count + 1
     393        idtracers(count) = "hco2plus"
     394    endif
     395    if (noms(iq) == "hcoplus") then
     396        igcm_hcoplus=iq
     397        mmol(igcm_hcoplus)=29.
     398        count = count + 1
     399        idtracers(count) = "hcoplus"
     400    endif
     401    if (noms(iq) == "h2oplus") then
     402        igcm_h2oplus=iq
     403        mmol(igcm_h2oplus)=18.
     404        count = count + 1
     405        idtracers(count) = "h2oplus"
     406    endif
     407    if (noms(iq) == "h3oplus") then
     408        igcm_h3oplus=iq
     409        mmol(igcm_h3oplus)=19.
     410        count = count + 1
     411        idtracers(count) = "h3oplus"
     412    endif
     413    if (noms(iq) == "ohplus") then
     414        igcm_ohplus=iq
     415        mmol(igcm_ohplus)=17.
     416        count = count + 1
     417        idtracers(count) = "ohplus"
     418    endif
     419    if (noms(iq) == "elec") then
     420        igcm_elec=iq
     421        mmol(igcm_elec)=1./1822.89
     422        count = count + 1
     423        idtracers(count) = "elec"
     424    endif
     425    if (noms(iq) == "h2o_vap") then
     426        igcm_h2o_vap=iq
     427        mmol(igcm_h2o_vap)=18.
     428        count = count + 1
     429        idtracers(count) = "h2o_vap"
     430    endif
     431    if (noms(iq) == "hdo_vap") then
     432        igcm_hdo_vap=iq
     433        mmol(igcm_hdo_vap)=19.
     434        count = count + 1
     435        idtracers(count) = "hdo_vap"
     436    endif
     437    if (noms(iq) == "od") then
     438        igcm_od=iq
     439        mmol(igcm_od)=18.
     440        count = count + 1
     441        idtracers(count) = "od"
     442    endif
     443    if (noms(iq) == "d") then
     444        igcm_d=iq
     445        mmol(igcm_d)=2.
     446        count = count + 1
     447        idtracers(count) = "d"
     448    endif
     449    if (noms(iq) == "hd") then
     450        igcm_hd=iq
     451        mmol(igcm_hd)=3.
     452        count = count + 1
     453        idtracers(count) = "hd"
     454    endif
     455    if (noms(iq) == "do2") then
     456        igcm_do2=iq
     457        mmol(igcm_do2)=34.
     458        count = count + 1
     459        idtracers(count) = "do2"
     460    endif
     461    if (noms(iq) == "hdo2") then
     462        igcm_hdo2=iq
     463        mmol(igcm_hdo2)=35.
     464        count = count + 1
     465        idtracers(count) = "hdo2"
     466    endif
     467    if (noms(iq) == "co2_ice") then
     468        igcm_co2_ice=iq
     469        mmol(igcm_co2_ice)=44.
     470        count = count + 1
     471        idtracers(count) = "co2_ice"
     472    endif
     473    if (noms(iq) == "h2o_ice") then
     474        igcm_h2o_ice=iq
     475        mmol(igcm_h2o_ice)=18.
     476        count = count + 1
     477        idtracers(count) = "h2o_ice"
     478    endif
     479    if (noms(iq) == "hdo_ice") then
     480        igcm_hdo_ice=iq
     481        mmol(igcm_hdo_ice)=19.
     482        count = count + 1
     483        idtracers(count) = "hdo_ice"
     484    endif
     485    ! Other stuff: e.g. for simulations using co2 + neutral gaz
     486    if (noms(iq) == "Ar_N2") then
     487        igcm_ar_n2=iq
     488        mmol(igcm_ar_n2)=30.
     489        count = count + 1
     490        idtracers(count) = "Ar_N2"
     491    endif
     492    if (co2clouds) then
     493        if (noms(iq) == "ccnco2_mass") then
     494            igcm_ccnco2_mass=iq
     495            count = count + 1
     496            idtracers(count) = "ccnco2_mass"
     497        endif
     498        if (noms(iq) == "ccnco2_number") then
     499            igcm_ccnco2_number=iq
     500            count = count + 1
     501            idtracers(count) = "ccnco2_number"
     502        endif
     503        if (meteo_flux) then
     504            if (noms(iq) == "ccnco2_meteor_mass") then
    496505                igcm_ccnco2_meteor_mass=iq
    497                 count=count+1
     506                count = count + 1
    498507                idtracers(count) = "ccnco2_meteor_mass"
    499              endif
    500              if (noms(iq).eq."ccnco2_meteor_number") then
     508            endif
     509            if (noms(iq) == "ccnco2_meteor_number") then
    501510                igcm_ccnco2_meteor_number=iq
    502                 count=count+1
     511                count = count + 1
    503512                idtracers(count) = "ccnco2_meteor_number"
    504              endif
    505            end if
    506            if (co2useh2o) then
    507            if (noms(iq).eq."ccnco2_h2o_number") then
    508               igcm_ccnco2_h2o_number=iq
    509               count=count+1
    510               idtracers(count) = "ccnco2_h2o_number"
    511            endif
    512            if (noms(iq).eq."ccnco2_h2o_mass_ice") then
    513               igcm_ccnco2_h2o_mass_ice=iq
    514               count=count+1
    515               idtracers(count) = "ccnco2_h2o_mass_ice"
    516            endif
    517            if (noms(iq).eq."ccnco2_h2o_mass_ccn") then
    518               igcm_ccnco2_h2o_mass_ccn=iq
    519               count=count+1
    520               idtracers(count) = "ccnco2_h2o_mass_ccn"
    521            endif
    522            end if
    523         endif
    524       enddo                     ! of do iq=1,nq
    525      
    526       ! check that we identified all tracers:
    527       if (count /= nq) then
    528         write(*,*) "initracer: found only",count,"tracers but",
    529      &nq,"are expected according to traceur.def!"
    530         write(*,*) "initracer: the only identified tracers are:"
    531         do iq = 1,count
    532           write(*,*) '      ',iq,trim(idtracers(iq))
    533         enddo
    534         call abort_physic("initracer","tracer mismatch",1)
    535       else
    536         write(*,*) "initracer: found all expected tracers, namely:"
    537         do iq = 1,nq
    538           write(*,*) '      ',iq,' ',trim(noms(iq))
    539         enddo
    540       endif
    541 
    542       ! if water cycle but iceparty=.false., there will nevertheless be
    543       ! water ice at the surface (iceparty is not used anymore, but this
    544       ! part is still relevant, as we want to stay compatible with the
    545       ! older versions).
    546       if (water.and.(igcm_h2o_ice.eq.0)) then
    547         igcm_h2o_ice=igcm_h2o_vap ! so that qsurf(i_h2o_ice) is identified
    548                                   ! even though there is no q(i_h2o_ice)
    549       else
    550        ! surface ice qsurf(i_h2o_ice) was loaded twice by phyetat0,
    551        ! as qsurf(i_h2o_vap) & as qsurf(i_h2o_ice), so to be clean:
    552        if (igcm_h2o_vap.ne.0) then
    553          qsurf(1:ngrid,igcm_h2o_vap)=0
    554        endif
    555       endif
    556 
    557       ! Additional test required for HDO
    558       ! We need to compute some things for H2O before HDO
    559       if (hdo) then
    560         if (igcm_h2o_vap.gt.igcm_hdo_vap) then
    561            call abort_physic("initracer",
    562      &          "Tracer H2O must be initialized before HDO",1)
    563         else if ((nqfils(igcm_h2o_ice).lt.1)
    564      &             .or. (nqfils(igcm_h2o_vap).lt.1)) then
    565            write(*,*) "HDO must be transported as a son",
    566      &                " of H2O: complete traceur.def"
    567            call abort_physic("initracer","adapt your tracer.def",1)
    568         else if ((igcm_hdo_ice.lt.nq-2)
    569      &             .or. (igcm_hdo_vap.lt.nq-2)) then
    570            write(*,*) "The isotopes (HDO) must be placed at",
    571      &                " the end of the list in traceur.def"
    572            call abort_physic("initracer","adapt your tracer.def",1)
    573         endif
    574       endif
    575 
    576 c------------------------------------------------------------
    577 c     Initialize tracers .... (in tracer_mod)
    578 c------------------------------------------------------------
    579       ! start by setting everything to (default) zero
    580       rho_q(1:nq)=0     ! tracer density (kg.m-3)
    581       radius(1:nq)=0.   ! tracer particle radius (m)
    582       alpha_lift(1:nq) =0.  ! tracer saltation vertical flux/horiz flux ratio (m-1)
    583       alpha_devil(1:nq)=0.  ! tracer lifting coefficient by dust devils
    584 
    585 
    586       ! some reference values
    587       rho_dust=2500.  ! Mars dust density (kg.m-3)
    588       rho_ice=920.    ! Water ice density (kg.m-3)
    589       rho_ice_co2=1650.
    590 
    591       if (doubleq) then
    592 c       "doubleq" technique
    593 c       -------------------
    594 c      (transport of mass and number mixing ratio)
    595 c       iq=1: Q mass mixing ratio, iq=2: N number mixing ratio
    596 
    597         if( (nq.lt.2).or.(water.and.(nq.lt.4))
    598      *       .or.(hdo.and.(nq.lt.6) )) then
    599           write(*,*)'initracer: nq is too low : nq=', nq
    600           write(*,*)'water= ',water,' doubleq= ',doubleq   
     513            endif
    601514        end if
    602 
    603         nueff_lift = 0.5
    604         varian=sqrt(log(1.+nueff_lift))
    605 
    606         rho_q(igcm_dust_mass)=rho_dust
    607         rho_q(igcm_dust_number)=rho_dust
    608 
    609 c       Intermediate calcul for computing geometric mean radius r0
    610 c       as a function of mass and number mixing ratio Q and N
    611 c       (r0 = (r3n_q * Q/ N)^(1/3))
    612         r3n_q = exp(-4.5*varian**2)*(3./4.)/(pi*rho_dust)
    613 
    614 c       Intermediate calcul for computing effective radius reff
    615 c       from geometric mean radius r0
    616 c       (reff = ref_r0 * r0)
    617         ref_r0 = exp(2.5*varian**2)
    618        
    619 c       lifted dust :
    620 c       '''''''''''
    621         reff_lift = 3.0e-6 !3.e-6 !Effective radius of lifted dust (m)
    622         alpha_devil(igcm_dust_mass)=9.e-9   !  dust devil lift mass coeff
    623 c       alpha_lift(igcm_dust_mass)=3.0e-15  !  Lifted mass coeff
    624 
    625 !! default lifting settings
    626 !! -- GCM: alpha_lift not zero because large-scale lifting by default
    627 !! -- MESOSCALE: alpha_lift zero because no lifting at all in mesoscale by default
     515        if (co2useh2o) then
     516            if (noms(iq) == "ccnco2_h2o_number") then
     517                igcm_ccnco2_h2o_number=iq
     518                count = count + 1
     519                idtracers(count) = "ccnco2_h2o_number"
     520            endif
     521            if (noms(iq) == "ccnco2_h2o_mass_ice") then
     522                igcm_ccnco2_h2o_mass_ice=iq
     523                count = count + 1
     524                idtracers(count) = "ccnco2_h2o_mass_ice"
     525            endif
     526            if (noms(iq) == "ccnco2_h2o_mass_ccn") then
     527                igcm_ccnco2_h2o_mass_ccn=iq
     528                count = count + 1
     529                idtracers(count) = "ccnco2_h2o_mass_ccn"
     530            endif
     531        end if
     532    endif
     533enddo ! of do iq=1,nq
     534
     535! check that we identified all tracers:
     536if (count /= nq) then
     537    write(*,*) "initracer: found only",count,"tracers but",nq,"are expected according to traceur.def!"
     538    write(*,*) "initracer: the only identified tracers are:"
     539    do iq = 1,count
     540        write(*,*) '      ',iq,trim(idtracers(iq))
     541    enddo
     542    call abort_physic("initracer","tracer mismatch",1)
     543else
     544    write(*,*) "initracer: found all expected tracers, namely:"
     545    do iq = 1,nq
     546        write(*,*) '      ',iq,' ',trim(noms(iq))
     547    enddo
     548endif
     549
     550! if water cycle but iceparty=.false., there will nevertheless be
     551! water ice at the surface (iceparty is not used anymore, but this
     552! part is still relevant, as we want to stay compatible with the
     553! older versions).
     554if (water.and.(igcm_h2o_ice == 0)) then
     555    igcm_h2o_ice=igcm_h2o_vap ! so that qsurf(i_h2o_ice) is identified
     556                              ! even though there is no q(i_h2o_ice)
     557else
     558    ! surface ice qsurf(i_h2o_ice) was loaded twice by phyetat0,
     559    ! as qsurf(i_h2o_vap) & as qsurf(i_h2o_ice), so to be clean:
     560    if (igcm_h2o_vap /= 0) then
     561        qsurf(1:ngrid,igcm_h2o_vap)=0
     562    endif
     563endif
     564
     565! Additional test required for HDO
     566! We need to compute some things for H2O before HDO
     567if (hdo) then
     568    if (igcm_h2o_vap>igcm_hdo_vap) then
     569        call abort_physic("initracer","Tracer H2O must be initialized before HDO",1)
     570    else if ((nqfils(igcm_h2o_ice)<1) .or. (nqfils(igcm_h2o_vap)<1)) then
     571        write(*,*) "HDO must be transported as a son of H2O: complete traceur.def"
     572        call abort_physic("initracer","adapt your tracer.def",1)
     573    else if ((igcm_hdo_ice < nq-2) .or. (igcm_hdo_vap < nq-2)) then
     574        write(*,*) "The isotopes (HDO) must be placed at the end of the list in traceur.def"
     575        call abort_physic("initracer","adapt your tracer.def",1)
     576    endif
     577endif
     578
     579!------------------------------------------------------------
     580!     Initialize tracers .... (in tracer_mod)
     581!------------------------------------------------------------
     582! start by setting everything to (default) zero
     583rho_q(1:nq)=0     ! tracer density (kg.m-3)
     584radius(1:nq)=0.   ! tracer particle radius (m)
     585alpha_lift(1:nq) =0.  ! tracer saltation vertical flux/horiz flux ratio (m-1)
     586alpha_devil(1:nq)=0.  ! tracer lifting coefficient by dust devils
     587
     588
     589! some reference values
     590rho_dust=2500.  ! Mars dust density (kg.m-3)
     591rho_ice=920.    ! Water ice density (kg.m-3)
     592rho_ice_co2=1650.
     593
     594if (doubleq) then
     595    ! "doubleq" technique
     596    ! -------------------
     597    ! transport of mass and number mixing ratio)
     598    ! iq=1: Q mass mixing ratio, iq=2: N number mixing ratio
     599
     600    if( (nq<2).or.(water.and.(nq<4)) .or.(hdo.and.(nq<6) )) then
     601        write(*,*)'initracer: nq is too low : nq=', nq
     602        write(*,*)'water= ',water,' doubleq= ',doubleq
     603    end if
     604
     605    nueff_lift = 0.5
     606    varian=sqrt(log(1.+nueff_lift))
     607
     608    rho_q(igcm_dust_mass)=rho_dust
     609    rho_q(igcm_dust_number)=rho_dust
     610
     611    ! Intermediate calcul for computing geometric mean radius r0
     612    ! as a function of mass and number mixing ratio Q and N
     613    ! (r0 = (r3n_q * Q/ N)^(1/3))
     614    r3n_q = exp(-4.5*varian**2)*(3./4.)/(pi*rho_dust)
     615
     616    ! Intermediate calcul for computing effective radius reff
     617    ! from geometric mean radius r0
     618    ! (reff = ref_r0 * r0)
     619    ref_r0 = exp(2.5*varian**2)
     620
     621    ! lifted dust :
     622    ! '''''''''''
     623    reff_lift = 3.0e-6 !3.e-6 !Effective radius of lifted dust (m)
     624    alpha_devil(igcm_dust_mass)=9.e-9   !  dust devil lift mass coeff
     625    ! alpha_lift(igcm_dust_mass)=3.0e-15  !  Lifted mass coeff
     626
     627    ! default lifting settings
     628    ! -- GCM: alpha_lift not zero because large-scale lifting by default
     629    ! -- MESOSCALE: alpha_lift zero because no lifting at all in mesoscale by default
    628630#ifdef MESOSCALE
    629         alpha_lift(igcm_dust_mass)=0.0
     631    alpha_lift(igcm_dust_mass)=0.0
    630632#else
    631         alpha_lift(igcm_dust_mass)=1.e-6 !1.e-6 !Lifted mass coeff
    632         IF (dustinjection.ge.1) THEN
    633                 reff_lift = 3.0e-6 ! Effective radius of lifted dust (m)
    634                 alpha_lift(igcm_dust_mass)=(4/3.)*reff_lift*rho_dust
    635      &                                          /2.4
    636         ENDIF
     633    alpha_lift(igcm_dust_mass)=1.e-6 !1.e-6 !Lifted mass coeff
     634    if (dustinjection >= 1) then
     635        reff_lift = 3.0e-6 ! Effective radius of lifted dust (m)
     636        alpha_lift(igcm_dust_mass)=(4/3.)*reff_lift*rho_dust/2.4
     637    endif
    637638#endif
    638639
    639         r0_lift = reff_lift/ref_r0
    640         alpha_devil(igcm_dust_number)=r3n_q*
    641      &                        alpha_devil(igcm_dust_mass)/r0_lift**3
    642         alpha_lift(igcm_dust_number)=r3n_q*
    643      &                        alpha_lift(igcm_dust_mass)/r0_lift**3
    644 
    645         radius(igcm_dust_mass) = reff_lift
    646         radius(igcm_dust_number) = reff_lift
    647 
    648         write(*,*) "initracer: doubleq_param reff_lift:", reff_lift
    649         write(*,*) "initracer: doubleq_param nueff_lift:", nueff_lift
    650         write(*,*) "initracer: doubleq_param alpha_lift:",
    651      &    alpha_lift(igcm_dust_mass)
    652 !c ----------------------------------------------------------------------
    653 !c rocket dust storm scheme
    654 !c lifting tracer stormdust using same distribution than
    655 !c normal dust
    656         if (rdstorm) then
    657           reff_storm=3.e-6 ! reff_lift !3.e-6
    658           r0_storm=reff_storm/ref_r0
    659           rho_q(igcm_stormdust_mass)=rho_dust
    660           rho_q(igcm_stormdust_number)=rho_dust
    661 
    662           alpha_devil(igcm_stormdust_mass)=9.e-9   ! dust devil lift mass coeff
    663           alpha_lift(igcm_stormdust_mass)=4./3./2.4*reff_storm*rho_dust
    664 
    665           write(*,*) 'alpha_lift(rds):',alpha_lift(igcm_stormdust_mass)
    666  
    667           alpha_devil(igcm_stormdust_number)=r3n_q*
    668      &                      alpha_devil(igcm_stormdust_mass)/r0_storm**3
    669           alpha_lift(igcm_stormdust_number)=r3n_q*
    670      &                       alpha_lift(igcm_stormdust_mass)/r0_storm**3
    671  
    672           radius(igcm_stormdust_mass) = reff_storm
    673           radius(igcm_stormdust_number) = reff_storm
    674         end if !(rdstorm)
    675 !c ----------------------------------------------------------------------
    676 !c mountain top dust flows scheme
    677 !c you need a radius value for topdust to active its sedimentation
    678 !c we take the same value as for the normal dust
    679         if (topflows) then
    680           rho_q(igcm_topdust_mass)=rho_dust
    681           rho_q(igcm_topdust_number)=rho_dust
    682           radius(igcm_topdust_mass) = 3.e-6
    683           radius(igcm_topdust_number) = 3.e-6
    684         end if !(topflows)
    685 !c ----------------------------------------------------------------------
    686      
    687       else
    688 
    689        ! initialize varian, which may be used (e.g. by surfacearea)
    690        ! even with conrath dust
    691        nueff_lift = 0.5
    692        varian=sqrt(log(1.+nueff_lift))
    693 
    694        if (dustbin.gt.1) then
    695         print*,'initracer: STOP!',
    696      $   ' properties of dust need to be set in initracer !!!'
     640    r0_lift = reff_lift/ref_r0
     641    alpha_devil(igcm_dust_number)=r3n_q*alpha_devil(igcm_dust_mass)/r0_lift**3
     642    alpha_lift(igcm_dust_number)=r3n_q*alpha_lift(igcm_dust_mass)/r0_lift**3
     643
     644    radius(igcm_dust_mass) = reff_lift
     645    radius(igcm_dust_number) = reff_lift
     646
     647    write(*,*) "initracer: doubleq_param reff_lift:", reff_lift
     648    write(*,*) "initracer: doubleq_param nueff_lift:", nueff_lift
     649    write(*,*) "initracer: doubleq_param alpha_lift:",alpha_lift(igcm_dust_mass)
     650    ! ----------------------------------------------------------------------
     651    ! rocket dust storm scheme
     652    ! lifting tracer stormdust using same distribution than
     653    ! normal dust
     654    if (rdstorm) then
     655        reff_storm=3.e-6 ! reff_lift !3.e-6
     656        r0_storm=reff_storm/ref_r0
     657        rho_q(igcm_stormdust_mass)=rho_dust
     658        rho_q(igcm_stormdust_number)=rho_dust
     659
     660        alpha_devil(igcm_stormdust_mass)=9.e-9   ! dust devil lift mass coeff
     661        alpha_lift(igcm_stormdust_mass)=4./3./2.4*reff_storm*rho_dust
     662
     663        write(*,*) 'alpha_lift(rds):',alpha_lift(igcm_stormdust_mass)
     664
     665        alpha_devil(igcm_stormdust_number)=r3n_q*alpha_devil(igcm_stormdust_mass)/r0_storm**3
     666        alpha_lift(igcm_stormdust_number)=r3n_q*alpha_lift(igcm_stormdust_mass)/r0_storm**3
     667
     668        radius(igcm_stormdust_mass) = reff_storm
     669        radius(igcm_stormdust_number) = reff_storm
     670    end if !(rdstorm)
     671    ! ----------------------------------------------------------------------
     672    ! mountain top dust flows scheme
     673    ! you need a radius value for topdust to active its sedimentation
     674    ! we take the same value as for the normal dust
     675    if (topflows) then
     676        rho_q(igcm_topdust_mass)=rho_dust
     677        rho_q(igcm_topdust_number)=rho_dust
     678        radius(igcm_topdust_mass) = 3.e-6
     679        radius(igcm_topdust_number) = 3.e-6
     680    end if !(topflows)
     681    ! ----------------------------------------------------------------------
     682
     683else
     684
     685    ! initialize varian, which may be used (e.g. by surfacearea)
     686    ! even with conrath dust
     687    nueff_lift = 0.5
     688    varian=sqrt(log(1.+nueff_lift))
     689
     690    if (dustbin>1) then
     691        print*,'initracer: STOP! properties of dust need to be set in initracer!!!'
    697692        call abort_physic("initracer","dustbin properties issue",1)
    698693
    699        else if (dustbin.eq.1) then
    700 
    701 c       This will be used for 1 dust particle size:
    702 c       ------------------------------------------
     694    else if (dustbin == 1) then
     695
     696!       This will be used for 1 dust particle size:
     697!       ------------------------------------------
    703698        radius(igcm_dustbin(1))=3.e-6
    704699        alpha_lift(igcm_dustbin(1))=0.0e-6
     
    706701        rho_q(igcm_dustbin(1))=rho_dust
    707702
    708        endif
    709       end if    ! (doubleq)
    710 
    711 
    712 c     Scavenging of dust particles by H2O clouds:
    713 c     ------------------------------------------
    714 c     Initialize the two tracers used for the CCNs
    715       if (water.AND.doubleq.AND.scavenging) then
    716         radius(igcm_ccn_mass) = radius(igcm_dust_mass)
    717         alpha_lift(igcm_ccn_mass) = 1e-30
    718         alpha_devil(igcm_ccn_mass) = 1e-30
    719         rho_q(igcm_ccn_mass) = rho_dust
    720 
    721         radius(igcm_ccn_number) = radius(igcm_ccn_mass)
    722         alpha_lift(igcm_ccn_number) = alpha_lift(igcm_ccn_mass)
    723         alpha_devil(igcm_ccn_number) = alpha_devil(igcm_ccn_mass)
    724         rho_q(igcm_ccn_number) = rho_q(igcm_ccn_mass)
    725       endif ! of if (water.AND.doubleq.AND.scavenging)
    726 
    727 c     Submicron dust mode:
    728 c     --------------------
    729 
    730       if (submicron) then
    731         radius(igcm_dust_submicron)=0.1e-6
    732         rho_q(igcm_dust_submicron)=rho_dust
    733         if (doubleq) then
    734 c         If doubleq is also active, we use the population ratio:
    735           alpha_lift(igcm_dust_submicron) =
    736      &      alpha_lift(igcm_dust_number)*popratio*
    737      &      rho_q(igcm_dust_submicron)*4./3.*pi*
    738      &      radius(igcm_dust_submicron)**3.
    739           alpha_devil(igcm_dust_submicron)=1.e-30
    740         else
    741           alpha_lift(igcm_dust_submicron)=1e-6
    742           alpha_devil(igcm_dust_submicron)=1.e-30
    743         endif ! (doubleq)
    744       end if  ! (submicron)
    745 
    746 c     Initialization for water vapor
    747 c     ------------------------------
    748       if(water) then
    749          radius(igcm_h2o_vap)=0.
    750          alpha_lift(igcm_h2o_vap) =0.
    751          alpha_devil(igcm_h2o_vap)=0.
    752          if(water.and.(nq.ge.2)) then
    753            radius(igcm_h2o_ice)=3.e-6
    754            rho_q(igcm_h2o_ice)=rho_ice
    755            alpha_lift(igcm_h2o_ice) =0.
    756            alpha_devil(igcm_h2o_ice)=0.
    757          elseif(water.and.(nq.lt.2)) then
    758             write(*,*) 'nq is too low : nq=', nq
    759             write(*,*) 'water= ',water
    760          endif
    761 
    762       end if  ! (water)
    763 
    764 c     Initialization for hdo vapor
    765 c     ------------------------------
    766       if (hdo) then
    767          radius(igcm_hdo_vap)=0.
    768          alpha_lift(igcm_hdo_vap) =0.
    769          alpha_devil(igcm_hdo_vap)=0.
    770          if(water.and.(nq.ge.2)) then
    771            radius(igcm_hdo_ice)=3.e-6
    772            rho_q(igcm_hdo_ice)=rho_ice
    773            alpha_lift(igcm_hdo_ice) =0.
    774            alpha_devil(igcm_hdo_ice)=0.
    775          elseif(hdo.and.(nq.lt.6)) then
    776             write(*,*) 'nq is too low : nq=', nq
    777             write(*,*) 'hdo= ',hdo
    778          endif
    779 
    780       end if  ! (hdo)
    781 
    782      
    783 
    784 c     Output for records:
    785 c     ~~~~~~~~~~~~~~~~~~
    786       write(*,*)
    787       Write(*,*) '******** initracer : dust transport parameters :'
    788       write(*,*) 'alpha_lift = ', alpha_lift
    789       write(*,*) 'alpha_devil = ', alpha_devil
    790       write(*,*) 'radius  = ', radius
    791       if(doubleq) then
    792         write(*,*) 'reff_lift (um) =  ', reff_lift
    793         write(*,*) 'size distribution variance  = ', varian
    794         write(*,*) 'r3n_q , ref_r0 : ', r3n_q , ref_r0
    795       end if
     703    endif
     704end if    ! (doubleq)
     705
     706
     707! Scavenging of dust particles by H2O clouds:
     708! ------------------------------------------
     709! Initialize the two tracers used for the CCNs
     710if (water.and.doubleq.and.scavenging) then
     711    radius(igcm_ccn_mass) = radius(igcm_dust_mass)
     712    alpha_lift(igcm_ccn_mass) = 1e-30
     713    alpha_devil(igcm_ccn_mass) = 1e-30
     714    rho_q(igcm_ccn_mass) = rho_dust
     715
     716    radius(igcm_ccn_number) = radius(igcm_ccn_mass)
     717    alpha_lift(igcm_ccn_number) = alpha_lift(igcm_ccn_mass)
     718    alpha_devil(igcm_ccn_number) = alpha_devil(igcm_ccn_mass)
     719    rho_q(igcm_ccn_number) = rho_q(igcm_ccn_mass)
     720endif ! of if (water.AND.doubleq.AND.scavenging)
     721
     722! Submicron dust mode:
     723! --------------------
     724if (submicron) then
     725    radius(igcm_dust_submicron)=0.1e-6
     726    rho_q(igcm_dust_submicron)=rho_dust
     727    if (doubleq) then
     728!        If doubleq is also active, we use the population ratio:
     729        alpha_lift(igcm_dust_submicron) = alpha_lift(igcm_dust_number)*popratio*rho_q(igcm_dust_submicron)*4./3.*pi*radius(igcm_dust_submicron)**3.
     730        alpha_devil(igcm_dust_submicron)=1.e-30
     731    else
     732        alpha_lift(igcm_dust_submicron)=1e-6
     733        alpha_devil(igcm_dust_submicron)=1.e-30
     734    endif ! (doubleq)
     735end if  ! (submicron)
     736
     737! Initialization for water vapor
     738! ------------------------------
     739if (water) then
     740    radius(igcm_h2o_vap)=0.
     741    alpha_lift(igcm_h2o_vap) =0.
     742    alpha_devil(igcm_h2o_vap)=0.
     743    if (water.and.(nq>=2)) then
     744        radius(igcm_h2o_ice)=3.e-6
     745        rho_q(igcm_h2o_ice)=rho_ice
     746        alpha_lift(igcm_h2o_ice) =0.
     747        alpha_devil(igcm_h2o_ice)=0.
     748    else if(water.and.(nq<2)) then
     749        write(*,*) 'nq is too low : nq=', nq
     750        write(*,*) 'water= ',water
     751    endif
     752end if  ! (water)
     753
     754! Initialization for hdo vapor
     755! ------------------------------
     756if (hdo) then
     757    radius(igcm_hdo_vap)=0.
     758    alpha_lift(igcm_hdo_vap) =0.
     759    alpha_devil(igcm_hdo_vap)=0.
     760    if (water.and.(nq>=2)) then
     761        radius(igcm_hdo_ice)=3.e-6
     762        rho_q(igcm_hdo_ice)=rho_ice
     763        alpha_lift(igcm_hdo_ice) =0.
     764        alpha_devil(igcm_hdo_ice)=0.
     765    else if (hdo.and.(nq<6)) then
     766        write(*,*) 'nq is too low : nq=', nq
     767        write(*,*) 'hdo= ',hdo
     768    endif
     769end if  ! (hdo)
     770
     771! Output for records:
     772! ~~~~~~~~~~~~~~~~~~
     773write(*,*)
     774Write(*,*) '******** initracer : dust transport parameters :'
     775write(*,*) 'alpha_lift = ', alpha_lift
     776write(*,*) 'alpha_devil = ', alpha_devil
     777write(*,*) 'radius  = ', radius
     778if(doubleq) then
     779    write(*,*) 'reff_lift (um) =  ', reff_lift
     780    write(*,*) 'size distribution variance  = ', varian
     781    write(*,*) 'r3n_q , ref_r0 : ', r3n_q , ref_r0
     782end if
    796783
    797784!
    798 !     some extra (possibly redundant) sanity checks for tracers:
    799 !     ---------------------------------------------------------
    800 
    801        if (doubleq) then
    802        ! verify that we indeed have dust_mass and dust_number tracers
    803          if (igcm_dust_mass.eq.0) then
    804            write(*,*) "initracer: error !!"
    805            write(*,*) "  cannot use doubleq option without ",
    806      &                "a dust_mass tracer !"
     785! some extra (possibly redundant) sanity checks for tracers:
     786! ---------------------------------------------------------
     787if (doubleq) then
     788    ! verify that we indeed have dust_mass and dust_number tracers
     789    if (igcm_dust_mass == 0) then
     790           write(*,*) "initracer: error!"
     791            write(*,*) "  Cannot use doubleq option without a dust_mass tracer!"
    807792           call abort_physic("initracer","doubleq issue",1)
    808          endif
    809          if (igcm_dust_number.eq.0) then
    810            write(*,*) "initracer: error !!"
    811            write(*,*) "  cannot use doubleq option without ",
    812      &                "a dust_number tracer !"
    813            call abort_physic("initracer","doubleq issue",1)
    814          endif
    815        endif
    816 
    817        if ((.not.doubleq).and.(dustbin.gt.0)) then
    818        ! verify that we indeed have 'dustbin' dust tracers
    819          count=0
    820          do iq=1,dustbin
    821            if (igcm_dustbin(iq).ne.0) then
    822              count=count+1
    823            endif
    824          enddo
    825          if (count.ne.dustbin) then
    826            write(*,*) "initracer: error !!"
    827            write(*,*) "  dustbin is set to ",dustbin,
    828      &                " but we only have the following dust tracers:"
    829            do iq=1,count
    830              write(*,*)"   ",trim(noms(igcm_dustbin(iq)))
    831            enddo
    832            call abort_physic("initracer","dustbin issue",1)
    833          endif
    834        endif
    835 
    836        if (water) then
    837        ! verify that we indeed have h2o_vap and h2o_ice tracers
    838          if (igcm_h2o_vap.eq.0) then
    839            write(*,*) "initracer: error !!"
    840            write(*,*) "  cannot use water option without ",
    841      &                "an h2o_vap tracer !"
    842            call abort_physic("initracer","water cycle issue",1)
    843          endif
    844          if (igcm_h2o_ice.eq.0) then
    845            write(*,*) "initracer: error !!"
    846            write(*,*) "  cannot use water option without ",
    847      &                "an h2o_ice tracer !"
    848            call abort_physic("initracer","water cycle issue",1)
    849          endif
    850        endif
    851 
    852        if (hdo) then
    853        ! verify that we indeed have hdo_vap and hdo_ice tracers
    854          if (igcm_hdo_vap.eq.0) then
    855            write(*,*) "initracer: error !!"
    856            write(*,*) "  cannot use hdo option without ",
    857      &                "an hdo_vap tracer !"
    858            call abort_physic("initracer","hdo cycle issue",1)
    859          endif
    860          if (igcm_hdo_ice.eq.0) then
    861            write(*,*) "initracer: error !!"
    862            write(*,*) "  cannot use hdo option without ",
    863      &                "an hdo_ice tracer !"
    864            call abort_physic("initracer","hdo cycle issue",1)
    865          endif
    866        endif
    867 
    868        if (microphys) then
    869        ! verify that we indeed have ccn_number and ccn_mass tracers
    870          if (igcm_ccn_number == 0) then
    871            write(*,*) "initracer: error !!"
    872            write(*,*) "  cannot use microphys option without ",
    873      &                "a ccn_number tracer !"
    874            call abort_physic("initracer","water cycle issue",1)
    875          endif
    876          if (igcm_ccn_mass == 0) then
    877            write(*,*) "initracer: error !!"
    878            write(*,*) "  cannot use microphys option without ",
    879      &                "a ccn_mass tracer !"
    880            call abort_physic("initracer","microphys issue",1)
    881          endif
    882        endif
    883 
    884 
    885        if (co2clouds) then
    886           !verify that we have co2_ice and co2 tracers
    887           if (igcm_co2 .eq. 0) then
    888              write(*,*) "initracer: error !!"
    889              write(*,*) "  cannot use co2 clouds option without ",
    890      &            "a co2 tracer !"
    891              call abort_physic("initracer","co2 clouds issue",1)
    892           end if
    893           if (igcm_co2_ice .eq. 0) then
    894              write(*,*) "initracer: error !!"
    895              write(*,*) "  cannot use co2 clouds option without ",
    896      &            "a co2_ice tracer !"
    897              call abort_physic("initracer","co2 clouds issue",1)
    898           end if
    899           if (igcm_ccnco2_number .eq. 0) then
    900              write(*,*) "initracer: error !!"
    901              write(*,*) "  cannot use co2 clouds option without ",
    902      &            "a ccnco2_number tracer !"
    903              call abort_physic("initracer","co2 clouds issue",1)
    904           end if
    905           if (igcm_ccnco2_mass .eq. 0) then
    906              write(*,*) "initracer: error !!"
    907              write(*,*) "  cannot use co2 clouds option without ",
    908      &            "a ccnco2_mass tracer !"
    909              call abort_physic("initracer","co2 clouds issue",1)
    910           end if
    911           if (co2useh2o) then
    912             if (igcm_ccnco2_h2o_number .eq. 0) then
    913                write(*,*) "initracer: error !!"
    914                write(*,*) "  cannot use co2 clouds option without ",
    915      &              "a ccnco2_h2o_number tracer !"
    916                call abort_physic("initracer","co2 clouds issue",1)
    917             end if
    918             if (igcm_ccnco2_h2o_mass_ice .eq. 0) then
    919                write(*,*) "initracer: error !!"
    920                write(*,*) "  cannot use co2 clouds option without ",
    921      &              "a ccnco2_h2o_mass_ice tracer !"
    922                call abort_physic("initracer","co2 clouds issue",1)
    923             end if
    924             if (igcm_ccnco2_h2o_mass_ccn .eq. 0) then
    925                write(*,*) "initracer: error !!"
    926                write(*,*) "  cannot use co2 clouds option without ",
    927      &              "a ccnco2_h2o_mass_ccn tracer !"
    928                call abort_physic("initracer","co2 clouds issue",1)
    929             end if
    930           end if
    931           if (meteo_flux) then
    932             if (igcm_ccnco2_meteor_number .eq. 0) then
    933                write(*,*) "initracer: error !!"
    934                write(*,*) "  cannot use co2 clouds option without ",
    935      &              "a ccnco2_meteor_number tracer !"
    936                call abort_physic("initracer","co2 clouds issue",1)
    937             end if
    938             if (igcm_ccnco2_meteor_mass .eq. 0) then
    939                write(*,*) "initracer: error !!"
    940                write(*,*) "  cannot use co2 clouds option without ",
    941      &              "a ccnco2_h2o_mass_ice tracer !"
    942                call abort_physic("initracer","co2 clouds issue",1)
    943             end if
    944             if (igcm_ccnco2_meteor_mass .eq. 0) then
    945                write(*,*) "initracer: error !!"
    946                write(*,*) "  cannot use co2 clouds option without ",
    947      &              "a ccnco2_meteor_mass tracer !"
    948                call abort_physic("initracer","co2 clouds issue",1)
    949             end if
    950           end if
    951        endif
    952  
    953        if (rdstorm) then
    954        ! verify that we indeed have stormdust_mass and stormdust_number tracers
    955          if (igcm_stormdust_mass.eq.0) then
    956            write(*,*) "initracer: error !!"
    957            write(*,*) "  cannot use rdstorm option without ",
    958      &                "a stormdust_mass tracer !"
    959            call abort_physic("initracer","rdstorm issue",1)
    960          endif
    961          if (igcm_stormdust_number.eq.0) then
    962            write(*,*) "initracer: error !!"
    963            write(*,*) "  cannot use rdstorm option without ",
    964      &                "a stormdust_number tracer !"
    965            call abort_physic("initracer","rdstorm issue",1)
    966          endif
    967        endif
    968 
    969        if (topflows) then
    970        ! verify that we indeed have topdust_mass and topdust_number tracers
    971          if (igcm_topdust_mass.eq.0) then
    972            write(*,*) "initracer: error !!"
    973            write(*,*) "  cannot use topflows option without ",
    974      &                "a topdust_mass tracer !"
    975            call abort_physic("initracer","topflows issue",1)
    976          endif
    977          if (igcm_topdust_number.eq.0) then
    978            write(*,*) "initracer: error !!"
    979            write(*,*) "  cannot use topflows option without ",
    980      &                "a topdust_number tracer !"
    981            call abort_physic("initracer","topflows issue",1)
    982          endif
    983        endif
    984      
    985        if (callnlte) then ! NLTE requirements
    986          if (nltemodel.ge.1) then
    987            ! check that co2, co, o and n2 tracers are available
    988            if (igcm_co2.eq.0) then
    989              write(*,*) "initracer: error !!"
    990              write(*,*) "  with nltemodel>0, we need the co2 tracer!"
    991              call abort_physic("initracer","missing co2 tracer",1)
    992            endif
    993            if (igcm_co.eq.0) then
    994              write(*,*) "initracer: error !!"
    995              write(*,*) "  with nltemodel>0, we need the co tracer!"
    996              call abort_physic("initracer","missing co tracer",1)
    997            endif
    998            if (igcm_o.eq.0) then
    999              write(*,*) "initracer: error !!"
    1000              write(*,*) "  with nltemodel>0, we need the o tracer!"
    1001              call abort_physic("initracer","missing o tracer",1)
    1002            endif
    1003            if (igcm_n2.eq.0) then
    1004              write(*,*) "initracer: error !!"
    1005              write(*,*) "  with nltemodel>0, we need the n2 tracer!"
    1006              call abort_physic("initracer","missing n2 tracer",1)
    1007            endif
    1008          endif
    1009        endif
    1010 
    1011        if (scavenging) then
    1012        ! verify that we indeed have ccn_mass and ccn_number tracers
    1013          if (igcm_ccn_mass.eq.0 .and. igcm_ccnco2_mass.eq.0) then
    1014            write(*,*) "initracer: error !!"
    1015            write(*,*) "  cannot use scavenging option without ",
    1016      &                "a ccn_mass or ccnco2_mass tracer !"
    1017              call abort_physic("initracer","scavenging issue",1)
    1018          endif
    1019          if (igcm_ccn_number.eq.0 .and. igcm_ccnco2_number.eq.0 ) then
    1020            write(*,*) "initracer: error !!"
    1021            write(*,*) "  cannot use scavenging option without ",
    1022      &                "a ccn_number or ccnco2_number tracer !"
    1023              call abort_physic("initracer","scavenging issue",1)
    1024          endif
    1025        endif ! of if (scavenging)
    1026 
    1027        if (photochem .or. callthermos) then
    1028        ! verify that we indeed have the chemistry tracers
    1029          if (igcm_co2.eq.0) then
    1030            write(*,*) "initracer: error !!"
    1031            write(*,*) "  cannot use chemistry option without ",
    1032      &                "a co2 tracer !"
    1033            call abort_physic("initracer","missing co2 tracer",1)
    1034          endif
    1035          if (igcm_co.eq.0) then
    1036            write(*,*) "initracer: error !!"
    1037            write(*,*) "  cannot use chemistry option without ",
    1038      &                "a co tracer !"
    1039            call abort_physic("initracer","missing co tracer",1)
    1040          endif
    1041          if (igcm_o.eq.0) then
    1042            write(*,*) "initracer: error !!"
    1043            write(*,*) "  cannot use chemistry option without ",
    1044      &                "a o tracer !"
    1045            call abort_physic("initracer","missing o tracer",1)
    1046          endif
    1047          if (igcm_o1d.eq.0) then
    1048            write(*,*) "initracer: error !!"
    1049            write(*,*) "  cannot use chemistry option without ",
    1050      &                "a o1d tracer !"
    1051            call abort_physic("initracer","missing o1d tracer",1)
    1052          endif
    1053          if (igcm_o2.eq.0) then
    1054            write(*,*) "initracer: error !!"
    1055            write(*,*) "  cannot use chemistry option without ",
    1056      &                "an o2 tracer !"
    1057            call abort_physic("initracer","missing o2 tracer",1)
    1058          endif
    1059          if (igcm_o3.eq.0) then
    1060            write(*,*) "initracer: error !!"
    1061            write(*,*) "  cannot use chemistry option without ",
    1062      &                "an o3 tracer !"
    1063            call abort_physic("initracer","missing o3 tracer",1)
    1064          endif
    1065          if (igcm_h.eq.0) then
    1066            write(*,*) "initracer: error !!"
    1067            write(*,*) "  cannot use chemistry option without ",
    1068      &                "a h tracer !"
    1069            call abort_physic("initracer","missing h tracer",1)
    1070          endif
    1071          if (igcm_h2.eq.0) then
    1072            write(*,*) "initracer: error !!"
    1073            write(*,*) "  cannot use chemistry option without ",
    1074      &                "a h2 tracer !"
    1075            call abort_physic("initracer","missing h2 tracer",1)
    1076          endif
    1077          if (igcm_oh.eq.0) then
    1078            write(*,*) "initracer: error !!"
    1079            write(*,*) "  cannot use chemistry option without ",
    1080      &                "an oh tracer !"
    1081            call abort_physic("initracer","missing oh tracer",1)
    1082          endif
    1083          if (igcm_ho2.eq.0) then
    1084            write(*,*) "initracer: error !!"
    1085            write(*,*) "  cannot use chemistry option without ",
    1086      &                "a ho2 tracer !"
    1087            call abort_physic("initracer","missing ho2 tracer",1)
    1088       endif
    1089          if (igcm_h2o2.eq.0) then
    1090            write(*,*) "initracer: error !!"
    1091            write(*,*) "  cannot use chemistry option without ",
    1092      &                "a h2o2 tracer !"
    1093            call abort_physic("initracer","missing h2o2 tracer",1)
    1094          endif
    1095          if (igcm_n2.eq.0) then
    1096            write(*,*) "initracer: error !!"
    1097            write(*,*) "  cannot use chemistry option without ",
    1098      &                "a n2 tracer !"
    1099            call abort_physic("initracer","missing n2 tracer",1)
    1100          endif
    1101          if (igcm_ar.eq.0) then
    1102            write(*,*) "initracer: error !!"
    1103            write(*,*) "  cannot use chemistry option without ",
    1104      &                "an ar tracer !"
    1105            call abort_physic("initracer","missing ar tracer",1)
    1106          endif
    1107        endif ! of if (photochem .or. callthermos)
     793    endif
     794    if (igcm_dust_number == 0) then
     795        write(*,*) "initracer: error!"
     796        write(*,*) "  Cannot use doubleq option without a dust_number tracer!"
     797        call abort_physic("initracer","doubleq issue",1)
     798        endif
     799endif
     800
     801if ((.not.doubleq).and.(dustbin>0)) then
     802    ! verify that we indeed have 'dustbin' dust tracers
     803    count=0
     804    do iq=1,dustbin
     805        if (igcm_dustbin(iq)/=0) then
     806            count = count + 1
     807        endif
     808    enddo
     809    if (count/=dustbin) then
     810        write(*,*) "initracer: error!"
     811        write(*,*) "  dustbin is set to ",dustbin," but we only have the following dust tracers:"
     812        do iq=1,count
     813            write(*,*)"   ",trim(noms(igcm_dustbin(iq)))
     814        enddo
     815        call abort_physic("initracer","dustbin issue",1)
     816    endif
     817endif
     818
     819if (water) then
     820    ! verify that we indeed have h2o_vap and h2o_ice tracers
     821    if (igcm_h2o_vap == 0) then
     822        write(*,*) "initracer: error!"
     823        write(*,*) "  Cannot use water option without an h2o_vap tracer!"
     824        call abort_physic("initracer","water cycle issue",1)
     825    endif
     826    if (igcm_h2o_ice == 0) then
     827        write(*,*) "initracer: error!"
     828        write(*,*) "  Cannot use water option without an h2o_ice tracer!"
     829        call abort_physic("initracer","water cycle issue",1)
     830    endif
     831endif
     832
     833if (hdo) then
     834    ! verify that we indeed have hdo_vap and hdo_ice tracers
     835    if (igcm_hdo_vap == 0) then
     836        write(*,*) "initracer: error!"
     837        write(*,*) "  Cannot use hdo option without an hdo_vap tracer!"
     838        call abort_physic("initracer","hdo cycle issue",1)
     839    endif
     840    if (igcm_hdo_ice == 0) then
     841        write(*,*) "initracer: error!"
     842        write(*,*) "  Cannot use hdo option without an hdo_ice tracer!"
     843        call abort_physic("initracer","hdo cycle issue",1)
     844    endif
     845endif
     846
     847if (microphys) then
     848    ! verify that we indeed have ccn_number and ccn_mass tracers
     849    if (igcm_ccn_number == 0) then
     850        write(*,*) "initracer: error!"
     851        write(*,*) "  Cannot use microphys option without a ccn_number tracer!"
     852        call abort_physic("initracer","microphys issue",1)
     853    endif
     854    if (igcm_ccn_mass == 0) then
     855        write(*,*) "initracer: error!"
     856        write(*,*) "  Cannot use microphys option without a ccn_mass tracer!"
     857        call abort_physic("initracer","microphys issue",1)
     858    endif
     859endif
     860
     861if (co2clouds) then
     862    !verify that we have co2_ice and co2 tracers
     863    if (igcm_co2 == 0) then
     864        write(*,*) "initracer: error!"
     865        write(*,*) "  Cannot use co2 clouds option without a co2 tracer!"
     866        call abort_physic("initracer","co2 clouds issue",1)
     867    end if
     868    if (igcm_co2_ice == 0) then
     869        write(*,*) "initracer: error!"
     870        write(*,*) "  Cannot use co2 clouds option without a co2_ice tracer!"
     871        call abort_physic("initracer","co2 clouds issue",1)
     872    end if
     873    if (igcm_ccnco2_number == 0) then
     874        write(*,*) "initracer: error!"
     875        write(*,*) "  Cannot use co2 clouds option without a ccnco2_number tracer!"
     876        call abort_physic("initracer","co2 clouds issue",1)
     877    end if
     878    if (igcm_ccnco2_mass == 0) then
     879        write(*,*) "initracer: error!"
     880        write(*,*) "  Cannot use co2 clouds option without a ccnco2_mass tracer!"
     881        call abort_physic("initracer","co2 clouds issue",1)
     882    end if
     883    if (co2useh2o) then
     884        if (igcm_ccnco2_h2o_number == 0) then
     885            write(*,*) "initracer: error!"
     886            write(*,*) "  Cannot use co2 clouds option without a ccnco2_h2o_number tracer!"
     887            call abort_physic("initracer","co2 clouds issue",1)
     888        end if
     889        if (igcm_ccnco2_h2o_mass_ice == 0) then
     890            write(*,*) "initracer: error!"
     891            write(*,*) "  Cannot use co2 clouds option without a ccnco2_h2o_mass_ice tracer!"
     892            call abort_physic("initracer","co2 clouds issue",1)
     893        end if
     894        if (igcm_ccnco2_h2o_mass_ccn == 0) then
     895            write(*,*) "initracer: error!"
     896            write(*,*) "  Cannot use co2 clouds option without a ccnco2_h2o_mass_ccn tracer!"
     897            call abort_physic("initracer","co2 clouds issue",1)
     898        end if
     899    end if
     900    if (meteo_flux) then
     901        if (igcm_ccnco2_meteor_number == 0) then
     902            write(*,*) "initracer: error!"
     903            write(*,*) "  Cannot use co2 clouds option without a ccnco2_meteor_number tracer!"
     904            call abort_physic("initracer","co2 clouds issue",1)
     905        end if
     906        if (igcm_ccnco2_meteor_mass == 0) then
     907            write(*,*) "initracer: error!"
     908            write(*,*) "  Cannot use co2 clouds option without a ccnco2_h2o_mass_ice tracer!"
     909            call abort_physic("initracer","co2 clouds issue",1)
     910        end if
     911        if (igcm_ccnco2_meteor_mass == 0) then
     912            write(*,*) "initracer: error!"
     913            write(*,*) "  Cannot use co2 clouds option without a ccnco2_meteor_mass tracer!"
     914            call abort_physic("initracer","co2 clouds issue",1)
     915        end if
     916    end if
     917endif
     918
     919if (rdstorm) then
     920    ! verify that we indeed have stormdust_mass and stormdust_number tracers
     921    if (igcm_stormdust_mass == 0) then
     922        write(*,*) "initracer: error!"
     923        write(*,*) "  Cannot use rdstorm option without a stormdust_mass tracer!"
     924        call abort_physic("initracer","rdstorm issue",1)
     925    endif
     926    if (igcm_stormdust_number == 0) then
     927        write(*,*) "initracer: error!"
     928        write(*,*) "  Cannot use rdstorm option without a stormdust_number tracer!"
     929        call abort_physic("initracer","rdstorm issue",1)
     930    endif
     931endif
     932
     933if (topflows) then
     934    ! verify that we indeed have topdust_mass and topdust_number tracers
     935    if (igcm_topdust_mass == 0) then
     936        write(*,*) "initracer: error!"
     937        write(*,*) "  Cannot use topflows option without a topdust_mass tracer!"
     938        call abort_physic("initracer","topflows issue",1)
     939    endif
     940    if (igcm_topdust_number == 0) then
     941        write(*,*) "initracer: error!"
     942        write(*,*) "  Cannot use topflows option without a topdust_number tracer!"
     943        call abort_physic("initracer","topflows issue",1)
     944    endif
     945endif
     946
     947if (callnlte) then ! NLTE requirements
     948    if (nltemodel>=1) then
     949        ! check that co2, co, o and n2 tracers are available
     950        if (igcm_co2 == 0) then
     951            write(*,*) "initracer: error!"
     952            write(*,*) "  with nltemodel>0, we need the co2 tracer!"
     953            call abort_physic("initracer","missing co2 tracer",1)
     954        endif
     955        if (igcm_co == 0) then
     956            write(*,*) "initracer: error!"
     957            write(*,*) "  with nltemodel>0, we need the co tracer!"
     958            call abort_physic("initracer","missing co tracer",1)
     959        endif
     960        if (igcm_o == 0) then
     961            write(*,*) "initracer: error!"
     962            write(*,*) "  with nltemodel>0, we need the o tracer!"
     963            call abort_physic("initracer","missing o tracer",1)
     964        endif
     965        if (igcm_n2 == 0) then
     966            write(*,*) "initracer: error!"
     967            write(*,*) "  with nltemodel>0, we need the n2 tracer!"
     968            call abort_physic("initracer","missing n2 tracer",1)
     969        endif
     970    endif
     971endif
     972
     973if (scavenging) then
     974    ! verify that we indeed have ccn_mass and ccn_number tracers
     975    if (igcm_ccn_mass == 0 .and. igcm_ccnco2_mass == 0) then
     976        write(*,*) "initracer: error!"
     977        write(*,*) "  Cannot use scavenging option without a ccn_mass or ccnco2_mass tracer!"
     978        call abort_physic("initracer","scavenging issue",1)
     979    endif
     980    if (igcm_ccn_number == 0 .and. igcm_ccnco2_number == 0 ) then
     981        write(*,*) "initracer: error!"
     982        write(*,*) "  Cannot use scavenging option without a ccn_number or ccnco2_number tracer!"
     983        call abort_physic("initracer","scavenging issue",1)
     984    endif
     985endif ! of if (scavenging)
     986
     987if (photochem .or. callthermos) then
     988    ! verify that we indeed have the chemistry tracers
     989    if (igcm_co2 == 0) then
     990        write(*,*) "initracer: error!"
     991        write(*,*) "  Cannot use chemistry option without a co2 tracer!"
     992        call abort_physic("initracer","missing co2 tracer",1)
     993    endif
     994    if (igcm_co == 0) then
     995        write(*,*) "initracer: error!"
     996        write(*,*) "  Cannot use chemistry option without a co tracer!"
     997        call abort_physic("initracer","missing co tracer",1)
     998    endif
     999    if (igcm_o == 0) then
     1000        write(*,*) "initracer: error!"
     1001        write(*,*) "  Cannot use chemistry option without a o tracer!"
     1002        call abort_physic("initracer","missing o tracer",1)
     1003    endif
     1004    if (igcm_o1d == 0) then
     1005        write(*,*) "initracer: error!"
     1006        write(*,*) "  Cannot use chemistry option without a o1d tracer!"
     1007        call abort_physic("initracer","missing o1d tracer",1)
     1008    endif
     1009    if (igcm_o2 == 0) then
     1010        write(*,*) "initracer: error!"
     1011        write(*,*) "  Cannot use chemistry option without an o2 tracer!"
     1012        call abort_physic("initracer","missing o2 tracer",1)
     1013    endif
     1014    if (igcm_o3 == 0) then
     1015        write(*,*) "initracer: error!"
     1016        write(*,*) "  Cannot use chemistry option without an o3 tracer!"
     1017        call abort_physic("initracer","missing o3 tracer",1)
     1018    endif
     1019    if (igcm_h == 0) then
     1020        write(*,*) "initracer: error!"
     1021        write(*,*) "  Cannot use chemistry option without a h tracer!"
     1022        call abort_physic("initracer","missing h tracer",1)
     1023    endif
     1024    if (igcm_h2 == 0) then
     1025        write(*,*) "initracer: error!"
     1026        write(*,*) "  Cannot use chemistry option without a h2 tracer!"
     1027        call abort_physic("initracer","missing h2 tracer",1)
     1028    endif
     1029    if (igcm_oh == 0) then
     1030        write(*,*) "initracer: error!"
     1031        write(*,*) "  Cannot use chemistry option without an oh tracer!"
     1032        call abort_physic("initracer","missing oh tracer",1)
     1033    endif
     1034    if (igcm_ho2 == 0) then
     1035        write(*,*) "initracer: error!"
     1036        write(*,*) "  Cannot use chemistry option without a ho2 tracer!"
     1037        call abort_physic("initracer","missing ho2 tracer",1)
     1038    endif
     1039    if (igcm_h2o2 == 0) then
     1040        write(*,*) "initracer: error!"
     1041        write(*,*) "  Cannot use chemistry option without a h2o2 tracer!"
     1042        call abort_physic("initracer","missing h2o2 tracer",1)
     1043    endif
     1044    if (igcm_n2 == 0) then
     1045        write(*,*) "initracer: error!"
     1046        write(*,*) "  Cannot use chemistry option without a n2 tracer!"
     1047        call abort_physic("initracer","missing n2 tracer",1)
     1048    endif
     1049    if (igcm_ar == 0) then
     1050        write(*,*) "initracer: error!"
     1051        write(*,*) "  Cannot use chemistry option without an ar tracer!"
     1052        call abort_physic("initracer","missing ar tracer",1)
     1053    endif
     1054endif ! of if (photochem .or. callthermos)
    11081055
    11091056! Initialisation for CO2 clouds
    1110       if (co2clouds) then
    1111         radius(igcm_ccnco2_mass) = radius(igcm_dust_mass)
    1112         alpha_lift(igcm_ccnco2_mass) = 1e-30
    1113         alpha_devil(igcm_ccnco2_mass) = 1e-30
    1114         rho_q(igcm_ccnco2_mass) = rho_dust
    1115         radius(igcm_ccnco2_number) = radius(igcm_ccnco2_mass)
    1116         alpha_lift(igcm_ccnco2_number) = alpha_lift(igcm_ccnco2_mass)
    1117         alpha_devil(igcm_ccnco2_number) = alpha_devil(igcm_ccnco2_mass)
    1118         rho_q(igcm_ccnco2_number) = rho_q(igcm_ccnco2_mass)
    1119 
    1120         radius(igcm_co2)=0.
    1121         alpha_lift(igcm_co2) =0.
    1122         alpha_devil(igcm_co2)=0.
    1123         radius(igcm_co2_ice)=1.e-8
    1124         rho_q(igcm_co2_ice)=rho_ice_co2
    1125         alpha_lift(igcm_co2_ice) =0.
    1126         alpha_devil(igcm_co2_ice)=0.
    1127 
    1128       endif
    1129 
    1130       end
     1057if (co2clouds) then
     1058    radius(igcm_ccnco2_mass) = radius(igcm_dust_mass)
     1059    alpha_lift(igcm_ccnco2_mass) = 1e-30
     1060    alpha_devil(igcm_ccnco2_mass) = 1e-30
     1061    rho_q(igcm_ccnco2_mass) = rho_dust
     1062    radius(igcm_ccnco2_number) = radius(igcm_ccnco2_mass)
     1063    alpha_lift(igcm_ccnco2_number) = alpha_lift(igcm_ccnco2_mass)
     1064    alpha_devil(igcm_ccnco2_number) = alpha_devil(igcm_ccnco2_mass)
     1065    rho_q(igcm_ccnco2_number) = rho_q(igcm_ccnco2_mass)
     1066
     1067    radius(igcm_co2)=0.
     1068    alpha_lift(igcm_co2) =0.
     1069    alpha_devil(igcm_co2)=0.
     1070    radius(igcm_co2_ice)=1.e-8
     1071    rho_q(igcm_co2_ice)=rho_ice_co2
     1072    alpha_lift(igcm_co2_ice) =0.
     1073    alpha_devil(igcm_co2_ice)=0.
     1074endif
     1075
     1076END SUBROUTINE initracer
     1077
     1078END MODULE initracer_mod
     1079
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r3847 r3855  
    132132      use lmdz_atke_turbulence_ini, only : atke_ini
    133133      use waterice_tifeedback_mod, only : waterice_tifeedback
     134      use initracer_mod, only: initracer
    134135      use callkeys_mod, only: calladj, calltherm, callatke, calldifv
    135136      use callkeys_mod, only: callrichsl, tke_heat_flux
     
    162163c   Tracers may be water vapor, ice OR chemical species OR dust particles
    163164c
    164 c   SEE comments in initracer.F about numbering of tracer species...
     165c   SEE comments in initracer_mod.F90 about numbering of tracer species...
    165166c
    166167c   It includes:
     
    709710c        initialize tracers
    710711c        ~~~~~~~~~~~~~~~~~~
    711          CALL initracer(ngrid,nq,qsurf)
     712         call initracer(ngrid,nq,qsurf)
    712713
    713714c        Initialize albedo and orbital calculation
Note: See TracChangeset for help on using the changeset viewer.