Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(inout) | :: | LoopType | |||
integer, | intent(inout) | :: | LoopNum | |||
integer, | intent(inout) | :: | ArrayCount | |||
integer, | intent(inout) | :: | LoopCount | |||
logical, | intent(inout) | :: | ConnectionFlag |
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.
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 FindFirstLastPtr(LoopType,LoopNum,ArrayCount,LoopCount,ConnectionFlag)
! SUBROUTINE INFORMATION:
! AUTHOR Dan Fisher
! DATE WRITTEN July 2005
! MODIFIED
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Initializes the energy components of the data structures
! METHODOLOGY EMPLOYED:
! Once all compsets have been established (second iteration) find all components
! subcomponents, etc.
! REFERENCES:
! na
! USE STATEMENTS:
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS
INTEGER,INTENT(INOUT) :: ArrayCount
INTEGER,INTENT(INOUT) :: LoopType
INTEGER,INTENT(INOUT) :: LoopNum
INTEGER,INTENT(INOUT) :: LoopCount
LOGICAL,INTENT(INOUT) :: ConnectionFlag
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, PARAMETER :: TypeComp = 1
INTEGER, PARAMETER :: TypeSubComp = 2
INTEGER, PARAMETER :: TypeSubSubComp = 3
INTEGER, PARAMETER :: EnergyTransfer = 1
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
TYPE IdentifyLoop
INTEGER :: LoopNum = 0
INTEGER :: LoopType = 0
END TYPE IdentifyLoop
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
TYPE (IdentifyLoop), SAVE, ALLOCATABLE, DIMENSION(:) :: LoopStack
TYPE (IdentifyLoop), SAVE, ALLOCATABLE, DIMENSION(:) :: TempLoopStack
INTEGER :: BranchNum
INTEGER :: Index
INTEGER :: DemandSideLoopNum
INTEGER :: DemandSideBranchNum
INTEGER :: DemandSideCompNum
INTEGER :: SupplySideCompNum
INTEGER :: DemandSideLoopType
LOGICAL,Save :: OneTimeFlag = .True. ! Flag set to make sure you initialize reports one time
LOGICAL :: Found
integer :: countloop
RETURN
IF(OneTimeFlag)THEN
ALLOCATE (LoopStack(MaxLoopArraySize))
ALLOCATE (TempLoopStack(MaxLoopArraySize))
ALLOCATE (DemandSideConnect(MaxCompArraySize))
OneTimeFlag = .FALSE.
END IF
LoopStack%LoopNum = 0
LoopStack%LoopType = 0
TempLoopStack%LoopNum = 0
TempLoopStack%LoopType = 0
ConnectionFlag = .FALSE.
! countloop=0
! write(outputfiledebug,*) '1228=lt,lc,lnum,cflag,arrcnt',looptype,loopcount,loopnum,connectionflag,arraycount
DO While (LoopCount > 0)
! write(outputfiledebug,*) '1231==lt,lc,lnum,cflag,arrcnt',looptype,loopcount,loopnum,connectionflag,arraycount
! write(outputfiledebug,*) 'loop=plname',trim(plantloop(loopnum)%name)
LoopCount = LoopCount - 1
! countloop=countloop+1
! if (countloop > 100) exit
IF (LoopType ==1)THEN
DO BranchNum = 1, VentRepPlantSupplySide(LoopNum)%TotalBranches
DO SupplySideCompNum = 1, VentRepPlantSupplySide(LoopNum)%Branch(BranchNum)%TotalComponents
DemandSideLoopType = &
VentRepPlantSupplySide(LoopNum)%Branch(BranchNum)%Comp(SupplySideCompNum)%ConnectPlant%LoopType
DemandSideLoopNum = &
VentRepPlantSupplySide(LoopNum)%Branch(BranchNum)%Comp(SupplySideCompNum)%ConnectPlant%LoopNum
DemandSideBranchNum = &
VentRepPlantSupplySide(LoopNum)%Branch(BranchNum)%Comp(SupplySideCompNum)%ConnectPlant%BranchNum
DemandSideCompNum = &
VentRepPlantSupplySide(LoopNum)%Branch(BranchNum)%Comp(SupplySideCompNum)%ConnectPlant%CompNum
!If the connection is valid load the connection array
IF(DemandSideLoopType == 1 .OR. DemandSideLoopType == 2)THEN
ConnectionFlag = .TRUE.
ArrayCount = ArrayCount + 1
IF(ArrayCount > MaxCompArraySize) THEN
! ALLOCATE(TempDemandSideConnect(MaxCompArraySize*2))
ALLOCATE(TempDemandSideConnect(MaxCompArraySize+100))
TempDemandSideConnect(1:MaxCompArraySize) = DemandSideConnect(1:MaxCompArraySize)
DEALLOCATE(DemandSideConnect)
ALLOCATE(DemandSideConnect(MaxCompArraySize*2))
DemandSideConnect(1:MaxCompArraySize) = TempDemandSideConnect(1:MaxCompArraySize)
DEALLOCATE(TempDemandSideConnect)
! MaxCompArraySize=MaxCompArraySize*2
MaxCompArraySize=MaxCompArraySize+100
END IF
DemandSideConnect(ArrayCount)%LoopType = DemandSideLoopType
DemandSideConnect(ArrayCount)%LoopNum = DemandSideLoopNum
DemandSideConnect(ArrayCount)%BranchNum = DemandSideBranchNum
DemandSideConnect(ArrayCount)%CompNum = DemandSideCompNum
found = .FALSE.
write(outputfiledebug,*) '1271=lstacksize',size(loopstack)
DO Index = 1, SIZE(LoopStack)
IF(DemandSideLoopNum == LoopStack(Index)%LoopNum .AND. &
DemandSideLoopType ==LoopStack(Index)%LoopType)THEN
found = .TRUE.
EXIT
END IF
END DO
IF(.NOT. found)THEN
LoopCount = LoopCount+1
! write(outputfiledebug,*) '1280=lc,mxsize',loopcount,maxlooparraysize
! write(outputfiledebug,*) '1281=dsloopnum,dslooptype',DemandSideLoopNum,DemandSideLoopType
IF(LoopCount > MaxLoopArraySize)THEN
! ALLOCATE(TempLoopStack(MaxLoopArraySize*2))
ALLOCATE(TempLoopStack(MaxLoopArraySize+100))
TempLoopStack(1:MaxLoopArraySize) = LoopStack(1:MaxLoopArraySize)
DEALLOCATE(LoopStack)
! ALLOCATE(LoopStack(MaxLoopArraySize*2))
ALLOCATE(LoopStack(MaxLoopArraySize+100))
LoopStack(1:MaxLoopArraySize) = TempLoopStack(1:MaxLoopArraySize)
DEALLOCATE(TempLoopStack)
! MaxLoopArraySize=MaxLoopArraySize*2
MaxLoopArraySize=MaxLoopArraySize+100
END IF
! write(outputfiledebug,*) '1294=lcnt,dsloopnum,dslooptype',loopcount,DemandSideLoopNum,DemandSideLoopType
LoopStack(LoopCount)%LoopNum = DemandSideLoopNum
LoopStack(LoopCount)%LoopType = DemandSideLoopType
END IF
END IF
END DO
END DO
ELSEIF(LoopType == 2)THEN
DO BranchNum = 1, VentRepCondSupplySide(LoopNum)%TotalBranches
DO SupplySideCompNum = 1, VentRepCondSupplySide(LoopNum)%Branch(BranchNum)%TotalComponents
DemandSideLoopType = &
VentRepCondSupplySide(LoopNum)%Branch(BranchNum)%Comp(SupplySideCompNum)%ConnectPlant%LoopType
DemandSideLoopNum = &
VentRepCondSupplySide(LoopNum)%Branch(BranchNum)%Comp(SupplySideCompNum)%ConnectPlant%LoopNum
DemandSideBranchNum = &
VentRepCondSupplySide(LoopNum)%Branch(BranchNum)%Comp(SupplySideCompNum)%ConnectPlant%BranchNum
DemandSideCompNum = &
VentRepCondSupplySide(LoopNum)%Branch(BranchNum)%Comp(SupplySideCompNum)%ConnectPlant%CompNum
!If the connection is valid load the connection array
IF(DemandSideLoopType == 1 .OR. DemandSideLoopType == 2)THEN
ConnectionFlag = .TRUE.
ArrayCount = ArrayCount + 1
IF(ArrayCount > MaxCompArraySize)THEN
! ALLOCATE(TempDemandSideConnect(MaxCompArraySize*2))
ALLOCATE(TempDemandSideConnect(MaxCompArraySize+100))
TempDemandSideConnect(1:MaxCompArraySize) = DemandSideConnect(1:MaxCompArraySize)
DEALLOCATE(DemandSideConnect)
! ALLOCATE(DemandSideConnect(MaxCompArraySize*2))
ALLOCATE(DemandSideConnect(MaxCompArraySize+100))
DemandSideConnect(1:MaxCompArraySize) = TempDemandSideConnect(1:MaxCompArraySize)
DEALLOCATE(TempDemandSideConnect)
! MaxCompArraySize=MaxCompArraySize*2
MaxCompArraySize=MaxCompArraySize+100
END IF
DemandSideConnect(ArrayCount)%LoopType = DemandSideLoopType
DemandSideConnect(ArrayCount)%LoopNum = DemandSideLoopNum
DemandSideConnect(ArrayCount)%BranchNum = DemandSideBranchNum
DemandSideConnect(ArrayCount)%CompNum = DemandSideCompNum
found = .FALSE.
DO Index = 1, SIZE(LoopStack)
IF(DemandSideLoopNum == LoopStack(Index)%LoopNum .AND. &
DemandSideLoopType ==LoopStack(Index)%LoopType)THEN
found = .TRUE.
EXIT
END IF
END DO
IF(.NOT. found)THEN
LoopCount = LoopCount+1
! write(outputfiledebug,*) '1341=lcnt,arrsize',loopcount,maxlooparraysize
! write(outputfiledebug,*) '1342=lsloopnum,dslooptype',DemandSideLoopNum,DemandSideLoopType
IF(LoopCount > MaxLoopArraySize)THEN
! ALLOCATE(TempLoopStack(MaxLoopArraySize*2))
ALLOCATE(TempLoopStack(MaxLoopArraySize+100))
TempLoopStack(1:MaxLoopArraySize) = LoopStack(1:MaxLoopArraySize)
DEALLOCATE(LoopStack)
! ALLOCATE(LoopStack(MaxLoopArraySize*2))
ALLOCATE(LoopStack(MaxLoopArraySize+100))
LoopStack(1:MaxLoopArraySize) = TempLoopStack(1:MaxLoopArraySize)
DEALLOCATE(TempLoopStack)
! MaxLoopArraySize=MaxLoopArraySize*2
MaxLoopArraySize=MaxLoopArraySize+100
END IF
LoopStack(LoopCount)%LoopNum = DemandSideLoopNum
LoopStack(LoopCount)%LoopType = DemandSideLoopType
END IF
END IF
END DO
END DO
ELSE
write(outputfiledebug,*) '1361=error'
!error
END IF
!now unload the LoopNum and LoopType arrays
IF(LoopCount > 0)THEN
LoopType = LoopStack(LoopCount)%LoopType
LoopNum = LoopStack(LoopCount)%LoopNum
END IF
END DO !While loop
RETURN
END SUBROUTINE FindFirstLastPtr