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

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

sources for flexwrf v3.1

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