source: flexpart.git/src/outgrid_init_nest.f90 @ 0ecc1fe

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 0ecc1fe was 0ecc1fe, checked in by Espen Sollum ATMOS <eso@…>, 6 years ago

Changed handling of nested input fields to be consistent with non-nested

  • Property mode set to 100644
File size: 9.2 KB
Line 
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
22subroutine outgrid_init_nest
23
24!*****************************************************************************
25!                                                                            *
26!  This routine calculates, for each grid cell of the output nest, the       *
27!  volume and the surface area.                                              *
28!                                                                            *
29!     Author: A. Stohl                                                       *
30!                                                                            *
31!    30 August 2004                                                          *
32!                                                                            *
33!*****************************************************************************
34!                                                                            *
35! Variables:                                                                 *
36!                                                                            *
37! arean              surface area of all output nest cells                   *
38! volumen            volumes of all output nest cells                        *
39!                                                                            *
40!*****************************************************************************
41
42  use unc_mod
43  use outg_mod
44  use par_mod
45  use com_mod
46
47  implicit none
48
49  integer :: ix,jy,kz,ks,kp,nage,l,iix,jjy,ixp,jyp,i1,j1,j,ngrid
50  integer :: stat
51  real :: ylat,gridarea,ylatp,ylatm,hzone,cosfactm,cosfactp
52  real :: xlon,xl,yl,ddx,ddy,rddx,rddy,p1,p2,p3,p4,xtn,ytn,oroh
53  real,parameter :: eps=nxmax/3.e5
54
55
56
57! gridunc,griduncn        uncertainty of outputted concentrations
58  allocate(griduncn(0:numxgridn-1,0:numygridn-1,numzgrid,maxspec, &
59       maxpointspec_act,nclassunc,maxageclass),stat=stat)
60  if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
61
62  if (ldirect.gt.0) then
63    allocate(wetgriduncn(0:numxgridn-1,0:numygridn-1,maxspec, &
64         maxpointspec_act,nclassunc,maxageclass),stat=stat)
65    if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
66    allocate(drygriduncn(0:numxgridn-1,0:numygridn-1,maxspec, &
67         maxpointspec_act,nclassunc,maxageclass),stat=stat)
68    if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
69  endif
70
71#ifdef USE_MPIINPLACE
72#else
73! Extra field for totals at MPI root process
74  if (lroot.and.mpi_mode.gt.0) then
75! If MPI_IN_PLACE option is not used in mpi_mod.f90::mpif_tm_reduce_grid_nest(),
76! then an aux array is needed for parallel grid reduction
77    allocate(griduncn0(0:numxgridn-1,0:numygridn-1,numzgrid,maxspec, &
78         maxpointspec_act,nclassunc,maxageclass),stat=stat)
79    if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
80! allocate a dummy to avoid compilator complaints
81  else if (.not.lroot.and.mpi_mode.gt.0) then
82    allocate(griduncn0(1,1,1,1,1,1,1),stat=stat)
83  end if
84#endif
85!    if (ldirect.gt.0) then
86  if (lroot.and.mpi_mode.gt.0) then
87    allocate(wetgriduncn0(0:numxgridn-1,0:numygridn-1,maxspec, &
88         maxpointspec_act,nclassunc,maxageclass),stat=stat)
89    if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
90    allocate(drygriduncn0(0:numxgridn-1,0:numygridn-1,maxspec, &
91         maxpointspec_act,nclassunc,maxageclass),stat=stat)
92    if (stat.ne.0) write(*,*)'ERROR:could not allocate nested gridunc'
93!  endif
94! allocate a dummy to avoid compilator complaints
95  else if (.not.lroot.and.mpi_mode.gt.0) then
96    allocate(wetgriduncn0(1,1,1,1,1,1),stat=stat)
97    allocate(drygriduncn0(1,1,1,1,1,1),stat=stat)
98  end if
99
100! Compute surface area and volume of each grid cell: area, volume;
101! and the areas of the northward and eastward facing walls: areaeast, areanorth
102!***********************************************************************
103
104  do jy=0,numygridn-1
105    ylat=outlat0n+(real(jy)+0.5)*dyoutn
106    ylatp=ylat+0.5*dyoutn
107    ylatm=ylat-0.5*dyoutn
108    if ((ylatm.lt.0).and.(ylatp.gt.0.)) then
109      hzone=dyoutn*r_earth*pi180
110    else
111
112! Calculate area of grid cell with formula M=2*pi*R*h*dx/360,
113! see Netz, Formeln der Mathematik, 5. Auflage (1983), p.90
114!************************************************************
115
116      cosfactp=cos(ylatp*pi180)
117      cosfactm=cos(ylatm*pi180)
118      if (cosfactp.lt.cosfactm) then
119        hzone=sqrt(1-cosfactp**2)- &
120             sqrt(1-cosfactm**2)
121        hzone=hzone*r_earth
122      else
123        hzone=sqrt(1-cosfactm**2)- &
124             sqrt(1-cosfactp**2)
125        hzone=hzone*r_earth
126      endif
127    endif
128
129
130
131! Surface are of a grid cell at a latitude ylat
132!**********************************************
133
134    gridarea=2.*pi*r_earth*hzone*dxoutn/360.
135
136    do ix=0,numxgridn-1
137      arean(ix,jy)=gridarea
138
139! Volume = area x box height
140!***************************
141
142      volumen(ix,jy,1)=arean(ix,jy)*outheight(1)
143      do kz=2,numzgrid
144        volumen(ix,jy,kz)=arean(ix,jy)*(outheight(kz)-outheight(kz-1))
145      end do
146    end do
147  end do
148
149
150!**************************************************************************
151! Determine average height of model topography in nesteed output grid cells
152!**************************************************************************
153
154! Loop over all output grid cells
155!********************************
156
157  do jjy=0,numygridn-1
158    do iix=0,numxgridn-1
159      oroh=0.
160
161! Take 100 samples of the topography in every grid cell
162!******************************************************
163
164      do j1=1,10
165        ylat=outlat0n+(real(jjy)+real(j1)/10.-0.05)*dyoutn
166        yl=(ylat-ylat0)/dy
167        do i1=1,10
168          xlon=outlon0n+(real(iix)+real(i1)/10.-0.05)*dxoutn
169          xl=(xlon-xlon0)/dx
170
171! Determine the nest we are in
172!*****************************
173
174          ngrid=0
175          do j=numbnests,1,-1
176            if ((xl.gt.xln(j)+eps).and.(xl.lt.xrn(j)-eps).and. &
177                 (yl.gt.yln(j)+eps).and.(yl.lt.yrn(j)-eps)) then
178              ngrid=j
179              goto 43
180            endif
181          end do
18243        continue
183
184! Determine (nested) grid coordinates and auxiliary parameters used for interpolation
185!*****************************************************************************
186
187          if (ngrid.gt.0) then
188            xtn=(xl-xln(ngrid))*xresoln(ngrid)
189            ytn=(yl-yln(ngrid))*yresoln(ngrid)
190            ix=int(xtn)
191            jy=int(ytn)
192            ddy=ytn-real(jy)
193            ddx=xtn-real(ix)
194          else
195            ix=int(xl)
196            jy=int(yl)
197            ddy=yl-real(jy)
198            ddx=xl-real(ix)
199          endif
200          ixp=ix+1
201          jyp=jy+1
202          rddx=1.-ddx
203          rddy=1.-ddy
204          p1=rddx*rddy
205          p2=ddx*rddy
206          p3=rddx*ddy
207          p4=ddx*ddy
208
209          if (ngrid.gt.0) then
210            oroh=oroh+p1*oron(ix ,jy ,ngrid) &
211                 + p2*oron(ixp,jy ,ngrid) &
212                 + p3*oron(ix ,jyp,ngrid) &
213                 + p4*oron(ixp,jyp,ngrid)
214          else
215            oroh=oroh+p1*oro(ix ,jy) &
216                 + p2*oro(ixp,jy) &
217                 + p3*oro(ix ,jyp) &
218                 + p4*oro(ixp,jyp)
219          endif
220        end do
221      end do
222
223! Divide by the number of samples taken
224!**************************************
225
226      orooutn(iix,jjy)=oroh/100.
227    end do
228  end do
229
230
231
232!*******************************
233! Initialization of output grids
234!*******************************
235
236  do kp=1,maxpointspec_act
237    do ks=1,nspec
238      do nage=1,nageclass
239        do jy=0,numygridn-1
240          do ix=0,numxgridn-1
241            do l=1,nclassunc
242! Deposition fields
243              if (ldirect.gt.0) then
244                wetgriduncn(ix,jy,ks,kp,l,nage)=0.
245                drygriduncn(ix,jy,ks,kp,l,nage)=0.
246              endif
247! Concentration fields
248              do kz=1,numzgrid
249                griduncn(ix,jy,kz,ks,kp,l,nage)=0.
250              end do
251            end do
252          end do
253        end do
254      end do
255    end do
256  end do
257
258
259end subroutine outgrid_init_nest
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG