Ignore:
File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/petra/src/writeheader_txt.f90

    r20 r36  
    11!**********************************************************************
    2 ! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
     2! Copyright 1998-2015                                                 *
    33! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
    44! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
     
    3232  !                                                                            *
    3333  !     7 August 2002                                                          *
    34   !     modified IP 2013 for text output                                       *
     34  !                                                                            *
     35  !     2013, IP: IP, text            output                                   *
     36  !     2/2015, PS: version string length written, enclose version string in '
     37  !                 write out ldep_incr
     38  !
    3539  !*****************************************************************************
    3640  !                                                                            *
     
    5963  !************************
    6064
    61   open(unitheader,file=path(2)(1:length(2))//'header_txt', &
     65  open(unitheader,file=path(2)(1:length(2))//'header.txt', &
    6266       form='formatted',err=998)
    63   open(unitheader_txt,file=path(2)(1:length(2))//'header_txt_releases', &
     67  open(unitheader_rel,file=path(2)(1:length(2))//'header_releases.txt', &
    6468       form='formatted',err=998)
    6569
     
    6872  !*****************************
    6973 
    70   write(unitheader,*) '# ibdate,ibtime, iedate, ietime, flexversion'
    71   write(unitheader,*) ibdate, ibtime, iedate, ietime, trim(flexversion) !  'FLEXPART V9.0'
     74  write(unitheader,*) '# ibdate,ibtime, iedate, ietime, len(flexversion), flexversion'
     75  write(unitheader,*) ibdate, ibtime, iedate, ietime, len_trim(flexversion), "'"//trim(flexversion)//"'" !  'FLEXPART V9.0'
    7276  !if (ldirect.eq.1) then
    7377  !  write(unitheader,*) ibdate,ibtime,trim(flexversion) !  'FLEXPART V9.0'
     
    8791  write(unitheader,*) '# information on grid setup    '
    8892  write(unitheader,*) '#outlon0,outlat0,numxgrid,numygrid,dxout,dyout'
    89   write(unitheader,*) outlon0,outlat0,numxgrid,numygrid, &
    90        dxout,dyout 
     93  write(unitheader,*) outlon0,outlat0,numxgrid,numygrid, dxout,dyout
    9194  write(unitheader,*) '# numzgrid, outheight(.) '
    9295  write(unitheader,*) numzgrid,(outheight(i),i=1,numzgrid)
     
    119122
    120123
    121   write(unitheader_txt,*) '# information on release points'
    122   write(unitheader_txt,*) '# numpoint'
    123   write(unitheader_txt,*) numpoint
    124   write(unitheader_txt,*) '# for numpoint:'
     124  write(unitheader_rel,*) '# information on release points'
     125  write(unitheader_rel,*) '# numpoint'
     126  write(unitheader_rel,*) numpoint
     127  write(unitheader_rel,*) '# for numpoint:'
    125128  do i=1,numpoint
    126     write(unitheader_txt,*) ireleasestart(i),ireleaseend(i),kindz(i)
     129    write(unitheader_rel,*) ireleasestart(i),ireleaseend(i),kindz(i)
    127130    xp1=xpoint1(i)*dx+xlon0
    128131    yp1=ypoint1(i)*dy+ylat0
    129132    xp2=xpoint2(i)*dx+xlon0
    130133    yp2=ypoint2(i)*dy+ylat0
    131     write(unitheader_txt,*) xp1,yp1,xp2,yp2,zpoint1(i),zpoint2(i)
    132     write(unitheader_txt,*) npart(i),1
     134    write(unitheader_rel,*) xp1,yp1,xp2,yp2,zpoint1(i),zpoint2(i)
     135    write(unitheader_rel,*) npart(i),1
    133136    if (numpoint.le.1000) then
    134       write(unitheader_txt,*) compoint(i)
     137      write(unitheader_rel,*) compoint(i)
    135138    else
    136       write(unitheader_txt,*) compoint(1001)
     139      write(unitheader_rel,*) compoint(1001)
    137140    endif
    138141    do j=1,nspec
    139       write(unitheader_txt,*) xmass(i,j)
    140       write(unitheader_txt,*) xmass(i,j)
    141       write(unitheader_txt,*) xmass(i,j)
     142      write(unitheader_rel,*) xmass(i,j)
     143      write(unitheader_rel,*) xmass(i,j)
     144      write(unitheader_rel,*) xmass(i,j)
    142145    end do
    143146  end do
     
    148151  write(unitheader,*) '# information on model switches'
    149152  write(unitheader,*) '# method,lsubgrid,lconvection, ind_source,ind_receptor'
    150   write(unitheader,*) method,lsubgrid,lconvection, &
    151        ind_source,ind_receptor
     153  write(unitheader,*) method,lsubgrid,lconvection,ind_source,ind_receptor
    152154
    153155  ! Write age class information
     
    160162  !Do not write topography to text output file. Keep it on the binary one
    161163  !********************************
    162 
    163164  !do ix=0,numxgrid-1
    164165  !  write(unitheader,*) (oroout(ix,jy),jy=0,numygrid-1)
    165166  !end do
    166167
    167 
     168  ! Write deposition type
     169  !***********************
    168170 
    169 
     171  write(unitheader,*) '# information on incremental / accum. deposition'
     172  write(unitheader,*) ldep_incr
    170173
    171174  close(unitheader)
    172   close(unitheader_txt)
    173 
     175  close(unitheader_rel)
    174176
    175177!  open(unitheader,file=path(2)(1:length(2))//'header_nml', &
     
    181183
    182184
    183 998   write(*,*) ' #### FLEXPART MODEL ERROR!   THE FILE         #### '
     185998 continue
     186  write(*,*) ' #### FLEXPART MODEL ERROR!   THE FILE         #### '
    184187  write(*,*) ' #### '//path(2)(1:length(2))//'header_txt'//' #### '
    185188  write(*,*) ' #### CANNOT BE OPENED. IF A FILE WITH THIS    #### '
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG