Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/FLEXPART.f90

    r30 r20  
    4545  use conv_mod
    4646
    47 #ifdef NETCDF_OUTPUT
    48   use netcdf_output_mod, only: writeheader_netcdf
    49 #endif
    50 
    51 
    5247  implicit none
    5348
     
    6560  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
    6661
    67   ! FLEXPART version string
    68   flexversion='Version 9.2 beta (2014-07-01)'
    69   verbosity=0
    70 
     62  !
     63  flexversion='Version 9.1.8  (2013-12-08)'
     64  !verbosity=0
    7165  ! Read the pathnames where input/output files are stored
    7266  !*******************************************************
     
    8276    call getarg(1,arg1)
    8377    pathfile=arg1
     78    verbosity=0
    8479    if (arg1(1:1).eq.'-') then
    85       write(pathfile,'(a11)') './pathnames'
    86       inline_options=arg1
     80        write(pathfile,'(a11)') './pathnames'
     81        inline_options=arg1
    8782    endif
    8883  case (0)
    8984    write(pathfile,'(a11)') './pathnames'
     85    verbosity=0
    9086  end select
    9187 
     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
    92111  ! Print the GPL License statement
    93112  !*******************************************************
    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'
     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'
    120119  endif
    121120  call readpaths(pathfile)
     121   
    122122 
    123123  if (verbosity.gt.1) then !show clock info
     
    131131  endif
    132132
     133
    133134  ! Read the user specifications for the current model run
    134135  !*******************************************************
    135136
    136137  if (verbosity.gt.0) then
    137     write(*,*) 'call readcommand'
     138        WRITE(*,*) 'call readcommand'
    138139  endif
    139140  call readcommand
    140141  if (verbosity.gt.0) then
    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
     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
    149151
    150152  ! Read the age classes to be used
    151153  !********************************
    152154  if (verbosity.gt.0) then
    153     write(*,*) 'call readageclasses'
     155        WRITE(*,*) 'call readageclasses'
    154156  endif
    155157  call readageclasses
    156158
    157159  if (verbosity.gt.1) then   
    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
     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
    160162  endif     
     163 
     164
    161165
    162166  ! Read, which wind fields are available within the modelling period
     
    164168
    165169  if (verbosity.gt.0) then
    166     write(*,*) 'call readavailable'
     170        WRITE(*,*) 'call readavailable'
    167171  endif 
    168172  call readavailable
     
    173177 
    174178  if (verbosity.gt.0) then
    175      write(*,*) 'call gridcheck'
     179     WRITE(*,*) 'call gridcheck'
    176180  endif
    177181
     
    179183
    180184  if (verbosity.gt.1) then   
    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
     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
    183187  endif     
    184 
    185   if (verbosity.gt.0) then
    186     write(*,*) 'call gridcheck_nests'
     188 
     189
     190  if (verbosity.gt.0) then
     191        WRITE(*,*) 'call gridcheck_nests'
    187192  endif 
    188193  call gridcheck_nests
    189194
     195
    190196  ! Read the output grid specifications
    191197  !************************************
    192198
    193199  if (verbosity.gt.0) then
    194     write(*,*) 'call readoutgrid'
     200        WRITE(*,*) 'call readoutgrid'
    195201  endif
    196202
     
    198204
    199205  if (nested_output.eq.1) then
    200     call readoutgrid_nest
     206          call readoutgrid_nest
    201207    if (verbosity.gt.0) then
    202       write(*,*) '# readoutgrid_nest'
     208        WRITE(*,*) '# readoutgrid_nest'
    203209    endif
    204210  endif
     
    226232  call readlanduse
    227233
     234
    228235  ! Assign fractional cover of landuse classes to each ECMWF grid point
    229236  !********************************************************************
     
    234241  call assignland
    235242
     243
     244
    236245  ! Read the coordinates of the release locations
    237246  !**********************************************
     
    242251  call readreleases
    243252
     253
    244254  ! Read and compute surface resistances to dry deposition of gases
    245255  !****************************************************************
     
    257267    print*,'call coordtrafo'
    258268  endif
     269
    259270
    260271  ! Initialize all particles to non-existent
     
    284295  endif
    285296
     297
    286298  ! Calculate volume, surface area, etc., of all output grid cells
    287299  ! Allocate fluxes and OHfield if necessary
    288300  !***************************************************************
    289301
     302
    290303  if (verbosity.gt.0) then
    291304    print*,'call outgrid_init'
     
    294307  if (nested_output.eq.1) call outgrid_init_nest
    295308
     309
    296310  ! Read the OH field
    297311  !******************
     
    299313  if (OHREA.eqv..TRUE.) then
    300314    if (verbosity.gt.0) then
    301       print*,'call readOHfield'
     315       print*,'call readOHfield'
    302316    endif
    303     call readOHfield
     317       call readOHfield
    304318  endif
    305319
     
    308322  !******************************************************************
    309323
    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
    327324
    328325  if (verbosity.gt.0) then
     
    335332  !if (nested_output.eq.1) call writeheader_nest
    336333  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
     334
    337335  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
    338336  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
    339337
    340   if (lnetcdfout.ne.1) then
    341     open(unitdates,file=path(2)(1:length(2))//'dates')
    342   end if
     338
     339
     340  !open(unitdates,file=path(2)(1:length(2))//'dates')
    343341
    344342  if (verbosity.gt.0) then
     
    348346  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
    349347
     348
    350349  ! Releases can only start and end at discrete times (multiples of lsynctime)
    351350  !***************************************************************************
     
    355354  endif
    356355  do i=1,numpoint
    357     ireleasestart(i)=nint(real(ireleasestart(i))/real(lsynctime))*lsynctime
    358     ireleaseend(i)=nint(real(ireleaseend(i))/real(lsynctime))*lsynctime
     356    ireleasestart(i)=nint(real(ireleasestart(i))/ &
     357         real(lsynctime))*lsynctime
     358    ireleaseend(i)=nint(real(ireleaseend(i))/ &
     359         real(lsynctime))*lsynctime
    359360  end do
     361
    360362
    361363  ! Initialize cloud-base mass fluxes for the convection scheme
     
    379381  end do
    380382
     383
    381384  ! Calculate particle trajectories
    382385  !********************************
     
    384387  if (verbosity.gt.0) then
    385388     if (verbosity.gt.1) then   
    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
     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
    388391     endif
    389392     if (info_flag.eq.1) then
    390        print*, 'Info only mode (stop)'   
    391        stop
     393         print*, 'info only mode (stop)'   
     394         stop
    392395     endif
    393396     print*,'call timemanager'
     
    396399  call timemanager
    397400
    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
     401
     402  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLE&
     403       &XPART MODEL RUN!'
    406404
    407405end program flexpart
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG