Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | Name | |||
integer, | intent(out) | :: | NumNodes | |||
integer, | intent(out), | DIMENSION(:) | :: | NodeNumbers | ||
logical, | intent(out) | :: | ErrFlag | |||
integer, | intent(in) | :: | NodeFluidType | |||
character(len=*), | intent(in) | :: | NodeObjectType | |||
character(len=*), | intent(in) | :: | NodeObjectName | |||
integer, | intent(in) | :: | NodeConnectionType | |||
integer, | intent(in) | :: | NodeFluidStream | |||
logical, | intent(in) | :: | ObjectIsParent | |||
character(len=*), | intent(in), | optional | :: | InputFieldName |
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 GetNodeList(Name,NumNodes,NodeNumbers,ErrFlag,NodeFluidType,NodeObjectType,NodeObjectName, &
NodeConnectionType,NodeFluidStream,ObjectIsParent,InputFieldName)
! SUBROUTINE INFORMATION:
! AUTHOR Linda K. Lawrie
! DATE WRITTEN September 1999
! MODIFIED February 2003, Error Flag added
! February 2004, Fluid Type
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is called when the Get routines are specifically looking
! for a Node List. It should exist.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
CHARACTER(len=*), INTENT(IN) :: Name ! Node List Name for which information is obtained
INTEGER, INTENT(OUT) :: NumNodes ! Number of nodes accompanying this Name
INTEGER, INTENT(OUT), DIMENSION(:) :: NodeNumbers ! NodeNumbers accompanying this Name
LOGICAL, INTENT(OUT) :: ErrFlag ! Set to true when requested Node List not found
INTEGER, INTENT(IN) :: NodeFluidType ! Fluidtype for checking/setting node FluidType
CHARACTER(len=*), INTENT(IN) :: NodeObjectType ! Node Object Type (i.e. "Chiller:Electric")
CHARACTER(len=*), INTENT(IN) :: NodeObjectName ! Node Object Name (i.e. "MyChiller")
INTEGER, INTENT(IN) :: NodeConnectionType ! Node Connection Type (see DataLoopNode)
INTEGER, INTENT(IN) :: NodeFluidStream ! Which Fluid Stream (1,2,3,...)
LOGICAL, INTENT(IN) :: ObjectIsParent ! True/False
CHARACTER(len=*), INTENT(IN), OPTIONAL :: InputFieldName ! Input Field Name
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: RoutineName='GetNodeList: '
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER Try ! Indicator for this Name
IF (GetNodeInputFlag) THEN
CALL GetNodeListsInput(ErrFlag)
GetNodeInputFlag=.false.
ENDIF
! FluidType=NodeFluidType
NumNodes=0
NodeNumbers(1)=0
ErrFlag=.false.
Try=0
IF (NumOfNodeLists > 0) THEN
Try=FindItemInList(Name,NodeLists(1:NumOfNodeLists)%Name,NumOfNodeLists)
ENDIF
IF (Try /= 0) THEN
CALL GetNodeNums(Name,NumNodes,NodeNumbers,ErrFlag,NodeFluidType,NodeObjectType,NodeObjectName,NodeConnectionType, &
NodeFluidStream,ObjectIsParent,InputFieldName=InputFieldName)
ELSE
! only valid "error" here is when the Node List is blank
IF (Name /= Blank) THEN
CALL ShowSevereError(RoutineName//trim(NodeObjectType)//'="'//trim(NodeObjectName)//'", invalid data.')
IF (PRESENT(InputFieldName)) CALL ShowContinueError('...Ref field='//trim(InputFieldName))
CALL ShowContinueError('NodeList not found="'//TRIM(Name)//'".')
ErrFlag=.true.
ENDIF
ENDIF
RETURN
END SUBROUTINE GetNodeList