DownstreamCell Subroutine

public subroutine DownstreamCell(iin, jin, dir, is, js, dx, grid)

returns the position (is,js) of the downstream cell and, optionally, the flow path length, considering cardinal and diagonal direction

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: iin

current cell

integer(kind=short), intent(in) :: jin

current cell

integer(kind=long), intent(in) :: dir

flow direction

integer(kind=short), intent(out) :: is

downstream cell

integer(kind=short), intent(out) :: js

downstream cell

real(kind=float), intent(out), optional :: dx

flow path length [m]

type(grid_integer), intent(in), optional :: grid

used to define coordinate reference system


Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: ddx
real(kind=float), public :: x
real(kind=float), public :: xs
real(kind=float), public :: y
real(kind=float), public :: ys

Source Code

SUBROUTINE DownstreamCell &
!
(iin, jin, dir, is, js, dx, grid)

IMPLICIT NONE

!Arguments with intent in:
INTEGER (KIND = short), INTENT (IN) :: iin, jin !!current cell
INTEGER (KIND = long), INTENT (IN) :: dir !!flow direction 
TYPE(grid_integer), INTENT (IN),OPTIONAL:: grid !!used to define coordinate reference system

!Arguments with intent out:
INTEGER (KIND = short), INTENT (OUT) :: is,js !!downstream cell
REAL (KIND = float), INTENT (OUT) ,OPTIONAL :: dx !!flow path length [m]

!Local declarations
REAL (KIND = float) :: ddx,x,y,xs,ys

!--------------------end of declarations---------------------------------------

!east
IF ( dir == E ) THEN
    js = jin + 1
    is = iin
END IF

!south east
IF ( dir == SE ) THEN
    js = jin + 1
    is = iin + 1
END IF

!south
IF ( dir == S ) THEN
    js = jin
    is = iin + 1
END IF

!south west
IF ( dir == SW ) THEN
    js = jin - 1
    is = iin + 1
END IF

!west
IF ( dir == W ) THEN
    js = jin - 1
    is = iin
END IF

!north west
IF ( dir == NW ) THEN
    js = jin - 1
    is = iin - 1
END IF

!north
IF ( dir == N ) THEN
    js = jin
    is = iin - 1
END IF

!north easth
IF ( dir == NE ) THEN
    js = jin + 1
    is = iin - 1
END IF

IF ((PRESENT(dx)).and.(PRESENT(grid))) THEN
    CALL GetXY (iin,jin,grid,x,y)
    CALL GetXY (is,js,grid,xs,ys)
    
    point1 % system = grid % grid_mapping
    point2 % system = grid % grid_mapping

    point1 % northing = y  
    point1 % easting = x
    point2 % northing = ys  
    point2 % easting = xs

    ddx = distance(point1,point2)
    dx = ddx
    RETURN

ELSE IF ((PRESENT(dx)) .AND. .NOT. (PRESENT(grid))) THEN
   CALL Catch ('error', 'Morphology', 'missing grid while calculating downstream distance')
END IF

END SUBROUTINE DownstreamCell