Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/concoutput.f90

    r36 r20  
    11!**********************************************************************
    2 ! Copyright 1998-2015                                                 *
     2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
    33! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
    44! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
     
    4747  !                                                                            *
    4848  !     2008 new sparse matrix format                                          *
    49   !     PS, 2/2015: option to produce incremental deposition output
    50   !                 access= -> position=
    5149  !                                                                            *
    5250  !*****************************************************************************
     
    110108  write(adate,'(i8.8)') jjjjmmdd
    111109  write(atime,'(i6.6)') ihmmss
    112   open(unitdates,file=path(2)(1:length(2))//'dates', position='append')
     110  open(unitdates,file=path(2)(1:length(2))//'dates', ACCESS='APPEND')
    113111  write(unitdates,'(a)') adate//atime
    114112  close(unitdates) 
     
    590588  !*************************
    591589
    592   creceptor=0.
    593   gridunc=0.
    594   if (ldep_incr) then ! incremental deposition output
    595     wetgridunc=0.
    596     drygridunc=0.
    597   endif
    598  
     590  do ks=1,nspec
     591  do kp=1,maxpointspec_act
     592    do i=1,numreceptor
     593      creceptor(i,ks)=0.
     594    end do
     595    do jy=0,numygrid-1
     596      do ix=0,numxgrid-1
     597        do l=1,nclassunc
     598          do nage=1,nageclass
     599            do kz=1,numzgrid
     600              gridunc(ix,jy,kz,ks,kp,l,nage)=0.
     601            end do
     602          end do
     603        end do
     604      end do
     605    end do
     606  end do
     607  end do
     608
     609
    599610end subroutine concoutput
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG