Changes in / [52aabab:e603ee6] in flexpart.git


Ignore:
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • .gitignore

    r4ba50e6 re603ee6  
    1 FP_ecmwf_gfortran*
    2 *.o
    3 *_mod.mod
    41.DS_Store
    52output
  • src/FLEXPART.f90

    r414a5e5 rb4d29ce  
    5050  integer :: idummy = -320
    5151  character(len=256) :: inline_options  !pathfile, flexversion, arg2
    52   integer :: index_v
     52
    5353
    5454  ! Generate a large number of random numbers
     
    6161
    6262  ! FLEXPART version string
    63   ! flexversion='Version 9.2 beta (2014-07-01)'
    64   flexversion='Version 9.2.0.1 (2015-01-27)'
    65   ! default inlide options
    66   inline_options='none'
    67   !verbosity flags  defined in com_mod.f90
    68  
     63  flexversion='Version 9.2 beta (2014-07-01)'
     64  verbosity=0
     65
    6966  ! Read the pathnames where input/output files are stored
    7067  !*******************************************************
    7168
     69  inline_options='none'
    7270  select case (iargc())
    73   case (2) !2 parameters: pathfile and inline options
     71  case (2)
    7472    call getarg(1,arg1)
    7573    pathfile=arg1
    7674    call getarg(2,arg2)
    7775    inline_options=arg2
    78   case (1) !1 parameter pathfiel or inline options
     76  case (1)
    7977    call getarg(1,arg1)
    8078    pathfile=arg1
     
    8381      inline_options=arg1
    8482    endif
    85   case (0) !default behavior
     83  case (0)
    8684    write(pathfile,'(a11)') './pathnames'
    8785  end select
     
    9189  print*,'Welcome to FLEXPART ', trim(flexversion)
    9290  print*,'FLEXPART is free software released under the GNU General Public License.'
    93 
    94   ! inline options allow to fine tune the verbosity during run time
    95   ! e.g.: show compilation parameters or input variables, time execution     
     91 
    9692  if (inline_options(1:1).eq.'-') then
    97    ! if (index(inline_options,'v').gt.0) then
    98    !    print*, 'verbose mode'
    99    !    verbosity=1
    100    !    index_v=index(inline_options,'v')
    101    !    if (inline_options(index_v+1:index_v+1).eq.'2') then
    102    !    verbosity=2
    103    !    endif         
    104    ! endif   
    105  
    106     !if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
    107     if (index(inline_options,'v').gt.0) then
    108        index_v=index(inline_options,'v')
    109        print*, 'Verbose mode: display  additional information during run'
     93    if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
     94       print*, 'Verbose mode 1: display detailed information during run'
    11095       verbosity=1
    111        if (inline_options(index_v+1:index_v+1).eq.'2') then
     96    endif
     97    if (trim(inline_options).eq.'-v2') then
     98       print*, 'Verbose mode 2: display more detailed information during run'
    11299       verbosity=2
    113        endif
    114        print*, 'verbosity level=', verbosity !inline_options(index_v+1:index_v+1)
    115              
    116     endif
    117     !iif (trim(inline_options).eq.'-v2') then
    118     !   print*, 'Verbose mode 2: display more detailed information during run'
    119     !   verbosity=2
    120     !endif
    121 
    122     if (index(inline_options,'i').gt.0) then   
    123     !if (trim(inline_options).eq.'-i') then
    124        index_v=index(inline_options,'i')
    125        print*, 'Info mode: provide run specific information and stop'
     100    endif
     101    if (trim(inline_options).eq.'-i') then
     102       print*, 'Info mode: provide detailed run specific information and stop'
    126103       verbosity=1
    127104       info_flag=1
    128        !if (trim(inline_options).eq.'-i2') then
    129        if (inline_options(index_v+1:index_v+1).eq.'2') then
    130            print*, 'Including input files'
    131        !   verbosity=1
    132        info_flag=2
    133        endif
    134     endif
    135     !if (trim(inline_options).eq.'-i2') then
    136     !   print*, 'Info mode: provide more detailed run specific information and stop'
    137     !   verbosity=1
    138     !   info_flag=2
    139     !endif
    140     if (index(inline_options,'t').gt.0) then
    141        time_flag=1
    142        print*, 'timing execution: not implemented'
    143        !stop
    144     endif
    145     if (index(inline_options,'d').gt.0) then
    146        debug_flag=1
    147        print*, 'debug: not implemented'
    148        print*, 'debug_flag=', debug_flag
    149        !stop
    150     endif
     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
    151111  endif
    152112           
    153113  if (verbosity.gt.0) then
    154     print*, 'FLEXPART>******************************'
    155     print*, 'FLEXPART>* verbosity level:', verbosity
    156     print*, 'FLEXPART>* info only:      ', info_flag
    157     print*, 'FLEXPART>* time execution: ', time_flag
    158     print*, 'FLEXPART>******************************'
    159    
    160     print*, 'FLEXPART> parameters from par_mod'   
    161     print*, 'FLEXPART> nxmax=  ', nxmax
    162     print*, 'FLEXPART> nymax=  ', nymax
    163     print*, 'FLEXPART> nuvzmax=', nuvzmax
    164     print*, 'FLEXPART> nwzmax= ', nwzmax
    165     print*, 'FLEXPART> nzmax=  ', nzmax
    166     print*, 'FLEXPART> nxshift=', nxshift
    167     print*, 'FLEXPART> maxpart=', maxpart
    168     print*, 'FLEXPART> maxspec=', maxspec
    169 
    170     if (info_flag.eq.1) stop
    171114    write(*,*) 'call readpaths'
    172115  endif
    173116  call readpaths(pathfile)
    174117 
    175   !if (time_flag.gt.1) then !show clock info
     118  if (verbosity.gt.1) then !show clock info
     119     !print*,'length(4)',length(4)
    176120     !count=0,count_rate=1000
    177   CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
     121     CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
    178122     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
    179123     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
    180124     !WRITE(*,*) 'SYSTEM_CLOCK, count_rate', count_rate
    181125     !WRITE(*,*) 'SYSTEM_CLOCK, count_max', count_max
    182   !endif
     126  endif
    183127
    184128  ! Read the user specifications for the current model run
     
    190134  call readcommand
    191135  if (verbosity.gt.0) then
    192     write(*,*) '    ldirect      =', ldirect
    193     write(*,*) '    ibdate,ibtime=', ibdate,ibtime
     136    write(*,*) '    ldirect=', ldirect
     137    write(*,*) '    ibdate,ibtime=',ibdate,ibtime
    194138    write(*,*) '    iedate,ietime=', iedate,ietime
    195   endif
    196     if (time_flag.gt.0) then   
     139    if (verbosity.gt.1) then   
    197140      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    198141      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    199142    endif     
     143  endif
    200144
    201145  ! Read the age classes to be used
     
    206150  call readageclasses
    207151
    208   if (time_flag.gt.1) then   
     152  if (verbosity.gt.1) then   
    209153    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    210154    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     
    224168 
    225169  if (verbosity.gt.0) then
    226      write(*,*) 'FLEXPART> call gridcheck'
    227   endif
     170     write(*,*) 'call gridcheck'
     171  endif
     172
    228173  call gridcheck
    229174
    230   if (time_flag.gt.0) then   
     175  if (verbosity.gt.1) then   
    231176    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    232177    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     
    242187
    243188  if (verbosity.gt.0) then
    244     write(*,*) 'FLEXPART> call readoutgrid'
     189    write(*,*) 'call readoutgrid'
    245190  endif
    246191
     
    250195    call readoutgrid_nest
    251196    if (verbosity.gt.0) then
    252       write(*,*) 'FLEXPART> readoutgrid_nest'
     197      write(*,*) '# readoutgrid_nest'
    253198    endif
    254199  endif
     
    258203
    259204  if (verbosity.eq.1) then
    260      print*,'FLEXPART> call readreceptors'
     205     print*,'call readreceptors'
    261206  endif
    262207  call readreceptors
     
    272217
    273218  if (verbosity.gt.0) then
    274     print*,'FLEXPART> call readlanduse'
     219    print*,'call readlanduse'
    275220  endif
    276221  call readlanduse
     
    280225
    281226  if (verbosity.gt.0) then
    282     print*,'FLEXPART> call assignland'
     227    print*,'call assignland'
    283228  endif
    284229  call assignland
     
    288233
    289234  if (verbosity.gt.0) then
    290     print*,'FLEXPART> call readreleases'
     235    print*,'call readreleases'
    291236  endif
    292237  call readreleases
     
    328273  else
    329274    if (verbosity.gt.0) then
    330       print*,'set numpart=0, numparticlecount=0'
     275      print*,'numpart=0, numparticlecount=0'
    331276    endif   
    332277    numpart=0
     
    363308
    364309  call writeheader
    365   ! write header in ASCII format
     310  ! FLEXPART 9.2 ticket ?? write header in ASCII format
    366311  call writeheader_txt
    367312  !if (nested_output.eq.1) call writeheader_nest
     
    412357  !********************************
    413358
    414   if (time_flag.gt.0) then   
    415     CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    416     write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    417   endif
    418   if (info_flag.eq.2) then
    419     print*, 'info only mode (stop before call timemanager)'
    420     stop
    421   endif
    422   if (verbosity.gt.0) then
     359  if (verbosity.gt.0) then
     360     if (verbosity.gt.1) then   
     361       CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     362       write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     363     endif
     364     if (info_flag.eq.1) then
     365       print*, 'info only mode (stop)'   
     366       stop
     367     endif
    423368     print*,'call timemanager'
    424369  endif
  • src/com_mod.f90

    re92a713 rb4d29ce  
    2323  !****************************************************************
    2424
    25   character :: path(numpath+2*maxnests)*256
     25  character :: path(numpath+2*maxnests)*120
    2626  integer :: length(numpath+2*maxnests)
    2727  character(len=256) :: pathfile, flexversion, arg1, arg2
     
    686686  integer :: verbosity=0
    687687  integer :: info_flag=0
    688   integer :: time_flag=0
    689   integer :: debug_flag=0
    690688  integer :: count_clock, count_clock0,  count_rate, count_max
    691689  logical :: nmlout=.true.
  • src/gridcheck.f90

    r6470a47 rb4d29ce  
    446446       nuvz+1,nwz
    447447  write(*,*)
    448   write(*,'(a)') 'gridcheck> Mother domain:'
    449   write(*,'(a,f10.5,a,f10.5,a,f10.5)') 'gridcheck>  Longitude range: ', &
     448  write(*,'(a)') ' Mother domain:'
     449  write(*,'(a,f10.5,a,f10.5,a,f10.5)') '  Longitude range: ', &
    450450       xlon0,' to ',xlon0+(nx-1)*dx,'   Grid distance: ',dx
    451   write(*,'(a,f10.5,a,f10.5,a,f10.5)') 'gridcheck>  Latitude range : ', &
     451  write(*,'(a,f10.5,a,f10.5,a,f10.5)') '  Latitude range : ', &
    452452       ylat0,' to ',ylat0+(ny-1)*dy,'   Grid distance: ',dy
    453453  write(*,*)
     
    545545       '###### '
    546546  write(*,*)
    547   !write(*,'(a)') '!!! PLEASE INSERT A NEW CD-ROM AND   !!!'
    548   !write(*,'(a)') '!!! PRESS ANY KEY TO CONTINUE...     !!!'
    549   !write(*,'(a)') '!!! ...OR TERMINATE FLEXPART PRESSING!!!'
    550   !write(*,'(a)') '!!! THE "X" KEY...                   !!!'
    551   !write(*,*)
    552   !read(*,'(a)') opt
    553   !if(opt.eq.'X') then
     547  write(*,'(a)') '!!! PLEASE INSERT A NEW CD-ROM AND   !!!'
     548  write(*,'(a)') '!!! PRESS ANY KEY TO CONTINUE...     !!!'
     549  write(*,'(a)') '!!! ...OR TERMINATE FLEXPART PRESSING!!!'
     550  write(*,'(a)') '!!! THE "X" KEY...                   !!!'
     551  write(*,*)
     552  read(*,'(a)') opt
     553  if(opt.eq.'X') then
    554554    stop
    555   !else
    556   !  goto 5
    557   !endif
     555  else
     556    goto 5
     557  endif
    558558
    559559end subroutine gridcheck
  • src/makefile

    rda396a2 r4fbe7a5  
    66LIBPATH1 = /xnilu_wrk/flex_wrk/bin64/grib_api/lib
    77LIBPATH2 =   /usr/lib/x86_64-linux-gnu/
    8 FFLAGS   =   -O2           -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -I$(INCPATH)
     8FFLAGS   =   -O2 -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -I$(INCPATH)
    99#FFLAGS   =   -fbounds-check -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -I$(INCPATH)
    1010LDFLAGS  = $(FFLAGS) -L$(LIBPATH2) -L$(LIBPATH1) -lgrib_api_f90 -lgrib_api -lm -ljasper
  • src/par_mod.f90

    rda396a2 r0b71109  
    123123  !integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92 !FNL XF
    124124  !integer,parameter :: nxmax=361,nymax=181,nuvzmax=152,nwzmax=152,nzmax=152 !ECMWF new
    125   !integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92 !ECMWF
     125  integer,parameter :: nxmax=361,nymax=181,nuvzmax=92,nwzmax=92,nzmax=92 !ECMWF
    126126  !integer,parameter :: nxmax=361,nymax=181,nuvzmax=26,nwzmax=26,nzmax=26
    127127  !integer,parameter :: nxmax=721,nymax=361,nuvzmax=64,nwzmax=64,nzmax=64
    128   integer,parameter :: nxmax=721,nymax=361,nuvzmax=138,nwzmax=138,nzmax=138 !ECMWF 0.5
    129128  !integer,parameter :: nxmax=1201,nymax=235,nuvzmax=58,nwzmax=58,nzmax=58
    130129
    131130  integer,parameter :: nxshift=359 ! for ECMWF
    132   !integer,parameter :: nxshift=718 ! for ECMWF 0.5
    133131  !integer,parameter :: nxshift=0     ! for GFS or FNL (XF)
    134132
     
    156154  !*********************************************
    157155
    158   !integer,parameter :: maxnests=0, nxmaxn=0, nymaxn=0
    159   integer,parameter :: maxnests=1,nxmaxn=361,nymaxn=351 !ECMWF
     156  integer,parameter :: maxnests=0, nxmaxn=0, nymaxn=0
     157  !integer,parameter :: maxnests=1,nxmaxn=351,nymaxn=351 !ECMWF
    160158  !integer,parameter :: maxnests=1, nxmaxn=201, nymaxn=161 ! FNL XF
    161159  ! maxnests                maximum number of nested grids
     
    200198  !**************************************************
    201199
    202   integer,parameter :: maxpart=4000000
    203   integer,parameter :: maxspec=1
     200  integer,parameter :: maxpart=150000
     201  integer,parameter :: maxspec=4
    204202
    205203
  • src/readcommand.f90

    rcd1f691 rb4d29ce  
    444444  if ((ipout.ne.0).and.(ipout.ne.1).and.(ipout.ne.2)) then
    445445    write(*,*) ' #### FLEXPART MODEL ERROR! FILE COMMAND:     #### '
    446     write(*,*) ' #### IPOUT MUST BE 0, 1, or 2!                #### '
     446    write(*,*) ' #### IPOUT MUST BE 1, 2 OR 3!                #### '
    447447    stop
    448448  endif
  • src/readpaths.f90

    r18c1336 rb4d29ce  
    6363    length(i)=index(path(i),' ')-1
    6464
    65 
    66   if (verbosity.gt.0) then
    67       print*, 'path read', i, '=',  path(i)
    68   end if
    6965   
    70   end do
    71 
    72 
    73     do i=1,numpath
    74  
    7566    string_test = path(i)
    7667    character_test = string_test(length(i):length(i))
    7768    !print*, 'character_test,  string_test ', character_test,  string_test
    7869      if ((character_test .NE. '/') .AND. (i .LT. 4))  then
    79          print*, 'readpaths> WARNING: path not ending in /'
     70         print*, 'WARNING: path not ending in /'
    8071         print*, path(i)
    8172         path(i) = string_test(1:length(i)) // '/'
     
    8374         print*, 'fix: padded with /'
    8475         print*, path(i)
    85          print*, 'length(i) increased 1',  length(i)
     76         print*, 'length(i) increased 1'
    8677      endif
    87 
    88     end do
    89 
    90 
     78  end do
    9179
    9280  ! Check whether any nested subdomains are to be used
     
    1079530   numbnests=i-1
    10896
    109   if (verbosity.gt.0) then
    110       do i=1,numpath
    111       print*, 'path tested', i, '=',  path(i)
    112       end do
    113   end if
    114 
    11597  close(unitpath)
    11698  return
    117 
    118    
    119 
    12099
    121100998   write(*,*) ' #### TRAJECTORY MODEL ERROR! ERROR WHILE     #### '
  • src/readreleases.f90

    r242571d rb4d29ce  
    126126  ! prepare namelist output if requested
    127127  if (nmlout.eqv..true.) then
    128     !open(unitreleasesout,file=path(2)(1:length(2))//'RELEASES.namelist',access='append',status='new',err=1000)
    129     open(unitreleasesout,file=path(2)(1:length(2))//'RELEASES.namelist',err=1000)
     128    open(unitreleasesout,file=path(2)(1:length(2))//'RELEASES.namelist',access='append',status='new',err=1000)
    130129  endif
    131130
     
    259258  if (stat.ne.0) write(*,*)'ERROR: could not allocate xmasssave'
    260259
    261   write (*,*) 'readreleases> Releasepoints : ', numpoint
     260  write (*,*) 'Releasepoints : ', numpoint
    262261
    263262  do i=1,numpoint
     
    294293
    295294  do i=1,nspec
    296     if (verbosity.gt.0) then
    297       print*, 'readreleases> call readspecies', i
    298     endif
    299  
    300295    if (readerror.ne.0) then
    301296      read(unitreleases,*,err=998) specnum_rel(i)
     
    499494  endif ! if namelist format
    500495
    501 
    502   if (verbosity.gt.1 .and. numpoint.eq.1) then ! verbosity 2 or larger
    503     write(*,*) 'numpoint=', numpoint
    504     print*,  id1,it1
    505     print*,  id2,it2
    506     print*,  xpoint1(numpoint)
    507     print*,  ypoint1(numpoint)
    508     print*,  xpoint2(numpoint)
    509     print*,  ypoint2(numpoint)
    510     print*,  'kindz=' , kindz(numpoint)
    511     print*,  zpoint1(numpoint)
    512     print*,  zpoint2(numpoint)
    513     print*,  npart(numpoint)
    514     do i=1,nspec
    515       !mass(i)=
    516       print*, 'xmass=', xmass(numpoint,i)
    517     end do
    518     print*, compoint(numpoint)
    519   endif
    520 
    521 
    522496  ! If a release point contains no particles, stop and issue error message
    523497  !***********************************************************************
     
    562536        write(*,*) 'after simulation stops.'
    563537        write(*,*) 'Make files COMMAND and RELEASES consistent.'
    564         write(*,*) jul1, ' < ' , bdate
    565         write(*,*) ' .or. '
    566         write(*,*) jul2 , ' > ', edate
    567        
    568538        stop
    569539      endif
     
    593563  endif
    594564
    595   if (verbosity.gt.1 .and. numpoint.eq.1) then ! verbosity 2 or larger
    596     print*, 'ireleasestart(',numpoint,')', ireleasestart(numpoint)
    597     print*, 'ireleaseend(',numpoint,')', ireleaseend(numpoint)
    598   endif
    599 
    600565  ! Determine the release rate (particles per second) and total number
    601566  ! of particles released during the simulation
  • src/readspecies.f90

    r43c8684 rb4d29ce  
    103103  write(aspecnumb,'(i3.3)') specnum(pos_spec)
    104104  open(unitspecies,file=path(1)(1:length(1))//'SPECIES/SPECIES_'//aspecnumb,status='old',form='formatted',err=998)
    105  
    106   if (verbosity.gt.0) then
    107     write(*,*) 'reading SPECIES',specnum(pos_spec)
    108   endif
     105  !write(*,*) 'reading SPECIES',specnum(pos_spec)
    109106
    110107  ASSSPEC=.FALSE.
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG