source: branches/ignacio/FLEXPART_9.1.7.1/src/FLEXPART.f90 @ 14

Last change on this file since 14 was 14, checked in by igpis, 11 years ago

based on 9.1from hasod; 9.1.1 add sack (trunk); 9.1.2 add NIK scavenging; 9.1.3 add new pesei depo scheme; 9.1.4 warning at readpositions; 9.1.5 xuekun FNL; 9.1.6 rlt FLEXINVERT; 9.1.7 update dates, check slash in COMMAND

File size: 9.5 KB
Line 
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
51  ! character(len=256) :: pathfile, flexversion, arg2
52
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
62  !
63  flexversion='Version 9.1.6.2   (Build 2013-09-04)'
64  !verbosity=0
65  ! Read the pathnames where input/output files are stored
66  !*******************************************************
67
68  select case (iargc())
69  case (2)
70    call getarg(1,arg1)
71    pathfile=arg1
72    call getarg(2,arg2)
73    if (trim(arg2).eq.'-v') then
74       print*, 'verbose mode: additional information will be displayed'
75       verbosity=1
76    endif
77  case (1)
78    call getarg(1,arg1)
79    pathfile=arg1
80    if (trim(arg1).eq.'-i') then
81        write(*,*) trim(flexversion) !add a function with more info
82        stop
83    endif 
84    if (trim(arg1).eq.'-v') then
85       print*, 'verbose mode: additional information will be displayed'
86       verbosity=1
87       write(pathfile,'(a11)') './pathnames'
88     endif
89  case (0)
90    write(pathfile,'(a11)') './pathnames'
91  end select
92
93  ! Print the GPL License statement
94  !*******************************************************
95  ! print*,'Welcome to FLEXPART Version 9.1 (Build 20121029)'
96  print*,'Welcome to FLEXPART', trim(flexversion)
97  print*,'FLEXPART is free software released under the GNU Genera'// &
98       'l Public License.'
99           
100
101  call readpaths(pathfile)
102
103  if (verbosity.eq.1) then
104     print*,'length(4)',length(4)
105     !count=0,count_rate=1000
106     CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
107     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
108     WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
109     WRITE(*,*) 'SYSTEM_CLOCK, count_rate', count_rate
110     WRITE(*,*) 'SYSTEM_CLOCK, count_max', count_max
111  endif
112
113
114  ! Read the user specifications for the current model run
115  !*******************************************************
116
117  call readcommand
118
119
120  ! Read the age classes to be used
121  !********************************
122
123  call readageclasses
124
125
126  ! Read, which wind fields are available within the modelling period
127  !******************************************************************
128
129  call readavailable
130
131
132  ! Read the model grid specifications,
133  ! both for the mother domain and eventual nests
134  !**********************************************
135
136  call gridcheck
137  call gridcheck_nests
138
139
140  ! Read the output grid specifications
141  !************************************
142
143  call readoutgrid
144  if (nested_output.eq.1) call readoutgrid_nest
145
146
147  ! Read the receptor points for which extra concentrations are to be calculated
148  !*****************************************************************************
149
150  call readreceptors
151  if (verbosity.eq.1) then
152     print*,'readreceptors'
153  endif
154
155  ! Read the physico-chemical species property table
156  !*************************************************
157  !SEC: now only needed SPECIES are read in readreleases.f
158  !call readspecies
159
160
161  ! Read the landuse inventory
162  !***************************
163
164  if (verbosity.eq.1) then
165    print*,'readlanduse'
166  endif
167  call readlanduse
168
169
170  ! Assign fractional cover of landuse classes to each ECMWF grid point
171  !********************************************************************
172
173  if (verbosity.eq.1) then
174    print*,'assignland'
175  endif
176  call assignland
177
178
179
180  ! Read the coordinates of the release locations
181  !**********************************************
182
183  if (verbosity.eq.1) then
184    print*,'readreleases'
185  endif
186  call readreleases
187
188  ! Read and compute surface resistances to dry deposition of gases
189  !****************************************************************
190
191  if (verbosity.eq.1) then
192    print*,'readdepo'
193  endif
194  call readdepo
195
196
197  ! Convert the release point coordinates from geografical to grid coordinates
198  !***************************************************************************
199
200  if (verbosity.eq.1) then
201    print*,'coordtrafo'
202  endif
203  call coordtrafo
204
205
206  ! Initialize all particles to non-existent
207  !*****************************************
208
209  if (verbosity.eq.1) then
210    print*,'Initialize all particles to non-existent'
211  endif
212  do j=1,maxpart
213    itra1(j)=-999999999
214  end do
215
216  ! For continuation of previous run, read in particle positions
217  !*************************************************************
218
219  if (ipin.eq.1) then
220    if (verbosity.eq.1) then
221      print*,'readpartpositions'
222    endif
223    call readpartpositions
224  else
225    numpart=0
226    numparticlecount=0
227  endif
228
229
230  ! Calculate volume, surface area, etc., of all output grid cells
231  ! Allocate fluxes and OHfield if necessary
232  !***************************************************************
233
234  call outgrid_init
235  if (nested_output.eq.1) call outgrid_init_nest
236
237
238  ! Read the OH field
239  !******************
240
241  if (OHREA.eqv..TRUE.) &
242       call readOHfield
243
244  ! Write basic information on the simulation to a file "header"
245  ! and open files that are to be kept open throughout the simulation
246  !******************************************************************
247
248  call writeheader
249  call writeheader_txt
250  !if (nested_output.eq.1) call writeheader_nest
251  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
252  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
253  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
254
255
256
257  !open(unitdates,file=path(2)(1:length(2))//'dates')
258  call openreceptors
259  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
260
261
262  ! Releases can only start and end at discrete times (multiples of lsynctime)
263  !***************************************************************************
264
265  do i=1,numpoint
266    ireleasestart(i)=nint(real(ireleasestart(i))/ &
267         real(lsynctime))*lsynctime
268    ireleaseend(i)=nint(real(ireleaseend(i))/ &
269         real(lsynctime))*lsynctime
270  end do
271
272
273  ! Initialize cloud-base mass fluxes for the convection scheme
274  !************************************************************
275
276  do jy=0,nymin1
277    do ix=0,nxmin1
278      cbaseflux(ix,jy)=0.
279    end do
280  end do
281  do inest=1,numbnests
282    do jy=0,nyn(inest)-1
283      do ix=0,nxn(inest)-1
284        cbasefluxn(ix,jy,inest)=0.
285      end do
286    end do
287  end do
288
289
290  ! Calculate particle trajectories
291  !********************************
292  if (verbosity.eq.1) then
293     print*,'call timemanager'
294     CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
295     WRITE(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/count_rate !, count_rate, count_max
296  endif
297  call timemanager
298
299
300  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLE&
301       &XPART MODEL RUN!'
302
303end program flexpart
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG