source: flexpart.git/src/concoutput_surf_nest_mpi.f90 @ 8a65cb0

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

Added code, makefile for dev branch

  • Property mode set to 100755
File size: 24.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_surf_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  !     2014 eso: MPI version. Only called by root process                     *
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  use mpi_mod
66
67  implicit none
68
69  real(kind=dp) :: jul
70  integer :: itime,i,ix,jy,kz,ks,kp,l,iix,jjy,kzz,nage,jjjjmmdd,ihmmss
71  integer :: sp_count_i,sp_count_r
72  real :: sp_fact
73  real :: outnum,densityoutrecept(maxreceptor),xl,yl
74
75  !real densityoutgrid(0:numxgrid-1,0:numygrid-1,numzgrid),
76  !    +grid(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec,maxpointspec_act,
77  !    +    maxageclass)
78  !real wetgrid(0:numxgrid-1,0:numygrid-1,maxspec,maxpointspec_act,
79  !    +       maxageclass)
80  !real drygrid(0:numxgrid-1,0:numygrid-1,maxspec,
81  !    +       maxpointspec_act,maxageclass)
82  !real gridsigma(0:numxgrid-1,0:numygrid-1,numzgrid,maxspec,
83  !    +       maxpointspec_act,maxageclass),
84  !    +     drygridsigma(0:numxgrid-1,0:numygrid-1,maxspec,
85  !    +     maxpointspec_act,maxageclass),
86  !    +     wetgridsigma(0:numxgrid-1,0:numygrid-1,maxspec,
87  !    +     maxpointspec_act,maxageclass)
88  !real factor(0:numxgrid-1,0:numygrid-1,numzgrid)
89  !real sparse_dump_r(numxgrid*numygrid*numzgrid)
90  !integer sparse_dump_i(numxgrid*numygrid*numzgrid)
91
92  !real sparse_dump_u(numxgrid*numygrid*numzgrid)
93  real :: auxgrid(nclassunc)
94  real :: halfheight,dz,dz1,dz2,tot_mu(maxspec,maxpointspec_act)
95  real,parameter :: smallnum = tiny(0.0) ! smallest number that can be handled
96  real,parameter :: weightair=28.97
97  logical :: sp_zer
98  character :: adate*8,atime*6
99  character(len=3) :: anspec
100
101! Measure execution time
102  if (mp_measure_time) then
103    call cpu_time(mp_root_time_beg)
104    mp_root_wtime_beg = mpi_wtime()
105  end if
106
107  if (verbosity.eq.1) then
108     print*,'inside concoutput_surf '
109     CALL SYSTEM_CLOCK(count_clock)
110     WRITE(*,*) 'SYSTEM_CLOCK',count_clock - count_clock0   
111  endif
112
113  ! Determine current calendar date, needed for the file name
114  !**********************************************************
115
116  jul=bdate+real(itime,kind=dp)/86400._dp
117  call caldate(jul,jjjjmmdd,ihmmss)
118  write(adate,'(i8.8)') jjjjmmdd
119  write(atime,'(i6.6)') ihmmss
120
121
122  ! For forward simulations, output fields have dimension MAXSPEC,
123  ! for backward simulations, output fields have dimension MAXPOINT.
124  ! Thus, make loops either about nspec, or about numpoint
125  !*****************************************************************
126
127
128    if (ldirect.eq.1) then
129       do ks=1,nspec
130         do kp=1,maxpointspec_act
131           tot_mu(ks,kp)=1
132         end do
133       end do
134   else
135      do ks=1,nspec
136             do kp=1,maxpointspec_act
137               tot_mu(ks,kp)=xmass(kp,ks)
138             end do
139      end do
140    endif
141
142
143  !*******************************************************************
144  ! Compute air density: sufficiently accurate to take it
145  ! from coarse grid at some time
146  ! Determine center altitude of output layer, and interpolate density
147  ! data to that altitude
148  !*******************************************************************
149
150  do kz=1,numzgrid
151    if (kz.eq.1) then
152      halfheight=outheight(1)/2.
153    else
154      halfheight=(outheight(kz)+outheight(kz-1))/2.
155    endif
156    do kzz=2,nz
157      if ((height(kzz-1).lt.halfheight).and. &
158           (height(kzz).gt.halfheight)) goto 46
159    end do
16046   kzz=max(min(kzz,nz),2)
161    dz1=halfheight-height(kzz-1)
162    dz2=height(kzz)-halfheight
163    dz=dz1+dz2
164    do jy=0,numygridn-1
165      do ix=0,numxgridn-1
166        xl=outlon0n+real(ix)*dxoutn
167        yl=outlat0n+real(jy)*dyoutn
168        xl=(xl-xlon0)/dx
169        yl=(yl-ylat0)/dy
170        iix=max(min(nint(xl),nxmin1),0)
171        jjy=max(min(nint(yl),nymin1),0)
172        densityoutgrid(ix,jy,kz)=(rho(iix,jjy,kzz,2)*dz1+ &
173             rho(iix,jjy,kzz-1,2)*dz2)/dz
174      end do
175    end do
176  end do
177
178    do i=1,numreceptor
179      xl=xreceptor(i)
180      yl=yreceptor(i)
181      iix=max(min(nint(xl),nxmin1),0)
182      jjy=max(min(nint(yl),nymin1),0)
183      densityoutrecept(i)=rho(iix,jjy,1,2)
184    end do
185
186
187  ! Output is different for forward and backward simulations
188    do kz=1,numzgrid
189      do jy=0,numygridn-1
190        do ix=0,numxgridn-1
191          if (ldirect.eq.1) then
192            factor3d(ix,jy,kz)=1.e12/volumen(ix,jy,kz)/outnum
193          else
194            factor3d(ix,jy,kz)=real(abs(loutaver))/outnum
195          endif
196        end do
197      end do
198    end do
199
200  !*********************************************************************
201  ! Determine the standard deviation of the mean concentration or mixing
202  ! ratio (uncertainty of the output) and the dry and wet deposition
203  !*********************************************************************
204
205  do ks=1,nspec
206
207  write(anspec,'(i3.3)') ks
208  if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
209    if (ldirect.eq.1) then
210      open(unitoutgrid,file=path(2)(1:length(2))//'grid_conc_nest_' &
211           //adate// &
212           atime//'_'//anspec,form='unformatted')
213    else
214      open(unitoutgrid,file=path(2)(1:length(2))//'grid_time_nest_' &
215           //adate// &
216           atime//'_'//anspec,form='unformatted')
217    endif
218     write(unitoutgrid) itime
219   endif
220
221  if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
222   open(unitoutgridppt,file=path(2)(1:length(2))//'grid_pptv_nest_' &
223        //adate// &
224        atime//'_'//anspec,form='unformatted')
225
226    write(unitoutgridppt) itime
227  endif
228
229  do kp=1,maxpointspec_act
230  do nage=1,nageclass
231
232    do jy=0,numygridn-1
233      do ix=0,numxgridn-1
234
235  ! WET DEPOSITION
236        if ((WETDEP).and.(ldirect.gt.0)) then
237            do l=1,nclassunc
238              auxgrid(l)=wetgriduncn0(ix,jy,ks,kp,l,nage)
239            end do
240            call mean(auxgrid,wetgrid(ix,jy), &
241                 wetgridsigma(ix,jy),nclassunc)
242  ! Multiply by number of classes to get total concentration
243            wetgrid(ix,jy)=wetgrid(ix,jy) &
244                 *nclassunc
245  ! Calculate standard deviation of the mean
246            wetgridsigma(ix,jy)= &
247                 wetgridsigma(ix,jy)* &
248                 sqrt(real(nclassunc))
249        endif
250
251  ! DRY DEPOSITION
252        if ((DRYDEP).and.(ldirect.gt.0)) then
253            do l=1,nclassunc
254              auxgrid(l)=drygriduncn0(ix,jy,ks,kp,l,nage)
255            end do
256            call mean(auxgrid,drygrid(ix,jy), &
257                 drygridsigma(ix,jy),nclassunc)
258  ! Multiply by number of classes to get total concentration
259            drygrid(ix,jy)=drygrid(ix,jy)* &
260                 nclassunc
261  ! Calculate standard deviation of the mean
262            drygridsigma(ix,jy)= &
263                 drygridsigma(ix,jy)* &
264                 sqrt(real(nclassunc))
265        endif
266
267  ! CONCENTRATION OR MIXING RATIO
268        do kz=1,numzgrid
269            do l=1,nclassunc
270              auxgrid(l)=griduncn(ix,jy,kz,ks,kp,l,nage)
271            end do
272            call mean(auxgrid,grid(ix,jy,kz), &
273                 gridsigma(ix,jy,kz),nclassunc)
274  ! Multiply by number of classes to get total concentration
275            grid(ix,jy,kz)= &
276                 grid(ix,jy,kz)*nclassunc
277  ! Calculate standard deviation of the mean
278            gridsigma(ix,jy,kz)= &
279                 gridsigma(ix,jy,kz)* &
280                 sqrt(real(nclassunc))
281        end do
282      end do
283    end do
284
285
286  !*******************************************************************
287  ! Generate output: may be in concentration (ng/m3) or in mixing
288  ! ratio (ppt) or both
289  ! Output the position and the values alternated multiplied by
290  ! 1 or -1, first line is number of values, number of positions
291  ! For backward simulations, the unit is seconds, stored in grid_time
292  !*******************************************************************
293
294  ! Concentration output
295  !*********************
296  if ((iout.eq.1).or.(iout.eq.3).or.(iout.eq.5)) then
297
298  ! Wet deposition
299         sp_count_i=0
300         sp_count_r=0
301         sp_fact=-1.
302         sp_zer=.true.
303         if ((ldirect.eq.1).and.(WETDEP)) then
304         do jy=0,numygridn-1
305            do ix=0,numxgridn-1
306  !oncentraion greater zero
307              if (wetgrid(ix,jy).gt.smallnum) then
308                 if (sp_zer.eqv..true.) then ! first non zero value
309                    sp_count_i=sp_count_i+1
310                    sparse_dump_i(sp_count_i)=ix+jy*numxgridn
311                    sp_zer=.false.
312                    sp_fact=sp_fact*(-1.)
313                 endif
314                 sp_count_r=sp_count_r+1
315                 sparse_dump_r(sp_count_r)= &
316                      sp_fact*1.e12*wetgrid(ix,jy)/arean(ix,jy)
317                 sparse_dump_u(sp_count_r)= &
318                      1.e12*wetgridsigma(ix,jy)/area(ix,jy)
319              else ! concentration is zero
320                  sp_zer=.true.
321              endif
322            end do
323         end do
324         else
325            sp_count_i=0
326            sp_count_r=0
327         endif
328         write(unitoutgrid) sp_count_i
329         write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
330         write(unitoutgrid) sp_count_r
331         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
332         write(unitoutgrid) sp_count_r
333         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
334
335  ! Dry deposition
336         sp_count_i=0
337         sp_count_r=0
338         sp_fact=-1.
339         sp_zer=.true.
340         if ((ldirect.eq.1).and.(DRYDEP)) then
341          do jy=0,numygridn-1
342            do ix=0,numxgridn-1
343              if (drygrid(ix,jy).gt.smallnum) then
344                 if (sp_zer.eqv..true.) then ! first non zero value
345                    sp_count_i=sp_count_i+1
346                    sparse_dump_i(sp_count_i)=ix+jy*numxgridn
347                    sp_zer=.false.
348                    sp_fact=sp_fact*(-1.)
349                 endif
350                 sp_count_r=sp_count_r+1
351                 sparse_dump_r(sp_count_r)= &
352                      sp_fact* &
353                      1.e12*drygrid(ix,jy)/arean(ix,jy)
354                 sparse_dump_u(sp_count_r)= &
355                      1.e12*drygridsigma(ix,jy)/area(ix,jy)
356              else ! concentration is zero
357                  sp_zer=.true.
358              endif
359            end do
360          end do
361         else
362            sp_count_i=0
363            sp_count_r=0
364         endif
365         write(unitoutgrid) sp_count_i
366         write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
367         write(unitoutgrid) sp_count_r
368         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
369         write(unitoutgrid) sp_count_r
370         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
371
372
373
374  ! Concentrations
375
376  ! if surf_only write only 1st layer
377
378         if(surf_only.eq.1) then
379         sp_count_i=0
380         sp_count_r=0
381         sp_fact=-1.
382         sp_zer=.true.
383          do kz=1,1
384            do jy=0,numygridn-1
385              do ix=0,numxgridn-1
386                if (grid(ix,jy,kz).gt.smallnum) then
387                  if (sp_zer.eqv..true.) then ! first non zero value
388                    sp_count_i=sp_count_i+1
389                    sparse_dump_i(sp_count_i)= &
390                         ix+jy*numxgridn+kz*numxgridn*numygridn
391                    sp_zer=.false.
392                    sp_fact=sp_fact*(-1.)
393                   endif
394                   sp_count_r=sp_count_r+1
395                   sparse_dump_r(sp_count_r)= &
396                        sp_fact* &
397                        grid(ix,jy,kz)* &
398                        factor3d(ix,jy,kz)/tot_mu(ks,kp)
399  !                 if ((factor(ix,jy,kz)/tot_mu(ks,kp)).eq.0)
400  !    +              write (*,*) factor(ix,jy,kz),tot_mu(ks,kp),ks,kp
401                   sparse_dump_u(sp_count_r)= &
402                        gridsigma(ix,jy,kz)* &
403                        factor3d(ix,jy,kz)/tot_mu(ks,kp)
404              else ! concentration is zero
405                  sp_zer=.true.
406              endif
407              end do
408            end do
409          end do
410         write(unitoutgrid) sp_count_i
411         write(unitoutgrid) (sparse_dump_i(i),i=1,sp_count_i)
412         write(unitoutgrid) sp_count_r
413         write(unitoutgrid) (sparse_dump_r(i),i=1,sp_count_r)
414         write(unitoutgrid) sp_count_r
415         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
416         else
417
418  ! write full vertical resolution
419
420         sp_count_i=0
421         sp_count_r=0
422         sp_fact=-1.
423         sp_zer=.true.
424          do kz=1,numzgrid
425            do jy=0,numygridn-1
426              do ix=0,numxgridn-1
427                if (grid(ix,jy,kz).gt.smallnum) then
428                  if (sp_zer.eqv..true.) then ! first non zero value
429                    sp_count_i=sp_count_i+1
430                    sparse_dump_i(sp_count_i)= &
431                         ix+jy*numxgridn+kz*numxgridn*numygridn
432                    sp_zer=.false.
433                    sp_fact=sp_fact*(-1.)
434                   endif
435                   sp_count_r=sp_count_r+1
436                   sparse_dump_r(sp_count_r)= &
437                        sp_fact* &
438                        grid(ix,jy,kz)* &
439                        factor3d(ix,jy,kz)/tot_mu(ks,kp)
440  !                 if ((factor(ix,jy,kz)/tot_mu(ks,kp)).eq.0)
441  !    +              write (*,*) factor(ix,jy,kz),tot_mu(ks,kp),ks,kp
442                   sparse_dump_u(sp_count_r)= &
443                        gridsigma(ix,jy,kz)* &
444                        factor3d(ix,jy,kz)/tot_mu(ks,kp)
445              else ! concentration is zero
446                  sp_zer=.true.
447              endif
448              end do
449            end do
450          end do
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         write(unitoutgrid) sp_count_r
456         write(unitoutgrid) (sparse_dump_u(i),i=1,sp_count_r)
457         endif ! surf_only
458
459
460    endif !  concentration output
461
462  ! Mixing ratio output
463  !********************
464
465  if ((iout.eq.2).or.(iout.eq.3)) then      ! mixing ratio
466
467  ! Wet deposition
468         sp_count_i=0
469         sp_count_r=0
470         sp_fact=-1.
471         sp_zer=.true.
472         if ((ldirect.eq.1).and.(WETDEP)) then
473          do jy=0,numygridn-1
474            do ix=0,numxgridn-1
475                if (wetgrid(ix,jy).gt.smallnum) then
476                  if (sp_zer.eqv..true.) then ! first non zero value
477                    sp_count_i=sp_count_i+1
478                    sparse_dump_i(sp_count_i)= &
479                         ix+jy*numxgridn
480                    sp_zer=.false.
481                    sp_fact=sp_fact*(-1.)
482                 endif
483                 sp_count_r=sp_count_r+1
484                 sparse_dump_r(sp_count_r)= &
485                      sp_fact* &
486                      1.e12*wetgrid(ix,jy)/arean(ix,jy)
487                 sparse_dump_u(sp_count_r)= &
488                      1.e12*wetgridsigma(ix,jy)/area(ix,jy)
489              else ! concentration is zero
490                  sp_zer=.true.
491              endif
492            end do
493          end do
494         else
495           sp_count_i=0
496           sp_count_r=0
497         endif
498         write(unitoutgridppt) sp_count_i
499         write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
500         write(unitoutgridppt) sp_count_r
501         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
502         write(unitoutgridppt) sp_count_r
503         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
504
505
506  ! Dry deposition
507         sp_count_i=0
508         sp_count_r=0
509         sp_fact=-1.
510         sp_zer=.true.
511         if ((ldirect.eq.1).and.(DRYDEP)) then
512          do jy=0,numygridn-1
513            do ix=0,numxgridn-1
514                if (drygrid(ix,jy).gt.smallnum) then
515                  if (sp_zer.eqv..true.) then ! first non zero value
516                    sp_count_i=sp_count_i+1
517                    sparse_dump_i(sp_count_i)= &
518                         ix+jy*numxgridn
519                    sp_zer=.false.
520                    sp_fact=sp_fact*(-1)
521                 endif
522                 sp_count_r=sp_count_r+1
523                 sparse_dump_r(sp_count_r)= &
524                      sp_fact* &
525                      1.e12*drygrid(ix,jy)/arean(ix,jy)
526                 sparse_dump_u(sp_count_r)= &
527                      1.e12*drygridsigma(ix,jy)/area(ix,jy)
528              else ! concentration is zero
529                  sp_zer=.true.
530              endif
531            end do
532          end do
533         else
534           sp_count_i=0
535           sp_count_r=0
536         endif
537         write(unitoutgridppt) sp_count_i
538         write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
539         write(unitoutgridppt) sp_count_r
540         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
541         write(unitoutgridppt) sp_count_r
542         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
543
544
545  ! Mixing ratios
546
547    ! if surf_only write only 1st layer
548
549         if(surf_only.eq.1) then
550         sp_count_i=0
551         sp_count_r=0
552         sp_fact=-1.
553         sp_zer=.true.
554          do kz=1,1
555            do jy=0,numygridn-1
556              do ix=0,numxgridn-1
557                if (grid(ix,jy,kz).gt.smallnum) then
558                  if (sp_zer.eqv..true.) then ! first non zero value
559                    sp_count_i=sp_count_i+1
560                    sparse_dump_i(sp_count_i)= &
561                         ix+jy*numxgridn+kz*numxgridn*numygridn
562                    sp_zer=.false.
563                    sp_fact=sp_fact*(-1.)
564                 endif
565                 sp_count_r=sp_count_r+1
566                 sparse_dump_r(sp_count_r)= &
567                      sp_fact* &
568                      1.e12*grid(ix,jy,kz) &
569                      /volumen(ix,jy,kz)/outnum* &
570                      weightair/weightmolar(ks)/densityoutgrid(ix,jy,kz)
571                 sparse_dump_u(sp_count_r)= &
572                      1.e12*gridsigma(ix,jy,kz)/volumen(ix,jy,kz)/ &
573                      outnum*weightair/weightmolar(ks)/ &
574                      densityoutgrid(ix,jy,kz)
575              else ! concentration is zero
576                  sp_zer=.true.
577              endif
578              end do
579            end do
580          end do
581         write(unitoutgridppt) sp_count_i
582         write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
583         write(unitoutgridppt) sp_count_r
584         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
585         write(unitoutgridppt) sp_count_r
586         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
587         else
588
589  ! write full vertical resolution
590
591         sp_count_i=0
592         sp_count_r=0
593         sp_fact=-1.
594         sp_zer=.true.
595          do kz=1,numzgrid
596            do jy=0,numygridn-1
597              do ix=0,numxgridn-1
598                if (grid(ix,jy,kz).gt.smallnum) then
599                  if (sp_zer.eqv..true.) then ! first non zero value
600                    sp_count_i=sp_count_i+1
601                    sparse_dump_i(sp_count_i)= &
602                         ix+jy*numxgridn+kz*numxgridn*numygridn
603                    sp_zer=.false.
604                    sp_fact=sp_fact*(-1.)
605                 endif
606                 sp_count_r=sp_count_r+1
607                 sparse_dump_r(sp_count_r)= &
608                      sp_fact* &
609                      1.e12*grid(ix,jy,kz) &
610                      /volumen(ix,jy,kz)/outnum* &
611                      weightair/weightmolar(ks)/densityoutgrid(ix,jy,kz)
612                 sparse_dump_u(sp_count_r)= &
613                      1.e12*gridsigma(ix,jy,kz)/volumen(ix,jy,kz)/ &
614                      outnum*weightair/weightmolar(ks)/ &
615                      densityoutgrid(ix,jy,kz)
616              else ! concentration is zero
617                  sp_zer=.true.
618              endif
619              end do
620            end do
621          end do
622         write(unitoutgridppt) sp_count_i
623         write(unitoutgridppt) (sparse_dump_i(i),i=1,sp_count_i)
624         write(unitoutgridppt) sp_count_r
625         write(unitoutgridppt) (sparse_dump_r(i),i=1,sp_count_r)
626         write(unitoutgridppt) sp_count_r
627         write(unitoutgridppt) (sparse_dump_u(i),i=1,sp_count_r)
628         endif ! surf_only
629
630      endif ! output for ppt
631
632  end do
633  end do
634
635    close(unitoutgridppt)
636    close(unitoutgrid)
637
638  end do
639
640
641
642  ! Reinitialization of grid
643  !*************************
644
645  do ks=1,nspec
646  do kp=1,maxpointspec_act
647    do i=1,numreceptor
648      creceptor(i,ks)=0.
649    end do
650    do jy=0,numygridn-1
651      do ix=0,numxgridn-1
652        do l=1,nclassunc
653          do nage=1,nageclass
654            do kz=1,numzgrid
655              griduncn(ix,jy,kz,ks,kp,l,nage)=0.
656            end do
657          end do
658        end do
659      end do
660    end do
661  end do
662  end do
663
664  if (mp_measure_time) then
665    call cpu_time(mp_root_time_end)
666    mp_root_wtime_end = mpi_wtime()
667    mp_root_time_total = mp_root_time_total + (mp_root_time_end - mp_root_time_beg)
668    mp_root_wtime_total = mp_root_wtime_total + (mp_root_wtime_end - mp_root_wtime_beg)
669  end if
670
671end subroutine concoutput_surf_nest
672
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG