source: flexpart.git/src/FLEXPART.f90 @ 2753a5c

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 2753a5c was 2753a5c, checked in by Ignacio Pisso <ip@…>, 5 years ago

resolved merging conflicts with GFS branch

  • Property mode set to 100644
File size: 14.9 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  !*****************************************************************************
[6ecb30a]35  ! Changes:                                                                   *
36  !   Unified ECMWF and GFS builds                                             *
37  !   Marian Harustak, 12.5.2017                                               *
38  !     - Added detection of metdata format using gributils routines           *
39  !     - Distinguished calls to ecmwf/gfs gridcheck versions based on         *
40  !       detected metdata format                                              *
41  !     - Passed metdata format down to timemanager                            *
42  !*****************************************************************************
[e200b7a]43  !                                                                            *
44  ! Variables:                                                                 *
45  !                                                                            *
46  ! Constants:                                                                 *
47  !                                                                            *
48  !*****************************************************************************
49
50  use point_mod
51  use par_mod
52  use com_mod
53  use conv_mod
[a9cf4b1]54
[8a65cb0]55  use random_mod, only: gasdev1
[6ecb30a]56  use class_gribfile
[e200b7a]57
[a9cf4b1]58#ifdef USE_NCF
59  use netcdf_output_mod, only: writeheader_netcdf
60#endif
61
[e200b7a]62  implicit none
63
64  integer :: i,j,ix,jy,inest
65  integer :: idummy = -320
[f13406c]66  character(len=256) :: inline_options  !pathfile, flexversion, arg2
[6ecb30a]67  integer :: metdata_format = GRIBFILE_CENTRE_UNKNOWN
68  integer :: detectformat
69
[8a65cb0]70
71
72  ! Initialize arrays in com_mod
73  !*****************************
[b0434e1]74  call com_mod_allocate_part(maxpart)
75 
[8a65cb0]76
[e200b7a]77  ! Generate a large number of random numbers
78  !******************************************
79
80  do i=1,maxrand-1,2
81    call gasdev1(idummy,rannumb(i),rannumb(i+1))
82  end do
83  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
84
[4c64400]85
[b4d29ce]86  ! FLEXPART version string
[fddc6ec]87  flexversion_major = '10' ! Major version number, also used for species file names
[d8eed02]88  flexversion='Version '//trim(flexversion_major)//'.2beta (2017-08-01)'
[8a65cb0]89  verbosity=0
90
[f13406c]91  ! Read the pathnames where input/output files are stored
92  !*******************************************************
93
[8a65cb0]94  inline_options='none'
[f13406c]95  select case (iargc())
[8a65cb0]96  case (2)
[f13406c]97    call getarg(1,arg1)
98    pathfile=arg1
99    call getarg(2,arg2)
100    inline_options=arg2
[8a65cb0]101  case (1)
[f13406c]102    call getarg(1,arg1)
103    pathfile=arg1
104    if (arg1(1:1).eq.'-') then
[b4d29ce]105      write(pathfile,'(a11)') './pathnames'
106      inline_options=arg1
[f13406c]107    endif
[8a65cb0]108  case (0)
[f13406c]109    write(pathfile,'(a11)') './pathnames'
110  end select
111 
[e200b7a]112  ! Print the GPL License statement
113  !*******************************************************
[4fbe7a5]114  print*,'Welcome to FLEXPART ', trim(flexversion)
[b4d29ce]115  print*,'FLEXPART is free software released under the GNU General Public License.'
[414a5e5]116 
[8a65cb0]117  if (inline_options(1:1).eq.'-') then
118    if (trim(inline_options).eq.'-v'.or.trim(inline_options).eq.'-v1') then
119       print*, 'Verbose mode 1: display detailed information during run'
[b4d29ce]120       verbosity=1
[8a65cb0]121    endif
122    if (trim(inline_options).eq.'-v2') then
123       print*, 'Verbose mode 2: display more detailed information during run'
[b4d29ce]124       verbosity=2
125    endif
[8a65cb0]126    if (trim(inline_options).eq.'-i') then
127       print*, 'Info mode: provide detailed run specific information and stop'
[b4d29ce]128       verbosity=1
129       info_flag=1
130    endif
[8a65cb0]131    if (trim(inline_options).eq.'-i2') then
132       print*, 'Info mode: provide more detailed run specific information and stop'
133       verbosity=2
134       info_flag=1
[b4d29ce]135    endif
136  endif
137           
[f13406c]138  if (verbosity.gt.0) then
[50958b8]139    print*, 'nxmax=',nxmax
140    print*, 'nymax=',nymax
141    print*, 'nzmax=',nzmax
142    print*,'nxshift=',nxshift
[b4d29ce]143    write(*,*) 'call readpaths'
[f13406c]144  endif
145  call readpaths(pathfile)
146 
[8a65cb0]147  if (verbosity.gt.1) then !show clock info
148     !print*,'length(4)',length(4)
[f13406c]149     !count=0,count_rate=1000
[8a65cb0]150     CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
[f13406c]151     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
152     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
153     !WRITE(*,*) 'SYSTEM_CLOCK, count_rate', count_rate
154     !WRITE(*,*) 'SYSTEM_CLOCK, count_max', count_max
[8a65cb0]155  endif
[e200b7a]156
157  ! Read the user specifications for the current model run
158  !*******************************************************
159
[f13406c]160  if (verbosity.gt.0) then
[8a65cb0]161    write(*,*) 'call readcommand'
[f13406c]162  endif
[e200b7a]163  call readcommand
[f13406c]164  if (verbosity.gt.0) then
[8a65cb0]165    write(*,*) '    ldirect=', ldirect
166    write(*,*) '    ibdate,ibtime=',ibdate,ibtime
[b4d29ce]167    write(*,*) '    iedate,ietime=', iedate,ietime
[8a65cb0]168    if (verbosity.gt.1) then   
[b4d29ce]169      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
170      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
171    endif     
[8a65cb0]172  endif
[e200b7a]173
174  ! Read the age classes to be used
175  !********************************
[f13406c]176  if (verbosity.gt.0) then
[8a65cb0]177    write(*,*) 'call readageclasses'
[f13406c]178  endif
[e200b7a]179  call readageclasses
180
[8a65cb0]181  if (verbosity.gt.1) then   
[b4d29ce]182    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
183    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]184  endif     
[e200b7a]185
186  ! Read, which wind fields are available within the modelling period
187  !******************************************************************
188
[f13406c]189  if (verbosity.gt.0) then
[8a65cb0]190    write(*,*) 'call readavailable'
[f13406c]191  endif 
[e200b7a]192  call readavailable
193
[6ecb30a]194  ! Detect metdata format
195  !**********************
196
197  metdata_format = detectformat()
198
199  if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
200    print *,'ECMWF metdata detected'
201  elseif (metdata_format.eq.GRIBFILE_CENTRE_NCEP) then
202    print *,'NCEP metdata detected'
203  else
204    print *,'Unknown metdata format'
[0c00f1f]205    stop
[6ecb30a]206  endif
207
208
209
[b0434e1]210  ! If nested wind fields are used, allocate arrays
211  !************************************************
212
213  if (verbosity.gt.0) then
214    write(*,*) 'call com_mod_allocate_nests'
215  endif
216  call com_mod_allocate_nests
217
[e200b7a]218  ! Read the model grid specifications,
219  ! both for the mother domain and eventual nests
220  !**********************************************
[f13406c]221 
222  if (verbosity.gt.0) then
[8a65cb0]223     write(*,*) 'call gridcheck'
[f13406c]224  endif
[8a65cb0]225
[6ecb30a]226  if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
227    call gridcheck_ecmwf
228  else
229    call gridcheck_gfs
230  end if
[f13406c]231
[8a65cb0]232  if (verbosity.gt.1) then   
[b4d29ce]233    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
234    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]235  endif     
236
237  if (verbosity.gt.0) then
[8a65cb0]238    write(*,*) 'call gridcheck_nests'
[f13406c]239  endif 
[e200b7a]240  call gridcheck_nests
241
242  ! Read the output grid specifications
243  !************************************
244
[f13406c]245  if (verbosity.gt.0) then
[8a65cb0]246    write(*,*) 'call readoutgrid'
[f13406c]247  endif
248
[e200b7a]249  call readoutgrid
250
[f13406c]251  if (nested_output.eq.1) then
[b4d29ce]252    call readoutgrid_nest
[f13406c]253    if (verbosity.gt.0) then
[8a65cb0]254      write(*,*) '# readoutgrid_nest'
[f13406c]255    endif
256  endif
[e200b7a]257
258  ! Read the receptor points for which extra concentrations are to be calculated
259  !*****************************************************************************
260
[f13406c]261  if (verbosity.eq.1) then
[8a65cb0]262     print*,'call readreceptors'
[f13406c]263  endif
[e200b7a]264  call readreceptors
265
266  ! Read the physico-chemical species property table
267  !*************************************************
268  !SEC: now only needed SPECIES are read in readreleases.f
269  !call readspecies
270
271
272  ! Read the landuse inventory
273  !***************************
274
[f13406c]275  if (verbosity.gt.0) then
[8a65cb0]276    print*,'call readlanduse'
[f13406c]277  endif
[e200b7a]278  call readlanduse
279
280  ! Assign fractional cover of landuse classes to each ECMWF grid point
281  !********************************************************************
282
[f13406c]283  if (verbosity.gt.0) then
[8a65cb0]284    print*,'call assignland'
[f13406c]285  endif
[e200b7a]286  call assignland
287
288  ! Read the coordinates of the release locations
289  !**********************************************
290
[f13406c]291  if (verbosity.gt.0) then
[8a65cb0]292    print*,'call readreleases'
[f13406c]293  endif
[e200b7a]294  call readreleases
295
296  ! Read and compute surface resistances to dry deposition of gases
297  !****************************************************************
298
[f13406c]299  if (verbosity.gt.0) then
[8a65cb0]300    print*,'call readdepo'
[f13406c]301  endif
[e200b7a]302  call readdepo
303
304  ! Convert the release point coordinates from geografical to grid coordinates
305  !***************************************************************************
306
[f13406c]307  call coordtrafo 
308  if (verbosity.gt.0) then
[8a65cb0]309    print*,'call coordtrafo'
[f13406c]310  endif
[e200b7a]311
312  ! Initialize all particles to non-existent
313  !*****************************************
314
[f13406c]315  if (verbosity.gt.0) then
[8a65cb0]316    print*,'Initialize all particles to non-existent'
[f13406c]317  endif
[e200b7a]318  do j=1,maxpart
319    itra1(j)=-999999999
320  end do
321
322  ! For continuation of previous run, read in particle positions
323  !*************************************************************
324
325  if (ipin.eq.1) then
[f13406c]326    if (verbosity.gt.0) then
[8a65cb0]327      print*,'call readpartpositions'
[f13406c]328    endif
[e200b7a]329    call readpartpositions
330  else
[f13406c]331    if (verbosity.gt.0) then
[8a65cb0]332      print*,'numpart=0, numparticlecount=0'
[f13406c]333    endif   
[e200b7a]334    numpart=0
335    numparticlecount=0
336  endif
337
338  ! Calculate volume, surface area, etc., of all output grid cells
339  ! Allocate fluxes and OHfield if necessary
340  !***************************************************************
341
[f13406c]342  if (verbosity.gt.0) then
[8a65cb0]343    print*,'call outgrid_init'
[f13406c]344  endif
[e200b7a]345  call outgrid_init
346  if (nested_output.eq.1) call outgrid_init_nest
347
348  ! Read the OH field
349  !******************
350
[f13406c]351  if (OHREA.eqv..TRUE.) then
352    if (verbosity.gt.0) then
[8a65cb0]353      print*,'call readOHfield'
[f13406c]354    endif
[b4d29ce]355    call readOHfield
[f13406c]356  endif
[e200b7a]357
358  ! Write basic information on the simulation to a file "header"
359  ! and open files that are to be kept open throughout the simulation
360  !******************************************************************
361
[a9cf4b1]362#ifdef USE_NCF
[8a65cb0]363  if (lnetcdfout.eq.1) then
364    call writeheader_netcdf(lnest=.false.)
365  else
366    call writeheader
367  end if
368
369  if (nested_output.eq.1) then
370    if (lnetcdfout.eq.1) then
371      call writeheader_netcdf(lnest=.true.)
372    else
373      call writeheader_nest
374    endif
375  endif
[a9cf4b1]376#endif
[8a65cb0]377
[f13406c]378  if (verbosity.gt.0) then
[8a65cb0]379    print*,'call writeheader'
[f13406c]380  endif
381
[e200b7a]382  call writeheader
[8a65cb0]383  ! FLEXPART 9.2 ticket ?? write header in ASCII format
[f13406c]384  call writeheader_txt
385  !if (nested_output.eq.1) call writeheader_nest
386  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
387  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
388  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
389
390  !open(unitdates,file=path(2)(1:length(2))//'dates')
391
392  if (verbosity.gt.0) then
[8a65cb0]393    print*,'call openreceptors'
[f13406c]394  endif
[e200b7a]395  call openreceptors
396  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
397
398  ! Releases can only start and end at discrete times (multiples of lsynctime)
399  !***************************************************************************
400
[f13406c]401  if (verbosity.gt.0) then
[8a65cb0]402    print*,'discretize release times'
[f13406c]403  endif
[e200b7a]404  do i=1,numpoint
[b4d29ce]405    ireleasestart(i)=nint(real(ireleasestart(i))/real(lsynctime))*lsynctime
406    ireleaseend(i)=nint(real(ireleaseend(i))/real(lsynctime))*lsynctime
[e200b7a]407  end do
408
409  ! Initialize cloud-base mass fluxes for the convection scheme
410  !************************************************************
411
[f13406c]412  if (verbosity.gt.0) then
[8a65cb0]413    print*,'Initialize cloud-base mass fluxes for the convection scheme'
[f13406c]414  endif
415
[e200b7a]416  do jy=0,nymin1
417    do ix=0,nxmin1
418      cbaseflux(ix,jy)=0.
419    end do
420  end do
421  do inest=1,numbnests
422    do jy=0,nyn(inest)-1
423      do ix=0,nxn(inest)-1
424        cbasefluxn(ix,jy,inest)=0.
425      end do
426    end do
427  end do
428
[4c64400]429  ! Inform whether output kernel is used or not
430  !*********************************************
431  if (lroot) then
[fe32dca]432    if (.not.lusekerneloutput) then
[4c64400]433      write(*,*) "Concentrations are calculated without using kernel"
434    else
435      write(*,*) "Concentrations are calculated using kernel"
436    end if
437  end if
438
439
[e200b7a]440  ! Calculate particle trajectories
441  !********************************
442
[f13406c]443  if (verbosity.gt.0) then
[8a65cb0]444     if (verbosity.gt.1) then   
445       CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
446       write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
447     endif
448     if (info_flag.eq.1) then
449       print*, 'info only mode (stop)'   
450       stop
451     endif
452     print*,'call timemanager'
[f13406c]453  endif
454
[6ecb30a]455  call timemanager(metdata_format)
[e200b7a]456
[e9e0f06]457  if (verbosity.gt.0) then
[8a65cb0]458! NIK 16.02.2005
[e9e0f06]459    do i=1,nspec
460      if (tot_inc_count(i).gt.0) then
461         write(*,*) '**********************************************'
462         write(*,*) 'Scavenging statistics for species ', species(i), ':'
463         write(*,*) 'Total number of occurences of below-cloud scavenging', &
464           & tot_blc_count(i)
465         write(*,*) 'Total number of occurences of in-cloud    scavenging', &
466           & tot_inc_count(i)
467         write(*,*) '**********************************************'
468      endif
469    end do
470    write (*,*) 'timemanager> call wetdepo'
471  endif
[c8fc724]472 
[8a65cb0]473  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLE&
474       &XPART MODEL RUN!'
[e200b7a]475
476end program flexpart
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG