source: flexpart.git/src/concoutput.f90 @ 6b22af9

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

Local branch for espen, working with OpenMP version of readwind

  • Property mode set to 100644
File size: 23.3 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 concoutput(itime,outnum,gridtotalunc,wetgridtotalunc, &
23     drygridtotalunc)
24!                        i     i          o             o
25!       o
26!*****************************************************************************
27!                                                                            *
28!     Output of the concentration grid and the receptor concentrations.      *
29!                                                                            *
30!     Author: A. Stohl                                                       *
31!                                                                            *
32!     24 May 1995                                                            *
33!                                                                            *
34!     13 April 1999, Major update: if output size is smaller, dump output    *
35!                    in sparse matrix format; additional output of           *
36!                    uncertainty                                             *
37!                                                                            *
38!     05 April 2000, Major update: output of age classes; output for backward*
39!                    runs is time spent in grid cell times total mass of     *
40!                    species.                                                *
41!                                                                            *
42!     17 February 2002, Appropriate dimensions for backward and forward runs *
43!                       are now specified in file par_mod                    *
44!                                                                            *
45!     June 2006, write grid in sparse matrix with a single write command     *
46!                in order to save disk space                                 *
47!                                                                            *
48!     2008 new sparse matrix format                                          *
49!                                                                            *
50!*****************************************************************************
51!                                                                            *
52! Variables:                                                                 *
53! outnum          number of samples                                          *
54! ncells          number of cells with non-zero concentrations               *
55! sparse          .true. if in sparse matrix format, else .false.            *
56! tot_mu          1 for forward, initial mass mixing ration for backw. runs  *
57!                                                                            *
58!*****************************************************************************
59
60  use unc_mod
61  use point_mod
62  use outg_mod
63  use par_mod
64  use com_mod
65
66  implicit none
67
68  real(kind=dp) :: jul
69  integer :: itime,i,ix,jy,kz,ks,kp,l,iix,jjy,kzz,nage,jjjjmmdd,ihmmss
70  integer :: sp_count_i,sp_count_r
71  real :: sp_fact
72  real :: outnum,densityoutrecept(maxreceptor),xl,yl
73
74!real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
75!    +grid(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec,maxpointspec_act,
76!    +    maxageclass)
77!real wetgrid(0:numxgrid-1,0:numygrid-1,maxspec,maxpointspec_act,
78!    +       maxageclass)
79!real drygrid(0:numxgrid-1,0:numygrid-1,maxspec,
80!    +       maxpointspec_act,maxageclass)
81!real gridsigma(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec,
82!    +       maxpointspec_act,maxageclass),
83!    +     drygridsigma(0:numxgrid-1,0:numygrid-1,maxspec,
84!    +     maxpointspec_act,maxageclass),
85!    +     wetgridsigma(0:numxgrid-1,0:numygrid-1,maxspec,
86!    +     maxpointspec_act,maxageclass)
87!real factor(0:numxgrid-1,0:numygrid-1,numzgrid)
88!real sparse_dump_r(numxgrid*numygrid*numzgrid)
89!integer sparse_dump_i(numxgrid*numygrid*numzgrid)
90
91!real sparse_dump_u(numxgrid*numygrid*numzgrid)
92  real :: auxgrid(nclassunc),gridtotal,gridsigmatotal,gridtotalunc
93  real :: wetgridtotal,wetgridsigmatotal,wetgridtotalunc
94  real :: drygridtotal,drygridsigmatotal,drygridtotalunc
95  real :: halfheight,dz,dz1,dz2,tot_mu(maxspec,maxpointspec_act)
96  real,parameter :: smallnum = tiny(0.0) ! smallest number that can be handled
97  real,parameter :: weightair=28.97
98  logical :: sp_zer
99  logical,save :: init=.true.
100  character :: adate*8,atime*6
101  character(len=3) :: anspec
102  integer :: mind
103! mind        eso:added to ensure identical results between 2&3-fields versions
104  character(LEN=8),save :: file_stat='REPLACE'
105  logical :: ldates_file
106  integer :: ierr
107  character(LEN=100) :: dates_char
108
109! Determine current calendar date, needed for the file name
110!**********************************************************
111
112  jul=bdate+real(itime,kind=dp)/86400._dp
113  call caldate(jul,jjjjmmdd,ihmmss)
114  write(adate,'(i8.8)') jjjjmmdd
115  write(atime,'(i6.6)') ihmmss
116
117! Overwrite existing dates file on first call, later append to it
118! This fixes a bug where the dates file kept growing across multiple runs
119
120! If 'dates' file exists in output directory, make a backup
121  inquire(file=path(2)(1:length(2))//'dates', exist=ldates_file)
122  if (ldates_file.and.init) then
123    open(unit=unitdates, file=path(2)(1:length(2))//'dates',form='formatted', &
124         &access='sequential', status='old', action='read', iostat=ierr)
125    open(unit=unittmp, file=path(2)(1:length(2))//'dates.bak', access='sequential', &
126         &status='replace', action='write', form='formatted', iostat=ierr)
127    do while (.true.)
128      read(unitdates, '(a)', iostat=ierr) dates_char
129      if (ierr.ne.0) exit
130      write(unit=unittmp, fmt='(a)', iostat=ierr, advance='yes') trim(dates_char)
131    end do
132    close(unit=unitdates)
133    close(unit=unittmp)
134  end if
135
136  open(unitdates,file=path(2)(1:length(2))//'dates', ACCESS='APPEND', STATUS=file_stat)
137  write(unitdates,'(a)') adate//atime
138  close(unitdates) 
139
140  IF (init) THEN
141    file_stat='OLD'
142    init=.false.
143  END IF
144
145
146! For forward simulations, output fields have dimension MAXSPEC,
147! for backward simulations, output fields have dimension MAXPOINT.
148! Thus, make loops either about nspec, or about numpoint
149!*****************************************************************
150
151
152  if (ldirect.eq.1) then
153    do ks=1,nspec
154      do kp=1,maxpointspec_act
155        tot_mu(ks,kp)=1
156      end do
157    end do
158  else
159    do ks=1,nspec
160      do kp=1,maxpointspec_act
161        tot_mu(ks,kp)=xmass(kp,ks)
162      end do
163    end do
164  endif
165
166
167!*******************************************************************
168! Compute air density: sufficiently accurate to take it
169! from coarse grid at some time
170! Determine center altitude of output layer, and interpolate density
171! data to that altitude
172!*******************************************************************
173
174  mind=memind(2)
175  do kz=1,numzgrid
176    if (kz.eq.1) then
177      halfheight=outheight(1)/2.
178    else
179      halfheight=(outheight(kz)+outheight(kz-1))/2.
180    endif
181    do kzz=2,nz
182      if ((height(kzz-1).lt.halfheight).and. &
183           (height(kzz).gt.halfheight)) goto 46
184    end do
18546  kzz=max(min(kzz,nz),2)
186    dz1=halfheight-height(kzz-1)
187    dz2=height(kzz)-halfheight
188    dz=dz1+dz2
189    do jy=0,numygrid-1
190      do ix=0,numxgrid-1
191        xl=outlon0+real(ix)*dxout
192        yl=outlat0+real(jy)*dyout
193        xl=(xl-xlon0)/dx
194        yl=(yl-ylat0)/dy !v9.1.1
195        iix=max(min(nint(xl),nxmin1),0)
196        jjy=max(min(nint(yl),nymin1),0)
197! densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
198!      rho(iix,jjy,kzz-1,2)*dz2)/dz
199        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
200             rho(iix,jjy,kzz-1,mind)*dz2)/dz
201      end do
202    end do
203  end do
204
205  do i=1,numreceptor
206    xl=xreceptor(i)
207    yl=yreceptor(i)
208    iix=max(min(nint(xl),nxmin1),0)
209    jjy=max(min(nint(yl),nymin1),0)
210!densityoutrecept(i)=rho(iix,jjy,1,2)
211    densityoutrecept(i)=rho(iix,jjy,1,mind)
212  end do
213
214
215! Output is different for forward and backward simulations
216  do kz=1,numzgrid
217    do jy=0,numygrid-1
218      do ix=0,numxgrid-1
219        if (ldirect.eq.1) then
220          factor3d(ix,jy,kz)=1.e12/volume(ix,jy,kz)/outnum
221        else
222          factor3d(ix,jy,kz)=real(abs(loutaver))/outnum
223        endif
224      end do
225    end do
226  end do
227
228!*********************************************************************
229! Determine the standard deviation of the mean concentration or mixing
230! ratio (uncertainty of the output) and the dry and wet deposition
231!*********************************************************************
232
233  gridtotal=0.
234  gridsigmatotal=0.
235  gridtotalunc=0.
236  wetgridtotal=0.
237  wetgridsigmatotal=0.
238  wetgridtotalunc=0.
239  drygridtotal=0.
240  drygridsigmatotal=0.
241  drygridtotalunc=0.
242
243  do ks=1,nspec
244
245    write(anspec,'(i3.3)') ks
246    if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
247      if (ldirect.eq.1) then
248        open(unitoutgrid,file=path(2)(1:length(2))//'grid_conc_'//adate// &
249             atime//'_'//anspec,form='unformatted')
250      else
251        open(unitoutgrid,file=path(2)(1:length(2))//'grid_time_'//adate// &
252             atime//'_'//anspec,form='unformatted')
253      endif
254      write(unitoutgrid) itime
255    endif
256
257    if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
258      open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_'//adate// &
259           atime//'_'//anspec,form='unformatted')
260
261      write(unitoutgridppt) itime
262    endif
263
264    do kp=1,maxpointspec_act
265      do nage=1,nageclass
266
267        do jy=0,numygrid-1
268          do ix=0,numxgrid-1
269
270! WET DEPOSITION
271            if ((WETDEP).and.(ldirect.gt.0)) then
272              do l=1,nclassunc
273                auxgrid(l)=wetgridunc(ix,jy,ks,kp,l,nage)
274              end do
275              call mean(auxgrid,wetgrid(ix,jy), &
276                   wetgridsigma(ix,jy),nclassunc)
277! Multiply by number of classes to get total concentration
278              wetgrid(ix,jy)=wetgrid(ix,jy) &
279                   *nclassunc
280              wetgridtotal=wetgridtotal+wetgrid(ix,jy)
281! Calculate standard deviation of the mean
282              wetgridsigma(ix,jy)= &
283                   wetgridsigma(ix,jy)* &
284                   sqrt(real(nclassunc))
285              wetgridsigmatotal=wetgridsigmatotal+ &
286                   wetgridsigma(ix,jy)
287            endif
288
289! DRY DEPOSITION
290            if ((DRYDEP).and.(ldirect.gt.0)) then
291              do l=1,nclassunc
292                auxgrid(l)=drygridunc(ix,jy,ks,kp,l,nage)
293              end do
294              call mean(auxgrid,drygrid(ix,jy), &
295                   drygridsigma(ix,jy),nclassunc)
296! Multiply by number of classes to get total concentration
297              drygrid(ix,jy)=drygrid(ix,jy)* &
298                   nclassunc
299              drygridtotal=drygridtotal+drygrid(ix,jy)
300! Calculate standard deviation of the mean
301              drygridsigma(ix,jy)= &
302                   drygridsigma(ix,jy)* &
303                   sqrt(real(nclassunc))
304125           drygridsigmatotal=drygridsigmatotal+ &
305                   drygridsigma(ix,jy)
306            endif
307
308! CONCENTRATION OR MIXING RATIO
309            do kz=1,numzgrid
310              do l=1,nclassunc
311                auxgrid(l)=gridunc(ix,jy,kz,ks,kp,l,nage)
312              end do
313              call mean(auxgrid,grid(ix,jy,kz), &
314                   gridsigma(ix,jy,kz),nclassunc)
315! Multiply by number of classes to get total concentration
316              grid(ix,jy,kz)= &
317                   grid(ix,jy,kz)*nclassunc
318              gridtotal=gridtotal+grid(ix,jy,kz)
319! Calculate standard deviation of the mean
320              gridsigma(ix,jy,kz)= &
321                   gridsigma(ix,jy,kz)* &
322                   sqrt(real(nclassunc))
323              gridsigmatotal=gridsigmatotal+ &
324                   gridsigma(ix,jy,kz)
325            end do
326          end do
327        end do
328
329
330
331
332!*******************************************************************
333! Generate output: may be in concentration (ng/m3) or in mixing
334! ratio (ppt) or both
335! Output the position and the values alternated multiplied by
336! 1 or -1, first line is number of values, number of positions
337! For backward simulations, the unit is seconds, stored in grid_time
338!*******************************************************************
339
340! Concentration output
341!*********************
342        if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
343
344! Wet deposition
345          sp_count_i=0
346          sp_count_r=0
347          sp_fact=-1.
348          sp_zer=.true.
349          if ((ldirect.eq.1).and.(WETDEP)) then
350            do jy=0,numygrid-1
351              do ix=0,numxgrid-1
352!oncentraion greater zero
353                if (wetgrid(ix,jy).gt.smallnum) then
354                  if (sp_zer.eqv..true.) then ! first non zero value
355                    sp_count_i=sp_count_i+1
356                    sparse_dump_i(sp_count_i)=ix+jy*numxgrid
357                    sp_zer=.false.
358                    sp_fact=sp_fact*(-1.)
359                  endif
360                  sp_count_r=sp_count_r+1
361                  sparse_dump_r(sp_count_r)= &
362                       sp_fact*1.e12*wetgrid(ix,jy)/area(ix,jy)
363!                sparse_dump_u(sp_count_r)=
364!+                1.e12*wetgridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
365                else ! concentration is zero
366                  sp_zer=.true.
367                endif
368              end do
369            end do
370          else
371            sp_count_i=0
372            sp_count_r=0
373          endif
374          write(unitoutgrid) sp_count_i
375          write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
376          write(unitoutgrid) sp_count_r
377          write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
378!       write(unitoutgrid) sp_count_u
379!       write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
380
381! Dry deposition
382          sp_count_i=0
383          sp_count_r=0
384          sp_fact=-1.
385          sp_zer=.true.
386          if ((ldirect.eq.1).and.(DRYDEP)) then
387            do jy=0,numygrid-1
388              do ix=0,numxgrid-1
389                if (drygrid(ix,jy).gt.smallnum) then
390                  if (sp_zer.eqv..true.) then ! first non zero value
391                    sp_count_i=sp_count_i+1
392                    sparse_dump_i(sp_count_i)=ix+jy*numxgrid
393                    sp_zer=.false.
394                    sp_fact=sp_fact*(-1.)
395                  endif
396                  sp_count_r=sp_count_r+1
397                  sparse_dump_r(sp_count_r)= &
398                       sp_fact* &
399                       1.e12*drygrid(ix,jy)/area(ix,jy)
400!                sparse_dump_u(sp_count_r)=
401!+                1.e12*drygridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
402                else ! concentration is zero
403                  sp_zer=.true.
404                endif
405              end do
406            end do
407          else
408            sp_count_i=0
409            sp_count_r=0
410          endif
411          write(unitoutgrid) sp_count_i
412          write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
413          write(unitoutgrid) sp_count_r
414          write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
415!       write(*,*) sp_count_u
416!       write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
417
418
419
420! Concentrations
421          sp_count_i=0
422          sp_count_r=0
423          sp_fact=-1.
424          sp_zer=.true.
425          do kz=1,numzgrid
426            do jy=0,numygrid-1
427              do ix=0,numxgrid-1
428                if (grid(ix,jy,kz).gt.smallnum) then
429                  if (sp_zer.eqv..true.) then ! first non zero value
430                    sp_count_i=sp_count_i+1
431                    sparse_dump_i(sp_count_i)= &
432                         ix+jy*numxgrid+kz*numxgrid*numygrid
433                    sp_zer=.false.
434                    sp_fact=sp_fact*(-1.)
435                  endif
436                  sp_count_r=sp_count_r+1
437                  sparse_dump_r(sp_count_r)= &
438                       sp_fact* &
439                       grid(ix,jy,kz)* &
440                       factor3d(ix,jy,kz)/tot_mu(ks,kp)
441!                 if ((factor(ix,jy,kz)/tot_mu(ks,kp)).eq.0)
442!    +              write (*,*) factor(ix,jy,kz),tot_mu(ks,kp),ks,kp
443!                sparse_dump_u(sp_count_r)=
444!+               ,gridsigma(ix,jy,kz,ks,kp,nage)*
445!+               factor(ix,jy,kz)/tot_mu(ks,kp)
446                else ! concentration is zero
447                  sp_zer=.true.
448                endif
449              end do
450            end do
451          end do
452          write(unitoutgrid) sp_count_i
453          write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
454          write(unitoutgrid) sp_count_r
455          write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
456!       write(unitoutgrid) sp_count_u
457!       write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
458
459
460
461        endif !  concentration output
462
463! Mixing ratio output
464!********************
465
466        if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
467
468! Wet deposition
469          sp_count_i=0
470          sp_count_r=0
471          sp_fact=-1.
472          sp_zer=.true.
473          if ((ldirect.eq.1).and.(WETDEP)) then
474            do jy=0,numygrid-1
475              do ix=0,numxgrid-1
476                if (wetgrid(ix,jy).gt.smallnum) then
477                  if (sp_zer.eqv..true.) then ! first non zero value
478                    sp_count_i=sp_count_i+1
479                    sparse_dump_i(sp_count_i)= &
480                         ix+jy*numxgrid
481                    sp_zer=.false.
482                    sp_fact=sp_fact*(-1.)
483                  endif
484                  sp_count_r=sp_count_r+1
485                  sparse_dump_r(sp_count_r)= &
486                       sp_fact* &
487                       1.e12*wetgrid(ix,jy)/area(ix,jy)
488!                sparse_dump_u(sp_count_r)=
489!    +            ,1.e12*wetgridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
490                else ! concentration is zero
491                  sp_zer=.true.
492                endif
493              end do
494            end do
495          else
496            sp_count_i=0
497            sp_count_r=0
498          endif
499          write(unitoutgridppt) sp_count_i
500          write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
501          write(unitoutgridppt) sp_count_r
502          write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
503!       write(unitoutgridppt) sp_count_u
504!       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
505
506
507! Dry deposition
508          sp_count_i=0
509          sp_count_r=0
510          sp_fact=-1.
511          sp_zer=.true.
512          if ((ldirect.eq.1).and.(DRYDEP)) then
513            do jy=0,numygrid-1
514              do ix=0,numxgrid-1
515                if (drygrid(ix,jy).gt.smallnum) then
516                  if (sp_zer.eqv..true.) then ! first non zero value
517                    sp_count_i=sp_count_i+1
518                    sparse_dump_i(sp_count_i)= &
519                         ix+jy*numxgrid
520                    sp_zer=.false.
521                    sp_fact=sp_fact*(-1)
522                  endif
523                  sp_count_r=sp_count_r+1
524                  sparse_dump_r(sp_count_r)= &
525                       sp_fact* &
526                       1.e12*drygrid(ix,jy)/area(ix,jy)
527!                sparse_dump_u(sp_count_r)=
528!    +            ,1.e12*drygridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
529                else ! concentration is zero
530                  sp_zer=.true.
531                endif
532              end do
533            end do
534          else
535            sp_count_i=0
536            sp_count_r=0
537          endif
538          write(unitoutgridppt) sp_count_i
539          write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
540          write(unitoutgridppt) sp_count_r
541          write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
542!       write(unitoutgridppt) sp_count_u
543!       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
544
545
546! Mixing ratios
547          sp_count_i=0
548          sp_count_r=0
549          sp_fact=-1.
550          sp_zer=.true.
551          do kz=1,numzgrid
552            do jy=0,numygrid-1
553              do ix=0,numxgrid-1
554                if (grid(ix,jy,kz).gt.smallnum) then
555                  if (sp_zer.eqv..true.) then ! first non zero value
556                    sp_count_i=sp_count_i+1
557                    sparse_dump_i(sp_count_i)= &
558                         ix+jy*numxgrid+kz*numxgrid*numygrid
559                    sp_zer=.false.
560                    sp_fact=sp_fact*(-1.)
561                  endif
562                  sp_count_r=sp_count_r+1
563                  sparse_dump_r(sp_count_r)= &
564                       sp_fact* &
565                       1.e12*grid(ix,jy,kz) &
566                       /volume(ix,jy,kz)/outnum* &
567                       weightair/weightmolar(ks)/densityoutgrid(ix,jy,kz)
568!                sparse_dump_u(sp_count_r)=
569!+              ,1.e12*gridsigma(ix,jy,kz,ks,kp,nage)/volume(ix,jy,kz)/
570!+              outnum*weightair/weightmolar(ks)/
571!+              densityoutgrid(ix,jy,kz)
572                else ! concentration is zero
573                  sp_zer=.true.
574                endif
575              end do
576            end do
577          end do
578          write(unitoutgridppt) sp_count_i
579          write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
580          write(unitoutgridppt) sp_count_r
581          write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
582!       write(unitoutgridppt) sp_count_u
583!       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
584
585        endif ! output for ppt
586
587      end do
588    end do
589
590    close(unitoutgridppt)
591    close(unitoutgrid)
592
593  end do
594
595  if (gridtotal.gt.0.) gridtotalunc=gridsigmatotal/gridtotal
596  if (wetgridtotal.gt.0.) wetgridtotalunc=wetgridsigmatotal/ &
597       wetgridtotal
598  if (drygridtotal.gt.0.) drygridtotalunc=drygridsigmatotal/ &
599       drygridtotal
600
601! Dump of receptor concentrations
602
603  if (numreceptor.gt.0 .and. (iout.eq.2 .or. iout.eq.3)  ) then
604    write(unitoutreceptppt) itime
605    do ks=1,nspec
606      write(unitoutreceptppt) (1.e12*creceptor(i,ks)/outnum* &
607           weightair/weightmolar(ks)/densityoutrecept(i),i=1,numreceptor)
608    end do
609  endif
610
611! Dump of receptor concentrations
612
613  if (numreceptor.gt.0) then
614    write(unitoutrecept) itime
615    do ks=1,nspec
616      write(unitoutrecept) (1.e12*creceptor(i,ks)/outnum, &
617           i=1,numreceptor)
618    end do
619  endif
620
621
622
623! Reinitialization of grid
624!*************************
625
626  do ks=1,nspec
627    do kp=1,maxpointspec_act
628      do i=1,numreceptor
629        creceptor(i,ks)=0.
630      end do
631      do jy=0,numygrid-1
632        do ix=0,numxgrid-1
633          do l=1,nclassunc
634            do nage=1,nageclass
635              do kz=1,numzgrid
636                gridunc(ix,jy,kz,ks,kp,l,nage)=0.
637              end do
638            end do
639          end do
640        end do
641      end do
642    end do
643  end do
644
645
646end subroutine concoutput
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG