Changeset 341f4b7 in flexpart.git for src/readspecies.f90


Ignore:
Timestamp:
Apr 20, 2016, 1:39:51 PM (8 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
61df8d9
Parents:
32b49c3
Message:

SPECIES files converted to namelist format. Fixed-format SPCIES files renamed with .oldformat extension. Added 2 wet depo parameters to old-format SPECIES. Renamed internal variables and parameters used for wet deposition. incloud_ratio increased to 2.2

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readspecies.f90

    r32b49c3 r341f4b7  
    4242  ! decaytime(maxtable)  half time for radiological decay                      *
    4343  ! specname(maxtable)   names of chemical species, radionuclides              *
    44   ! weta, wetb           Parameters for determining below-cloud scavenging     *
    45   ! weta_in              Parameter for determining in-cloud scavenging         *
    46   ! wetb_in              Parameter for determining in-cloud scavenging         *
     44  ! weta_gas, wetb_gas   Parameters for determining below-cloud scavenging     *
     45  ! ccn_aero              Parameter for determining in-cloud scavenging         *
     46  ! in_aero              Parameter for determining in-cloud scavenging         *
    4747  ! ohcconst             OH reaction rate constant C                           *
    4848  ! ohdconst             OH reaction rate constant D                           *
     
    6666
    6767  character(len=16) :: pspecies
    68   real :: pdecay, pweta, pwetb, preldiff, phenry, pf0, pdensity, pdquer
     68  real :: pdecay, pweta_gas, pwetb_gas, preldiff, phenry, pf0, pdensity, pdquer
    6969  real :: pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, pspec_ass, pkao
    70   real :: pweta_in, pwetb_in, pwetc_in, pwetd_in
     70  real :: pcrain_aero, pcsnow_aero, pccn_aero, pin_aero
    7171  integer :: readerror
    7272
    7373! declare namelist
    7474  namelist /species_params/ &
    75        pspecies, pdecay, pweta, pwetb, &
    76        pweta_in, pwetb_in, pwetc_in, pwetd_in, &
     75       pspecies, pdecay, pweta_gas, pwetb_gas, &
     76       pcrain_aero, pcsnow_aero, pccn_aero, pin_aero, &
    7777       preldiff, phenry, pf0, pdensity, pdquer, &
    7878       pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, pspec_ass, pkao
    7979
    80   pspecies=" "
     80  pspecies="" ! read failure indicator value
    8181  pdecay=-999.9
    82   pweta=-9.9E-09
    83   pwetb=0.0
    84   pweta_in=-9.9E-09
    85   pwetb_in=-9.9E-09
    86 !  pwetc_in=-9.9E-09
    87 !  pwetd_in=-9.9E-09
     82  pweta_gas=-9.9E-09
     83  pwetb_gas=0.0
     84  pcrain_aero=-9.9E-09
     85  pcsnow_aero=-9.9E-09
     86  pccn_aero=-9.9E-09
     87  pin_aero=-9.9E-09
    8888  preldiff=-9.9
    8989  phenry=0.0
     
    9898  pspec_ass=-9
    9999  pkao=-99.99
    100   pweightmolar=-789.0 ! read failure indicator value
     100  pweightmolar=-999.9
    101101
    102102! Open the SPECIES file and read species names and properties
     
    113113  close(unitspecies)
    114114
    115   if ((pweightmolar.eq.-789.0).or.(readerror.ne.0)) then ! no namelist found
     115!  if ((pweightmolar.eq.-789.0).or.(readerror.ne.0)) then ! no namelist found
     116  if ((len(pspecies).eq.0).or.(readerror.ne.0)) then ! no namelist found
    116117
    117118    readerror=1
     
    127128    read(unitspecies,'(f18.1)',end=22) decay(pos_spec)
    128129!  write(*,*) decay(pos_spec)
    129     read(unitspecies,'(e18.1)',end=22) weta(pos_spec)
    130 !  write(*,*) weta(pos_spec)
    131     read(unitspecies,'(f18.2)',end=22) wetb(pos_spec)
    132 !  write(*,*) wetb(pos_spec)
    133 
     130    read(unitspecies,'(e18.1)',end=22) weta_gas(pos_spec)
     131!  write(*,*) weta_gas(pos_spec)
     132    read(unitspecies,'(f18.2)',end=22) wetb_gas(pos_spec)
     133!  write(*,*) wetb_gas(pos_spec)
     134    read(unitspecies,'(e18.1)',end=22) crain_aero(pos_spec)
     135!  write(*,*) crain_aero(pos_spec)
     136    read(unitspecies,'(f18.2)',end=22) csnow_aero(pos_spec)
     137!  write(*,*) csnow_aero(pos_spec)
    134138!*** NIK 31.01.2013: including in-cloud scavening parameters
    135     read(unitspecies,'(e18.1)',end=22) weta_in(pos_spec)
    136 !  write(*,*) weta_in(pos_spec)
    137     read(unitspecies,'(f18.2)',end=22) wetb_in(pos_spec)
    138 !  write(*,*) wetb_in(pos_spec)
    139 ! read(unitspecies,'(f18.2)',end=22) wetc_in(pos_spec)
    140 !  write(*,*) wetc_in(pos_spec)
    141 ! read(unitspecies,'(f18.2)',end=22) wetd_in(pos_spec)
    142 !  write(*,*) wetd_in(pos_spec)
    143 
     139    read(unitspecies,'(e18.1)',end=22) ccn_aero(pos_spec)
     140!  write(*,*) ccn_aero(pos_spec)
     141    read(unitspecies,'(f18.2)',end=22) in_aero(pos_spec)
     142!  write(*,*) in_aero(pos_spec)
    144143    read(unitspecies,'(f18.1)',end=22) reldiff(pos_spec)
    145144!  write(*,*) reldiff(pos_spec)
     
    171170    pspecies=species(pos_spec)
    172171    pdecay=decay(pos_spec)
    173     pweta=weta(pos_spec)
    174     pwetb=wetb(pos_spec)
    175     pweta_in=weta_in(pos_spec)
    176     pwetb_in=wetb_in(pos_spec)
    177 !    pwetc_in=wetc_in(pos_spec)
    178 !    pwetd_in=wetd_in(pos_spec)
     172    pweta_gas=weta_gas(pos_spec)
     173    pwetb_gas=wetb_gas(pos_spec)
     174    pcrain_aero=crain_aero(pos_spec)
     175    pcsnow_aero=csnow_aero(pos_spec)
     176    pccn_aero=ccn_aero(pos_spec)
     177    pin_aero=in_aero(pos_spec)
    179178    preldiff=reldiff(pos_spec)
    180179    phenry=henry(pos_spec)
     
    195194    species(pos_spec)=pspecies
    196195    decay(pos_spec)=pdecay
    197     weta(pos_spec)=pweta
    198     wetb(pos_spec)=pwetb
    199     weta_in(pos_spec)=pweta_in
    200     wetb_in(pos_spec)=pwetb_in
    201 !    wetc_in(pos_spec)=pwetc_in
    202 !    wetd_in(pos_spec)=pwetd_in
     196    weta_gas(pos_spec)=pweta_gas
     197    wetb_gas(pos_spec)=pwetb_gas
     198    crain_aero=pcrain_aero
     199    csnow_aero=pcsnow_aero
     200    ccn_aero(pos_spec)=pccn_aero
     201    in_aero(pos_spec)=pin_aero
    203202    reldiff(pos_spec)=preldiff
    204203    henry(pos_spec)=phenry
     
    222221! Check scavenging parameters given in SPECIES file
    223222
    224   if (weta(pos_spec).gt.0.0 .or. wetb(pos_spec).gt.0.0 .or. weta_in(pos_spec).gt.0.0 .or. wetb_in(pos_spec).gt.0.0) then
     223  if (weta_gas(pos_spec).gt.0.0 .or. wetb_gas(pos_spec).gt.0.0 .or. ccn_aero(pos_spec).gt.0.0 .or. in_aero(pos_spec).gt.0.0) then
    225224
    226225  if (dquer(pos_spec).gt.0) then !is particle
    227226    if (lroot) then
    228227      write(*,'(a,f5.2)') '  Particle below-cloud scavenging parameter A &
    229            &(Rain collection efficiency)  ', weta(pos_spec)
     228           &(Rain collection efficiency)  ', crain_aero(pos_spec)
    230229      write(*,'(a,f5.2)') '  Particle below-cloud scavenging parameter B &
    231            &(Snow collection efficiency)  ', wetb(pos_spec)
    232     end if
    233     if (weta(pos_spec).gt.1.0 .or. wetb(pos_spec).gt.1.0) then
     230           &(Snow collection efficiency)  ', csnow_aero(pos_spec)
     231    end if
     232    if (weta_gas(pos_spec).gt.1.0 .or. wetb_gas(pos_spec).gt.1.0) then
    234233      if (lroot) then
    235234        write(*,*) '*******************************************'
     
    242241    if (lroot) then
    243242      write(*,'(a,f5.2)') '  Particle in-cloud scavenging parameter Ai &
    244            &(CCN efficiency)  ', weta_in(pos_spec)
     243           &(CCN efficiency)  ', ccn_aero(pos_spec)
    245244      write(*,'(a,f5.2)') '  Particle in-cloud scavenging parameter Bi &
    246            &(IN efficiency)  ', wetb_in(pos_spec)
    247     end if
    248     if (weta_in(pos_spec).gt.1.0 .or. weta_in(pos_spec).lt.0.01) then
     245           &(IN efficiency)  ', in_aero(pos_spec)
     246    end if
     247    if (ccn_aero(pos_spec).gt.1.0 .or. ccn_aero(pos_spec).lt.0.01) then
    249248      if (lroot) then
    250249        write(*,*) '*******************************************'
     
    254253      end if
    255254    endif
    256     if (wetb_in(pos_spec).gt.1.0 .or. wetb_in(pos_spec).lt.0.01) then
     255    if (in_aero(pos_spec).gt.1.0 .or. in_aero(pos_spec).lt.0.01) then
    257256      if (lroot) then
    258257        write(*,*) '*******************************************'
     
    265264  else !is gas
    266265    if (lroot) then
    267       write(*,*) '  Gas below-cloud scavenging parameter A  ', weta(pos_spec)
    268       write(*,'(a,f5.2)') '  Gas below-cloud scavenging parameter B  ', wetb(pos_spec)
     266      write(*,*) '  Gas below-cloud scavenging parameter A  ', weta_gas(pos_spec)
     267      write(*,'(a,f5.2)') '  Gas below-cloud scavenging parameter B  ', wetb_gas(pos_spec)
    269268      write(*,*) ' Gas in-cloud scavenging uses default values as in Hertel et al 1995'
    270269    end if
    271     if (weta(pos_spec).gt.0.) then !if wet deposition is turned on
    272       if (weta(pos_spec).gt.1E-04 .or. weta(pos_spec).lt.1E-09) then
     270    if (weta_gas(pos_spec).gt.0.) then !if wet deposition is turned on
     271      if (weta_gas(pos_spec).gt.1E-04 .or. weta_gas(pos_spec).lt.1E-09) then
    273272        if (lroot) then
    274273          write(*,*) '*******************************************'
     
    279278      endif
    280279    end if
    281     if (wetb(pos_spec).gt.0.) then !if wet deposition is turned on
    282       if (wetb(pos_spec).gt.0.8 .or. wetb(pos_spec).lt.0.6) then
     280    if (wetb_gas(pos_spec).gt.0.) then !if wet deposition is turned on
     281      if (wetb_gas(pos_spec).gt.0.8 .or. wetb_gas(pos_spec).lt.0.6) then
    283282        if (lroot) then
    284283          write(*,*) '*******************************************'
     
    292291  endif
    293292
    294   if (((weta(pos_spec).gt.0).or.(wetb(pos_spec).gt.0)).and.(henry(pos_spec).le.0)) then
     293  if (((weta_gas(pos_spec).gt.0).or.(wetb_gas(pos_spec).gt.0)).and.(henry(pos_spec).le.0)) then
    295294    if (dquer(pos_spec).le.0) goto 996 ! no particle, no henry set
    296295  endif
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG