Changeset 27 for trunk/src/FLEXPART.f90


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/FLEXPART.f90

    r24 r27  
    6060  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
    6161
    62   !
    63   flexversion='Version 9.2 beta (2014-05-23)'
    64   !verbosity=0
     62  ! FLEXPART version string
     63  flexversion='Version 9.2 beta (2014-07-01)'
     64  verbosity=0
     65
    6566  ! Read the pathnames where input/output files are stored
    6667  !*******************************************************
     
    7677    call getarg(1,arg1)
    7778    pathfile=arg1
    78     verbosity=0
    7979    if (arg1(1:1).eq.'-') then
    80         write(pathfile,'(a11)') './pathnames'
    81         inline_options=arg1
     80      write(pathfile,'(a11)') './pathnames'
     81      inline_options=arg1
    8282    endif
    8383  case (0)
    8484    write(pathfile,'(a11)') './pathnames'
    85     verbosity=0
    8685  end select
    8786 
    88     if (inline_options(1:1).eq.'-') then
    89       print*, 'inline options=', inline_options       
    90       if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
    91          print*, 'verbose mode 1: additional information will be displayed'
    92          verbosity=1
    93       endif
    94       if (trim(inline_options).eq.'-v2') then
    95          print*, 'verbose mode 2: additional information will be displayed'
    96          verbosity=2
    97       endif
    98       if (trim(inline_options).eq.'-i') then
    99          print*, 'info mode: will provide run specific information and stop'
    100          verbosity=1
    101          info_flag=1
    102       endif
    103       if (trim(inline_options).eq.'-i2') then
    104          print*, 'info mode: will provide run specific information and stop'
    105          verbosity=2
    106          info_flag=1
    107       endif
    108     endif
    109 
    110 
    11187  ! Print the GPL License statement
    11288  !*******************************************************
    11389  print*,'Welcome to FLEXPART ', trim(flexversion)
    114   print*,'FLEXPART is free software released under the GNU Genera'// &
    115        'l Public License.'
    116            
    117   if (verbosity.gt.0) then
    118         WRITE(*,*) 'call readpaths'
     90  print*,'FLEXPART is free software released under the GNU General Public License.'
     91 
     92  if (inline_options(1:1).eq.'-') then
     93    if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
     94       print*, 'Verbose mode 1: display detailed information during run'
     95       verbosity=1
     96    endif
     97    if (trim(inline_options).eq.'-v2') then
     98       print*, 'Verbose mode 2: display more detailed information during run'
     99       verbosity=2
     100    endif
     101    if (trim(inline_options).eq.'-i') then
     102       print*, 'Info mode: provide detailed run specific information and stop'
     103       verbosity=1
     104       info_flag=1
     105    endif
     106    if (trim(inline_options).eq.'-i2') then
     107       print*, 'Info mode: provide more detailed run specific information and stop'
     108       verbosity=2
     109       info_flag=1
     110    endif
     111  endif
     112           
     113  if (verbosity.gt.0) then
     114    write(*,*) 'call readpaths'
    119115  endif
    120116  call readpaths(pathfile)
    121    
    122117 
    123118  if (verbosity.gt.1) then !show clock info
     
    131126  endif
    132127
    133 
    134128  ! Read the user specifications for the current model run
    135129  !*******************************************************
    136130
    137131  if (verbosity.gt.0) then
    138         WRITE(*,*) 'call readcommand'
     132    write(*,*) 'call readcommand'
    139133  endif
    140134  call readcommand
    141135  if (verbosity.gt.0) then
    142         WRITE(*,*) '    ldirect=', ldirect
    143         WRITE(*,*) '    ibdate,ibtime=',ibdate,ibtime
    144         WRITE(*,*) '    iedate,ietime=', iedate,ietime
    145         if (verbosity.gt.1) then   
    146                 CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    147                 WRITE(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    148         endif     
    149   endif
    150 
     136    write(*,*) '    ldirect=', ldirect
     137    write(*,*) '    ibdate,ibtime=',ibdate,ibtime
     138    write(*,*) '    iedate,ietime=', iedate,ietime
     139    if (verbosity.gt.1) then   
     140      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     141      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     142    endif     
     143  endif
    151144
    152145  ! Read the age classes to be used
    153146  !********************************
    154147  if (verbosity.gt.0) then
    155         WRITE(*,*) 'call readageclasses'
     148    write(*,*) 'call readageclasses'
    156149  endif
    157150  call readageclasses
    158151
    159152  if (verbosity.gt.1) then   
    160                 CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    161                 WRITE(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     153    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     154    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    162155  endif     
    163  
    164 
    165156
    166157  ! Read, which wind fields are available within the modelling period
     
    168159
    169160  if (verbosity.gt.0) then
    170         WRITE(*,*) 'call readavailable'
     161    write(*,*) 'call readavailable'
    171162  endif 
    172163  call readavailable
     
    177168 
    178169  if (verbosity.gt.0) then
    179      WRITE(*,*) 'call gridcheck'
     170     write(*,*) 'call gridcheck'
    180171  endif
    181172
     
    183174
    184175  if (verbosity.gt.1) then   
    185      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    186      WRITE(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     176    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     177    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    187178  endif     
    188  
    189 
    190   if (verbosity.gt.0) then
    191         WRITE(*,*) 'call gridcheck_nests'
     179
     180  if (verbosity.gt.0) then
     181    write(*,*) 'call gridcheck_nests'
    192182  endif 
    193183  call gridcheck_nests
    194184
    195 
    196185  ! Read the output grid specifications
    197186  !************************************
    198187
    199188  if (verbosity.gt.0) then
    200         WRITE(*,*) 'call readoutgrid'
     189    write(*,*) 'call readoutgrid'
    201190  endif
    202191
     
    204193
    205194  if (nested_output.eq.1) then
    206           call readoutgrid_nest
     195    call readoutgrid_nest
    207196    if (verbosity.gt.0) then
    208         WRITE(*,*) '# readoutgrid_nest'
     197      write(*,*) '# readoutgrid_nest'
    209198    endif
    210199  endif
     
    232221  call readlanduse
    233222
    234 
    235223  ! Assign fractional cover of landuse classes to each ECMWF grid point
    236224  !********************************************************************
     
    241229  call assignland
    242230
    243 
    244 
    245231  ! Read the coordinates of the release locations
    246232  !**********************************************
     
    251237  call readreleases
    252238
    253 
    254239  ! Read and compute surface resistances to dry deposition of gases
    255240  !****************************************************************
     
    267252    print*,'call coordtrafo'
    268253  endif
    269 
    270254
    271255  ! Initialize all particles to non-existent
     
    295279  endif
    296280
    297 
    298281  ! Calculate volume, surface area, etc., of all output grid cells
    299282  ! Allocate fluxes and OHfield if necessary
    300283  !***************************************************************
    301284
    302 
    303285  if (verbosity.gt.0) then
    304286    print*,'call outgrid_init'
     
    307289  if (nested_output.eq.1) call outgrid_init_nest
    308290
    309 
    310291  ! Read the OH field
    311292  !******************
     
    313294  if (OHREA.eqv..TRUE.) then
    314295    if (verbosity.gt.0) then
    315        print*,'call readOHfield'
    316     endif
    317        call readOHfield
     296      print*,'call readOHfield'
     297    endif
     298    call readOHfield
    318299  endif
    319300
     
    321302  ! and open files that are to be kept open throughout the simulation
    322303  !******************************************************************
    323 
    324304
    325305  if (verbosity.gt.0) then
     
    332312  !if (nested_output.eq.1) call writeheader_nest
    333313  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
    334 
    335314  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
    336315  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
    337316
    338 
    339 
    340317  !open(unitdates,file=path(2)(1:length(2))//'dates')
    341318
     
    346323  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
    347324
    348 
    349325  ! Releases can only start and end at discrete times (multiples of lsynctime)
    350326  !***************************************************************************
     
    354330  endif
    355331  do i=1,numpoint
    356     ireleasestart(i)=nint(real(ireleasestart(i))/ &
    357          real(lsynctime))*lsynctime
    358     ireleaseend(i)=nint(real(ireleaseend(i))/ &
    359          real(lsynctime))*lsynctime
    360   end do
    361 
     332    ireleasestart(i)=nint(real(ireleasestart(i))/real(lsynctime))*lsynctime
     333    ireleaseend(i)=nint(real(ireleaseend(i))/real(lsynctime))*lsynctime
     334  end do
    362335
    363336  ! Initialize cloud-base mass fluxes for the convection scheme
     
    381354  end do
    382355
    383 
    384356  ! Calculate particle trajectories
    385357  !********************************
     
    388360     if (verbosity.gt.1) then   
    389361       CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    390        WRITE(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     362       write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    391363     endif
    392364     if (info_flag.eq.1) then
    393          print*, 'info only mode (stop)'   
    394          stop
     365       print*, 'info only mode (stop)'   
     366       stop
    395367     endif
    396368     print*,'call timemanager'
     
    399371  call timemanager
    400372
    401 
    402   write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLE&
    403        &XPART MODEL RUN!'
     373  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLEXPART MODEL RUN!'
    404374
    405375end program flexpart
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG