Changeset 8a65cb0 in flexpart.git for src/FLEXPART.f90


Ignore:
Timestamp:
Mar 2, 2015, 3:11:55 PM (9 years ago)
Author:
Espen Sollum ATMOS <espen@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
1d207bb
Parents:
60403cd
Message:

Added code, makefile for dev branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/FLEXPART.f90

    rb7ae015 r8a65cb0  
    4444  use com_mod
    4545  use conv_mod
     46  use netcdf_output_mod, only: writeheader_netcdf
     47  use random_mod, only: gasdev1
    4648
    4749  implicit none
     
    5052  integer :: idummy = -320
    5153  character(len=256) :: inline_options  !pathfile, flexversion, arg2
    52   integer :: index_v
     54
     55
     56  ! Initialize arrays in com_mod
     57  !*****************************
     58  call com_mod_allocate(maxpart)
     59
     60
    5361
    5462  ! Generate a large number of random numbers
     
    6169
    6270  ! FLEXPART version string
    63   ! flexversion='Version 9.2 beta (2014-07-01)'
    64   !flexversion='Version 9.2.0.1 (2015-01-27)'
    65   flexversion='Version 9.2.0.2 (2015-03-01)'
    66   ! default inlide options
    67   inline_options='none'
    68   !verbosity flags  defined in com_mod.f90
    69  
     71  flexversion='Version 10.0pre  (2015-03-01)'
     72  verbosity=0
     73
    7074  ! Read the pathnames where input/output files are stored
    7175  !*******************************************************
    7276
     77  inline_options='none'
    7378  select case (iargc())
    74   case (2) !2 parameters: pathfile and inline options
     79  case (2)
    7580    call getarg(1,arg1)
    7681    pathfile=arg1
    7782    call getarg(2,arg2)
    7883    inline_options=arg2
    79   case (1) !1 parameter pathfiel or inline options
     84  case (1)
    8085    call getarg(1,arg1)
    8186    pathfile=arg1
     
    8489      inline_options=arg1
    8590    endif
    86   case (0) !default behavior
     91  case (0)
    8792    write(pathfile,'(a11)') './pathnames'
    8893  end select
     
    9297  print*,'Welcome to FLEXPART ', trim(flexversion)
    9398  print*,'FLEXPART is free software released under the GNU General Public License.'
    94 
    95   ! inline options allow to fine tune the verbosity during run time
    96   ! e.g.: show compilation parameters or input variables, time execution     
     99 
    97100  if (inline_options(1:1).eq.'-') then
    98    ! if (index(inline_options,'v').gt.0) then
    99    !    print*, 'verbose mode'
    100    !    verbosity=1
    101    !    index_v=index(inline_options,'v')
    102    !    if (inline_options(index_v+1:index_v+1).eq.'2') then
    103    !    verbosity=2
    104    !    endif         
    105    ! endif   
    106  
    107     !if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
    108     if (index(inline_options,'v').gt.0) then
    109        index_v=index(inline_options,'v')
    110        print*, 'Verbose mode: display  additional information during run'
     101    if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
     102       print*, 'Verbose mode 1: display detailed information during run'
    111103       verbosity=1
    112        if (inline_options(index_v+1:index_v+1).eq.'2') then
     104    endif
     105    if (trim(inline_options).eq.'-v2') then
     106       print*, 'Verbose mode 2: display more detailed information during run'
    113107       verbosity=2
    114        endif
    115        print*, 'verbosity level=', verbosity !inline_options(index_v+1:index_v+1)
    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        index_v=index(inline_options,'i')
    124        print*, 'Info mode: provide compile and run specific information, then stop'
     108    endif
     109    if (trim(inline_options).eq.'-i') then
     110       print*, 'Info mode: provide detailed run specific information and stop'
    125111       verbosity=1
    126112       info_flag=1
    127        if (inline_options(index_v+1:index_v+1).eq.'2') then
    128        info_flag=2
    129        endif
    130     endif
    131     if (index(inline_options,'t').gt.0) then
    132        time_flag=1
    133        print*, 'timing execution activated'
    134        !stop
    135     endif
    136     if (index(inline_options,'d').gt.0) then
    137        debug_flag=1
    138        print*, 'debug messages activated'
    139        print*, 'debug_flag=', debug_flag
    140        !these messages give additional info on top on verbose mode
    141     endif
     113    endif
     114    if (trim(inline_options).eq.'-i2') then
     115       print*, 'Info mode: provide more detailed run specific information and stop'
     116       verbosity=2
     117       info_flag=1
     118    endif
    142119  endif
    143120           
    144121  if (verbosity.gt.0) then
    145     print*, 'FLEXPART>******************************'
    146     print*, 'FLEXPART>* verbosity level:', verbosity
    147     print*, 'FLEXPART>* info only:      ', info_flag
    148     print*, 'FLEXPART>* time execution: ', time_flag
    149     print*, 'FLEXPART>******************************'
    150    
    151     print*, 'FLEXPART> parameters from par_mod'   
    152     print*, 'FLEXPART> nxmax=  ', nxmax
    153     print*, 'FLEXPART> nymax=  ', nymax
    154     print*, 'FLEXPART> nuvzmax=', nuvzmax
    155     print*, 'FLEXPART> nwzmax= ', nwzmax
    156     print*, 'FLEXPART> nzmax=  ', nzmax
    157     print*, 'FLEXPART> nxshift=', nxshift
    158     print*, 'FLEXPART> maxpart=', maxpart
    159     print*, 'FLEXPART> maxspec=', maxspec
    160 
    161     if (info_flag.eq.1) stop
    162122    write(*,*) 'call readpaths'
    163123  endif
    164124  call readpaths(pathfile)
    165125 
    166   !if (time_flag.gt.1) then !show clock info
     126  if (verbosity.gt.1) then !show clock info
     127     !print*,'length(4)',length(4)
    167128     !count=0,count_rate=1000
    168   CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
     129     CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
    169130     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
    170131     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
    171132     !WRITE(*,*) 'SYSTEM_CLOCK, count_rate', count_rate
    172133     !WRITE(*,*) 'SYSTEM_CLOCK, count_max', count_max
    173   !endif
     134  endif
    174135
    175136  ! Read the user specifications for the current model run
     
    177138
    178139  if (verbosity.gt.0) then
    179     write(*,*) 'FLEXPART> call readcommand'
     140    write(*,*) 'call readcommand'
    180141  endif
    181142  call readcommand
    182143  if (verbosity.gt.0) then
    183     write(*,*) '    ldirect      =', ldirect
    184     write(*,*) '    ibdate,ibtime=', ibdate,ibtime
     144    write(*,*) '    ldirect=', ldirect
     145    write(*,*) '    ibdate,ibtime=',ibdate,ibtime
    185146    write(*,*) '    iedate,ietime=', iedate,ietime
    186   endif
    187     if (time_flag.gt.0) then   
     147    if (verbosity.gt.1) then   
    188148      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    189149      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    190150    endif     
     151  endif
    191152
    192153  ! Read the age classes to be used
    193154  !********************************
    194155  if (verbosity.gt.0) then
    195     write(*,*) 'FLEXPART> call readageclasses'
     156    write(*,*) 'call readageclasses'
    196157  endif
    197158  call readageclasses
    198159
    199   if (time_flag.gt.1) then   
     160  if (verbosity.gt.1) then   
    200161    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    201162    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     
    206167
    207168  if (verbosity.gt.0) then
    208     write(*,*) 'FLEXPART> call readavailable'
     169    write(*,*) 'call readavailable'
    209170  endif 
    210171  call readavailable
     
    215176 
    216177  if (verbosity.gt.0) then
    217      write(*,*) 'FLEXPART> call gridcheck'
    218   endif
     178     write(*,*) 'call gridcheck'
     179  endif
     180
    219181  call gridcheck
    220182
    221   if (time_flag.gt.0) then   
     183  if (verbosity.gt.1) then   
    222184    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    223185    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     
    225187
    226188  if (verbosity.gt.0) then
    227     write(*,*) 'FLEXPART> call gridcheck_nests'
     189    write(*,*) 'call gridcheck_nests'
    228190  endif 
    229191  call gridcheck_nests
     
    233195
    234196  if (verbosity.gt.0) then
    235     write(*,*) 'FLEXPART> call readoutgrid'
     197    write(*,*) 'call readoutgrid'
    236198  endif
    237199
     
    241203    call readoutgrid_nest
    242204    if (verbosity.gt.0) then
    243       write(*,*) 'FLEXPART> readoutgrid_nest'
     205      write(*,*) '# readoutgrid_nest'
    244206    endif
    245207  endif
     
    249211
    250212  if (verbosity.eq.1) then
    251      print*,'FLEXPART> call readreceptors'
     213     print*,'call readreceptors'
    252214  endif
    253215  call readreceptors
     
    263225
    264226  if (verbosity.gt.0) then
    265     print*,'FLEXPART> call readlanduse'
     227    print*,'call readlanduse'
    266228  endif
    267229  call readlanduse
     
    271233
    272234  if (verbosity.gt.0) then
    273     print*,'FLEXPART> call assignland'
     235    print*,'call assignland'
    274236  endif
    275237  call assignland
     
    279241
    280242  if (verbosity.gt.0) then
    281     print*,'FLEXPART> call readreleases'
     243    print*,'call readreleases'
    282244  endif
    283245  call readreleases
     
    287249
    288250  if (verbosity.gt.0) then
    289     print*,'FLEXPART> call readdepo'
     251    print*,'call readdepo'
    290252  endif
    291253  call readdepo
     
    296258  call coordtrafo 
    297259  if (verbosity.gt.0) then
    298     print*,'FLEXPART> call coordtrafo'
     260    print*,'call coordtrafo'
    299261  endif
    300262
     
    303265
    304266  if (verbosity.gt.0) then
    305     print*,'FLEXPART> Initialize all particles to non-existent'
     267    print*,'Initialize all particles to non-existent'
    306268  endif
    307269  do j=1,maxpart
     
    314276  if (ipin.eq.1) then
    315277    if (verbosity.gt.0) then
    316       print*,'FLEXPART> call readpartpositions'
     278      print*,'call readpartpositions'
    317279    endif
    318280    call readpartpositions
    319281  else
    320282    if (verbosity.gt.0) then
    321       print*,'FLEXPART> set numpart=0, numparticlecount=0'
     283      print*,'numpart=0, numparticlecount=0'
    322284    endif   
    323285    numpart=0
     
    330292
    331293  if (verbosity.gt.0) then
    332     print*,'FLEXPART> call outgrid_init'
     294    print*,'call outgrid_init'
    333295  endif
    334296  call outgrid_init
     
    340302  if (OHREA.eqv..TRUE.) then
    341303    if (verbosity.gt.0) then
    342       print*,'FLEXPART> call readOHfield'
     304      print*,'call readOHfield'
    343305    endif
    344306    call readOHfield
    345307  endif
     308
     309  !! testing !!
     310  ! open(999,file=trim(path(1))//'OH_FIELDS/jscalar_50N.txt',action='write',status='new')
     311  ! open(998,file=trim(path(1))//'OH_FIELDS/jscalar_50S.txt',action='write',status='new')
     312
    346313
    347314  ! Write basic information on the simulation to a file "header"
     
    349316  !******************************************************************
    350317
    351   if (verbosity.gt.0) then
    352     print*,'FLEXPART> call variuos writeheader routines'
     318  if (lnetcdfout.eq.1) then
     319    call writeheader_netcdf(lnest=.false.)
     320  else
     321    call writeheader
     322  end if
     323
     324  if (nested_output.eq.1) then
     325    if (lnetcdfout.eq.1) then
     326      call writeheader_netcdf(lnest=.true.)
     327    else
     328      call writeheader_nest
     329    endif
     330  endif
     331
     332  if (verbosity.gt.0) then
     333    print*,'call writeheader'
    353334  endif
    354335
    355336  call writeheader
    356   ! write header in ASCII format
     337  ! FLEXPART 9.2 ticket ?? write header in ASCII format
    357338  call writeheader_txt
    358339  !if (nested_output.eq.1) call writeheader_nest
     
    364345
    365346  if (verbosity.gt.0) then
    366     print*,'FLEXPART> call openreceptors'
     347    print*,'call openreceptors'
    367348  endif
    368349  call openreceptors
     
    373354
    374355  if (verbosity.gt.0) then
    375     print*,'FLEXPART> discretize release times'
     356    print*,'discretize release times'
    376357  endif
    377358  do i=1,numpoint
     
    384365
    385366  if (verbosity.gt.0) then
    386     print*,'FLEXPART> Initialize cloud-base mass fluxes for the convection scheme'
     367    print*,'Initialize cloud-base mass fluxes for the convection scheme'
    387368  endif
    388369
     
    403384  !********************************
    404385
    405   if (time_flag.gt.0) then   
    406     CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    407     write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    408   endif
    409   if (info_flag.eq.2) then
    410     print*, 'FLEXPART> info only mode (stop before call timemanager)'
    411     stop
    412   endif
    413   if (verbosity.gt.0) then
    414      print*,'FLEXPART> call timemanager'
     386  if (verbosity.gt.0) then
     387     if (verbosity.gt.1) then   
     388       CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
     389       write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     390     endif
     391     if (info_flag.eq.1) then
     392       print*, 'info only mode (stop)'   
     393       stop
     394     endif
     395     print*,'call timemanager'
    415396  endif
    416397
    417398  call timemanager
    418399
    419   write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLEXPART MODEL RUN!'
     400! NIK 16.02.2005
     401  write(*,*) '**********************************************'
     402  write(*,*) 'Total number of occurences of below-cloud scavenging', tot_blc_count
     403  write(*,*) 'Total number of occurences of in-cloud    scavenging', tot_inc_count
     404  write(*,*) '**********************************************'
     405
     406  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLE&
     407       &XPART MODEL RUN!'
    420408
    421409end program flexpart
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG