returns a grid_integer containing Horton orders. Horton orders are computed on the entire space-filled basin.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(grid_integer), | intent(in) | :: | flowDirection | |||
type(grid_integer), | intent(inout) | :: | orders | |||
integer, | intent(out), | optional | :: | basinOrder |
the maximum order of the basin |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
integer, | public | :: | cellsCount | ||||
integer, | public | :: | col |
current cell |
|||
logical, | public | :: | confluence |
true if confluence |
|||
integer, | public | :: | i | ||||
integer, | public | :: | iDown |
downstream cell |
|||
integer, | public | :: | j | ||||
integer, | public | :: | jDown |
downstream cell |
|||
integer, | public | :: | numConf |
number of confluences |
|||
integer, | public | :: | order |
Horton order |
|||
logical, | public | :: | outlet |
true if basin outlet |
|||
integer, | public | :: | row |
current cell |
SUBROUTINE HortonOrders & ! (flowDirection,orders,basinOrder) IMPLICIT NONE !Arguments with intent in: TYPE (grid_integer), INTENT (IN) :: flowDirection !Arguments with intent out or inout TYPE (grid_integer), INTENT (INOUT) :: orders INTEGER, OPTIONAL, INTENT (OUT) :: basinOrder !!the maximum order of the basin !local declarations: LOGICAL :: confluence !!true if confluence LOGICAL :: outlet !!true if basin outlet INTEGER :: row, col !!current cell INTEGER :: iDown, jDown !!downstream cell INTEGER :: numConf !!number of confluences INTEGER :: order !! Horton order INTEGER :: cellsCount INTEGER :: i, j !--------------------------------end of declaration---------------------------- order = 1 numConf = 1 DO WHILE (numConf > 0) ! se non trovo confluenze ! di classe order ! l'operazione รจ terminata CALL Catch ('info', 'Morphology', 'Elaborating reaches of stream order: ', & argument = ToString(order)) numConf = 0 !-----follow the reach till a confluence or a basin outlet------ DO j = 1,orders % jdim DO i = 1,orders % idim IF(CellIsSpring(i,j,flowDirection)) THEN !found a spring row = i col = j outlet = .FALSE. confluence = .FALSE. cellsCount = 0 orders % mat(i,j) = 1 DO WHILE (.NOT. outlet) ! follow the reach till the basin outlet IF (orders % mat(row,col) == order ) THEN cellsCount = cellsCount + 1 ENDIF CALL DownstreamCell(row, col, & flowDirection%mat(row,col), & iDown, jDown) IF (cellsCount >= 1 ) THEN !I am in the reach of that order !check if downstream cell is a confluence to increment horton order !Downstream the confluence, till the basin outlet, as temptative value, !order is increased by 1 (order + 1) IF ( .NOT. confluence ) THEN CALL ConfluenceIsAround (iDown, jDown, row, col, & flowDirection,confluence,orders,order) IF(confluence) numConf = numConf + 1 ENDIF outlet = CheckOutlet (row,col,iDown,jDown,flowDirection) IF (.NOT. outlet) THEN IF (.NOT. confluence) THEN orders % mat(iDown,jDown) = order ELSE orders % mat(iDown,jDown) = order + 1 ENDIF ENDIF ENDIF ! cellsCount >= 1 outlet = CheckOutlet(row,col,iDown,jDown,flowDirection) !loop row = iDown col = jDown END DO ENDIF ENDDO ENDDO !ciclo sulla matrice ordini !------------------------------------------------------------------------------ order = order + 1 ENDDO IF ( PRESENT (basinOrder) ) THEN basinOrder = order - 1 END IF END SUBROUTINE HortonOrders