Ignore:
Timestamp:
Jul 3, 2014, 2:55:50 PM (10 years ago)
Author:
hasod
Message:
  • Implemented optional namelist input for COMMAND, RELEASES, SPECIES, AGECLASSES,OUTGRID,OUTGRID_NEST,RECEPTORS
  • Implemented com_mod switch nmlout to write input files as namelist to the output directory (.true. by default)
  • Proposed updated startup and runtime output (may change back to previous info if desired)
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/readspecies.f90

    r24 r27  
    3030  !                                                                            *
    3131  !   11 July 1996                                                             *
    32   !                                                                            *
     32  !
    3333  !   Changes:                                                                 *
    3434  !   N. Kristiansen, 31.01.2013: Including parameters for in-cloud scavenging *
     35  !                                                                            *
     36  !   HSO, 13 August 2013
     37  !   added optional namelist input
    3538  !                                                                            *
    3639  !*****************************************************************************
     
    6265  logical :: spec_found
    6366
     67  character(len=16) :: pspecies
     68  real :: pdecay, pweta, pwetb, preldiff, phenry, pf0, pdensity, pdquer
     69  real :: pdsigma, pdryvel, pweightmolar, pohreact, pspec_ass, pkao
     70  real :: pweta_in, pwetb_in, pwetc_in, pwetd_in
     71  integer :: readerror
     72
     73  ! declare namelist
     74  namelist /species_params/ &
     75   pspecies, pdecay, pweta, pwetb, &
     76   pweta_in, pwetb_in, pwetc_in, pwetd_in, &
     77   preldiff, phenry, pf0, pdensity, pdquer, &
     78   pdsigma, pdryvel, pweightmolar, pohreact, pspec_ass, pkao
     79
     80  pspecies=" "
     81  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
     88  preldiff=-9.9
     89  phenry=0.0
     90  pf0=0.0
     91  pdensity=-9.9E09
     92  pdquer=0.0
     93  pdsigma=0.0
     94  pdryvel=-9.99
     95  pohreact=-9.9E-09
     96  pspec_ass=-9
     97  pkao=-99.99
     98  pweightmolar=-789.0 ! read failure indicator value
     99
    64100  ! Open the SPECIES file and read species names and properties
    65101  !************************************************************
    66102  specnum(pos_spec)=id_spec
    67103  write(aspecnumb,'(i3.3)') specnum(pos_spec)
    68   open(unitspecies,file= &
    69        path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old', &
    70        err=998)
     104  open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',form='formatted',err=998)
    71105  !write(*,*) 'reading SPECIES',specnum(pos_spec)
    72106
    73107  ASSSPEC=.FALSE.
    74108
    75   do i=1,6
    76     read(unitspecies,*)
    77   end do
     109  ! try namelist input
     110  read(unitspecies,species_params,iostat=readerror)
     111  close(unitspecies)
     112   
     113  if ((pweightmolar.eq.-789.0).or.(readerror.ne.0)) then ! no namelist found
     114
     115    readerror=1
     116
     117    open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',err=998)
     118
     119    do i=1,6
     120      read(unitspecies,*)
     121    end do
    78122
    79123    read(unitspecies,'(a10)',end=22) species(pos_spec)
     
    86130  !  write(*,*) wetb(pos_spec)
    87131
    88 !*** NIK 31.01.2013: including in-cloud scavening parameters
     132  !*** NIK 31.01.2013: including in-cloud scavening parameters
    89133   read(unitspecies,'(e18.1)',end=22) weta_in(pos_spec)
    90134  !  write(*,*) weta_in(pos_spec)
     
    118162    read(unitspecies,'(f18.2)',end=22) kao(pos_spec)
    119163  !       write(*,*) kao(pos_spec)
    120     i=pos_spec
    121 
    122     if ((weta(pos_spec).gt.0).and.(henry(pos_spec).le.0)) then
    123        if (dquer(pos_spec).le.0) goto 996 ! no particle, no henry set
     164
     165    pspecies=species(pos_spec)
     166    pdecay=decay(pos_spec)
     167    pweta=weta(pos_spec)
     168    pwetb=wetb(pos_spec)
     169    pweta_in=weta_in(pos_spec)
     170    pwetb_in=wetb_in(pos_spec)
     171    pwetc_in=wetc_in(pos_spec)
     172    pwetd_in=wetd_in(pos_spec)
     173    preldiff=reldiff(pos_spec)
     174    phenry=henry(pos_spec)
     175    pf0=f0(pos_spec)
     176    pdensity=density(pos_spec)
     177    pdquer=dquer(pos_spec)
     178    pdsigma=dsigma(pos_spec)
     179    pdryvel=dryvel(pos_spec)
     180    pweightmolar=weightmolar(pos_spec)
     181    pohreact=ohreact(pos_spec)
     182    pspec_ass=spec_ass(pos_spec)
     183    pkao=kao(pos_spec)
     184
     185  else
     186
     187    species(pos_spec)=pspecies
     188    decay(pos_spec)=pdecay
     189    weta(pos_spec)=pweta
     190    wetb(pos_spec)=pwetb
     191    weta_in(pos_spec)=pweta_in
     192    wetb_in(pos_spec)=pwetb_in
     193    wetc_in(pos_spec)=pwetc_in
     194    wetd_in(pos_spec)=pwetd_in
     195    reldiff(pos_spec)=preldiff
     196    henry(pos_spec)=phenry
     197    f0(pos_spec)=pf0
     198    density(pos_spec)=pdensity
     199    dquer(pos_spec)=pdquer
     200    dsigma(pos_spec)=pdsigma
     201    dryvel(pos_spec)=pdryvel
     202    weightmolar(pos_spec)=pweightmolar
     203    ohreact(pos_spec)=pohreact
     204    spec_ass(pos_spec)=pspec_ass
     205    kao(pos_spec)=pkao
     206
     207  endif
     208
     209  i=pos_spec
     210
     211  if ((weta(pos_spec).gt.0).and.(henry(pos_spec).le.0)) then
     212   if (dquer(pos_spec).le.0) goto 996 ! no particle, no henry set
     213  endif
     214
     215  if (spec_ass(pos_spec).gt.0) then
     216    spec_found=.FALSE.
     217    do j=1,pos_spec-1
     218      if (spec_ass(pos_spec).eq.specnum(j)) then
     219        spec_ass(pos_spec)=j
     220        spec_found=.TRUE.
     221        ASSSPEC=.TRUE.
     222      endif
     223    end do
     224    if (spec_found.eqv..FALSE.) then
     225      goto 997
    124226    endif
    125 
    126     if (spec_ass(pos_spec).gt.0) then
    127        spec_found=.FALSE.
    128        do j=1,pos_spec-1
    129           if (spec_ass(pos_spec).eq.specnum(j)) then
    130              spec_ass(pos_spec)=j
    131              spec_found=.TRUE.
    132              ASSSPEC=.TRUE.
    133           endif
    134        end do
    135        if (spec_found.eqv..FALSE.) then
    136           goto 997
    137        endif
    138     endif
    139 
    140     if (dsigma(i).eq.1.) dsigma(i)=1.0001   ! avoid floating exception
    141     if (dsigma(i).eq.0.) dsigma(i)=1.0001   ! avoid floating exception
    142 
    143     if ((reldiff(i).gt.0.).and.(density(i).gt.0.)) then
    144       write(*,*) '#### FLEXPART MODEL ERROR! FILE "SPECIES"    ####'
    145       write(*,*) '#### IS CORRUPT. SPECIES CANNOT BE BOTH      ####'
    146       write(*,*) '#### PARTICLE AND GAS.                       ####'
    147       write(*,*) '#### SPECIES NUMBER',aspecnumb
    148       stop
    149     endif
     227  endif
     228
     229  if (dsigma(i).eq.1.) dsigma(i)=1.0001   ! avoid floating exception
     230  if (dsigma(i).eq.0.) dsigma(i)=1.0001   ! avoid floating exception
     231
     232  if ((reldiff(i).gt.0.).and.(density(i).gt.0.)) then
     233    write(*,*) '#### FLEXPART MODEL ERROR! FILE "SPECIES"    ####'
     234    write(*,*) '#### IS CORRUPT. SPECIES CANNOT BE BOTH      ####'
     235    write(*,*) '#### PARTICLE AND GAS.                       ####'
     236    write(*,*) '#### SPECIES NUMBER',aspecnumb
     237    stop
     238  endif
    15023920   continue
    151240
    152 
    153   ! Read in daily and day-of-week variation of emissions, if available
    154   !*******************************************************************
     241  if (readerror.ne.0) then ! text format input
     242
     243    ! Read in daily and day-of-week variation of emissions, if available
     244    !*******************************************************************
     245    ! HSO: This is not yet implemented as namelist parameters
    155246
    156247    do j=1,24           ! initialize everything to no variation
     
    172263    end do
    173264
    174 22   close(unitspecies)
    175 
    176    return
     265  endif
     266
     26722 close(unitspecies)
     268
     269  ! namelist output if requested
     270  if (nmlout.eqv..true.) then
     271    open(unitspecies,file=path(2)(1:length(2))//'SPECIES_'//aspecnumb//'.namelist',access='append',status='new',err=1000)
     272    write(unitspecies,nml=species_params)
     273    close(unitspecies)
     274  endif
     275
     276  return
    177277
    178278996   write(*,*) '#####################################################'
     
    203303  stop
    204304
     3051000 write(*,*) ' #### FLEXPART MODEL ERROR! FILE "SPECIES_',aspecnumb,'.namelist'
     306  write(*,*) ' #### CANNOT BE OPENED IN THE DIRECTORY       #### '
     307  write(*,'(a)') path(2)(1:length(2))
     308  stop
    205309
    206310end subroutine readspecies
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG