source: flexpart.git/src/FLEXPART.f90 @ b7ae015

10.4.1_peseiFPv9.3.1FPv9.3.1b_testingFPv9.3.2GFS_025bugfixes+enhancementsdevfp9.3.1-20161214-nc4grib2nc4_repairrelease-10release-10.4.1scaling-bugunivie
Last change on this file since b7ae015 was b7ae015, checked in by Ignacio Pisso <Ignacio.Pisso@…>, 9 years ago

clean up runtime messages and adjust verbosity level

  • Property mode set to 100644
File size: 14.0 KB
RevLine 
[e200b7a]1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22program flexpart
23
24  !*****************************************************************************
25  !                                                                            *
26  !     This is the Lagrangian Particle Dispersion Model FLEXPART.             *
27  !     The main program manages the reading of model run specifications, etc. *
28  !     All actual computing is done within subroutine timemanager.            *
29  !                                                                            *
30  !     Author: A. Stohl                                                       *
31  !                                                                            *
32  !     18 May 1996                                                            *
33  !                                                                            *
34  !*****************************************************************************
35  !                                                                            *
36  ! Variables:                                                                 *
37  !                                                                            *
38  ! Constants:                                                                 *
39  !                                                                            *
40  !*****************************************************************************
41
42  use point_mod
43  use par_mod
44  use com_mod
45  use conv_mod
46
47  implicit none
48
49  integer :: i,j,ix,jy,inest
50  integer :: idummy = -320
[f13406c]51  character(len=256) :: inline_options  !pathfile, flexversion, arg2
[414a5e5]52  integer :: index_v
[e200b7a]53
54  ! Generate a large number of random numbers
55  !******************************************
56
57  do i=1,maxrand-1,2
58    call gasdev1(idummy,rannumb(i),rannumb(i+1))
59  end do
60  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
61
[b4d29ce]62  ! FLEXPART version string
[414a5e5]63  ! flexversion='Version 9.2 beta (2014-07-01)'
[b7ae015]64  !flexversion='Version 9.2.0.1 (2015-01-27)'
65  flexversion='Version 9.2.0.2 (2015-03-01)'
[414a5e5]66  ! default inlide options
67  inline_options='none'
68  !verbosity flags  defined in com_mod.f90
69 
[f13406c]70  ! Read the pathnames where input/output files are stored
71  !*******************************************************
72
73  select case (iargc())
[414a5e5]74  case (2) !2 parameters: pathfile and inline options
[f13406c]75    call getarg(1,arg1)
76    pathfile=arg1
77    call getarg(2,arg2)
78    inline_options=arg2
[414a5e5]79  case (1) !1 parameter pathfiel or inline options
[f13406c]80    call getarg(1,arg1)
81    pathfile=arg1
82    if (arg1(1:1).eq.'-') then
[b4d29ce]83      write(pathfile,'(a11)') './pathnames'
84      inline_options=arg1
[f13406c]85    endif
[414a5e5]86  case (0) !default behavior
[f13406c]87    write(pathfile,'(a11)') './pathnames'
88  end select
89 
[e200b7a]90  ! Print the GPL License statement
91  !*******************************************************
[4fbe7a5]92  print*,'Welcome to FLEXPART ', trim(flexversion)
[b4d29ce]93  print*,'FLEXPART is free software released under the GNU General Public License.'
[414a5e5]94
95  ! inline options allow to fine tune the verbosity during run time
96  ! e.g.: show compilation parameters or input variables, time execution     
[b4d29ce]97  if (inline_options(1:1).eq.'-') then
[414a5e5]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'
[b4d29ce]111       verbosity=1
[414a5e5]112       if (inline_options(index_v+1:index_v+1).eq.'2') then
[b4d29ce]113       verbosity=2
[414a5e5]114       endif
115       print*, 'verbosity level=', verbosity !inline_options(index_v+1:index_v+1)
[b4d29ce]116    endif
[414a5e5]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')
[b7ae015]124       print*, 'Info mode: provide compile and run specific information, then stop'
[b4d29ce]125       verbosity=1
126       info_flag=1
[414a5e5]127       if (inline_options(index_v+1:index_v+1).eq.'2') then
128       info_flag=2
129       endif
[b4d29ce]130    endif
[414a5e5]131    if (index(inline_options,'t').gt.0) then
132       time_flag=1
[b7ae015]133       print*, 'timing execution activated'
[414a5e5]134       !stop
[b4d29ce]135    endif
[414a5e5]136    if (index(inline_options,'d').gt.0) then
137       debug_flag=1
[b7ae015]138       print*, 'debug messages activated'
[414a5e5]139       print*, 'debug_flag=', debug_flag
[b7ae015]140       !these messages give additional info on top on verbose mode
[414a5e5]141    endif
[b4d29ce]142  endif
143           
[f13406c]144  if (verbosity.gt.0) then
[414a5e5]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
[b4d29ce]162    write(*,*) 'call readpaths'
[f13406c]163  endif
164  call readpaths(pathfile)
165 
[414a5e5]166  !if (time_flag.gt.1) then !show clock info
[f13406c]167     !count=0,count_rate=1000
[414a5e5]168  CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
[f13406c]169     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
170     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
171     !WRITE(*,*) 'SYSTEM_CLOCK, count_rate', count_rate
172     !WRITE(*,*) 'SYSTEM_CLOCK, count_max', count_max
[414a5e5]173  !endif
[e200b7a]174
175  ! Read the user specifications for the current model run
176  !*******************************************************
177
[f13406c]178  if (verbosity.gt.0) then
[b7ae015]179    write(*,*) 'FLEXPART> call readcommand'
[f13406c]180  endif
[e200b7a]181  call readcommand
[f13406c]182  if (verbosity.gt.0) then
[414a5e5]183    write(*,*) '    ldirect      =', ldirect
184    write(*,*) '    ibdate,ibtime=', ibdate,ibtime
[b4d29ce]185    write(*,*) '    iedate,ietime=', iedate,ietime
[414a5e5]186  endif
187    if (time_flag.gt.0) then   
[b4d29ce]188      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
189      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
190    endif     
[e200b7a]191
192  ! Read the age classes to be used
193  !********************************
[f13406c]194  if (verbosity.gt.0) then
[b7ae015]195    write(*,*) 'FLEXPART> call readageclasses'
[f13406c]196  endif
[e200b7a]197  call readageclasses
198
[414a5e5]199  if (time_flag.gt.1) then   
[b4d29ce]200    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
201    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]202  endif     
[e200b7a]203
204  ! Read, which wind fields are available within the modelling period
205  !******************************************************************
206
[f13406c]207  if (verbosity.gt.0) then
[b7ae015]208    write(*,*) 'FLEXPART> call readavailable'
[f13406c]209  endif 
[e200b7a]210  call readavailable
211
212  ! Read the model grid specifications,
213  ! both for the mother domain and eventual nests
214  !**********************************************
[f13406c]215 
216  if (verbosity.gt.0) then
[414a5e5]217     write(*,*) 'FLEXPART> call gridcheck'
[f13406c]218  endif
[e200b7a]219  call gridcheck
[f13406c]220
[414a5e5]221  if (time_flag.gt.0) then   
[b4d29ce]222    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
223    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]224  endif     
225
226  if (verbosity.gt.0) then
[b7ae015]227    write(*,*) 'FLEXPART> call gridcheck_nests'
[f13406c]228  endif 
[e200b7a]229  call gridcheck_nests
230
231  ! Read the output grid specifications
232  !************************************
233
[f13406c]234  if (verbosity.gt.0) then
[414a5e5]235    write(*,*) 'FLEXPART> call readoutgrid'
[f13406c]236  endif
237
[e200b7a]238  call readoutgrid
239
[f13406c]240  if (nested_output.eq.1) then
[b4d29ce]241    call readoutgrid_nest
[f13406c]242    if (verbosity.gt.0) then
[414a5e5]243      write(*,*) 'FLEXPART>  readoutgrid_nest'
[f13406c]244    endif
245  endif
[e200b7a]246
247  ! Read the receptor points for which extra concentrations are to be calculated
248  !*****************************************************************************
249
[f13406c]250  if (verbosity.eq.1) then
[414a5e5]251     print*,'FLEXPART> call readreceptors'
[f13406c]252  endif
[e200b7a]253  call readreceptors
254
255  ! Read the physico-chemical species property table
256  !*************************************************
257  !SEC: now only needed SPECIES are read in readreleases.f
258  !call readspecies
259
260
261  ! Read the landuse inventory
262  !***************************
263
[f13406c]264  if (verbosity.gt.0) then
[414a5e5]265    print*,'FLEXPART> call readlanduse'
[f13406c]266  endif
[e200b7a]267  call readlanduse
268
269  ! Assign fractional cover of landuse classes to each ECMWF grid point
270  !********************************************************************
271
[f13406c]272  if (verbosity.gt.0) then
[414a5e5]273    print*,'FLEXPART> call assignland'
[f13406c]274  endif
[e200b7a]275  call assignland
276
277  ! Read the coordinates of the release locations
278  !**********************************************
279
[f13406c]280  if (verbosity.gt.0) then
[414a5e5]281    print*,'FLEXPART> call readreleases'
[f13406c]282  endif
[e200b7a]283  call readreleases
284
285  ! Read and compute surface resistances to dry deposition of gases
286  !****************************************************************
287
[f13406c]288  if (verbosity.gt.0) then
[b7ae015]289    print*,'FLEXPART> call readdepo'
[f13406c]290  endif
[e200b7a]291  call readdepo
292
293  ! Convert the release point coordinates from geografical to grid coordinates
294  !***************************************************************************
295
[f13406c]296  call coordtrafo 
297  if (verbosity.gt.0) then
[b7ae015]298    print*,'FLEXPART> call coordtrafo'
[f13406c]299  endif
[e200b7a]300
301  ! Initialize all particles to non-existent
302  !*****************************************
303
[f13406c]304  if (verbosity.gt.0) then
[b7ae015]305    print*,'FLEXPART> Initialize all particles to non-existent'
[f13406c]306  endif
[e200b7a]307  do j=1,maxpart
308    itra1(j)=-999999999
309  end do
310
311  ! For continuation of previous run, read in particle positions
312  !*************************************************************
313
314  if (ipin.eq.1) then
[f13406c]315    if (verbosity.gt.0) then
[b7ae015]316      print*,'FLEXPART> call readpartpositions'
[f13406c]317    endif
[e200b7a]318    call readpartpositions
319  else
[f13406c]320    if (verbosity.gt.0) then
[b7ae015]321      print*,'FLEXPART> set numpart=0, numparticlecount=0'
[f13406c]322    endif   
[e200b7a]323    numpart=0
324    numparticlecount=0
325  endif
326
327  ! Calculate volume, surface area, etc., of all output grid cells
328  ! Allocate fluxes and OHfield if necessary
329  !***************************************************************
330
[f13406c]331  if (verbosity.gt.0) then
[b7ae015]332    print*,'FLEXPART> call outgrid_init'
[f13406c]333  endif
[e200b7a]334  call outgrid_init
335  if (nested_output.eq.1) call outgrid_init_nest
336
337  ! Read the OH field
338  !******************
339
[f13406c]340  if (OHREA.eqv..TRUE.) then
341    if (verbosity.gt.0) then
[b7ae015]342      print*,'FLEXPART> call readOHfield'
[f13406c]343    endif
[b4d29ce]344    call readOHfield
[f13406c]345  endif
[e200b7a]346
347  ! Write basic information on the simulation to a file "header"
348  ! and open files that are to be kept open throughout the simulation
349  !******************************************************************
350
[f13406c]351  if (verbosity.gt.0) then
[b7ae015]352    print*,'FLEXPART> call variuos writeheader routines'
[f13406c]353  endif
354
[e200b7a]355  call writeheader
[414a5e5]356  ! write header in ASCII format
[f13406c]357  call writeheader_txt
358  !if (nested_output.eq.1) call writeheader_nest
359  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
360  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
361  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
362
363  !open(unitdates,file=path(2)(1:length(2))//'dates')
364
365  if (verbosity.gt.0) then
[b7ae015]366    print*,'FLEXPART> call openreceptors'
[f13406c]367  endif
[e200b7a]368  call openreceptors
369  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
370
371  ! Releases can only start and end at discrete times (multiples of lsynctime)
372  !***************************************************************************
373
[f13406c]374  if (verbosity.gt.0) then
[b7ae015]375    print*,'FLEXPART> discretize release times'
[f13406c]376  endif
[e200b7a]377  do i=1,numpoint
[b4d29ce]378    ireleasestart(i)=nint(real(ireleasestart(i))/real(lsynctime))*lsynctime
379    ireleaseend(i)=nint(real(ireleaseend(i))/real(lsynctime))*lsynctime
[e200b7a]380  end do
381
382  ! Initialize cloud-base mass fluxes for the convection scheme
383  !************************************************************
384
[f13406c]385  if (verbosity.gt.0) then
[b7ae015]386    print*,'FLEXPART> Initialize cloud-base mass fluxes for the convection scheme'
[f13406c]387  endif
388
[e200b7a]389  do jy=0,nymin1
390    do ix=0,nxmin1
391      cbaseflux(ix,jy)=0.
392    end do
393  end do
394  do inest=1,numbnests
395    do jy=0,nyn(inest)-1
396      do ix=0,nxn(inest)-1
397        cbasefluxn(ix,jy,inest)=0.
398      end do
399    end do
400  end do
401
402  ! Calculate particle trajectories
403  !********************************
404
[414a5e5]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
[b7ae015]410    print*, 'FLEXPART> info only mode (stop before call timemanager)'
[414a5e5]411    stop
412  endif
[f13406c]413  if (verbosity.gt.0) then
[b7ae015]414     print*,'FLEXPART> call timemanager'
[f13406c]415  endif
416
[e200b7a]417  call timemanager
418
[b4d29ce]419  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLEXPART MODEL RUN!'
[e200b7a]420
421end program flexpart
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG