source: flexpart.git/src/outgrid_init_nest.f90 @ 3481cc1

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 3481cc1 was 3481cc1, checked in by Ignacio Pisso <ip@…>, 4 years ago

move license from headers to a different file

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