source: branches/jerome/src_flexwrf_v3.1/concoutput_nest_irreg.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: 23.6 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
24subroutine concoutput_nest_irreg(itime,outnum)
25  !                        i     i
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  !   JB: TO BE MODIFIED                                                       *
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)
93  real :: halfheight,dz,dz1,dz2,tot_mu(maxspec,maxpointspec_act)
94  real,parameter :: smallnum = tiny(0.0) ! smallest number that can be handled
95  ! real,parameter :: weightair=28.97 !AD: moved this to par_mod.f90
96  logical :: sp_zer
97  character :: adate*8,atime*6
98  character(len=3) :: anspec
99
100
101!     write(*,'(//a,a//)') &
102!         '*** Stopping in concoutput_nest ***', &
103!         '    This is not implemented for FLEXPART_WRF yet'
104!     stop
105
106  ! Determine current calendar date, needed for the file name
107  !**********************************************************
108
109  jul=bdate+real(itime,kind=dp)/86400._dp
110  call caldate(jul,jjjjmmdd,ihmmss)
111  write(adate,'(i8.8)') jjjjmmdd
112  write(atime,'(i6.6)') ihmmss
113
114
115  ! For forward simulations, output fields have dimension MAXSPEC,
116  ! for backward simulations, output fields have dimension MAXPOINT.
117  ! Thus, make loops either about nspec, or about numpoint
118  !*****************************************************************
119
120
121    if (ldirect.eq.1) then
122       do ks=1,nspec
123         do kp=1,maxpointspec_act
124           tot_mu(ks,kp)=1
125         end do
126       end do
127   else
128      do ks=1,nspec
129             do kp=1,maxpointspec_act
130               tot_mu(ks,kp)=xmass(kp,ks)
131             end do
132      end do
133    endif
134
135
136  !*******************************************************************
137  ! Compute air density: sufficiently accurate to take it
138  ! from coarse grid at some time
139  ! Determine center altitude of output layer, and interpolate density
140  ! data to that altitude
141  !*******************************************************************
142
143  do kz=1,numzgrid
144    if (kz.eq.1) then
145      halfheight=outheight(1)/2.
146    else
147      halfheight=(outheight(kz)+outheight(kz-1))/2.
148    endif
149    do kzz=2,nz
150      if ((height(kzz-1).lt.halfheight).and. &
151           (height(kzz).gt.halfheight)) goto 46
152    end do
15346   kzz=max(min(kzz,nz),2)
154    dz1=halfheight-height(kzz-1)
155    dz2=height(kzz)-halfheight
156    dz=dz1+dz2
157    do jy=0,numygridn-1
158      do ix=0,numxgridn-1
159        xl=out_xm0n+float(ix)*dxoutn
160        yl=out_ym0n+float(jy)*dyoutn
161!        xl=outlon0n+real(ix)*dxoutn
162!        yl=outlat0n+real(jy)*dyoutn
163!        xl=(xl-xlon0)/dx
164!        yl=(yl-ylat0)/dy
165            xl=(xl-xmet0)/dx
166            yl=(yl-ymet0)/dy
167        iix=max(min(nint(xl),nxmin1),0)
168        jjy=max(min(nint(yl),nymin1),0)
169        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
170             rho(iix,jjy,kzz-1,2)*dz2)/dz
171      end do
172    end do
173  end do
174
175    do i=1,numreceptor
176      xl=xreceptor(i)
177      yl=yreceptor(i)
178      iix=max(min(nint(xl),nxmin1),0)
179      jjy=max(min(nint(yl),nymin1),0)
180      densityoutrecept(i)=rho(iix,jjy,1,2)
181    end do
182
183
184  ! Output is different for forward and backward simulations
185    do kz=1,numzgrid
186      do jy=0,numygridn-1
187        do ix=0,numxgridn-1
188          if (ldirect.eq.1) then
189            factor3d(ix,jy,kz)=1.e12/volumen(ix,jy,kz)/outnum
190          else
191            factor3d(ix,jy,kz)=real(abs(loutaver))/outnum
192          endif
193        end do
194      end do
195    end do
196
197  !*********************************************************************
198  ! Determine the standard deviation of the mean concentration or mixing
199  ! ratio (uncertainty of the output) and the dry and wet deposition
200  !*********************************************************************
201!  print*,'IN CONCOUT',nspec,iout,iouttype,ldirect
202  do ks=1,nspec
203
204    write(anspec,'(i3.3)') ks
205    if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
206      if (ldirect.eq.1) then
207        if (iouttype.eq.0) &
208          open(unitoutgrid,file=path(1)(1:length(1))//'grid_conc_nest_' &
209             //adate// &
210             atime//'_'//anspec,form='unformatted')
211        if (iouttype.eq.1) &
212          open(unitoutgrid,file=path(1)(1:length(1))//'grid_conc_nest_' &
213             //adate// &
214             atime//'_'//anspec,form='formatted')
215      else
216        if (iouttype.eq.0) &
217          open(unitoutgrid,file=path(1)(1:length(1))//'grid_time_nest_' &
218             //adate// &
219             atime//'_'//anspec,form='unformatted')
220        if (iouttype.eq.1) &
221          open(unitoutgrid,file=path(1)(1:length(1))//'grid_time_nest_' &
222             //adate// &
223             atime//'_'//anspec,form='formatted')
224      endif
225      if (iouttype.eq.0) write(unitoutgrid) itime
226      if (iouttype.eq.1) write(unitoutgrid,*) itime
227    endif
228
229  if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
230    if (iouttype.eq.0) &
231      open(unitoutgridppt,file=path(1)(1:length(1))//'grid_pptv_nest_' &
232        //adate// &
233        atime//'_'//anspec,form='unformatted')
234    if (iouttype.eq.1) &
235      open(unitoutgridppt,file=path(1)(1:length(1))//'grid_pptv_nest_' &
236        //adate// &
237        atime//'_'//anspec,form='formatted')
238
239!   write(unitoutgridppt) itime
240    if (iouttype.eq.0) write(unitoutgridppt) itime
241    if (iouttype.eq.1) write(unitoutgridppt,*) itime
242  endif
243
244  do kp=1,maxpointspec_act
245  do nage=1,nageclass
246
247    do jy=0,numygridn-1
248      do ix=0,numxgridn-1
249
250  ! WET DEPOSITION
251        if ((WETDEP).and.(ldirect.gt.0)) then
252          do l=1,nclassunc
253            auxgrid(l)=wetgriduncn(ix,jy,ks,kp,l,nage)
254          end do
255          call mean(auxgrid,wetgrid(ix,jy), &
256            wetgridsigma(ix,jy),nclassunc)
257  ! Multiply by number of classes to get total concentration
258          wetgrid(ix,jy)=wetgrid(ix,jy) &
259            *nclassunc
260  ! Calculate standard deviation of the mean
261          wetgridsigma(ix,jy)= &
262            wetgridsigma(ix,jy)* &
263            sqrt(real(nclassunc))
264        endif
265
266  ! DRY DEPOSITION
267        if ((DRYDEP).and.(ldirect.gt.0)) then
268          do l=1,nclassunc
269            auxgrid(l)=drygriduncn(ix,jy,ks,kp,l,nage)
270          end do
271          call mean(auxgrid,drygrid(ix,jy), &
272            drygridsigma(ix,jy),nclassunc)
273  ! Multiply by number of classes to get total concentration
274          drygrid(ix,jy)=drygrid(ix,jy)* &
275            nclassunc
276  ! Calculate standard deviation of the mean
277          drygridsigma(ix,jy)= &
278            drygridsigma(ix,jy)* &
279            sqrt(real(nclassunc))
280        endif
281
282  ! CONCENTRATION OR MIXING RATIO
283        do kz=1,numzgrid
284          do l=1,nclassunc
285            auxgrid(l)=griduncn(ix,jy,kz,ks,kp,l,nage)
286          end do
287          call mean(auxgrid,grid(ix,jy,kz), &
288            gridsigma(ix,jy,kz),nclassunc)
289  ! Multiply by number of classes to get total concentration
290            grid(ix,jy,kz)= &
291              grid(ix,jy,kz)*nclassunc
292  ! Calculate standard deviation of the mean
293            gridsigma(ix,jy,kz)= &
294              gridsigma(ix,jy,kz)* &
295              sqrt(real(nclassunc))
296        end do
297      end do
298    end do
299
300
301  !*******************************************************************
302  ! Generate output: may be in concentration (ng/m3) or in mixing
303  ! ratio (ppt) or both
304  ! Output the position and the values alternated multiplied by
305  ! 1 or -1, first line is number of values, number of positions
306  ! For backward simulations, the unit is seconds, stored in grid_time
307  !*******************************************************************
308
309    if (iouttype.eq.2) then   ! netcdf output
310      if (option_verbose.ge.1) then
311        write(*,*) 'concoutput_irreg: Calling write_ncconc for main outgrid'
312      endif
313      call write_ncconc(itime,outnum,ks,kp,nage,tot_mu(ks,kp),1) ! 1= nest level
314    else  ! binary or ascii output
315
316      ! Concentration output
317      !*********************
318      if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
319
320! Wet deposition
321        sp_count_i=0
322        sp_count_r=0
323        sp_fact=-1.
324        sp_zer=.true.
325        if ((ldirect.eq.1).and.(WETDEP)) then
326          do jy=0,numygridn-1
327            do ix=0,numxgridn-1
328  !oncentraion greater zero
329              if (wetgrid(ix,jy).gt.smallnum) then
330                if (sp_zer.eqv..true.) then ! first non zero value
331                  sp_count_i=sp_count_i+1
332                  sparse_dump_i(sp_count_i)=ix+jy*numxgridn
333                  sp_zer=.false.
334                  sp_fact=sp_fact*(-1.)
335                endif
336                sp_count_r=sp_count_r+1
337                sparse_dump_r(sp_count_r)= &
338                  sp_fact*1.e12*wetgrid(ix,jy)/arean(ix,jy)
339  !               sparse_dump_u(sp_count_r)=
340  !+              1.e12*wetgridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
341              else ! concentration is zero
342                sp_zer=.true.
343              endif
344            end do
345          end do
346        else
347          sp_count_i=0
348          sp_count_r=0
349        endif
350        if (iouttype.eq.0) then
351          write(unitoutgrid) sp_count_i
352          write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
353          write(unitoutgrid) sp_count_r
354          write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
355        endif
356        if (iouttype.eq.1) then
357          write(unitoutgrid,*) sp_count_i
358          write(unitoutgrid,*) (sparse_dump_i(i),i=1,sp_count_i)
359          write(unitoutgrid,*) sp_count_r
360          write(unitoutgrid,*) (sparse_dump_r(i),i=1,sp_count_r)
361        endif
362  !       write(unitoutgrid) sp_count_u
363  !       write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
364
365  ! Dry deposition
366        sp_count_i=0
367        sp_count_r=0
368        sp_fact=-1.
369        sp_zer=.true.
370        if ((ldirect.eq.1).and.(DRYDEP)) then
371          do jy=0,numygridn-1
372          do ix=0,numxgridn-1
373            if (drygrid(ix,jy).gt.smallnum) then
374              if (sp_zer.eqv..true.) then ! first non zero value
375                sp_count_i=sp_count_i+1
376                sparse_dump_i(sp_count_i)=ix+jy*numxgridn
377                sp_zer=.false.
378                sp_fact=sp_fact*(-1.)
379              endif
380              sp_count_r=sp_count_r+1
381              sparse_dump_r(sp_count_r)= &
382              sp_fact* &
383                1.e12*drygrid(ix,jy)/arean(ix,jy)
384  !             sparse_dump_u(sp_count_r)=
385  !+            1.e12*drygridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
386            else ! concentration is zero
387              sp_zer=.true.
388            endif
389          end do
390          end do
391        else
392          sp_count_i=0
393          sp_count_r=0
394        endif
395        if (iouttype.eq.0) then
396          write(unitoutgrid) sp_count_i
397          write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
398          write(unitoutgrid) sp_count_r
399          write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
400        endif
401        if (iouttype.eq.1) then
402          write(unitoutgrid,*) sp_count_i
403          write(unitoutgrid,*) (sparse_dump_i(i),i=1,sp_count_i)
404          write(unitoutgrid,*) sp_count_r
405          write(unitoutgrid,*) (sparse_dump_r(i),i=1,sp_count_r)
406        endif
407  !       write(*,*) sp_count_u
408  !       write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
409
410
411
412  ! Concentrations
413        sp_count_i=0
414        sp_count_r=0
415        sp_fact=-1.
416        sp_zer=.true.
417        do kz=1,numzgrid
418          do jy=0,numygridn-1
419            do ix=0,numxgridn-1
420              if (grid(ix,jy,kz).gt.smallnum) then
421                if (sp_zer.eqv..true.) then ! first non zero value
422                  sp_count_i=sp_count_i+1
423                  sparse_dump_i(sp_count_i)= &
424                    ix+jy*numxgridn+kz*numxgridn*numygridn
425                  sp_zer=.false.
426                  sp_fact=sp_fact*(-1.)
427                endif
428                sp_count_r=sp_count_r+1
429                sparse_dump_r(sp_count_r)= &
430                  sp_fact* &
431                  grid(ix,jy,kz)* &
432                  factor3d(ix,jy,kz)/tot_mu(ks,kp)
433  !               if ((factor(ix,jy,kz)/tot_mu(ks,kp)).eq.0)
434  !    +            write (*,*) factor(ix,jy,kz),tot_mu(ks,kp),ks,kp
435  !                sparse_dump_u(sp_count_r)=
436  !+               ,gridsigma(ix,jy,kz,ks,kp,nage)*
437  !+               factor(ix,jy,kz)/tot_mu(ks,kp)
438              else ! concentration is zero
439                sp_zer=.true.
440              endif
441            end do
442          end do
443        end do
444        if (iouttype.eq.0) then
445          write(unitoutgrid) sp_count_i
446          write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
447          write(unitoutgrid) sp_count_r
448          write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
449        endif
450        if (iouttype.eq.1) then
451          write(unitoutgrid,*) sp_count_i
452          write(unitoutgrid,*) (sparse_dump_i(i),i=1,sp_count_i)
453          write(unitoutgrid,*) sp_count_r
454          write(unitoutgrid,*) (sparse_dump_r(i),i=1,sp_count_r)
455        endif
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,numygridn-1
475            do ix=0,numxgridn-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*numxgridn
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)/arean(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        if (iouttype.eq.0) then
500          write(unitoutgridppt) sp_count_i
501          write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
502          write(unitoutgridppt) sp_count_r
503          write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
504        endif
505        if (iouttype.eq.1) then
506          write(unitoutgridppt,*) sp_count_i
507          write(unitoutgridppt,*) (sparse_dump_i(i),i=1,sp_count_i)
508          write(unitoutgridppt,*) sp_count_r
509          write(unitoutgridppt,*) (sparse_dump_r(i),i=1,sp_count_r)
510        endif
511  !       write(unitoutgridppt) sp_count_u
512  !       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
513
514
515! Dry deposition
516        sp_count_i=0
517        sp_count_r=0
518        sp_fact=-1.
519        sp_zer=.true.
520        if ((ldirect.eq.1).and.(DRYDEP)) then
521          do jy=0,numygridn-1
522            do ix=0,numxgridn-1
523              if (drygrid(ix,jy).gt.smallnum) then
524                if (sp_zer.eqv..true.) then ! first non zero value
525                  sp_count_i=sp_count_i+1
526                  sparse_dump_i(sp_count_i)= &
527                       ix+jy*numxgridn
528                  sp_zer=.false.
529                  sp_fact=sp_fact*(-1)
530                endif
531                sp_count_r=sp_count_r+1
532                sparse_dump_r(sp_count_r)= &
533                    sp_fact* &
534                    1.e12*drygrid(ix,jy)/arean(ix,jy)
535  !                sparse_dump_u(sp_count_r)=
536  !    +            ,1.e12*drygridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
537              else ! concentration is zero
538                sp_zer=.true.
539              endif
540            end do
541          end do
542        else
543          sp_count_i=0
544          sp_count_r=0
545        endif
546        if (iouttype.eq.0) then
547          write(unitoutgridppt) sp_count_i
548          write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
549          write(unitoutgridppt) sp_count_r
550          write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
551        endif
552        if (iouttype.eq.1) then
553          write(unitoutgridppt,*) sp_count_i
554          write(unitoutgridppt,*) (sparse_dump_i(i),i=1,sp_count_i)
555          write(unitoutgridppt,*) sp_count_r
556          write(unitoutgridppt,*) (sparse_dump_r(i),i=1,sp_count_r)
557        endif
558!       write(unitoutgridppt) sp_count_u
559!       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
560
561
562! Mixing ratios
563        sp_count_i=0
564        sp_count_r=0
565        sp_fact=-1.
566        sp_zer=.true.
567        do kz=1,numzgrid
568          do jy=0,numygridn-1
569            do ix=0,numxgridn-1
570              if (grid(ix,jy,kz).gt.smallnum) then
571                if (sp_zer.eqv..true.) then ! first non zero value
572                  sp_count_i=sp_count_i+1
573                  sparse_dump_i(sp_count_i)= &
574                       ix+jy*numxgridn+kz*numxgridn*numygridn
575                  sp_zer=.false.
576                  sp_fact=sp_fact*(-1.)
577                endif
578                sp_count_r=sp_count_r+1
579                sparse_dump_r(sp_count_r)= &
580                    sp_fact* &
581                    1.e12*grid(ix,jy,kz) &
582                    /volumen(ix,jy,kz)/outnum* &
583                    weightair/weightmolar(ks)/densityoutgrid(ix,jy,kz)
584!                sparse_dump_u(sp_count_r)=
585!+              ,1.e12*gridsigma(ix,jy,kz,ks,kp,nage)/volume(ix,jy,kz)/
586!+              outnum*weightair/weightmolar(ks)/
587!+              densityoutgrid(ix,jy,kz)
588              else ! concentration is zero
589                sp_zer=.true.
590              endif
591            end do
592          end do
593        end do
594        if (iouttype.eq.0) then
595          write(unitoutgridppt) sp_count_i
596          write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
597          write(unitoutgridppt) sp_count_r
598          write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
599        endif
600        if (iouttype.eq.1) then
601          write(unitoutgridppt,*) sp_count_i
602          write(unitoutgridppt,*) (sparse_dump_i(i),i=1,sp_count_i)
603          write(unitoutgridppt,*) sp_count_r
604          write(unitoutgridppt,*) (sparse_dump_r(i),i=1,sp_count_r)
605        endif
606!       write(unitoutgridppt) sp_count_u
607!       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
608
609      endif ! output for ppt
610
611    endif ! iouttype.eq.2
612
613  end do
614  end do
615
616  if ((iouttype.eq.0).or.(iouttype.eq.1)) then ! binary or ascii output
617    close(unitoutgridppt)
618    close(unitoutgrid)
619  endif
620
621  end do  ! ks=1,nspec
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,numygridn-1
632      do ix=0,numxgridn-1
633        do l=1,nclassunc
634          do nage=1,nageclass
635            do kz=1,numzgrid
636              griduncn(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_nest_irreg
647
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG