Changeset 05cf28d in flexpart.git


Ignore:
Timestamp:
Apr 22, 2016, 9:35:28 AM (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:
356dcb9
Parents:
61df8d9
Message:

Updated checks and warning messages for wet deposition parameters given in SPECIES files

Location:
src
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • src/com_mod.f90

    r341f4b7 r05cf28d  
    199199  ! WET DEPOSITION
    200200  ! weta_gas, wetb_gas     parameters for below-cloud wet scavenging coefficients (gasses)
    201   ! crain_aero, in_aero    parameters for in-cloud wet scavenging coefficients (aerosols)
    202   ! wetc_in, wetd_in       parameters for in-cloud wet scavenging coefficients (aerosols)
     201  ! crain_aero, csnow_aero parameters for below-cloud wet scavenging coefficients (aerosols)
     202  ! ccn_aero, cin_aero     parameters for in-cloud wet scavenging coefficients (aerosols)
    203203
    204204  ! GAS DEPOSITION
  • src/par_mod.f90

    r341f4b7 r05cf28d  
    186186  !**************************************************
    187187
    188   integer,parameter :: maxpart=4000000
     188  integer,parameter :: maxpart=1000000
    189189  integer,parameter :: maxspec=1
    190190  real,parameter :: minmass=0.0001
  • src/readpartpositions.f90

    r8a65cb0 r05cf28d  
    105105  open(unitpartin,file=path(2)(1:length(2))//'partposit_end', &
    106106       form='unformatted',err=998)
     107 
    107108
     109100 read(unitpartin,end=99) itimein
     110  i=0
     111200 i=i+1
     112  read(unitpartin) npoint(i),xlonin,ylatin,ztra1(i),itramem(i), &
     113       topo,pvi,qvi,rhoi,hmixi,tri,tti,(xmass1(i,j),j=1,nspec)
     114 
     115  if (xlonin.eq.-9999.9) goto 100
     116  xtra1(i)=(xlonin-xlon0)/dx
     117  ytra1(i)=(ylatin-ylat0)/dy
     118  numparticlecount=max(numparticlecount,npoint(i))
     119  goto 200
    108120
    109 100   read(unitpartin,end=99) itimein
    110     i=0
    111 200   i=i+1
    112     read(unitpartin) npoint(i),xlonin,ylatin,ztra1(i),itramem(i), &
    113          topo,pvi,qvi,rhoi,hmixi,tri,tti,(xmass1(i,j),j=1,nspec)
    114 
    115     if (xlonin.eq.-9999.9) goto 100
    116     xtra1(i)=(xlonin-xlon0)/dx
    117     ytra1(i)=(ylatin-ylat0)/dy
    118     numparticlecount=max(numparticlecount,npoint(i))
    119     goto 200
    120 
    121 99   numpart=i-1
     12199 numpart=i-1
    122122
    123123  close(unitpartin)
  • src/readpartpositions_mpi.f90

    r32b49c3 r05cf28d  
    133133  !***************************************
    134134
    135   open(unitpartin,file=path(2)(1:length(2))//'partposit_end', &
     135    open(unitpartin,file=path(2)(1:length(2))//'partposit_end', &
    136136         form='unformatted',err=998)
    137137   
  • src/readreleases.f90

    r341f4b7 r05cf28d  
    362362  ! Check if wet deposition or OH reaction shall be calculated
    363363  !***********************************************************
    364 ! NIK 15.02.2015, with new wet dep scheme either A or B parameters can be assigned a positive value which switches on wet dep
    365     if (weta_gas(i).gt.0. .or. wetb_gas(i).gt.0.)  then ! :TODO: or particle
     364
     365  ! ESO 04.2016 check for below-cloud scavenging (gas or aerosol)
     366    if ((dquer(i).le.0..and.(weta_gas(i).gt.0. .or. wetb_gas(i).gt.0.)) .or. &
     367         &(dquer(i).gt.0. .and. (crain_aero(i) .gt. 0. .or. csnow_aero(i).gt.0.)))  then
    366368      WETDEP=.true.
    367369      if (lroot) then
    368         write (*,*) 'Below-cloud scavenging: ON'
    369       !  write (*,*) 'Below-cloud scavenging coefficients: ',weta(i),i
     370        write (*,*) '  Below-cloud scavenging: ON'
     371!  write (*,*) 'Below-cloud scavenging coefficients: ',weta(i),i
    370372      end if
    371373    else
    372       if (lroot) write (*,*) 'Below-cloud scavenging: OFF'
     374      if (lroot) write (*,*) '  Below-cloud scavenging: OFF'
    373375    endif
    374376   
    375377! NIK 31.01.2013 + 10.12.2013 + 15.02.2015
    376     if (ccn_aero(i).gt.0. .or. in_aero(i).gt.0.)  then
     378    if (dquer(i).gt.0..and.(ccn_aero(i).gt.0. .or. in_aero(i).gt.0.))  then
    377379      WETDEP=.true.
    378380      if (lroot) then
    379         write (*,*) 'In-cloud scavenging: ON'
     381        write (*,*) '  In-cloud scavenging: ON'
    380382!        write (*,*) 'In-cloud scavenging coefficients: ',&
    381383!           &ccn_aero(i),in_aero(i),i !,wetc_in(i), wetd_in(i),i
    382384      end if
    383385    else
    384       if (lroot) write (*,*) 'In-cloud scavenging: OFF'
     386      if (lroot) write (*,*) '  In-cloud scavenging: OFF'
    385387    endif
    386388
    387389    if (ohcconst(i).gt.0.) then
    388390      OHREA=.true.
    389       if (lroot) write (*,*) 'OHreaction switched on: ',ohcconst(i),i
     391      if (lroot) write (*,*) '  OHreaction switched on: ',ohcconst(i),i
    390392    endif
    391393
  • src/readspecies.f90

    r341f4b7 r05cf28d  
    4040  !                                                                            *
    4141  ! Variables:                                                                 *
    42   ! decaytime(maxtable)  half time for radiological decay                      *
    43   ! specname(maxtable)   names of chemical species, radionuclides              *
    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         *
    47   ! ohcconst             OH reaction rate constant C                           *
    48   ! ohdconst             OH reaction rate constant D                           *
    49   ! ohnconst             OH reaction rate constant n                           *
    50   ! id_spec              SPECIES number as referenced in RELEASE file          *
    51   ! id_pos               position where SPECIES data shall be stored           *
     42  ! decaytime(maxtable)   half time for radiological decay                     *
     43  ! specname(maxtable)    names of chemical species, radionuclides             *
     44  ! weta_gas, wetb_gas    Parameters for below-cloud scavenging of gasses      *
     45  ! crain_aero,csnow_aero Parameters for below-cloud scavenging of aerosols    *
     46  ! ccn_aero,in_aero      Parameters for in-cloud scavenging of aerosols       *
     47  ! ohcconst              OH reaction rate constant C                          *
     48  ! ohdconst              OH reaction rate constant D                          *
     49  ! ohnconst              OH reaction rate constant n                          *
     50  ! id_spec               SPECIES number as referenced in RELEASE file         *
     51  ! id_pos                position where SPECIES data shall be stored          *
    5252  !                                                                            *
    5353  ! Constants:                                                                 *
     
    113113  close(unitspecies)
    114114
    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
     115  if ((len(trim(pspecies)).eq.0).or.(readerror.ne.0)) then ! no namelist found
     116    if (lroot) write(*,*) "SPECIES file not in NAMELIST format, attempting to &
     117         &read as fixed format"
    117118
    118119    readerror=1
     
    150151!  write(*,*) density(pos_spec)
    151152    read(unitspecies,'(e18.1)',end=22) dquer(pos_spec)
    152   write(*,*) 'dquer(pos_spec):', dquer(pos_spec)
     153write(*,*) 'dquer(pos_spec):', dquer(pos_spec)
    153154    read(unitspecies,'(e18.1)',end=22) dsigma(pos_spec)
    154155!  write(*,*) dsigma(pos_spec)
     
    221222! Check scavenging parameters given in SPECIES file
    222223
    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
    224 
    225   if (dquer(pos_spec).gt.0) then !is particle
    226     if (lroot) then
    227       write(*,'(a,f5.2)') '  Particle below-cloud scavenging parameter A &
    228            &(Rain collection efficiency)  ', crain_aero(pos_spec)
    229       write(*,'(a,f5.2)') '  Particle below-cloud scavenging parameter B &
    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
    233       if (lroot) then
     224  if (lroot) then
     225! Particles
     226!**********
     227    if (dquer(pos_spec).gt.0) then
     228      if (ccn_aero(pos_spec) .gt. 0) then
     229        write(*,'(a,f5.2)') '  Particle CCN  efficiency (CCNeff):', ccn_aero(pos_spec)
     230      else
     231        write(*,'(a)')      '  Particle CCN  efficiency (CCNeff):   OFF'
     232      endif
     233      if (in_aero(pos_spec) .gt. 0) then
     234        write(*,'(a,f5.2)') '  Particle  IN  efficiency (INeff) :', in_aero(pos_spec)
     235      else
     236        write(*,'(a)')      '  Particle  IN  efficiency (INeff) :   OFF'
     237      endif
     238      if (crain_aero(pos_spec) .gt. 0) then
     239        write(*,'(a,f5.2)') '  Particle Rain efficiency (Crain) :', crain_aero(pos_spec)
     240      else
     241        write(*,'(a)')      '  Particle Rain efficiency (Crain) :   OFF'
     242      endif
     243      if (csnow_aero(pos_spec) .gt. 0) then
     244        write(*,'(a,f5.2)') '  Particle Snow efficiency (Csnow) :', csnow_aero(pos_spec)
     245      else
     246        write(*,'(a)')      '  Particle Snow efficiency (Csnow) :   OFF'
     247      end if
     248      if (density(pos_spec) .gt. 0) then
     249        write(*,'(a)') '  Dry deposition is turned         :   ON'
     250      else
     251        write(*,'(a)') '  Dry deposition is (density<0)    :   OFF'
     252      end if
     253      if (crain_aero(pos_spec).gt.10.0 .or. csnow_aero(pos_spec).gt.10.0 .or. &
     254           &ccn_aero(pos_spec).gt.1.0 .or. in_aero(pos_spec).gt.1.0) then
    234255        write(*,*) '*******************************************'
    235         write(*,*) ' WARNING: Particle below-cloud scavenging parameter A or B &
    236              &is out of likely range'
    237         write(*,*) '          Likely range is 0.0-1.0'
     256        write(*,*) ' WARNING: Particle Scavenging parameter likely out of range '
     257        write(*,*) '       Likely   range for Crain    0.0-10'
     258        write(*,*) '       Likely   range for Csnow    0.0-10'
     259        write(*,*) '       Physical range for CCNeff   0.0-1'
     260        write(*,*) '       Physical range for INeff    0.0-1'
    238261        write(*,*) '*******************************************'
    239262      end if
    240     endif
    241     if (lroot) then
    242       write(*,'(a,f5.2)') '  Particle in-cloud scavenging parameter Ai &
    243            &(CCN efficiency)  ', ccn_aero(pos_spec)
    244       write(*,'(a,f5.2)') '  Particle in-cloud scavenging parameter Bi &
    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
    248       if (lroot) then
    249         write(*,*) '*******************************************'
    250         write(*,*) ' WARNING: Particle in-cloud scavenging parameter A is out of likely range'
    251         write(*,*) '          Likely range is 0.0-1.0 for CCN '
    252         write(*,*) '*******************************************'
    253       end if
    254     endif
    255     if (in_aero(pos_spec).gt.1.0 .or. in_aero(pos_spec).lt.0.01) then
    256       if (lroot) then
    257         write(*,*) '*******************************************'
    258         write(*,*) ' WARNING: Particle in-cloud scavenging parameter B is out of likely range'
    259         write(*,*) '          Likely range is 0.0-1.0 for Ice nuclei (IN) '
    260         write(*,*) '*******************************************'
    261       end if
    262     endif
    263 
    264   else !is gas
    265     if (lroot) then
    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)
    268       write(*,*) ' Gas in-cloud scavenging uses default values as in Hertel et al 1995'
    269     end if
    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
    272         if (lroot) then
     263    else
     264! Gas
     265!****
     266      if (weta_gas(pos_spec) .gt. 0 .and. wetb_gas(pos_spec).gt.0) then
     267        write(*,*)          '  Wet removal for gases      is turned: ON'
     268        write(*,*)          '  Gas below-cloud scavenging parameter A  ', &
     269             &weta_gas(pos_spec)
     270        write(*,'(a,f5.2)') '  Gas below-cloud scavenging parameter B  ', &
     271             &wetb_gas(pos_spec)
     272      else
     273        write(*,*)          '  Wet removal for gases      is turned: OFF '
     274      end if
     275      if (reldiff(i).gt.0.) then
     276        write(*,*)          '  Dry deposition for gases   is turned: ON '
     277      else
     278        write(*,*)          '  Dry deposition for gases   is turned: OFF '
     279      end if
     280      if (weta_gas(pos_spec).gt.0.) then !if wet deposition is turned on
     281        if (weta_gas(pos_spec).gt.1E-04 .or. weta_gas(pos_spec).lt.1E-09 .or. &
     282             &wetb_gas(pos_spec).gt.0.8 .or. wetb_gas(pos_spec).lt.0.4) then
    273283          write(*,*) '*******************************************'
    274           write(*,*) ' WARNING: Gas below-cloud scavenging parameter A is out of likely range'
    275           write(*,*) '          Likely range is 1E-04 to 1E-08 (see Hertel et al 1995)'
     284          write(*,*) ' WARNING: Gas below-cloud scavengig is out of likely range'
     285          write(*,*) '          Likely range for A is 1E-04 to 1E-08'
     286          write(*,*) '          Likely range for B is 0.60  to 0.80 '
    276287          write(*,*) '*******************************************'
    277288        end if
    278289      endif
     290
     291      if (((weta_gas(pos_spec).gt.0).or.(wetb_gas(pos_spec).gt.0)).and.&
     292           &(henry(pos_spec).le.0)) then
     293        if (dquer(pos_spec).le.0) goto 996 ! no particle, no henry set
     294      endif
    279295    end if
    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
    282         if (lroot) then
    283           write(*,*) '*******************************************'
    284           write(*,*) ' WARNING: Gas below-cloud scavenging parameter B is out of likely range'
    285           write(*,*) '          Likely range is 0.6 to 0.8 (see Hertel et al 1995)'
    286           write(*,*) '*******************************************'
    287         end if
    288       endif
    289     end if
    290   endif
    291   endif
    292 
    293   if (((weta_gas(pos_spec).gt.0).or.(wetb_gas(pos_spec).gt.0)).and.(henry(pos_spec).le.0)) then
    294     if (dquer(pos_spec).le.0) goto 996 ! no particle, no henry set
    295   endif
     296  end if
    296297
    297298  if (spec_ass(pos_spec).gt.0) then
     
    304305      endif
    305306    end do
    306     if (spec_found.eqv..FALSE.) then
     307    if (spec_found.eqv..false.) then
    307308      goto 997
    308309    endif
  • src/timemanager.f90

    rec7fc72 r05cf28d  
    102102  implicit none
    103103
    104   integer :: j,ks,kp,l,n,itime,nstop,nstop1
     104  integer :: j,ks,kp,l,n,itime=0,nstop,nstop1
    105105! integer :: ksp
    106106  integer :: loutnext,loutstart,loutend
  • src/timemanager_mpi.f90

    r341f4b7 r05cf28d  
    137137
    138138
    139 !  itime=0
    140139  if (lroot.or.mp_dev_mode) then
    141     write(*,45) itime,numpart*mp_partgroup_np,gridtotalunc,wetgridtotalunc,drygridtotalunc
    142   !  write(*,46) float(itime)/3600,itime,numpart*mp_partgroup_np
     140  !  write(*,45) itime,numpart*mp_partgroup_np,gridtotalunc,wetgridtotalunc,drygridtotalunc
     141    write(*,46) float(itime)/3600,itime,numpart*mp_partgroup_np
    143142   
    144143    if (verbosity.gt.0) then
  • src/wetdepo.f90

    r341f4b7 r05cf28d  
    350350
    351351! AEROSOL
    352 !**************************************************
    353           if (dquer(ks).gt.0.) then ! is particle
    354 
     352!********
     353          if (dquer(ks).gt.0.) then
    355354            S_i= frac_act/cl
    356355
    357 !*********************
    358356! GAS
    359           else ! is gas
     357!****
     358          else
    360359
    361360            cle=(1-cl)/(henry(ks)*(r_air/3500.)*act_temp)+cl
    362361!REPLACE to switch old/ new scheme
    363 ! S_i=frac_act/cle
     362          ! S_i=frac_act/cle
    364363            S_i=1/cle
    365364          endif ! gas or particle
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG