Changeset 20 for trunk/src/FLEXPART.f90


Ignore:
Timestamp:
Dec 23, 2013, 6:23:38 PM (10 years ago)
Author:
igpis
Message:

move version 9.1.8 form branches to trunk. Contributions from HSO, saeck, pesei, NIK, RT, XKF, IP and others

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/FLEXPART.f90

    r4 r20  
    4949  integer :: i,j,ix,jy,inest
    5050  integer :: idummy = -320
     51  character(len=256) :: inline_options  !pathfile, flexversion, arg2
     52
    5153
    5254  ! Generate a large number of random numbers
     
    5860  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
    5961
     62  !
     63  flexversion='Version 9.1.8  (2013-12-08)'
     64  !verbosity=0
     65  ! Read the pathnames where input/output files are stored
     66  !*******************************************************
     67
     68  inline_options='none'
     69  select case (iargc())
     70  case (2)
     71    call getarg(1,arg1)
     72    pathfile=arg1
     73    call getarg(2,arg2)
     74    inline_options=arg2
     75  case (1)
     76    call getarg(1,arg1)
     77    pathfile=arg1
     78    verbosity=0
     79    if (arg1(1:1).eq.'-') then
     80        write(pathfile,'(a11)') './pathnames'
     81        inline_options=arg1
     82    endif
     83  case (0)
     84    write(pathfile,'(a11)') './pathnames'
     85    verbosity=0
     86  end select
     87 
     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
    60111  ! Print the GPL License statement
    61112  !*******************************************************
    62   print*,'Welcome to FLEXPART Version 9.0'
     113  print*,'Welcome to FLEXPART', trim(flexversion)
    63114  print*,'FLEXPART is free software released under the GNU Genera'// &
    64115       'l Public License.'
    65 
    66   ! Read the pathnames where input/output files are stored
    67   !*******************************************************
    68 
    69   call readpaths
     116           
     117  if (verbosity.gt.0) then
     118        WRITE(*,*) 'call readpaths'
     119  endif
     120  call readpaths(pathfile)
     121   
     122 
     123  if (verbosity.gt.1) then !show clock info
     124     !print*,'length(4)',length(4)
     125     !count=0,count_rate=1000
     126     CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
     127     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
     128     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
     129     !WRITE(*,*) 'SYSTEM_CLOCK, count_rate', count_rate
     130     !WRITE(*,*) 'SYSTEM_CLOCK, count_max', count_max
     131  endif
     132
    70133
    71134  ! Read the user specifications for the current model run
    72135  !*******************************************************
    73136
     137  if (verbosity.gt.0) then
     138        WRITE(*,*) 'call readcommand'
     139  endif
    74140  call readcommand
     141  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
    75150
    76151
    77152  ! Read the age classes to be used
    78153  !********************************
    79 
     154  if (verbosity.gt.0) then
     155        WRITE(*,*) 'call readageclasses'
     156  endif
    80157  call readageclasses
     158
     159  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
     162  endif     
     163 
    81164
    82165
     
    84167  !******************************************************************
    85168
     169  if (verbosity.gt.0) then
     170        WRITE(*,*) 'call readavailable'
     171  endif 
    86172  call readavailable
    87 
    88173
    89174  ! Read the model grid specifications,
    90175  ! both for the mother domain and eventual nests
    91176  !**********************************************
     177 
     178  if (verbosity.gt.0) then
     179     WRITE(*,*) 'call gridcheck'
     180  endif
    92181
    93182  call gridcheck
     183
     184  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
     187  endif     
     188 
     189
     190  if (verbosity.gt.0) then
     191        WRITE(*,*) 'call gridcheck_nests'
     192  endif 
    94193  call gridcheck_nests
    95194
     
    98197  !************************************
    99198
     199  if (verbosity.gt.0) then
     200        WRITE(*,*) 'call readoutgrid'
     201  endif
     202
    100203  call readoutgrid
    101   if (nested_output.eq.1) call readoutgrid_nest
    102 
     204
     205  if (nested_output.eq.1) then
     206          call readoutgrid_nest
     207    if (verbosity.gt.0) then
     208        WRITE(*,*) '# readoutgrid_nest'
     209    endif
     210  endif
    103211
    104212  ! Read the receptor points for which extra concentrations are to be calculated
    105213  !*****************************************************************************
    106214
     215  if (verbosity.eq.1) then
     216     print*,'call readreceptors'
     217  endif
    107218  call readreceptors
    108 
    109219
    110220  ! Read the physico-chemical species property table
     
    117227  !***************************
    118228
     229  if (verbosity.gt.0) then
     230    print*,'call readlanduse'
     231  endif
    119232  call readlanduse
    120233
     
    123236  !********************************************************************
    124237
     238  if (verbosity.gt.0) then
     239    print*,'call assignland'
     240  endif
    125241  call assignland
    126242
     
    130246  !**********************************************
    131247
     248  if (verbosity.gt.0) then
     249    print*,'call readreleases'
     250  endif
    132251  call readreleases
     252
    133253
    134254  ! Read and compute surface resistances to dry deposition of gases
    135255  !****************************************************************
    136256
     257  if (verbosity.gt.0) then
     258    print*,'call readdepo'
     259  endif
    137260  call readdepo
    138 
    139261
    140262  ! Convert the release point coordinates from geografical to grid coordinates
    141263  !***************************************************************************
    142264
    143   call coordtrafo
     265  call coordtrafo 
     266  if (verbosity.gt.0) then
     267    print*,'call coordtrafo'
     268  endif
    144269
    145270
     
    147272  !*****************************************
    148273
     274  if (verbosity.gt.0) then
     275    print*,'Initialize all particles to non-existent'
     276  endif
    149277  do j=1,maxpart
    150278    itra1(j)=-999999999
     
    155283
    156284  if (ipin.eq.1) then
     285    if (verbosity.gt.0) then
     286      print*,'call readpartpositions'
     287    endif
    157288    call readpartpositions
    158289  else
     290    if (verbosity.gt.0) then
     291      print*,'numpart=0, numparticlecount=0'
     292    endif   
    159293    numpart=0
    160294    numparticlecount=0
     
    166300  !***************************************************************
    167301
     302
     303  if (verbosity.gt.0) then
     304    print*,'call outgrid_init'
     305  endif
    168306  call outgrid_init
    169307  if (nested_output.eq.1) call outgrid_init_nest
     
    173311  !******************
    174312
    175   if (OHREA.eqv..TRUE.) &
     313  if (OHREA.eqv..TRUE.) then
     314    if (verbosity.gt.0) then
     315       print*,'call readOHfield'
     316    endif
    176317       call readOHfield
     318  endif
    177319
    178320  ! Write basic information on the simulation to a file "header"
     
    180322  !******************************************************************
    181323
     324
     325  if (verbosity.gt.0) then
     326    print*,'call writeheader'
     327  endif
     328
    182329  call writeheader
    183   if (nested_output.eq.1) call writeheader_nest
    184   open(unitdates,file=path(2)(1:length(2))//'dates')
     330  ! FLEXPART 9.2 ticket ?? write header in ASCII format
     331  call writeheader_txt
     332  !if (nested_output.eq.1) call writeheader_nest
     333  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
     334
     335  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
     336  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
     337
     338
     339
     340  !open(unitdates,file=path(2)(1:length(2))//'dates')
     341
     342  if (verbosity.gt.0) then
     343    print*,'call openreceptors'
     344  endif
    185345  call openreceptors
    186346  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
     
    190350  !***************************************************************************
    191351
     352  if (verbosity.gt.0) then
     353    print*,'discretize release times'
     354  endif
    192355  do i=1,numpoint
    193356    ireleasestart(i)=nint(real(ireleasestart(i))/ &
     
    200363  ! Initialize cloud-base mass fluxes for the convection scheme
    201364  !************************************************************
     365
     366  if (verbosity.gt.0) then
     367    print*,'Initialize cloud-base mass fluxes for the convection scheme'
     368  endif
    202369
    203370  do jy=0,nymin1
     
    218385  !********************************
    219386
     387  if (verbosity.gt.0) then
     388     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
     391     endif
     392     if (info_flag.eq.1) then
     393         print*, 'info only mode (stop)'   
     394         stop
     395     endif
     396     print*,'call timemanager'
     397  endif
     398
    220399  call timemanager
    221400
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG