Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/FLEXPART.f90

    r20 r30  
    4545  use conv_mod
    4646
     47#ifdef NETCDF_OUTPUT
     48  use netcdf_output_mod, only: writeheader_netcdf
     49#endif
     50
     51
    4752  implicit none
    4853
     
    6065  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
    6166
    62   !
    63   flexversion='Version 9.1.8  (2013-12-08)'
    64   !verbosity=0
     67  ! FLEXPART version string
     68  flexversion='Version 9.2 beta (2014-07-01)'
     69  verbosity=0
     70
    6571  ! Read the pathnames where input/output files are stored
    6672  !*******************************************************
     
    7682    call getarg(1,arg1)
    7783    pathfile=arg1
    78     verbosity=0
    7984    if (arg1(1:1).eq.'-') then
    80         write(pathfile,'(a11)') './pathnames'
    81         inline_options=arg1
     85      write(pathfile,'(a11)') './pathnames'
     86      inline_options=arg1
    8287    endif
    8388  case (0)
    8489    write(pathfile,'(a11)') './pathnames'
    85     verbosity=0
    8690  end select
    8791 
    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 
    11192  ! Print the GPL License statement
    11293  !*******************************************************
    113   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'
     94  print*,'Welcome to FLEXPART ', trim(flexversion)
     95  print*,'FLEXPART is free software released under the GNU General Public License.'
     96 
     97  if (inline_options(1:1).eq.'-') then
     98    if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
     99       print*, 'Verbose mode 1: display detailed information during run'
     100       verbosity=1
     101    endif
     102    if (trim(inline_options).eq.'-v2') then
     103       print*, 'Verbose mode 2: display more detailed information during run'
     104       verbosity=2
     105    endif
     106    if (trim(inline_options).eq.'-i') then
     107       print*, 'Info mode: provide detailed run specific information and stop'
     108       verbosity=1
     109       info_flag=1
     110    endif
     111    if (trim(inline_options).eq.'-i2') then
     112       print*, 'Info mode: provide more detailed run specific information and stop'
     113       verbosity=2
     114       info_flag=1
     115    endif
     116  endif
     117           
     118  if (verbosity.gt.0) then
     119    write(*,*) 'call readpaths'
    119120  endif
    120121  call readpaths(pathfile)
    121    
    122122 
    123123  if (verbosity.gt.1) then !show clock info
     
    131131  endif
    132132
    133 
    134133  ! Read the user specifications for the current model run
    135134  !*******************************************************
    136135
    137136  if (verbosity.gt.0) then
    138         WRITE(*,*) 'call readcommand'
     137    write(*,*) 'call readcommand'
    139138  endif
    140139  call readcommand
    141140  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 
     141    write(*,*) '    ldirect=', ldirect
     142    write(*,*) '    ibdate,ibtime=',ibdate,ibtime
     143    write(*,*) '    iedate,ietime=', iedate,ietime
     144    if (verbosity.gt.1) then   
     145      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     146      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     147    endif     
     148  endif
    151149
    152150  ! Read the age classes to be used
    153151  !********************************
    154152  if (verbosity.gt.0) then
    155         WRITE(*,*) 'call readageclasses'
     153    write(*,*) 'call readageclasses'
    156154  endif
    157155  call readageclasses
    158156
    159157  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
     158    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     159    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    162160  endif     
    163  
    164 
    165161
    166162  ! Read, which wind fields are available within the modelling period
     
    168164
    169165  if (verbosity.gt.0) then
    170         WRITE(*,*) 'call readavailable'
     166    write(*,*) 'call readavailable'
    171167  endif 
    172168  call readavailable
     
    177173 
    178174  if (verbosity.gt.0) then
    179      WRITE(*,*) 'call gridcheck'
     175     write(*,*) 'call gridcheck'
    180176  endif
    181177
     
    183179
    184180  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
     181    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     182    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    187183  endif     
    188  
    189 
    190   if (verbosity.gt.0) then
    191         WRITE(*,*) 'call gridcheck_nests'
     184
     185  if (verbosity.gt.0) then
     186    write(*,*) 'call gridcheck_nests'
    192187  endif 
    193188  call gridcheck_nests
    194189
    195 
    196190  ! Read the output grid specifications
    197191  !************************************
    198192
    199193  if (verbosity.gt.0) then
    200         WRITE(*,*) 'call readoutgrid'
     194    write(*,*) 'call readoutgrid'
    201195  endif
    202196
     
    204198
    205199  if (nested_output.eq.1) then
    206           call readoutgrid_nest
     200    call readoutgrid_nest
    207201    if (verbosity.gt.0) then
    208         WRITE(*,*) '# readoutgrid_nest'
     202      write(*,*) '# readoutgrid_nest'
    209203    endif
    210204  endif
     
    232226  call readlanduse
    233227
    234 
    235228  ! Assign fractional cover of landuse classes to each ECMWF grid point
    236229  !********************************************************************
     
    241234  call assignland
    242235
    243 
    244 
    245236  ! Read the coordinates of the release locations
    246237  !**********************************************
     
    251242  call readreleases
    252243
    253 
    254244  ! Read and compute surface resistances to dry deposition of gases
    255245  !****************************************************************
     
    267257    print*,'call coordtrafo'
    268258  endif
    269 
    270259
    271260  ! Initialize all particles to non-existent
     
    295284  endif
    296285
    297 
    298286  ! Calculate volume, surface area, etc., of all output grid cells
    299287  ! Allocate fluxes and OHfield if necessary
    300288  !***************************************************************
    301289
    302 
    303290  if (verbosity.gt.0) then
    304291    print*,'call outgrid_init'
     
    307294  if (nested_output.eq.1) call outgrid_init_nest
    308295
    309 
    310296  ! Read the OH field
    311297  !******************
     
    313299  if (OHREA.eqv..TRUE.) then
    314300    if (verbosity.gt.0) then
    315        print*,'call readOHfield'
    316     endif
    317        call readOHfield
     301      print*,'call readOHfield'
     302    endif
     303    call readOHfield
    318304  endif
    319305
     
    322308  !******************************************************************
    323309
     310  if (lnetcdfout.eq.1) then
     311#ifdef NETCDF_OUTPUT
     312    call writeheader_netcdf(lnest = .false.)
     313#endif
     314  else
     315    call writeheader
     316  end if
     317
     318  if (nested_output.eq.1) then
     319    if (lnetcdfout.eq.1) then
     320#ifdef NETCDF_OUTPUT
     321      call writeheader_netcdf(lnest = .true.)
     322#endif
     323    else
     324      call writeheader_nest
     325    endif
     326  endif
    324327
    325328  if (verbosity.gt.0) then
     
    332335  !if (nested_output.eq.1) call writeheader_nest
    333336  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
    334 
    335337  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
    336338  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
    337339
    338 
    339 
    340   !open(unitdates,file=path(2)(1:length(2))//'dates')
     340  if (lnetcdfout.ne.1) then
     341    open(unitdates,file=path(2)(1:length(2))//'dates')
     342  end if
    341343
    342344  if (verbosity.gt.0) then
     
    346348  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
    347349
    348 
    349350  ! Releases can only start and end at discrete times (multiples of lsynctime)
    350351  !***************************************************************************
     
    354355  endif
    355356  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
     357    ireleasestart(i)=nint(real(ireleasestart(i))/real(lsynctime))*lsynctime
     358    ireleaseend(i)=nint(real(ireleaseend(i))/real(lsynctime))*lsynctime
    360359  end do
    361 
    362360
    363361  ! Initialize cloud-base mass fluxes for the convection scheme
     
    381379  end do
    382380
    383 
    384381  ! Calculate particle trajectories
    385382  !********************************
     
    387384  if (verbosity.gt.0) then
    388385     if (verbosity.gt.1) then   
    389        CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    390        WRITE(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     386       call system_clock(count_clock, count_rate, count_max)
     387       write(*,*) 'System clock',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    391388     endif
    392389     if (info_flag.eq.1) then
    393          print*, 'info only mode (stop)'   
    394          stop
     390       print*, 'Info only mode (stop)'   
     391       stop
    395392     endif
    396393     print*,'call timemanager'
     
    399396  call timemanager
    400397
    401 
    402   write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLE&
    403        &XPART MODEL RUN!'
     398  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLEXPART MODEL RUN!'
     399
     400  ! output wall time
     401  if (verbosity .gt. 0) then
     402    call system_clock(count_clock,count_rate)
     403    tins=(count_clock - count_clock0)/real(count_rate)
     404    print*,'Wall time ',tins,'s, ',tins/60,'min, ',tins/3600,'h.'
     405  endif
    404406
    405407end program flexpart
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG