source: flexpart.git/src/FLEXPART.f90 @ 660bcb7

NetCDF
Last change on this file since 660bcb7 was 660bcb7, checked in by Anne Fouilloux <annefou@…>, 9 years ago

NETCDF outputs from svn trunk (hasod: ADD: netcdf module file)
I did not take changes in advance.f90; it will be added later.
I also changed OPENs where status was set to new and access is set to APPEND (had problems on abel.uio.no with intel compilers 2013.sp1.3)
It should contains technical changes only and results should be identical.

  • Property mode set to 100644
File size: 12.4 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
[660bcb7]47  use netcdf_output_mod, only: writeheader_netcdf
48
49
[e200b7a]50  implicit none
51
52  integer :: i,j,ix,jy,inest
53  integer :: idummy = -320
[f13406c]54  character(len=256) :: inline_options  !pathfile, flexversion, arg2
55
[e200b7a]56
57  ! Generate a large number of random numbers
58  !******************************************
59
60  do i=1,maxrand-1,2
61    call gasdev1(idummy,rannumb(i),rannumb(i+1))
62  end do
63  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
64
[b4d29ce]65  ! FLEXPART version string
66  flexversion='Version 9.2 beta (2014-07-01)'
67  verbosity=0
68
[f13406c]69  ! Read the pathnames where input/output files are stored
70  !*******************************************************
71
72  inline_options='none'
73  select case (iargc())
74  case (2)
75    call getarg(1,arg1)
76    pathfile=arg1
77    call getarg(2,arg2)
78    inline_options=arg2
79  case (1)
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
86  case (0)
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.'
94 
95  if (inline_options(1:1).eq.'-') then
96    if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
97       print*, 'Verbose mode 1: display detailed information during run'
98       verbosity=1
99    endif
100    if (trim(inline_options).eq.'-v2') then
101       print*, 'Verbose mode 2: display more detailed information during run'
102       verbosity=2
103    endif
104    if (trim(inline_options).eq.'-i') then
105       print*, 'Info mode: provide detailed run specific information and stop'
106       verbosity=1
107       info_flag=1
108    endif
109    if (trim(inline_options).eq.'-i2') then
110       print*, 'Info mode: provide more detailed run specific information and stop'
111       verbosity=2
112       info_flag=1
113    endif
114  endif
115           
[f13406c]116  if (verbosity.gt.0) then
[b4d29ce]117    write(*,*) 'call readpaths'
[f13406c]118  endif
119  call readpaths(pathfile)
120 
121  if (verbosity.gt.1) then !show clock info
122     !print*,'length(4)',length(4)
123     !count=0,count_rate=1000
124     CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
125     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
126     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
127     !WRITE(*,*) 'SYSTEM_CLOCK, count_rate', count_rate
128     !WRITE(*,*) 'SYSTEM_CLOCK, count_max', count_max
129  endif
[e200b7a]130
131  ! Read the user specifications for the current model run
132  !*******************************************************
133
[f13406c]134  if (verbosity.gt.0) then
[b4d29ce]135    write(*,*) 'call readcommand'
[f13406c]136  endif
[e200b7a]137  call readcommand
[f13406c]138  if (verbosity.gt.0) then
[b4d29ce]139    write(*,*) '    ldirect=', ldirect
140    write(*,*) '    ibdate,ibtime=',ibdate,ibtime
141    write(*,*) '    iedate,ietime=', iedate,ietime
142    if (verbosity.gt.1) then   
143      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
144      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
145    endif     
[f13406c]146  endif
[e200b7a]147
148  ! Read the age classes to be used
149  !********************************
[f13406c]150  if (verbosity.gt.0) then
[b4d29ce]151    write(*,*) 'call readageclasses'
[f13406c]152  endif
[e200b7a]153  call readageclasses
154
[f13406c]155  if (verbosity.gt.1) then   
[b4d29ce]156    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
157    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]158  endif     
[e200b7a]159
160  ! Read, which wind fields are available within the modelling period
161  !******************************************************************
162
[f13406c]163  if (verbosity.gt.0) then
[b4d29ce]164    write(*,*) 'call readavailable'
[f13406c]165  endif 
[e200b7a]166  call readavailable
167
168  ! Read the model grid specifications,
169  ! both for the mother domain and eventual nests
170  !**********************************************
[f13406c]171 
172  if (verbosity.gt.0) then
[b4d29ce]173     write(*,*) 'call gridcheck'
[f13406c]174  endif
[e200b7a]175
176  call gridcheck
[f13406c]177
178  if (verbosity.gt.1) then   
[b4d29ce]179    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
180    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]181  endif     
182
183  if (verbosity.gt.0) then
[b4d29ce]184    write(*,*) 'call gridcheck_nests'
[f13406c]185  endif 
[e200b7a]186  call gridcheck_nests
187
188  ! Read the output grid specifications
189  !************************************
190
[f13406c]191  if (verbosity.gt.0) then
[b4d29ce]192    write(*,*) 'call readoutgrid'
[f13406c]193  endif
194
[e200b7a]195  call readoutgrid
196
[f13406c]197  if (nested_output.eq.1) then
[b4d29ce]198    call readoutgrid_nest
[f13406c]199    if (verbosity.gt.0) then
[b4d29ce]200      write(*,*) '# readoutgrid_nest'
[f13406c]201    endif
202  endif
[e200b7a]203
204  ! Read the receptor points for which extra concentrations are to be calculated
205  !*****************************************************************************
206
[f13406c]207  if (verbosity.eq.1) then
208     print*,'call readreceptors'
209  endif
[e200b7a]210  call readreceptors
211
212  ! Read the physico-chemical species property table
213  !*************************************************
214  !SEC: now only needed SPECIES are read in readreleases.f
215  !call readspecies
216
217
218  ! Read the landuse inventory
219  !***************************
220
[f13406c]221  if (verbosity.gt.0) then
222    print*,'call readlanduse'
223  endif
[e200b7a]224  call readlanduse
225
226  ! Assign fractional cover of landuse classes to each ECMWF grid point
227  !********************************************************************
228
[f13406c]229  if (verbosity.gt.0) then
230    print*,'call assignland'
231  endif
[e200b7a]232  call assignland
233
234  ! Read the coordinates of the release locations
235  !**********************************************
236
[f13406c]237  if (verbosity.gt.0) then
238    print*,'call readreleases'
239  endif
[e200b7a]240  call readreleases
241
242  ! Read and compute surface resistances to dry deposition of gases
243  !****************************************************************
244
[f13406c]245  if (verbosity.gt.0) then
246    print*,'call readdepo'
247  endif
[e200b7a]248  call readdepo
249
250  ! Convert the release point coordinates from geografical to grid coordinates
251  !***************************************************************************
252
[f13406c]253  call coordtrafo 
254  if (verbosity.gt.0) then
255    print*,'call coordtrafo'
256  endif
[e200b7a]257
258  ! Initialize all particles to non-existent
259  !*****************************************
260
[f13406c]261  if (verbosity.gt.0) then
262    print*,'Initialize all particles to non-existent'
263  endif
[e200b7a]264  do j=1,maxpart
265    itra1(j)=-999999999
266  end do
267
268  ! For continuation of previous run, read in particle positions
269  !*************************************************************
270
271  if (ipin.eq.1) then
[f13406c]272    if (verbosity.gt.0) then
273      print*,'call readpartpositions'
274    endif
[e200b7a]275    call readpartpositions
276  else
[f13406c]277    if (verbosity.gt.0) then
278      print*,'numpart=0, numparticlecount=0'
279    endif   
[e200b7a]280    numpart=0
281    numparticlecount=0
282  endif
283
284  ! Calculate volume, surface area, etc., of all output grid cells
285  ! Allocate fluxes and OHfield if necessary
286  !***************************************************************
287
[f13406c]288  if (verbosity.gt.0) then
289    print*,'call outgrid_init'
290  endif
[e200b7a]291  call outgrid_init
292  if (nested_output.eq.1) call outgrid_init_nest
293
294  ! Read the OH field
295  !******************
296
[f13406c]297  if (OHREA.eqv..TRUE.) then
298    if (verbosity.gt.0) then
[b4d29ce]299      print*,'call readOHfield'
[f13406c]300    endif
[b4d29ce]301    call readOHfield
[f13406c]302  endif
[e200b7a]303
304  ! Write basic information on the simulation to a file "header"
305  ! and open files that are to be kept open throughout the simulation
306  !******************************************************************
307
[660bcb7]308  if (lnetcdfout.eq.1) then
309    call writeheader_netcdf(lnest = .false.)
310  else
311    call writeheader
312  end if
313
314  if (nested_output.eq.1) then
315    if (lnetcdfout.eq.1) then
316      call writeheader_netcdf(lnest = .true.)
317    else
318      call writeheader_nest
319    endif
320  endif
321
[f13406c]322  if (verbosity.gt.0) then
323    print*,'call writeheader'
324  endif
325
[e200b7a]326  call writeheader
[f13406c]327  ! FLEXPART 9.2 ticket ?? write header in ASCII format
328  call writeheader_txt
329  !if (nested_output.eq.1) call writeheader_nest
330  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
331  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
332  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
333
334  if (verbosity.gt.0) then
335    print*,'call openreceptors'
336  endif
[e200b7a]337  call openreceptors
338  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
339
340  ! Releases can only start and end at discrete times (multiples of lsynctime)
341  !***************************************************************************
342
[f13406c]343  if (verbosity.gt.0) then
344    print*,'discretize release times'
345  endif
[e200b7a]346  do i=1,numpoint
[b4d29ce]347    ireleasestart(i)=nint(real(ireleasestart(i))/real(lsynctime))*lsynctime
348    ireleaseend(i)=nint(real(ireleaseend(i))/real(lsynctime))*lsynctime
[e200b7a]349  end do
350
351  ! Initialize cloud-base mass fluxes for the convection scheme
352  !************************************************************
353
[f13406c]354  if (verbosity.gt.0) then
355    print*,'Initialize cloud-base mass fluxes for the convection scheme'
356  endif
357
[e200b7a]358  do jy=0,nymin1
359    do ix=0,nxmin1
360      cbaseflux(ix,jy)=0.
361    end do
362  end do
363  do inest=1,numbnests
364    do jy=0,nyn(inest)-1
365      do ix=0,nxn(inest)-1
366        cbasefluxn(ix,jy,inest)=0.
367      end do
368    end do
369  end do
370
371  ! Calculate particle trajectories
372  !********************************
373
[f13406c]374  if (verbosity.gt.0) then
375     if (verbosity.gt.1) then   
[660bcb7]376       call system_clock(count_clock, count_rate, count_max)
377       write(*,*) 'System clock',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]378     endif
379     if (info_flag.eq.1) then
[660bcb7]380       print*, 'Info only mode (stop)'   
[b4d29ce]381       stop
[f13406c]382     endif
383     print*,'call timemanager'
384  endif
385
[e200b7a]386  call timemanager
387
[b4d29ce]388  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLEXPART MODEL RUN!'
[e200b7a]389
[660bcb7]390  ! output wall time
391  if (verbosity .gt. 0) then
392    call system_clock(count_clock,count_rate)
393    tins=(count_clock - count_clock0)/real(count_rate)
394    print*,'Wall time ',tins,'s, ',tins/60,'min, ',tins/3600,'h.'
395  endif
396
[e200b7a]397end program flexpart
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG