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

univie
Last change on this file since c0884a8 was c0884a8, checked in by pesei <petra seibert at univie ac at>, 6 years ago

replace CTBTO code for checking type of GRIB

  • Property mode set to 100644
File size: 14.8 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                            *
[c0884a8]42  !                                                                            *
43  !  Petra Seibert, 2018-06-26: simplified version met data format detection   *
44  !                                                                            *
[6ecb30a]45  !*****************************************************************************
[e200b7a]46  !                                                                            *
47  ! Variables:                                                                 *
48  !                                                                            *
49  ! Constants:                                                                 *
50  !                                                                            *
51  !*****************************************************************************
52
53  use point_mod
54  use par_mod
55  use com_mod
56  use conv_mod
[a9cf4b1]57
[8a65cb0]58  use random_mod, only: gasdev1
[c0884a8]59  use check_gribfile_mod
[e200b7a]60
[a9cf4b1]61#ifdef USE_NCF
62  use netcdf_output_mod, only: writeheader_netcdf
63#endif
64
[e200b7a]65  implicit none
66
[c0884a8]67  integer :: i,j,ix,jy,inest,id_centre
[e200b7a]68  integer :: idummy = -320
[f13406c]69  character(len=256) :: inline_options  !pathfile, flexversion, arg2
[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
[77778f8]88  flexversion='Version '//trim(flexversion_major)//'.3beta (2018-06-08)'
[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
[b4d29ce]139    write(*,*) 'call readpaths'
[f13406c]140  endif
141  call readpaths(pathfile)
142 
[8a65cb0]143  if (verbosity.gt.1) then !show clock info
144     !print*,'length(4)',length(4)
[f13406c]145     !count=0,count_rate=1000
[8a65cb0]146     CALL SYSTEM_CLOCK(count_clock0, count_rate, count_max)
[f13406c]147     !WRITE(*,*) 'SYSTEM_CLOCK',count, count_rate, count_max
148     !WRITE(*,*) 'SYSTEM_CLOCK, count_clock0', count_clock0
149     !WRITE(*,*) 'SYSTEM_CLOCK, count_rate', count_rate
150     !WRITE(*,*) 'SYSTEM_CLOCK, count_max', count_max
[8a65cb0]151  endif
[e200b7a]152
153  ! Read the user specifications for the current model run
154  !*******************************************************
155
[f13406c]156  if (verbosity.gt.0) then
[8a65cb0]157    write(*,*) 'call readcommand'
[f13406c]158  endif
[e200b7a]159  call readcommand
[f13406c]160  if (verbosity.gt.0) then
[8a65cb0]161    write(*,*) '    ldirect=', ldirect
162    write(*,*) '    ibdate,ibtime=',ibdate,ibtime
[b4d29ce]163    write(*,*) '    iedate,ietime=', iedate,ietime
[8a65cb0]164    if (verbosity.gt.1) then   
[b4d29ce]165      CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
166      write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
167    endif     
[8a65cb0]168  endif
[e200b7a]169
170  ! Read the age classes to be used
171  !********************************
[f13406c]172  if (verbosity.gt.0) then
[8a65cb0]173    write(*,*) 'call readageclasses'
[f13406c]174  endif
[e200b7a]175  call readageclasses
176
[8a65cb0]177  if (verbosity.gt.1) then   
[b4d29ce]178    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
179    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]180  endif     
[e200b7a]181
182  ! Read, which wind fields are available within the modelling period
183  !******************************************************************
184
[f13406c]185  if (verbosity.gt.0) then
[8a65cb0]186    write(*,*) 'call readavailable'
[f13406c]187  endif 
[e200b7a]188  call readavailable
189
[6ecb30a]190  ! Detect metdata format
191  !**********************
[c0884a8]192 
193  call cg_get_centre(path(3)(1:length(3)) // trim(wfname(1)), id_centre)
194  if (id_centre.eq.icg_id_ecmwf) then
195    print *,'ECMWF met data detected'
196  elseif (id_centre.eq.icg_id_ncep) then
197    print *,'NCEP met data detected'
[6ecb30a]198  else
[c0884a8]199    print *,'Unknown met data format'
[0c00f1f]200    stop
[6ecb30a]201  endif
202
203
204
[b0434e1]205  ! If nested wind fields are used, allocate arrays
206  !************************************************
207
208  if (verbosity.gt.0) then
209    write(*,*) 'call com_mod_allocate_nests'
210  endif
211  call com_mod_allocate_nests
212
[e200b7a]213  ! Read the model grid specifications,
214  ! both for the mother domain and eventual nests
215  !**********************************************
[f13406c]216 
217  if (verbosity.gt.0) then
[8a65cb0]218     write(*,*) 'call gridcheck'
[f13406c]219  endif
[8a65cb0]220
[c0884a8]221  if (id_centre.eq.icg_id_ecmwf) then
[6ecb30a]222    call gridcheck_ecmwf
223  else
224    call gridcheck_gfs
225  end if
[f13406c]226
[8a65cb0]227  if (verbosity.gt.1) then   
[b4d29ce]228    CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
229    write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
[f13406c]230  endif     
231
232  if (verbosity.gt.0) then
[8a65cb0]233    write(*,*) 'call gridcheck_nests'
[f13406c]234  endif 
[e200b7a]235  call gridcheck_nests
236
237  ! Read the output grid specifications
238  !************************************
239
[f13406c]240  if (verbosity.gt.0) then
[8a65cb0]241    write(*,*) 'call readoutgrid'
[f13406c]242  endif
243
[e200b7a]244  call readoutgrid
245
[f13406c]246  if (nested_output.eq.1) then
[b4d29ce]247    call readoutgrid_nest
[f13406c]248    if (verbosity.gt.0) then
[8a65cb0]249      write(*,*) '# readoutgrid_nest'
[f13406c]250    endif
251  endif
[e200b7a]252
253  ! Read the receptor points for which extra concentrations are to be calculated
254  !*****************************************************************************
255
[f13406c]256  if (verbosity.eq.1) then
[8a65cb0]257     print*,'call readreceptors'
[f13406c]258  endif
[e200b7a]259  call readreceptors
260
261  ! Read the physico-chemical species property table
262  !*************************************************
263  !SEC: now only needed SPECIES are read in readreleases.f
264  !call readspecies
265
266
267  ! Read the landuse inventory
268  !***************************
269
[f13406c]270  if (verbosity.gt.0) then
[8a65cb0]271    print*,'call readlanduse'
[f13406c]272  endif
[e200b7a]273  call readlanduse
274
275  ! Assign fractional cover of landuse classes to each ECMWF grid point
276  !********************************************************************
277
[f13406c]278  if (verbosity.gt.0) then
[8a65cb0]279    print*,'call assignland'
[f13406c]280  endif
[e200b7a]281  call assignland
282
283  ! Read the coordinates of the release locations
284  !**********************************************
285
[f13406c]286  if (verbosity.gt.0) then
[8a65cb0]287    print*,'call readreleases'
[f13406c]288  endif
[e200b7a]289  call readreleases
290
291  ! Read and compute surface resistances to dry deposition of gases
292  !****************************************************************
293
[f13406c]294  if (verbosity.gt.0) then
[8a65cb0]295    print*,'call readdepo'
[f13406c]296  endif
[e200b7a]297  call readdepo
298
299  ! Convert the release point coordinates from geografical to grid coordinates
300  !***************************************************************************
301
[f13406c]302  call coordtrafo 
303  if (verbosity.gt.0) then
[8a65cb0]304    print*,'call coordtrafo'
[f13406c]305  endif
[e200b7a]306
307  ! Initialize all particles to non-existent
308  !*****************************************
309
[f13406c]310  if (verbosity.gt.0) then
[8a65cb0]311    print*,'Initialize all particles to non-existent'
[f13406c]312  endif
[e200b7a]313  do j=1,maxpart
314    itra1(j)=-999999999
315  end do
316
317  ! For continuation of previous run, read in particle positions
318  !*************************************************************
319
320  if (ipin.eq.1) then
[f13406c]321    if (verbosity.gt.0) then
[8a65cb0]322      print*,'call readpartpositions'
[f13406c]323    endif
[e200b7a]324    call readpartpositions
325  else
[f13406c]326    if (verbosity.gt.0) then
[8a65cb0]327      print*,'numpart=0, numparticlecount=0'
[f13406c]328    endif   
[e200b7a]329    numpart=0
330    numparticlecount=0
331  endif
332
333  ! Calculate volume, surface area, etc., of all output grid cells
334  ! Allocate fluxes and OHfield if necessary
335  !***************************************************************
336
[f13406c]337  if (verbosity.gt.0) then
[8a65cb0]338    print*,'call outgrid_init'
[f13406c]339  endif
[e200b7a]340  call outgrid_init
341  if (nested_output.eq.1) call outgrid_init_nest
342
343  ! Read the OH field
344  !******************
345
[f13406c]346  if (OHREA.eqv..TRUE.) then
347    if (verbosity.gt.0) then
[8a65cb0]348      print*,'call readOHfield'
[f13406c]349    endif
[b4d29ce]350    call readOHfield
[f13406c]351  endif
[e200b7a]352
353  ! Write basic information on the simulation to a file "header"
354  ! and open files that are to be kept open throughout the simulation
355  !******************************************************************
356
[a9cf4b1]357#ifdef USE_NCF
[8a65cb0]358  if (lnetcdfout.eq.1) then
359    call writeheader_netcdf(lnest=.false.)
360  else
361    call writeheader
362  end if
363
364  if (nested_output.eq.1) then
365    if (lnetcdfout.eq.1) then
366      call writeheader_netcdf(lnest=.true.)
367    else
368      call writeheader_nest
369    endif
370  endif
[a9cf4b1]371#endif
[8a65cb0]372
[f13406c]373  if (verbosity.gt.0) then
[8a65cb0]374    print*,'call writeheader'
[f13406c]375  endif
376
[e200b7a]377  call writeheader
[8a65cb0]378  ! FLEXPART 9.2 ticket ?? write header in ASCII format
[f13406c]379  call writeheader_txt
380  !if (nested_output.eq.1) call writeheader_nest
381  if (nested_output.eq.1.and.surf_only.ne.1) call writeheader_nest
382  if (nested_output.eq.1.and.surf_only.eq.1) call writeheader_nest_surf
383  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
384
385  !open(unitdates,file=path(2)(1:length(2))//'dates')
386
387  if (verbosity.gt.0) then
[8a65cb0]388    print*,'call openreceptors'
[f13406c]389  endif
[e200b7a]390  call openreceptors
391  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
392
393  ! Releases can only start and end at discrete times (multiples of lsynctime)
394  !***************************************************************************
395
[f13406c]396  if (verbosity.gt.0) then
[8a65cb0]397    print*,'discretize release times'
[f13406c]398  endif
[e200b7a]399  do i=1,numpoint
[b4d29ce]400    ireleasestart(i)=nint(real(ireleasestart(i))/real(lsynctime))*lsynctime
401    ireleaseend(i)=nint(real(ireleaseend(i))/real(lsynctime))*lsynctime
[e200b7a]402  end do
403
404  ! Initialize cloud-base mass fluxes for the convection scheme
405  !************************************************************
406
[f13406c]407  if (verbosity.gt.0) then
[8a65cb0]408    print*,'Initialize cloud-base mass fluxes for the convection scheme'
[f13406c]409  endif
410
[e200b7a]411  do jy=0,nymin1
412    do ix=0,nxmin1
413      cbaseflux(ix,jy)=0.
414    end do
415  end do
416  do inest=1,numbnests
417    do jy=0,nyn(inest)-1
418      do ix=0,nxn(inest)-1
419        cbasefluxn(ix,jy,inest)=0.
420      end do
421    end do
422  end do
423
[4c64400]424  ! Inform whether output kernel is used or not
425  !*********************************************
426  if (lroot) then
[fe32dca]427    if (.not.lusekerneloutput) then
[4c64400]428      write(*,*) "Concentrations are calculated without using kernel"
429    else
430      write(*,*) "Concentrations are calculated using kernel"
431    end if
432  end if
433
434
[e200b7a]435  ! Calculate particle trajectories
436  !********************************
437
[f13406c]438  if (verbosity.gt.0) then
[8a65cb0]439     if (verbosity.gt.1) then   
440       CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
441       write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
442     endif
443     if (info_flag.eq.1) then
444       print*, 'info only mode (stop)'   
445       stop
446     endif
447     print*,'call timemanager'
[f13406c]448  endif
449
[c0884a8]450  call timemanager(id_centre)
[e200b7a]451
[8a65cb0]452! NIK 16.02.2005
[c8fc724]453  do i=1,nspec
454    write(*,*) '**********************************************'
455    write(*,*) 'Scavenging statistics for species ', species(i), ':'
456    write(*,*) 'Total number of occurences of below-cloud scavenging', &
457         & tot_blc_count(i)
458    write(*,*) 'Total number of occurences of in-cloud    scavenging', &
459         & tot_inc_count(i)
460    write(*,*) '**********************************************'
461  end do
462 
[8a65cb0]463  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLE&
464       &XPART MODEL RUN!'
[e200b7a]465
466end program flexpart
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG