source: flexpart.git/src/concoutput_nest.f90 @ 2eefa58

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file since 2eefa58 was 2eefa58, checked in by Espen Sollum ATMOS <eso@…>, 5 years ago

Added Ronas changes for inversion output

  • Property mode set to 100644
File size: 22.9 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_nest(itime,outnum)
23  !                        i     i
24  !*****************************************************************************
25  !                                                                            *
26  !     Output of the concentration grid and the receptor concentrations.      *
27  !                                                                            *
28  !     Author: A. Stohl                                                       *
29  !                                                                            *
30  !     24 May 1995                                                            *
31  !                                                                            *
32  !     13 April 1999, Major update: if output size is smaller, dump output    *
33  !                    in sparse matrix format; additional output of           *
34  !                    uncertainty                                             *
35  !                                                                            *
36  !     05 April 2000, Major update: output of age classes; output for backward*
37  !                    runs is time spent in grid cell times total mass of     *
38  !                    species.                                                *
39  !                                                                            *
40  !     17 February 2002, Appropriate dimensions for backward and forward runs *
41  !                       are now specified in file par_mod                    *
42  !                                                                            *
43  !     June 2006, write grid in sparse matrix with a single write command     *
44  !                in order to save disk space                                 *
45  !                                                                            *
46  !     2008 new sparse matrix format                                          *
47  !                                                                            *
48  !*****************************************************************************
49  !                                                                            *
50  ! Variables:                                                                 *
51  ! outnum          number of samples                                          *
52  ! ncells          number of cells with non-zero concentrations               *
53  ! sparse          .true. if in sparse matrix format, else .false.            *
54  ! tot_mu          1 for forward, initial mass mixing ration for backw. runs  *
55  !                                                                            *
56  !*****************************************************************************
57
58  use unc_mod
59  use point_mod
60  use outg_mod
61  use par_mod
62  use com_mod
63  use mean_mod
64
65  implicit none
66
67  real(kind=dp) :: jul
68  integer :: itime,i,ix,jy,kz,ks,kp,l,iix,jjy,kzz,nage,jjjjmmdd,ihmmss
69  integer :: sp_count_i,sp_count_r
70  real :: sp_fact
71  real :: outnum,densityoutrecept(maxreceptor),xl,yl
72! RLT
73  real :: densitydryrecept(maxreceptor)
74  real :: factor_dryrecept(maxreceptor)
75
76  !real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
77  !    +grid(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec,maxpointspec_act,
78  !    +    maxageclass)
79  !real wetgrid(0:numxgrid-1,0:numygrid-1,maxspec,maxpointspec_act,
80  !    +       maxageclass)
81  !real drygrid(0:numxgrid-1,0:numygrid-1,maxspec,
82  !    +       maxpointspec_act,maxageclass)
83  !real gridsigma(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec,
84  !    +       maxpointspec_act,maxageclass),
85  !    +     drygridsigma(0:numxgrid-1,0:numygrid-1,maxspec,
86  !    +     maxpointspec_act,maxageclass),
87  !    +     wetgridsigma(0:numxgrid-1,0:numygrid-1,maxspec,
88  !    +     maxpointspec_act,maxageclass)
89  !real factor(0:numxgrid-1,0:numygrid-1,numzgrid)
90  !real sparse_dump_r(numxgrid*numygrid*numzgrid)
91  !integer sparse_dump_i(numxgrid*numygrid*numzgrid)
92
93  !real sparse_dump_u(numxgrid*numygrid*numzgrid)
94  real(dep_prec) :: auxgrid(nclassunc)
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  character :: adate*8,atime*6
100  character(len=3) :: anspec
101  logical :: lexist
102  integer :: mind
103! mind        eso:added to ensure identical results between 2&3-fields versions
104
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  mind=memind(2)
144  do kz=1,numzgrid
145    if (kz.eq.1) then
146      halfheight=outheight(1)/2.
147    else
148      halfheight=(outheight(kz)+outheight(kz-1))/2.
149    endif
150    do kzz=2,nz
151      if ((height(kzz-1).lt.halfheight).and. &
152           (height(kzz).gt.halfheight)) goto 46
153    end do
15446   kzz=max(min(kzz,nz),2)
155    dz1=halfheight-height(kzz-1)
156    dz2=height(kzz)-halfheight
157    dz=dz1+dz2
158    do jy=0,numygridn-1
159      do ix=0,numxgridn-1
160        xl=outlon0n+real(ix)*dxoutn
161        yl=outlat0n+real(jy)*dyoutn
162        xl=(xl-xlon0)/dx
163        yl=(yl-ylat0)/dy
164        iix=max(min(nint(xl),nxmin1),0)
165        jjy=max(min(nint(yl),nymin1),0)
166        ! densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
167        !      rho(iix,jjy,kzz-1,2)*dz2)/dz
168        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,mind)*dz1+ &
169             rho(iix,jjy,kzz-1,mind)*dz2)/dz
170! RLT
171        densitydrygrid(ix,jy,kz)=(rho_dry(iix,jjy,kzz,mind)*dz1+ &
172             rho_dry(iix,jjy,kzz-1,mind)*dz2)/dz
173      end do
174    end do
175  end do
176
177  do i=1,numreceptor
178    xl=xreceptor(i)
179    yl=yreceptor(i)
180    iix=max(min(nint(xl),nxmin1),0)
181    jjy=max(min(nint(yl),nymin1),0)
182    !densityoutrecept(i)=rho(iix,jjy,1,2)
183    densityoutrecept(i)=rho(iix,jjy,1,mind)
184! RLT
185    densitydryrecept(i)=rho_dry(iix,jjy,1,mind)
186  end do
187
188! RLT
189! conversion factor for output relative to dry air
190  factor_drygrid=densityoutgrid/densitydrygrid
191  factor_dryrecept=densityoutrecept/densitydryrecept
192
193  ! Output is different for forward and backward simulations
194    do kz=1,numzgrid
195      do jy=0,numygridn-1
196        do ix=0,numxgridn-1
197          if (ldirect.eq.1) then
198            factor3d(ix,jy,kz)=1.e12/volumen(ix,jy,kz)/outnum
199          else
200            factor3d(ix,jy,kz)=real(abs(loutaver))/outnum
201          endif
202        end do
203      end do
204    end do
205
206  !*********************************************************************
207  ! Determine the standard deviation of the mean concentration or mixing
208  ! ratio (uncertainty of the output) and the dry and wet deposition
209  !*********************************************************************
210
211  do ks=1,nspec
212
213  write(anspec,'(i3.3)') ks
214 
215  if (DRYBKDEP.or.WETBKDEP) then !scavdep output
216      if (DRYBKDEP) &
217      open(unitoutgrid,file=path(2)(1:length(2))//'grid_drydep_nest_'//adate// &
218           atime//'_'//anspec,form='unformatted')
219      if (WETBKDEP) &
220      open(unitoutgrid,file=path(2)(1:length(2))//'grid_wetdep_nest_'//adate// &
221           atime//'_'//anspec,form='unformatted')
222      write(unitoutgrid) itime
223  else
224     if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
225       if (ldirect.eq.1) then
226         open(unitoutgrid,file=path(2)(1:length(2))//'grid_conc_nest_' &
227           //adate// &
228           atime//'_'//anspec,form='unformatted')
229       else
230         open(unitoutgrid,file=path(2)(1:length(2))//'grid_time_nest_' &
231           //adate// &
232           atime//'_'//anspec,form='unformatted')
233       endif
234       write(unitoutgrid) itime
235     endif
236  endif
237
238  if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
239   open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_nest_' &
240        //adate// &
241        atime//'_'//anspec,form='unformatted')
242
243    write(unitoutgridppt) itime
244  endif
245
246  do kp=1,maxpointspec_act
247  do nage=1,nageclass
248
249    do jy=0,numygridn-1
250      do ix=0,numxgridn-1
251
252  ! WET DEPOSITION
253        if ((WETDEP).and.(ldirect.gt.0)) then
254            do l=1,nclassunc
255              auxgrid(l)=wetgriduncn(ix,jy,ks,kp,l,nage)
256            end do
257            call mean(auxgrid,wetgrid(ix,jy), &
258                 wetgridsigma(ix,jy),nclassunc)
259  ! Multiply by number of classes to get total concentration
260            wetgrid(ix,jy)=wetgrid(ix,jy) &
261                 *nclassunc
262  ! Calculate standard deviation of the mean
263            wetgridsigma(ix,jy)= &
264                 wetgridsigma(ix,jy)* &
265                 sqrt(real(nclassunc))
266        endif
267
268  ! DRY DEPOSITION
269        if ((DRYDEP).and.(ldirect.gt.0)) then
270            do l=1,nclassunc
271              auxgrid(l)=drygriduncn(ix,jy,ks,kp,l,nage)
272            end do
273            call mean(auxgrid,drygrid(ix,jy), &
274                 drygridsigma(ix,jy),nclassunc)
275  ! Multiply by number of classes to get total concentration
276            drygrid(ix,jy)=drygrid(ix,jy)* &
277                 nclassunc
278  ! Calculate standard deviation of the mean
279            drygridsigma(ix,jy)= &
280                 drygridsigma(ix,jy)* &
281                 sqrt(real(nclassunc))
282        endif
283
284  ! CONCENTRATION OR MIXING RATIO
285        do kz=1,numzgrid
286            do l=1,nclassunc
287              auxgrid(l)=griduncn(ix,jy,kz,ks,kp,l,nage)
288            end do
289            call mean(auxgrid,grid(ix,jy,kz), &
290                 gridsigma(ix,jy,kz),nclassunc)
291  ! Multiply by number of classes to get total concentration
292            grid(ix,jy,kz)= &
293                 grid(ix,jy,kz)*nclassunc
294  ! Calculate standard deviation of the mean
295            gridsigma(ix,jy,kz)= &
296                 gridsigma(ix,jy,kz)* &
297                 sqrt(real(nclassunc))
298        end do
299      end do
300    end do
301
302
303  !*******************************************************************
304  ! Generate output: may be in concentration (ng/m3) or in mixing
305  ! ratio (ppt) or both
306  ! Output the position and the values alternated multiplied by
307  ! 1 or -1, first line is number of values, number of positions
308  ! For backward simulations, the unit is seconds, stored in grid_time
309  !*******************************************************************
310
311  ! Concentration output
312  !*********************
313  if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
314
315  ! Wet deposition
316         sp_count_i=0
317         sp_count_r=0
318         sp_fact=-1.
319         sp_zer=.true.
320         if ((ldirect.eq.1).and.(WETDEP)) then
321         do jy=0,numygridn-1
322            do ix=0,numxgridn-1
323  !oncentraion greater zero
324              if (wetgrid(ix,jy).gt.smallnum) then
325                 if (sp_zer.eqv..true.) then ! first non zero value
326                    sp_count_i=sp_count_i+1
327                    sparse_dump_i(sp_count_i)=ix+jy*numxgridn
328                    sp_zer=.false.
329                    sp_fact=sp_fact*(-1.)
330                 endif
331                 sp_count_r=sp_count_r+1
332                 sparse_dump_r(sp_count_r)= &
333                      sp_fact*1.e12*wetgrid(ix,jy)/arean(ix,jy)
334  !                sparse_dump_u(sp_count_r)=
335  !+                1.e12*wetgridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
336              else ! concentration is zero
337                  sp_zer=.true.
338              endif
339            end do
340         end do
341         else
342            sp_count_i=0
343            sp_count_r=0
344         endif
345         write(unitoutgrid) sp_count_i
346         write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
347         write(unitoutgrid) sp_count_r
348         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
349  !       write(unitoutgrid) sp_count_u
350  !       write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
351
352  ! Dry deposition
353         sp_count_i=0
354         sp_count_r=0
355         sp_fact=-1.
356         sp_zer=.true.
357         if ((ldirect.eq.1).and.(DRYDEP)) then
358          do jy=0,numygridn-1
359            do ix=0,numxgridn-1
360              if (drygrid(ix,jy).gt.smallnum) then
361                 if (sp_zer.eqv..true.) then ! first non zero value
362                    sp_count_i=sp_count_i+1
363                    sparse_dump_i(sp_count_i)=ix+jy*numxgridn
364                    sp_zer=.false.
365                    sp_fact=sp_fact*(-1.)
366                 endif
367                 sp_count_r=sp_count_r+1
368                 sparse_dump_r(sp_count_r)= &
369                      sp_fact* &
370                      1.e12*drygrid(ix,jy)/arean(ix,jy)
371  !                sparse_dump_u(sp_count_r)=
372  !+                1.e12*drygridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
373              else ! concentration is zero
374                  sp_zer=.true.
375              endif
376            end do
377          end do
378         else
379            sp_count_i=0
380            sp_count_r=0
381         endif
382         write(unitoutgrid) sp_count_i
383         write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
384         write(unitoutgrid) sp_count_r
385         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
386  !       write(*,*) sp_count_u
387  !       write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
388
389
390
391  ! Concentrations
392         sp_count_i=0
393         sp_count_r=0
394         sp_fact=-1.
395         sp_zer=.true.
396          do kz=1,numzgrid
397            do jy=0,numygridn-1
398              do ix=0,numxgridn-1
399                if (grid(ix,jy,kz).gt.smallnum) then
400                  if (sp_zer.eqv..true.) then ! first non zero value
401                    sp_count_i=sp_count_i+1
402                    sparse_dump_i(sp_count_i)= &
403                         ix+jy*numxgridn+kz*numxgridn*numygridn
404                    sp_zer=.false.
405                    sp_fact=sp_fact*(-1.)
406                   endif
407                   sp_count_r=sp_count_r+1
408                   sparse_dump_r(sp_count_r)= &
409                        sp_fact* &
410                        grid(ix,jy,kz)* &
411                        factor3d(ix,jy,kz)/tot_mu(ks,kp)
412  !                 if ((factor(ix,jy,kz)/tot_mu(ks,kp)).eq.0)
413  !    +              write (*,*) factor(ix,jy,kz),tot_mu(ks,kp),ks,kp
414  !                sparse_dump_u(sp_count_r)=
415  !+               ,gridsigma(ix,jy,kz,ks,kp,nage)*
416  !+               factor(ix,jy,kz)/tot_mu(ks,kp)
417              else ! concentration is zero
418                  sp_zer=.true.
419              endif
420              end do
421            end do
422          end do
423         write(unitoutgrid) sp_count_i
424         write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
425         write(unitoutgrid) sp_count_r
426         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
427  !       write(unitoutgrid) sp_count_u
428  !       write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
429
430
431
432    endif !  concentration output
433
434  ! Mixing ratio output
435  !********************
436
437  if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
438
439  ! Wet deposition
440         sp_count_i=0
441         sp_count_r=0
442         sp_fact=-1.
443         sp_zer=.true.
444         if ((ldirect.eq.1).and.(WETDEP)) then
445          do jy=0,numygridn-1
446            do ix=0,numxgridn-1
447                if (wetgrid(ix,jy).gt.smallnum) then
448                  if (sp_zer.eqv..true.) then ! first non zero value
449                    sp_count_i=sp_count_i+1
450                    sparse_dump_i(sp_count_i)= &
451                         ix+jy*numxgridn
452                    sp_zer=.false.
453                    sp_fact=sp_fact*(-1.)
454                 endif
455                 sp_count_r=sp_count_r+1
456                 sparse_dump_r(sp_count_r)= &
457                      sp_fact* &
458                      1.e12*wetgrid(ix,jy)/arean(ix,jy)
459  !                sparse_dump_u(sp_count_r)=
460  !    +            ,1.e12*wetgridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
461              else ! concentration is zero
462                  sp_zer=.true.
463              endif
464            end do
465          end do
466         else
467           sp_count_i=0
468           sp_count_r=0
469         endif
470         write(unitoutgridppt) sp_count_i
471         write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
472         write(unitoutgridppt) sp_count_r
473         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
474  !       write(unitoutgridppt) sp_count_u
475  !       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
476
477
478  ! Dry deposition
479         sp_count_i=0
480         sp_count_r=0
481         sp_fact=-1.
482         sp_zer=.true.
483         if ((ldirect.eq.1).and.(DRYDEP)) then
484          do jy=0,numygridn-1
485            do ix=0,numxgridn-1
486                if (drygrid(ix,jy).gt.smallnum) then
487                  if (sp_zer.eqv..true.) then ! first non zero value
488                    sp_count_i=sp_count_i+1
489                    sparse_dump_i(sp_count_i)= &
490                         ix+jy*numxgridn
491                    sp_zer=.false.
492                    sp_fact=sp_fact*(-1)
493                 endif
494                 sp_count_r=sp_count_r+1
495                 sparse_dump_r(sp_count_r)= &
496                      sp_fact* &
497                      1.e12*drygrid(ix,jy)/arean(ix,jy)
498  !                sparse_dump_u(sp_count_r)=
499  !    +            ,1.e12*drygridsigma(ix,jy,ks,kp,nage)/area(ix,jy)
500              else ! concentration is zero
501                  sp_zer=.true.
502              endif
503            end do
504          end do
505         else
506           sp_count_i=0
507           sp_count_r=0
508         endif
509         write(unitoutgridppt) sp_count_i
510         write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
511         write(unitoutgridppt) sp_count_r
512         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
513  !       write(unitoutgridppt) sp_count_u
514  !       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
515
516
517  ! Mixing ratios
518         sp_count_i=0
519         sp_count_r=0
520         sp_fact=-1.
521         sp_zer=.true.
522          do kz=1,numzgrid
523            do jy=0,numygridn-1
524              do ix=0,numxgridn-1
525                if (grid(ix,jy,kz).gt.smallnum) then
526                  if (sp_zer.eqv..true.) then ! first non zero value
527                    sp_count_i=sp_count_i+1
528                    sparse_dump_i(sp_count_i)= &
529                         ix+jy*numxgridn+kz*numxgridn*numygridn
530                    sp_zer=.false.
531                    sp_fact=sp_fact*(-1.)
532                 endif
533                 sp_count_r=sp_count_r+1
534                 sparse_dump_r(sp_count_r)= &
535                      sp_fact* &
536                      1.e12*grid(ix,jy,kz) &
537                      /volumen(ix,jy,kz)/outnum* &
538                      weightair/weightmolar(ks)/densityoutgrid(ix,jy,kz)
539  !                sparse_dump_u(sp_count_r)=
540  !+              ,1.e12*gridsigma(ix,jy,kz,ks,kp,nage)/volume(ix,jy,kz)/
541  !+              outnum*weightair/weightmolar(ks)/
542  !+              densityoutgrid(ix,jy,kz)
543              else ! concentration is zero
544                  sp_zer=.true.
545              endif
546              end do
547            end do
548          end do
549         write(unitoutgridppt) sp_count_i
550         write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
551         write(unitoutgridppt) sp_count_r
552         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
553  !       write(unitoutgridppt) sp_count_u
554  !       write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
555
556      endif ! output for ppt
557
558  end do
559  end do
560
561    close(unitoutgridppt)
562    close(unitoutgrid)
563
564  end do
565
566! RLT Aug 2017
567! Write out conversion factor for dry air
568  inquire(file=path(2)(1:length(2))//'factor_drygrid_nest',exist=lexist)
569  if (lexist) then
570    ! open and append
571    open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
572            status='old',action='write',access='append')
573  else
574    ! create new
575    open(unitoutfactor,file=path(2)(1:length(2))//'factor_drygrid_nest',form='unformatted',&
576            status='new',action='write')
577  endif
578  sp_count_i=0
579  sp_count_r=0
580  sp_fact=-1.
581  sp_zer=.true.
582  do kz=1,numzgrid
583    do jy=0,numygridn-1
584      do ix=0,numxgridn-1
585        if (factor_drygrid(ix,jy,kz).gt.(1.+smallnum).or.factor_drygrid(ix,jy,kz).lt.(1.-smallnum)) then
586          if (sp_zer.eqv..true.) then ! first value not equal to one
587            sp_count_i=sp_count_i+1
588            sparse_dump_i(sp_count_i)= &
589                  ix+jy*numxgridn+kz*numxgridn*numygridn
590            sp_zer=.false.
591            sp_fact=sp_fact*(-1.)
592          endif
593          sp_count_r=sp_count_r+1
594          sparse_dump_r(sp_count_r)= &
595               sp_fact*factor_drygrid(ix,jy,kz)
596        else ! factor is one
597          sp_zer=.true.
598        endif
599      end do
600    end do
601  end do
602  write(unitoutfactor) sp_count_i
603  write(unitoutfactor) (sparse_dump_i(i),i=1,sp_count_i)
604  write(unitoutfactor) sp_count_r
605  write(unitoutfactor) (sparse_dump_r(i),i=1,sp_count_r)
606  close(unitoutfactor)
607
608
609  ! Reinitialization of grid
610  !*************************
611
612  ! do ks=1,nspec
613  ! do kp=1,maxpointspec_act
614  !   do i=1,numreceptor
615  !     creceptor(i,ks)=0.
616  !   end do
617  !   do jy=0,numygridn-1
618  !     do ix=0,numxgridn-1
619  !       do l=1,nclassunc
620  !         do nage=1,nageclass
621  !           do kz=1,numzgrid
622  !             griduncn(ix,jy,kz,ks,kp,l,nage)=0.
623  !           end do
624  !         end do
625  !       end do
626  !     end do
627  !   end do
628  ! end do
629  ! end do
630  creceptor(:,:)=0.
631  griduncn(:,:,:,:,:,:,:)=0.
632
633
634end subroutine concoutput_nest
635
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG