source: flexpart.git/src/FLEXPART.f90 @ 5f2e8f6

flexpart-noresm
Last change on this file since 5f2e8f6 was 5f2e8f6, checked in by Ignacio Pisso <Ignacio.Pisso@…>, 8 years ago

new flexpart noresm code in src

  • Property mode set to 100755
File size: 8.2 KB
Line 
1!**********************************************************************
2! Copyright 2016                                                      *
3! Andreas Stohl, Massimo Cassiani, Petra Seibert, A. Frank,           *
4! Gerhard Wotawa,  Caroline Forster, Sabine Eckhardt, John Burkhart,  *
5! Harald Sodemann, Ignacio Pisso                                      *
6!                                                                     *
7! This file is part of FLEXPART-NorESM                                *
8!                                                                     *
9! FLEXPART-NorESM is free software: you can redistribute it           *
10! 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-NorESM 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-NorESM.                                         *
22!  If not, see <http://www.gnu.org/licenses/>.                        *
23!**********************************************************************
24
25program flexpart_NorESM
26
27  !*****************************************************************************
28  !                                                                            *
29  !     This is the Lagrangian Particle Dispersion Model FLEXPART-NorESM.      *
30  !     based on FLEXPART version 9.0.1                                        *
31  !     The main program manages the reading of model run specifications, etc. *
32  !     All actual computing is done within subroutine timemanager.            *
33  !     Note: FLEXPRT-NorESM uses meteo files from the NorESM(CAM4 based)      *
34  !     climate model in netcdf format.                                        *
35  !     Note: some lines of code to check netcdf files content have been       *
36  !     copied/modfied from routines in FLEXPART-WRF                           *
37  !                                                                            *
38  !     Author:                                                                *
39  !     A. Stohl 18 May 1996                                                   *   
40  !                                                                            *
41  !     Modified by:                                                           *
42  !     M. Cassiani  2016                                                      *
43  !     Nested input not allowed                                               *
44  !                                                                            *
45  !*****************************************************************************
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
57
58  implicit none
59
60  integer :: i,j,ix,jy,inest
61  integer :: idummy = -320
62
63  ! Generate a large number of random numbers
64  !******************************************
65
66  do i=1,maxrand-1,2
67    call gasdev1(idummy,rannumb(i),rannumb(i+1))
68  end do
69  call gasdev1(idummy,rannumb(maxrand),rannumb(maxrand-1))
70
71  ! Print the GPL License statement
72  !*******************************************************
73  print*,'Welcome to FLEXPART-NorESM Version 1.0'
74  print*,'FLEXPART-NorESM is free software released under the GNU'// &
75       'General Public License.'
76
77  ! Read the pathnames where input/output files are stored
78  !*******************************************************
79
80  call readpaths
81
82  ! Read the user specifications for the current model run
83  !*******************************************************
84
85  call readcommand
86
87
88  ! Read the age classes to be used
89  !********************************
90
91  call readageclasses
92
93
94  ! Read, which wind fields are available within the modelling period
95  !******************************************************************
96
97  call readavailable
98
99
100  ! Read the model grid specifications,
101  ! both for the mother domain and eventual nests
102  !**********************************************
103
104  call gridcheck
105  !call gridcheck_nests ! NORESM VERSION NESTING OF INPUT NOT ACTIVATED : comment by  mc
106
107
108  ! Read the output grid specifications
109  !************************************
110
111  call readoutgrid
112  if (nested_output.eq.1) call readoutgrid_nest
113
114
115  ! Read the receptor points for which extra concentrations are to be calculated
116  !*****************************************************************************
117
118  call readreceptors
119
120
121  ! Read the physico-chemical species property table
122  !*************************************************
123  !SEC: now only needed SPECIES are read in readreleases.f
124  !call readspecies
125
126
127  ! Read the landuse inventory
128  !***************************
129
130  call readlanduse
131
132
133  ! Assign fractional cover of landuse classes to each grid point
134  !********************************************************************
135
136  call assignland
137
138
139
140  ! Read the coordinates of the release locations
141  !**********************************************
142
143  call readreleases
144
145  ! Read and compute surface resistances to dry deposition of gases
146  !****************************************************************
147
148  call readdepo
149
150
151  ! Convert the release point coordinates from geografical to grid coordinates
152  !***************************************************************************
153
154  call coordtrafo
155
156
157  ! Initialize all particles to non-existent
158  !*****************************************
159
160  do j=1,maxpart
161    itra1(j)=-999999999
162  end do
163
164  ! For continuation of previous run, read in particle positions
165  !*************************************************************
166
167  if (ipin.eq.1) then
168    call readpartpositions
169  else
170    numpart=0
171    numparticlecount=0
172  endif
173
174
175  ! Calculate volume, surface area, etc., of all output grid cells
176  ! Allocate fluxes and OHfield if necessary
177  !***************************************************************
178
179  call outgrid_init
180  if (nested_output.eq.1) call outgrid_init_nest
181
182
183  ! Read the OH field
184  !******************
185
186  if (OHREA.eqv..TRUE.) &
187       call readOHfield
188
189  ! Write basic information on the simulation to a file "header"
190  ! and open files that are to be kept open throughout the simulation
191  !******************************************************************
192
193  call writeheader
194  if (nested_output.eq.1) call writeheader_nest
195  open(unitdates,file=path(2)(1:length(2))//'dates')
196  call openreceptors
197  if ((iout.eq.4).or.(iout.eq.5)) call openouttraj
198
199
200  ! Releases can only start and end at discrete times (multiples of lsynctime)
201  !***************************************************************************
202
203  do i=1,numpoint
204    ireleasestart(i)=nint(real(ireleasestart(i))/ &
205         real(lsynctime))*lsynctime
206    ireleaseend(i)=nint(real(ireleaseend(i))/ &
207         real(lsynctime))*lsynctime
208  end do
209
210
211  ! Initialize cloud-base mass fluxes for the convection scheme
212  !************************************************************
213
214  do jy=0,nymin1
215    do ix=0,nxmin1
216      cbaseflux(ix,jy)=0.
217    end do
218  end do
219  do inest=1,numbnests
220    do jy=0,nyn(inest)-1
221      do ix=0,nxn(inest)-1
222        cbasefluxn(ix,jy,inest)=0.
223      end do
224    end do
225  end do
226
227
228  ! Calculate particle trajectories
229  !********************************
230
231  call timemanager
232
233
234  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLE&
235       &XPART MODEL RUN!'
236
237end program flexpart_NorESM
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG