Changes in src/readspecies.f90 [d6a245b:aa8c34a] in flexpart.git


Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/readspecies.f90

    rd6a245b raa8c34a  
    6767  character(len=16) :: pspecies
    6868  real :: pdecay, pweta_gas, pwetb_gas, preldiff, phenry, pf0, pdensity, pdquer
    69   real :: pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst
     69  real :: pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, pkao
    7070  real :: pcrain_aero, pcsnow_aero, pccn_aero, pin_aero
    71   real :: parea_dow(7), parea_hour(24), ppoint_dow(7), ppoint_hour(24)
    72   integer :: readerror
     71  integer :: readerror, pspec_ass
    7372
    7473! declare namelist
     
    7776       pcrain_aero, pcsnow_aero, pccn_aero, pin_aero, &
    7877       preldiff, phenry, pf0, pdensity, pdquer, &
    79        pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, &
    80        parea_dow, parea_hour, ppoint_dow, ppoint_hour
     78       pdsigma, pdryvel, pweightmolar, pohcconst, pohdconst, pohnconst, pspec_ass, pkao
    8179
    8280  pspecies="" ! read failure indicator value
     
    9896  pohdconst=-9.9E-09
    9997  pohnconst=2.0
     98  pspec_ass=-9
     99  pkao=-99.99
    100100  pweightmolar=-999.9
    101101
    102   do j=1,24           ! initialize everything to no variation
    103     area_hour(pos_spec,j)=1.
    104     point_hour(pos_spec,j)=1.
    105   end do
    106   do j=1,7
    107     area_dow(pos_spec,j)=1.
    108     point_dow(pos_spec,j)=1.
    109   end do
    110 
    111   if (readerror.ne.0) then ! text format input
    112102! Open the SPECIES file and read species names and properties
    113103!************************************************************
     
    174164    read(unitspecies,'(f8.2)',end=22) ohnconst(pos_spec)
    175165!  write(*,*) ohnconst(pos_spec)
    176 
    177 ! Read in daily and day-of-week variation of emissions, if available
    178 !*******************************************************************
    179 
    180     read(unitspecies,*,end=22)
    181     do j=1,24     ! 24 hours, starting with 0-1 local time
    182       read(unitspecies,*) ihour,area_hour(pos_spec,j),point_hour(pos_spec,j)
    183     end do
    184     read(unitspecies,*)
    185     do j=1,7      ! 7 days of the week, starting with Monday
    186       read(unitspecies,*) idow,area_dow(pos_spec,j),point_dow(pos_spec,j)
    187     end do
     166    read(unitspecies,'(i18)',end=22) spec_ass(pos_spec)
     167!  write(*,*) spec_ass(pos_spec)
     168    read(unitspecies,'(f18.2)',end=22) kao(pos_spec)
     169!       write(*,*) kao(pos_spec)
    188170
    189171    pspecies=species(pos_spec)
     
    206188    pohdconst=ohdconst(pos_spec)
    207189    pohnconst=ohnconst(pos_spec)
    208 
    209 
    210     do j=1,24     ! 24 hours, starting with 0-1 local time
    211       parea_hour(j)=area_hour(pos_spec,j)
    212       ppoint_hour(j)=point_hour(pos_spec,j)
    213     end do
    214     do j=1,7      ! 7 days of the week, starting with Monday
    215       parea_dow(j)=area_dow(pos_spec,j)
    216       ppoint_dow(j)=point_dow(pos_spec,j)
    217     end do
    218 
    219   else ! namelist available
     190    pspec_ass=spec_ass(pos_spec)
     191    pkao=kao(pos_spec)
     192
     193  else
    220194
    221195    species(pos_spec)=pspecies
     
    238212    ohdconst(pos_spec)=pohdconst
    239213    ohnconst(pos_spec)=pohnconst
    240 
    241     do j=1,24     ! 24 hours, starting with 0-1 local time
    242       area_hour(pos_spec,j)=parea_hour(j)
    243       point_hour(pos_spec,j)=ppoint_hour(j)
    244     end do
    245     do j=1,7      ! 7 days of the week, starting with Monday
    246       area_dow(pos_spec,j)=parea_dow(j)
    247       point_dow(pos_spec,j)=ppoint_dow(j)
    248     end do
     214    spec_ass(pos_spec)=pspec_ass
     215    kao(pos_spec)=pkao
    249216
    250217  endif
     
    336303  end if
    337304
     305  if (spec_ass(pos_spec).gt.0) then
     306    spec_found=.FALSE.
     307    do j=1,pos_spec-1
     308      if (spec_ass(pos_spec).eq.specnum(j)) then
     309        spec_ass(pos_spec)=j
     310        spec_found=.TRUE.
     311        ASSSPEC=.TRUE.
     312      endif
     313    end do
     314    if (spec_found.eqv..false.) then
     315      goto 997
     316    endif
     317  endif
     318
     319  if (dsigma(i).eq.1.) dsigma(i)=1.0001   ! avoid floating exception
    338320  if (dsigma(i).eq.0.) dsigma(i)=1.0001   ! avoid floating exception
    339321
     
    348330
    349331
     332! Read in daily and day-of-week variation of emissions, if available
     333!*******************************************************************
     334! HSO: This is not yet implemented as namelist parameters
     335
     336  do j=1,24           ! initialize everything to no variation
     337    area_hour(i,j)=1.
     338    point_hour(i,j)=1.
     339  end do
     340  do j=1,7
     341    area_dow(i,j)=1.
     342    point_dow(i,j)=1.
     343  end do
     344
     345  if (readerror.ne.0) then ! text format input
     346
     347    read(unitspecies,*,end=22)
     348    do j=1,24     ! 24 hours, starting with 0-1 local time
     349      read(unitspecies,*) ihour,area_hour(i,j),point_hour(i,j)
     350    end do
     351    read(unitspecies,*)
     352    do j=1,7      ! 7 days of the week, starting with Monday
     353      read(unitspecies,*) idow,area_dow(i,j),point_dow(i,j)
     354    end do
     355
    350356  endif
    351357
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG