ExportShape Subroutine

private subroutine ExportShape(dem, flowDirection)

export shape file of river network


(1.2) create shape file

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: dem
type(grid_integer), intent(in) :: flowDirection

Variables

Type Visibility Attributes Name Initial
integer, public :: K
real, public :: X
real, public :: Y
character(len=300), public :: command
integer, public :: dot
character(len=300), public :: filename
integer, public :: iin
integer, public :: ivalle
integer, public :: jin
integer, public :: jvalle
logical(kind=4), public :: res
integer, public :: system

Source Code

SUBROUTINE ExportShape &
!
( dem, flowDirection )



IMPLICIT NONE

!arguments with intent (in):
TYPE (grid_real), INTENT (IN) :: dem
TYPE (grid_integer), INTENT (IN) :: flowDirection


!local declarations
INTEGER                           :: K, jin,iin,ivalle,jvalle
INTEGER                           :: dot
REAL                              :: X,Y
LOGICAL(4)                        :: res
CHARACTER(300)                    :: command
CHARACTER(300)                    :: filename
INTEGER                           :: system
!------------------------------------------------------------------------------

 
!------------------------------------------------------------------------------
!(1.1) create "generate file"
!------------------------------------------------------------------------------
OPEN(unit=876,file='tratti.gen')
OPEN(unit=877,file='tratti.csv')
WRITE(877,'(a)')'#ID;X0;Y0;X1;Y1;CELLS;STHRALER;SLOPE_L/L;LENGTH_m;&
                    DRAINED_CELLS'

!scan all list elements
current => list
DO 
       
    WRITE(876,*) current % id
    jin = current % j0
    iin = current % i0

    WRITE(877,'(I8,";",E14.7,";",E14.7,";",E14.7,";",E14.7,";",I8,";",I8,";",E14.7,";",&
                E14.7,";",E14.7,";",I8,";",E14.7,";",E14.7,";",E14.7,";",E14.7,";",E14.7)') &
	        current % id, current % x0, current % y0, &
            current % x1, current % y1, current % n_cells, &
            current % order, current % slope, current % length,  &
            current % area 
    	
    DO WHILE (.not.((jin.EQ.current%j1)  .AND. &
	                (iin.EQ.current%i1)))

	    X = DEM%xllcorner + jin *  DEM%cellsize - DEM%cellsize / 2.
	    Y = DEM%yllcorner + (DEM%idim - (iin-1)) * DEM%cellsize - DEM%cellsize / 2.

        WRITE(876,'(f20.7,a1,f20.7)') X,',',Y

        CALL DownstreamCell(iin,jin,flowDirection%mat(iin,jin),ivalle,jvalle)
    	 
	    iin = ivalle
	    jin = jvalle  
    	   													 
    END DO  !end single reach
       
        X = DEM%xllcorner + jin *  DEM%cellsize - DEM%cellsize / 2.
	    Y = DEM%yllcorner + (DEM%idim - (iin-1)) * DEM%cellsize - DEM%cellsize / 2.

        WRITE(876,'(f20.7,a1,f20.7)') X,',',Y	

        WRITE(876,'(a3)') 'end'
       
    IF ( .NOT. ASSOCIATED (current % next) )THEN !found last element of list
        EXIT
    END IF
       
    current => current % next
       
END DO	!end cycle on all reaches

WRITE(876,'(a3)') 'end'

CLOSE(876)
CLOSE(877)

!!------------------------------------------------------------------------------
!!(1.2) create shape file
!!------------------------------------------------------------------------------
filename = 'stream_network'
!dot = SCAN (filename,'.')
!IF (dot /= 0) filename = filename(1:dot-1)
command = 'gen2shp ' // filename(1:len_trim(filename)) // ' lines < tratti.gen'
res = SYSTEM(command) 

!create dbf
command='txt2dbf -C10 -R20.7 -R20.7 -R20.7 -R20.7 -I10 -I10 -R15.7 -R15.2  &
        -R15.2 -I10 -d ; tratti.csv ' // filename(1:len_trim(filename)) // '.dbf'
res = SYSTEM(command)

!------------------------------------------------------------------------------
!(1.3) delete intermediate files
!------------------------------------------------------------------------------

res = SYSTEM('del tratti.gen')
res = SYSTEM('del tratti.csv')




RETURN
END SUBROUTINE ExportShape