source: branches/jerome/src_flexwrf_v3.1/outgrid_init_reg.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: 14.4 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
24      subroutine outgrid_init_reg()
25!*******************************************************************************
26!                                                                              *
27!     Note:  This is the FLEXPART_WRF version of subroutine outgrid_init.      *
28!            The computational grid is the WRF x-y grid rather than lat-lon.   *
29!                                                                              *
30!  This routine calculates, for each grid cell of the output grid, the         *
31!  volume, the surface area, and the areas of the northward and eastward       *
32!  facing surfaces.                                                            *
33!                                                                              *
34!     Author: A. Stohl                                                         *
35!                                                                              *
36!     7 August 2002                                                            *
37!                                                                              *
38!    26 Oct 2005, R. Easter - changes in gridarea, areaeast, areanorth         *
39!                             associated with WRF horizontal grid.             *
40!     Dec 2005, R. Easter - changed names of "*lon0*" & "*lat0*" variables     *
41!    July 2012, J. Brioude - modified for regular output grid                  *
42!*******************************************************************************
43!                                                                              *
44! Variables:                                                                   *
45!                                                                              *
46! area               surface area of all output grid cells                     *
47! areaeast           eastward facing wall area of all output grid cells        *
48! areanorth          northward facing wall area of all output grid cells       *
49! volume             volumes of all output grid cells                          *
50!                                                                              *
51!*******************************************************************************
52
53  use flux_mod
54  use oh_mod
55  use unc_mod
56  use outg_mod
57  use par_mod
58  use com_mod
59
60!      include 'includepar'
61!      include 'includecom'
62     implicit none
63      integer :: ix,jy,kz,k,i,nage,l,iix,jjy,ixp,jyp,i1,j1,j,ngrid
64      real :: ylat,gridarea,ylatp,ylatm,hzone,cosfact,cosfactm,cosfactp
65      real :: ymet,xlon   
66      real :: xmet,xl,yl,ddx,ddy,rddx,rddy,p1,p2,p3,p4,xtn,ytn,oroh
67  integer :: ks,kp,stat
68  real,parameter :: eps=nxmax/3.e5
69
70
71
72! Compute surface area and volume of each grid cell: area, volume;
73! and the areas of the northward and eastward facing walls: areaeast, areanorth
74!***********************************************************************
75
76      do jy=0,numygrid-1
77
78        ylat=outlat0+(float(jy)+0.5)*dyoutl
79        ylatp=ylat+0.5*dyoutl             
80        ylatm=ylat-0.5*dyoutl             
81        if ((ylatm.lt.0).and.(ylatp.gt.0.)) then   
82          hzone=dyoutl*r_earth*pi180         
83        else                 
84          cosfact=cos(ylat*pi180)*r_earth         
85          cosfactp=cos(ylatp*pi180)*r_earth       
86          cosfactm=cos(ylatm*pi180)*r_earth     
87          if (cosfactp.lt.cosfactm) then         
88            hzone=sqrt(r_earth**2-cosfactp**2)-  &
89            sqrt(r_earth**2-cosfactm**2)
90          else
91            hzone=sqrt(r_earth**2-cosfactm**2)- &
92            sqrt(r_earth**2-cosfactp**2)
93          endif
94        endif
95!
96!C Surface are of a grid cell at a latitude ylat
97!***********************************************
98!
99         gridarea=2.*pi*r_earth*hzone*dxoutl/360.
100
101! for FLEXPART_WRF, dx & dy are in meters, and no cos(lat) is needed
102! ??? maybe should incorporate map factor here,
103!     and also for areaeast & areanorth ???
104!       gridarea=dxout*dyout
105
106        do ix=0,numxgrid-1
107          area(ix,jy)=gridarea
108! Volume = area x box height
109!***************************
110
111          volume(ix,jy,1)=area(ix,jy)*outheight(1)
112
113! for FLEXPART_WRF, dx & dy are in meters, and no cos(lat) is needed
114          areaeast(ix,jy,1)=dyoutl*r_earth*pi180*outheight(1)
115          areanorth(ix,jy,1)=cos(ylat*pi180)*dxoutl*r_earth*pi180* &
116          outheight(1)
117!         areaeast(ix,jy,1)=dyout*outheight(1)
118!         areanorth(ix,jy,1)=dxout*outheight(1)
119
120          do kz=2,numzgrid
121
122             areaeast(ix,jy,kz)=dyoutl*r_earth*pi180* &
123             (outheight(kz)-outheight(kz-1))
124             areanorth(ix,jy,kz)=cos(ylat*pi180)*dxoutl*r_earth*pi180* &
125             (outheight(kz)-outheight(kz-1))
126!           areaeast(ix,jy,kz)=dyout*(outheight(kz)-outheight(kz-1))
127!           areanorth(ix,jy,kz)=dxout*(outheight(kz)-outheight(kz-1))
128
129          volume(ix,jy,kz)=area(ix,jy)*(outheight(kz)-outheight(kz-1))
130      end do
131    end do
132  end do
133
134
135
136
137!******************************************************************
138! Determine average height of model topography in output grid cells
139!******************************************************************
140
141! Loop over all output grid cells
142!********************************
143
144      do jjy=0,numygrid-1
145        do iix=0,numxgrid-1
146          oroh=0.
147
148! Take 100 samples of the topography in every grid cell
149!******************************************************
150
151          do j1=1,10
152! for FLEXPART_WRF, x & y coords are in meters,
153! and the lon & lat variables below are in meters.
154            ylat=outlat0+(float(jjy)+float(j1)/10.-0.05)*dyoutl !in degrees
155!            ymet=out_ym0+(real(jjy)+real(j1)/10.-0.05)*dyout
156!            yl=(ymet-ymet0)/dy
157            do i1=1,10
158            xlon=outlon0+(float(iix)+float(i1)/10.-0.05)*dxoutl !in degrees
159        call ll_to_xymeter_wrf(xlon,ylat,xmet,ymet)
160           yl=(ymet-ymet0)/dy
161           xl=(xmet-xmet0)/dx
162
163!              xmet=out_xm0+(real(iix)+real(i1)/10.-0.05)*dxout
164!              xl=(xmet-xmet0)/dx
165
166! Determine the nest we are in
167!*****************************
168
169              ngrid=0
170              do j=numbnests,1,-1
171                if ((xl.gt.xln(j)).and.(xl.lt.xrn(j)).and. &
172                (yl.gt.yln(j)).and.(yl.lt.yrn(j))) then
173                  ngrid=j
174                  goto 43
175                endif
176          end do
17743            continue
178
179! Determine (nested) grid coordinates and auxiliary parameters used for interpolation
180!************************************************************************************
181
182              if (ngrid.gt.0) then
183                xtn=(xl-xln(ngrid))*xresoln(ngrid)
184                ytn=(yl-yln(ngrid))*yresoln(ngrid)
185                ix=int(xtn)
186                jy=int(ytn)
187                ddy=ytn-real(jy)
188                ddx=xtn-real(ix)
189              else
190                ix=int(xl)
191                jy=int(yl)
192                ddy=yl-real(jy)
193                ddx=xl-real(ix)
194              endif
195              ixp=ix+1
196              jyp=jy+1
197              rddx=1.-ddx
198              rddy=1.-ddy
199              p1=rddx*rddy
200              p2=ddx*rddy
201              p3=rddx*ddy
202              p4=ddx*ddy
203
204          if (ngrid.gt.0) then
205            oroh=oroh+p1*oron(ix ,jy ,ngrid) &
206                 + p2*oron(ixp,jy ,ngrid) &
207                 + p3*oron(ix ,jyp,ngrid) &
208                 + p4*oron(ixp,jyp,ngrid)
209          else
210            oroh=oroh+p1*oro(ix ,jy) &
211                 + p2*oro(ixp,jy) &
212                 + p3*oro(ix ,jyp) &
213                 + p4*oro(ixp,jyp)
214          endif
215        end do
216      end do
217
218! Divide by the number of samples taken
219!**************************************
220
221          oroout(iix,jjy)=oroh/100.
222    end do
223  end do
224
225
226  ! if necessary allocate flux fields
227  if (iflux.eq.1) then
228    allocate(flux(6,0:numxgrid-1,0:numygrid-1,numzgrid, &
229         1:nspec,1:maxpointspec_act,1:nageclass),stat=stat)
230    if (stat.ne.0) write(*,*)'ERROR: could not allocate flux array '
231  endif
232 
233  !write (*,*) 'allocating: in a sec',OHREA
234  if (OHREA.eqv..TRUE.) then
235  !   write (*,*) 'allocating: ',maxxOH,maxyOH,maxzOH
236    allocate(OH_field(12,0:maxxOH-1,0:maxyOH-1,maxzOH) &
237         ,stat=stat)
238    if (stat.ne.0) write(*,*)'ERROR: could not allocate OH array '
239    allocate(OH_field_height(7) &
240         ,stat=stat)
241    if (stat.ne.0) write(*,*)'ERROR: could not allocate OH array '
242  endif
243  ! gridunc,griduncn        uncertainty of outputted concentrations
244  allocate(gridunc(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec, &
245       maxpointspec_act,nclassunc,maxageclass),stat=stat)
246    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
247
248   print*,'alloc gridunc',numxgrid-1,numygrid-1,numzgrid,maxspec, &
249          maxpointspec_act,nclassunc,maxageclass
250  if (ldirect.gt.0) then
251  allocate(wetgridunc(0:numxgrid-1,0:numygrid-1,maxspec, &
252       maxpointspec_act,nclassunc,maxageclass),stat=stat)
253    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
254  allocate(drygridunc(0:numxgrid-1,0:numygrid-1,maxspec, &
255       maxpointspec_act,nclassunc,maxageclass),stat=stat)
256    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
257  allocate(drygridunc2(0:numxgrid-1,0:numygrid-1,maxspec, &
258       maxpointspec_act,nclassunc,maxageclass),stat=stat)
259  endif
260  !write (*,*) 'Dimensions for fields', numxgrid,numygrid, &
261  !     maxspec,maxpointspec_act,nclassunc,maxageclass
262
263  write (*,*) ' Allocating fields for nested and global output (x,y): ', &
264       max(numxgrid,numxgridn),max(numygrid,numygridn)
265
266  ! allocate fields for concoutput with maximum dimension of outgrid
267  ! and outgrid_nest
268  allocate(gridsigma(0:max(numxgrid,numxgridn)-1, &
269       0:max(numygrid,numygridn)-1,numzgrid),stat=stat)
270    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
271  allocate(grid(0:max(numxgrid,numxgridn)-1, &
272       0:max(numygrid,numygridn)-1,numzgrid),stat=stat)
273  allocate(grid2(0:max(numxgrid,numxgridn)-1, &
274       0:max(numygrid,numygridn)-1,numzgrid,maxpointspec_act),stat=stat)
275  allocate(grid3(0:max(numxgrid,numxgridn)-1, &
276       0:max(numygrid,numygridn)-1,numzgrid,maxpointspec_act),stat=stat)
277    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
278  allocate(densityoutgrid(0:max(numxgrid,numxgridn)-1, &
279       0:max(numygrid,numygridn)-1,numzgrid),stat=stat)
280    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
281
282  allocate(factor3d(0:max(numxgrid,numxgridn)-1, &
283       0:max(numygrid,numygridn)-1,numzgrid),stat=stat)
284    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
285  allocate(sparse_dump_r(max(numxgrid,numxgridn)* &
286       max(numygrid,numygridn)*numzgrid),stat=stat)
287    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
288  allocate(sparse_dump_i(max(numxgrid,numxgridn)* &
289       max(numygrid,numygridn)*numzgrid),stat=stat)
290    if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
291
292  ! deposition fields are only allocated for forward runs
293  if (ldirect.gt.0) then
294     allocate(wetgridsigma(0:max(numxgrid,numxgridn)-1, &
295          0:max(numygrid,numygridn)-1),stat=stat)
296     if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
297     allocate(drygridsigma(0:max(numxgrid,numxgridn)-1, &
298          0:max(numygrid,numygridn)-1),stat=stat)
299     if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
300     allocate(wetgrid(0:max(numxgrid,numxgridn)-1, &
301          0:max(numygrid,numygridn)-1),stat=stat)
302     allocate(wetgrid2(0:max(numxgrid,numxgridn)-1, &
303          0:max(numygrid,numygridn)-1,maxpointspec_act),stat=stat)
304     if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
305     allocate(drygrid(0:max(numxgrid,numxgridn)-1, &
306          0:max(numygrid,numygridn)-1),stat=stat)
307     allocate(drygrid2(0:max(numxgrid,numxgridn)-1, &
308          0:max(numygrid,numygridn)-1,maxpointspec_act),stat=stat)
309     if (stat.ne.0) write(*,*)'ERROR: could not allocate gridunc'
310  endif
311
312  ! Initial condition field
313
314  if (linit_cond.gt.0) then
315    allocate(init_cond(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec, &
316         maxpointspec_act),stat=stat)
317    if (stat.ne.0) write(*,*)'ERROR: could not allocate init_cond'
318  endif
319
320  !************************
321  ! Initialize output grids
322  !************************
323
324  do ks=1,nspec
325  do kp=1,maxpointspec_act
326    do i=1,numreceptor
327  ! Receptor points
328      creceptor(i,ks)=0.
329    end do
330    do nage=1,nageclass
331      do jy=0,numygrid-1
332        do ix=0,numxgrid-1
333          do l=1,nclassunc
334  ! Deposition fields
335            if (ldirect.gt.0) then
336            wetgridunc(ix,jy,ks,kp,l,nage)=0.
337            drygridunc(ix,jy,ks,kp,l,nage)=0.
338            endif
339            do kz=1,numzgrid
340              if (iflux.eq.1) then
341  ! Flux fields
342                 do i=1,5
343                   flux(i,ix,jy,kz,ks,kp,nage)=0.
344                 end do
345              endif
346  ! Initial condition field
347              if ((l.eq.1).and.(nage.eq.1).and.(linit_cond.gt.0)) &
348                   init_cond(ix,jy,kz,ks,kp)=0.
349  ! Concentration fields
350              gridunc(ix,jy,kz,ks,kp,l,nage)=0.
351            end do
352          end do
353        end do
354      end do
355    end do
356  end do
357  end do
358
359
360
361end subroutine outgrid_init_reg
362
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG