source: branches/jerome/src_flexwrf_v3.1/flexwrf.f90 @ 16

Last change on this file since 16 was 16, checked in by jebri, 11 years ago

sources for flexwrf v3.1

File size: 11.2 KB
Line 
1!***********************************************************************
2!* Copyright 2012,2013                                                *
3!* Jerome Brioude, Delia Arnold, Andreas Stohl, Wayne Angevine,       *
4!* John Burkhart, Massimo Cassiani, Adam Dingwell, Richard C Easter, Sabine Eckhardt,*
5!* Stephanie Evan, Jerome D Fast, Don Morton, Ignacio Pisso,          *
6!* Petra Seibert, Gerard Wotawa, Caroline Forster, Harald Sodemann,   *
7!*                                                                     *
8!* This file is part of FLEXPART WRF                                   *
9!*                                                                     *
10!* FLEXPART is free software: you can redistribute it and/or modify    *
11!* it under the terms of the GNU General Public License as published by*
12!* the Free Software Foundation, either version 3 of the License, or   *
13!* (at your option) any later version.                                 *
14!*                                                                     *
15!* FLEXPART is distributed in the hope that it will be useful,         *
16!* but WITHOUT ANY WARRANTY; without even the implied warranty of      *
17!* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
18!* GNU General Public License for more details.                        *
19!*                                                                     *
20!* You should have received a copy of the GNU General Public License   *
21!* along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
22!***********************************************************************
23      program flexwrf
24!*******************************************************************************
25!                                                                              *
26!     This is the Lagrangian Particle Dispersion Model FLEXPART_WRF.           *
27!                                                                              *
28!         FLEXPART uses met. files from the ECMWF model (in grib format),      *
29!             and its internal computational grid is latitude-longitude.       *
30!                                                                              *
31!         FLEXPART_WRF uses met. files from the WRF model (in NetCDF format),  *
32!             and its internal computational grid is the WRF x-y grid.         *
33!                                                                              *
34!     The main program manages the reading of model run specifications, etc.   *
35!     All actual computing is done within subroutine timemanager.              *
36!                                                                              *
37!     Author: A. Stohl                                                         *
38!     18 May 1996                                                              *
39!                                                                              *
40!     Nov 2005, R. Easter - Added the above comments and changed               *
41!                           the program name to "flexpart_wrf"                 *
42!                                                                              *
43!     Feb 2012, J Brioude- modify the name of the pilt_wrf model from PNLL     *
44!                          to flexwrf.
45!                          start doing versions                                *
46!                input information should be put in flexwr.input               *
47!     Mar 2012, J Brioude: Hybrid parallelization of v74. everything converted *
48!                   in fortran 90, based on version 90.1 of the main stream    *
49!                   version of FLEXPART.                                       *
50!     Jun 2012, J Brioude: Add tests on arguments to the flexwrf input file. *
51!*******************************************************************************
52!                                                                              *
53! Variables:                                                                   *
54!                                                                              *
55! Constants:                                                                   *
56!                                                                              *
57!*******************************************************************************
58
59
60  use point_mod
61  use par_mod
62  use com_mod
63  use conv_mod
64
65  use luxury
66  use mt_stream
67
68  implicit none
69
70! include 'mpif.h'
71
72  integer :: i,j,ix,jy,inest,ii
73! ,MPI_COMM_WORLD
74  integer :: idummy = -320
75  integer :: inext,inextp,ma(55),iff
76! integer, dimension(MPI_STATUS_SIZE) :: status
77  integer :: myid,ntasks,islave
78!  integer, parameter :: master=0, mstgtag1=11, msgtag2=12
79   integer :: ierr
80
81  real, external :: ran3  ! added by mc to use RAN3 using the original JB random number system
82  integer, allocatable :: seed(:) ! here and below further variable used by the MT generator
83  integer(4) :: iseed = 73519232
84  integer :: id
85  type (mt_state) :: mts (0: MAX_STREAM)
86  character :: nummpi_id*2  !for test on pc
87
88!      if (myid.eq.0) then
89!let's comment the line above to let each node reading and making the same
90!thing.
91
92!  save inext,inextp,ma,iff
93  iff=0
94!  call MPI_INIT( ierr )
95!  call MPI_COMM_RANK ( MPI_COMM_WORLD, myid, ierr )
96!  call MPI_COMM_SIZE ( MPI_COMM_WORLD, ntasks, ierr )
97
98     if (command_argument_count().eq.0) then
99     print*,'the input file used is flexwrf.input in the ' // &
100      'local folder of the executable'
101     inputname='flexwrf.input'
102     endif
103     if (command_argument_count().gt.0) then
104         call get_command_argument(1,inputname,len2,ierr)
105     print*,'the input file used is ' // inputname
106     endif
107
108
109! Generate a large number of random numbers
110!******************************************
111      if (newrandomgen.eq.0) then
112!      idummy = -320-(myid*4049)
113       idummy = -320
114      do j=1,maxomp
115      do i=1,maxrand-1,2
116      ii=i+(j-1)*maxrand
117        call gasdev1(idummy,rannumb(ii),rannumb(ii+1),inext,inextp,ma,iff)
118      enddo
119      enddo
120      ii=maxrand*maxomp
121      call gasdev1(idummy,rannumb(ii),rannumb(ii-1),inext,inextp,ma,iff)
122!     print*,'rand',myid
123!     print*,rannumb(1:5)
124!     call ranlux(uniform_rannumb,maxrandomp)  ! this generate a uniform
125!     distribution
126      else
127      idummy=254 !+myid*443   !different seed for different mpi processes are produced so indepedent stream for any mpi process suing RANLUX are certain
128      call RLUXGO(3,idummy,0,0)  ! this set the luxury level to 3 and initalize the generator for any myid
129      do i=1,maxrand-1,2
130      call gasdevlux2R(rannumb(i),rannumb(i+1)) !this will generate a guassian distribution
131      end do
132      call gasdevlux2R(rannumb(maxrand),rannumb(maxrand-1))
133      ! Generate a stream of uniform deviate random numbers to be used for CBL
134      call ranlux(uniform_rannumb,maxrand)  ! this generate a uniform distribution
135
136!----- comment by MC: now initialize the mersenne twister generator for a number
137!max_stream of possible streams
138!----- to be called subsequently by any openmp process activated. note RANLUX
139!above is suppose to be the best generator
140!----- but it is slower than mersenne twister and moreover it would require some
141!adaptation for workiong with openmp processes
142      !do this on any mpi_process taht will have  a copy of all the MT generator
143      !initialization
144      ! set parameters
145
146      call set_mt19937
147
148      !  initialize MT state type
149      call new (mts(0))
150
151      call init (mts(0),iseed)   !iseed unique and defined above. note that the lenght of the period of the master stream is about 2^19000
152
153      !  initialize additional streams from the master. this is done jumping
154      !  between different points in the stream any child stream has period
155      !  2^256
156      do id=1, MAX_STREAM
157      call create_stream (mts(0),mts(id),id)
158      end do
159      end if
160
161
162! Read the unified input file - jdf
163!***************************
164
165      call readinput
166
167   if ( DRYDEP ) then
168! Read the landuse inventory
169!***************************
170
171      call readlanduse
172
173! Assign fractional cover of landuse classes to each ECMWF grid point
174!********************************************************************
175
176      call assignland
177
178! Read and compute surface resistances to dry deposition of gases
179!****************************************************************
180
181      call readdepo
182   endif
183
184! Convert the release point coordinates from geografical to grid coordinates
185!***************************************************************************
186
187      call coordtrafo
188
189! Initialize all particles to non-existent
190!*****************************************
191
192!      do j=1,maxpart
193!        itra1(j)=-999999999
194!      enddo
195
196! For continuation of previous run, read in particle positions
197!*************************************************************
198
199      if (ipin.eq.1) then
200        call readpartpositions
201      else
202        numpart=0
203    numparticlecount=0
204
205      endif
206
207
208! Calculate volume, surface area, etc., of all output grid cells
209!***************************************************************
210!      if (myid.eq.0) then
211      if (outgrid_option.eq.0) then
212      call outgrid_init_irreg
213      if (nested_output.eq.1) call outgrid_init_nest_irreg !need to be fixed
214      elseif (outgrid_option.eq.1) then
215      call outgrid_init_reg
216      if (nested_output.eq.1) call outgrid_init_nest_reg !need to be fixed
217      endif
218!      endif
219
220
221  ! Read the OH field
222  !******************
223
224  if (OHREA.eqv..TRUE.) &
225       call readohfield
226
227! Write basic information on the simulation to a file "header"
228! and open files that are to be kept open throughout the simulation
229!******************************************************************
230
231!      if (myid.eq.0) then
232      if (iouttype.eq.0 .or. iouttype.eq.1) then ! binary or ascii output
233        call writeheader
234        if (nested_output.eq.1) call writeheader_nest() !need to be fixed
235      else  ! netcdf output
236        call write_ncheader(0,0)
237        if (nested_output.eq.1)  call write_ncheader(0,1)
238      endif !iouttype
239!  open(unitdates,file=path(2)(1:length(2))//'dates')
240      open(unitdates,file=path(1)(1:length(1))//'dates')
241      call openreceptors
242      if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
243
244!      endif
245! Releases can only start and end at discrete times (multiples of lsynctime)
246!***************************************************************************
247     
248      do i=1,numpoint
249        ireleasestart(i)=nint(real(ireleasestart(i))/ &
250        real(lsynctime))*lsynctime
251        ireleaseend(i)=nint(real(ireleaseend(i))/ &
252        real(lsynctime))*lsynctime
253        enddo
254
255! Initialize cloud-base mass fluxes for the convection scheme
256!************************************************************
257
258      do jy=0,nymin1
259        do ix=0,nxmin1
260        cbaseflux(ix,jy)=0.
261    end do
262  end do
263
264      do  inest=1,numbnests
265        do  jy=0,nyn(inest)-1
266          do  ix=0,nxn(inest)-1
267          cbasefluxn(ix,jy,inest)=0.
268    end do
269  end do
270  end do
271
272
273! Calculate particle trajectories
274!********************************
275!     endif !if condition on myid
276!    call MPI_BARRIER(MPI_COMM_WORLD,ierr)
277
278      call timemanager(mts)
279
280
281      write(*,'(/a/)') 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY ' //  &
282        'COMPLETED A FLEXPART_WRF MODEL RUN!'
283
284!   call MPI_FINALIZE ( ierr )
285
286end program flexwrf
287
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG