Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | N1 | |||
integer, | intent(in) | :: | N1NumVert | |||
integer, | intent(in) | :: | N2 | |||
integer, | intent(in) | :: | N2NumVert | |||
integer, | intent(inout) | :: | NumVerticesOverlap | |||
integer, | intent(out) | :: | NIN |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE INCLOS(N1,N1NumVert,N2,N2NumVert,NumVerticesOverlap,NIN)
! SUBROUTINE INFORMATION:
! AUTHOR Legacy Code
! DATE WRITTEN
! MODIFIED na
! RE-ENGINEERED Lawrie, Oct 2000
! PURPOSE OF THIS SUBROUTINE:
! This subroutine determines which vertices of figure N1 lie within figure N2.
! METHODOLOGY EMPLOYED:
! For vertex N of figure N1 to lie within figure N2, it must be
! on or to the right of all sides of figure N2, assuming
! figure N2 is convex.
! REFERENCES:
! BLAST/IBLAST code, original author George Walton
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: N1 ! Figure number of figure 1
INTEGER, INTENT(IN) :: N1NumVert ! Number of vertices of figure 1
INTEGER, INTENT(IN) :: N2 ! Figure number of figure 2
INTEGER, INTENT(IN) :: N2NumVert ! Number of vertices of figure 2
INTEGER, INTENT(INOUT) :: NumVerticesOverlap ! Number of vertices which overlap
INTEGER, INTENT(OUT) :: NIN ! Number of vertices of figure 1 within figure 2
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER K ! Vertex number of the overlap
INTEGER M ! Side number of figure N2
INTEGER N ! Vertex number of figure N1
LOGICAL CycleMainLoop ! Sets when to cycle main loop
REAL(r64) HFunct
NIN=0
DO N = 1, N1NumVert
CycleMainLoop = .FALSE.
! Eliminate cases where vertex N is to the left of side M.
DO M = 1, N2NumVert
HFunct=HCX(N,N1)*HCA(M,N2)+HCY(N,N1)*HCB(M,N2)+HCC(M,N2)
IF (HFunct > 0.0D0 ) THEN
CycleMainLoop = .TRUE. ! Set to cycle to the next value of N
EXIT ! M DO loop
END IF
END DO
IF (CycleMainLoop) CYCLE
NIN=NIN+1
! Check for duplication of previously determined points.
IF (NumVerticesOverlap /= 0) THEN
DO K = 1, NumVerticesOverlap
IF ((XTEMP(K) == HCX(N,N1)).AND.(YTEMP(K) == HCY(N,N1))) THEN
CycleMainLoop = .TRUE. ! Set to cycle to the next value of N
EXIT ! K DO loop
END IF
END DO
IF (CycleMainLoop) CYCLE
END IF
! Record enclosed vertices in temporary arrays.
NumVerticesOverlap = NumVerticesOverlap + 1
XTEMP(NumVerticesOverlap) = HCX(N,N1)
YTEMP(NumVerticesOverlap) = HCY(N,N1)
END DO
RETURN
END SUBROUTINE INCLOS