Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
| Type | Intent | Optional | Attributes | Name | ||
|---|---|---|---|---|---|---|
| logical, | intent(inout) | :: | ErrorsFound | 
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 GetUserDefinedPatternData(ErrorsFound)
          ! SUBROUTINE INFORMATION:
          !       AUTHOR         Brent Griffith
          !       DATE WRITTEN   Aug 2005
          !       MODIFIED       na
          !       RE-ENGINEERED  na
          ! PURPOSE OF THIS SUBROUTINE:
          ! This routine "gets" all the data for the "User-Defined RoomAir"
          ! METHODOLOGY EMPLOYED:
          ! usual energyplus input routines
          ! for the actual patterns, a single structure array holds
          ! different patterns in nested derived types.
          ! REFERENCES:
          ! na
          ! USE STATEMENTS:
          ! na
  USE DataGlobals,    ONLY: NumOfZones
  USE DataInterfaces, ONLY: ShowMessage
  USE InputProcessor, ONLY : FindItemInList, GetNumObjectsFound, GetObjectItem, GetObjectDefMaxArgs
  USE DataIPShortCuts
  USE DataSurfaces,   ONLY: Surface, TotSurfaces, SurfaceClass_IntMass
  USE DataHeatBalance, ONLY: Zone
  USE ScheduleManager,  ONLY : GetScheduleIndex
  USE RoomAirModelUserTempPattern, ONLY: FigureNDheightInZone
  USE DataZoneEquipment, ONLY: ZoneEquipConfig
  USE DataErrorTracking, ONLY: TotalWarningErrors, TotalRoomAirPatternTooLow, TotalRoomAirPatternTooHigh
  USE General, ONLY: RoundSigDigits
  IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
          ! SUBROUTINE ARGUMENT DEFINITIONS:
  LOGICAL, INTENT(INOUT) :: ErrorsFound  ! True if errors found during this get input routine
          ! SUBROUTINE PARAMETER DEFINITIONS:
  CHARACTER(len=*), PARAMETER :: RoutineName='GetUserDefinedPatternData: '
          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na
          ! DERIVED TYPE DEFINITIONS:
          ! na
          ! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
  INTEGER                                     :: NumAlphas    !number of alphas
  INTEGER                                     :: NumNumbers   ! Number of numbers encountered
  INTEGER                                     :: Status       ! Notes if there was an error in processing the input
  INTEGER         :: thisSurfinZone !working variable for indexing surfaces within a ZoneInfo structure
  INTEGER         :: thisHBsurfID !working variable for indexing surfaces in main Surface structure
  INTEGER         :: thisPattern
!unused1208  INTEGER         :: void  ! unused integer needed for parameter in subroutine call
!unused1208  INTEGER         :: MaxAlphaCount !max number of alphas in a type of extensible object
!unused1208  INTEGER         :: MaxNumCount !Max number of Numbers in a type of extensible object
  INTEGER         :: i ! do loop indexer
  INTEGER         :: numPairs ! number of zeta/deltaTai pairs
  INTEGER         :: ObjNum ! loop indexer of input objects if the same type
  INTEGER         :: ZoneNum ! zone number in heat balance domain
  INTEGER         :: found !test for FindItemInList
    !access input file and setup
  numTempDistContrldZones = GetNumObjectsFound(cUserDefinedControlObject)
  NumConstantGradient     = GetNumObjectsFound(cTempPatternConstGradientObject)
  NumTwoGradientInterp    = GetNumObjectsFound(cTempPatternTwoGradientObject)
  NumNonDimensionalHeight = GetNumObjectsFound(cTempPatternNDHeightObject)
  NumSurfaceMapping       = GetNumObjectsFound(cTempPatternSurfMapObject)
  NumAirTempPatterns = NumConstantGradient + NumTwoGradientInterp +  NumNonDimensionalHeight + NumSurfaceMapping
  cCurrentModuleObject = cUserDefinedControlObject
  IF (numTempDistContrldZones == 0) THEN
     IF (NumAirTempPatterns /= 0) THEN ! user may have missed control object
        Call ShowWarningError('Missing '//TRIM(cCurrentModuleObject)//' object needed to use roomair temperature patterns')
       ! ErrorsFound = .true.
     ENDIF
   RETURN
  ENDIF
  ! now allocate AirPatternZoneInfo to length of all zones for easy indexing
  IF (.not. Allocated(AirPatternZoneInfo)) THEN
       ALLOCATE(AirPatternZoneInfo(NumOfZones))
  ENDIF
  DO ObjNum = 1, numTempDistContrldZones
    CALL GetObjectItem(cCurrentModuleObject,ObjNum,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,Status, &
                             AlphaBlank=lAlphaFieldBlanks, AlphaFieldnames=cAlphaFieldNames, &
                             NumericFieldNames=cNumericFieldNames)
     !first get zone ID
    ZoneNum = 0
    ZoneNum = FindItemInList(cAlphaArgs(2), zone%name, NumOfZones)
    IF (ZoneNum == 0 ) THEN   !throw error
      CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'", invalid data.')
      CALL ShowContinueError('Invalid-not found '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))//'".' )
       ErrorsFound = .TRUE.
       RETURN ! halt to avoid hard crash
    ENDIF
    AirPatternZoneInfo(ZoneNum)%IsUsed         = .TRUE.
    AirPatternZoneInfo(ZoneNum)%Name           = cAlphaArgs(1)  !Name of this Control Object
    AirPatternZoneInfo(ZoneNum)%ZoneName       = cAlphaArgs(2) ! Zone Name
    AirPatternZoneInfo(ZoneNum)%AvailSched     = cAlphaArgs(3)
    IF (lAlphaFieldBlanks(3)) THEN
      AirPatternZoneInfo(ZoneNum)%AvailSchedID   = ScheduleAlwaysOn
    ELSE
      AirPatternZoneInfo(ZoneNum)%AvailSchedID   = GetScheduleIndex(cAlphaArgs(3) )
      IF (AirPatternZoneInfo(ZoneNum)%AvailSchedID == 0) THEN
        CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'", invalid data.')
        CALL ShowContinueError('Invalid-not found '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3))//'".')
        ErrorsFound = .TRUE.
      END IF
    ENDIF
    AirPatternZoneInfo(ZoneNum)%PatternCntrlSched = cAlphaArgs(4) ! Schedule Name for Leading Pattern Control for this Zone
    AirPatternZoneInfo(ZoneNum)%PatternSchedID    = GetScheduleIndex(cAlphaArgs(4) )
    IF (AirPatternZoneInfo(ZoneNum)%PatternSchedID == 0) THEN
      CALL ShowSevereError(RoutineName//TRIM(cCurrentModuleObject)//'="'//TRIM(cAlphaArgs(1))//'", invalid data.')
      CALL ShowContinueError('Invalid-not found '//TRIM(cAlphaFieldNames(4))//'="'//TRIM(cAlphaArgs(4))//'".' )
      ErrorsFound = .TRUE.
    END IF
    AirPatternZoneInfo(ZoneNum)%ZoneID            = ZoneNum
    !   figure number of surfaces for this zone
    AirPatternZoneInfo(ZoneNum)%totNumSurfs       = Zone(ZoneNum)%SurfaceLast &
                                                         - Zone(ZoneNum)%SurfaceFirst + 1
    !   allocate nested derived type for surface info
    ALLOCATE(AirPatternZoneInfo(ZoneNum)%Surf(AirPatternZoneInfo(ZoneNum)%totNumSurfs ) )
    !   Fill in what we know for nested structure for surfaces
    DO thisSurfinZone = 1, AirPatternZoneInfo(ZoneNum)%totNumSurfs
        thisHBsurfID = Zone(ZoneNum)%SurfaceFirst + thisSurfinZone - 1
        IF (Surface(thisHBsurfID)%Class == SurfaceClass_IntMass) THEN
          AirPatternZoneInfo(ZoneNum)%Surf(thisSurfinZone)%SurfID = thisHBsurfID
          AirPatternZoneInfo(ZoneNum)%Surf(thisSurfinZone)%Zeta   = 0.5d0
          CYCLE
        ENDIF
        AirPatternZoneInfo(ZoneNum)%Surf(thisSurfinZone)%SurfID = thisHBsurfID
        AirPatternZoneInfo(ZoneNum)%Surf(thisSurfinZone)%Zeta   = FigureNDheightInZone(thisHBsurfID)
    ENDDO !loop through surfaces in this zone
  ENDDO ! loop through number of 'RoomAir:TemperaturePattern:UserDefined' objects
  ! Check against AirModel.  Make sure there is a match here.
  DO ZoneNum=1,NumOfZones
    IF (AirModel(ZoneNum)%AirModelType /= RoomAirModel_UserDefined) CYCLE
    IF (AirPatternZoneInfo(ZoneNum)%IsUsed) CYCLE  ! There is a Room Air Temperatures object for this zone
    CALL ShowSevereError(RoutineName//'AirModel for Zone=['//TRIM(Zone(ZoneNum)%Name)//'] is indicated as "User Defined".')
    CALL ShowContinueError('...but missing a '//TRIM(cCurrentModuleObject)//' object for control.')
    ErrorsFound=.true.
  ENDDO
    ! now get user defined temperature patterns
  IF (.not. ALLOCATED( RoomAirPattern)) THEN
       ALLOCATE( RoomAirPattern(NumAirTempPatterns))
  ENDIF
  ! Four different objects to get
  cCurrentModuleObject = cTempPatternConstGradientObject
  DO  ObjNum= 1, NumConstantGradient
    thisPattern = ObjNum
    CALL GetObjectItem(cCurrentModuleObject,ObjNum,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,Status, &
                             AlphaFieldnames=cAlphaFieldNames, NumericFieldNames=cNumericFieldNames)
    RoomAirPattern(thisPattern)%Name               = cAlphaArgs(1)
    RoomAirPattern(thisPattern)%PatrnID            = rNumericArgs(1)
    RoomAirPattern(thisPattern)%PatternMode        = ConstGradTempPattern
    RoomAirPattern(thisPattern)%DeltaTstat         = rNumericArgs(2)
    RoomAirPattern(thisPattern)%DeltaTleaving      = rNumericArgs(3)
    RoomAirPattern(thisPattern)%DeltaTexhaust      = rNumericArgs(4)
    RoomAirPattern(thisPattern)%GradPatrn%Gradient = rNumericArgs(5)
  ENDDO
  cCurrentModuleObject = cTempPatternTwoGradientObject
  DO ObjNum = 1,  NumTwoGradientInterp
    thisPattern = NumConstantGradient + ObjNum
    CALL GetObjectItem(cCurrentModuleObject,ObjNum,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,Status, &
                             AlphaFieldnames=cAlphaFieldNames, NumericFieldNames=cNumericFieldNames)
    RoomAirPattern(thisPattern)%PatternMode = TwoGradInterpPattern
    RoomAirPattern(thisPattern)%Name        = cAlphaArgs(1)
    RoomAirPattern(thisPattern)%PatrnID     = rNumericArgs(1)
    RoomAirPattern(thisPattern)%TwoGradPatrn%TstatHeight    = rNumericArgs(2)
    RoomAirPattern(thisPattern)%TwoGradPatrn%TleavingHeight = rNumericArgs(3)
    RoomAirPattern(thisPattern)%TwoGradPatrn%TexhaustHeight = rNumericArgs(4)
    RoomAirPattern(thisPattern)%TwoGradPatrn%LowGradient    = rNumericArgs(5)
    RoomAirPattern(thisPattern)%TwoGradPatrn%HiGradient     = rNumericArgs(6)
    If (SameString(cAlphaArgs(2), 'OutdoorDryBulbTemperature')) THEN
          RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode = OutdoorDrybulbMode
    ELSEIF (SameString(cAlphaArgs(2), 'ZoneDryBulbTemperature')) THEN
          RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode = ZoneAirTempMode
    ELSEIF (SameString(cAlphaArgs(2), 'ZoneAndOutdoorTemperatureDifference')) THEN
          RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode = DeltaOutdoorZone
    ELSEIF (SameString(cAlphaArgs(2), 'SensibleCoolingLoad')) THEN
          RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode = SensibleCoolingMode
    ELSEIF (SameString(cAlphaArgs(2), 'SensibleHeatingLoad')) THEN
          RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode = SensibleHeatingMode
    ELSE
       CALL ShowSevereError('Invalid '//TRIM(cAlphaFieldNames(2))//' = '//TRIM(cAlphaArgs(2)) )
       CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//' = '//TRIM(cAlphaArgs(1)) )
       ErrorsFound = .TRUE.
    ENDIF
    RoomAirPattern(thisPattern)%TwoGradPatrn%UpperBoundTempScale     = rNumericArgs(7)
    RoomAirPattern(thisPattern)%TwoGradPatrn%LowerBoundTempScale     = rNumericArgs(8)
    RoomAirPattern(thisPattern)%TwoGradPatrn%UpperBoundHeatRateScale = rNumericArgs(9)
    RoomAirPattern(thisPattern)%TwoGradPatrn%LowerBoundHeatRateScale = rNumericArgs(10)
    ! now test the input some
    IF (RoomAirPattern(thisPattern)%TwoGradPatrn%HiGradient    &
        == RoomAirPattern(thisPattern)%TwoGradPatrn%LowGradient ) THEN
       CALL ShowWarningError('Upper and lower gradients equal, use '//TRIM(cTempPatternConstGradientObject)//' instead ')
       CALL ShowContinueError('Entered in '//TRIM(cCurrentModuleObject)//' = '//TRIM(cAlphaArgs(1)) )
    ENDIF
    IF (  (RoomAirPattern(thisPattern)%TwoGradPatrn%UpperBoundTempScale                          &
        == RoomAirPattern(thisPattern)%TwoGradPatrn%LowerBoundTempScale )                     &
        .and. (                                                                               &
             (RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode == OutdoorDrybulbMode)    &
        .or. (RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode ==  ZoneAirTempMode) &
        .or. (RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode == DeltaOutdoorZone) &
               )     ) THEN
      ! throw error, will cause divide by zero when used for scaling
      CALL ShowSevereError('Error in temperature scale in '//TRIM(cCurrentModuleObject)//': '//trim(cAlphaArgs(1)) )
      errorsfound = .true.
    ENDIF
    IF (  (RoomAirPattern(thisPattern)%TwoGradPatrn%HiGradient                                   &
        == RoomAirPattern(thisPattern)%TwoGradPatrn%LowGradient )                                &
        .and. (                                                                                  &
             (RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode == SensibleCoolingMode) &
        .or. (RoomAirPattern(thisPattern)%TwoGradPatrn%InterpolationMode == SensibleHeatingMode) &
              ) )THEN
      ! throw error, will cause divide by zero when used for scaling
      CALL ShowSevereError('Error in load scale in '//TRIM(cCurrentModuleObject)//': '//trim(cAlphaArgs(1)) )
      errorsfound = .true.
    ENDIF
  ENDDO
  cCurrentModuleObject =   cTempPatternNDHeightObject
  DO ObjNum = 1, NumNonDimensionalHeight
     thisPattern = NumConstantGradient+NumTwoGradientInterp + ObjNum
     RoomAirPattern(thisPattern)%PatternMode =NonDimenHeightPattern
     CALL GetObjectItem(cCurrentModuleObject,ObjNum,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,Status, &
                             AlphaFieldnames=cAlphaFieldNames, NumericFieldNames=cNumericFieldNames)
     RoomAirPattern(thisPattern)%Name       = cAlphaArgs(1)
     RoomAirPattern(thisPattern)%PatrnID    = rNumericArgs(1)
     RoomAirPattern(thisPattern)%DeltaTstat = rNumericArgs(2)
     RoomAirPattern(thisPattern)%DeltaTleaving = rNumericArgs(3)
     RoomAirPattern(thisPattern)%DeltaTexhaust = rNumericArgs(4)
     NumPairs = floor( (REAL(NumNumbers,r64) - 4.0d0)/2.0d0 )
      ! TODO error checking
     ALLOCATE( RoomAirPattern(thisPattern)%VertPatrn%ZetaPatrn(NumPairs)     )
     ALLOCATE( RoomAirPattern(thisPattern)%VertPatrn%DeltaTaiPatrn(NumPairs) )
     ! init these since they can't be in derived type
     RoomAirPattern(thisPattern)%VertPatrn%ZetaPatrn     = 0.0d0
     RoomAirPattern(thisPattern)%VertPatrn%DeltaTaiPatrn = 0.0d0
     DO i=0, NumPairs-1
        RoomAirPattern(thisPattern)%VertPatrn%ZetaPatrn(i+1)     = rNumericArgs(2*i + 5)
        RoomAirPattern(thisPattern)%VertPatrn%DeltaTaiPatrn(i+1) = rNumericArgs(2*i + 6)
     ENDDO
     !TODO  check order (TODO sort ? )
     DO i=2, NumPairs
        If (RoomAirPattern(thisPattern)%VertPatrn%ZetaPatrn(i)   &
            < RoomAirPattern(thisPattern)%VertPatrn%ZetaPatrn(i-1) ) Then
          Call ShowSevereError('Zeta values not in increasing order in '//TRIM(cCurrentModuleObject)//': '// &
                                              trim( cAlphaArgs(1)) )
          ErrorsFound = .TRUE.
        ENDIF
     ENDDO
  ENDDO
  cCurrentModuleObject = cTempPatternSurfMapObject
  DO ObjNum = 1,NumSurfaceMapping
     thisPattern = NumConstantGradient+NumTwoGradientInterp+NumNonDimensionalHeight+ObjNum
     RoomAirPattern(thisPattern)%PatternMode = SurfMapTempPattern
     CALL GetObjectItem(cCurrentModuleObject,ObjNum,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,Status, &
                             AlphaFieldnames=cAlphaFieldNames, NumericFieldNames=cNumericFieldNames)
     RoomAirPattern(thisPattern)%Name       = cAlphaArgs(1)
     RoomAirPattern(thisPattern)%PatrnID    = rNumericArgs(1)
     RoomAirPattern(thisPattern)%DeltaTstat = rNumericArgs(2)
     RoomAirPattern(thisPattern)%DeltaTleaving = rNumericArgs(3)
     RoomAirPattern(thisPattern)%DeltaTexhaust = rNumericArgs(4)
     NumPairs = NumNumbers - 4
     IF (NumPairs /= (NumAlphas - 1) ) THEN
       CALL ShowSevereError('Error in number of entries in '//TRIM(cCurrentModuleObject)//' object: '//trim(cAlphaArgs(1)) )
       errorsfound = .true.
     ENDIF
     ALLOCATE(RoomAirPattern(thisPattern)%MapPatrn%SurfName(NumPairs))
     ALLOCATE(RoomAirPattern(thisPattern)%MapPatrn%DeltaTai(NumPairs))
     ALLOCATE(RoomAirPattern(thisPattern)%MapPatrn%SurfID(NumPairs))
     ! init just allocated
     RoomAirPattern(thisPattern)%MapPatrn%SurfName = ' '
     RoomAirPattern(thisPattern)%MapPatrn%DeltaTai = 0.0d0
     RoomAirPattern(thisPattern)%MapPatrn%SurfID   = 0
     DO I=1, numPairs
        RoomAirPattern(thisPattern)%MapPatrn%SurfName(I)  = cAlphaArgs(I+1)
        RoomAirPattern(thisPattern)%MapPatrn%DeltaTai(I)  = rNumericArgs(I+4)
        found = FindItemInList(cAlphaArgs(I+1), Surface%Name, TotSurfaces)
        IF (found /= 0) THEN
          RoomAirPattern(thisPattern)%MapPatrn%SurfID(I) = found
        ELSE
          CALL ShowSevereError('Surface name not found in '//TRIM(cCurrentModuleObject)//' object: '//trim(cAlphaArgs(1)) )
          errorsfound = .true.
        ENDIF
     ENDDO
     RoomAirPattern(thisPattern)%MapPatrn%numSurfs = numPairs
  ENDDO
  IF (TotalRoomAirPatternTooLow > 0) THEN
    call ShowWarningError('GetUserDefinedPatternData: RoomAirModelUserTempPattern: '//  &
       trim(RoundSigDigits(TotalRoomAirPatternTooLow))//  &
       ' problem(s) in non-dimensional height calculations, '//  &
       'too low surface height(s) in relation to floor height of zone(s).')
    call ShowContinueError('...Use OutputDiagnostics,DisplayExtraWarnings; to see details.')
    TotalWarningErrors=TotalWarningErrors+TotalRoomAirPatternTooLow
  ENDIF
  IF (TotalRoomAirPatternTooHigh > 0) THEN
    call ShowWarningError('GetUserDefinedPatternData: RoomAirModelUserTempPattern: '//  &
       trim(RoundSigDigits(TotalRoomAirPatternTooHigh))//  &
       ' problem(s) in non-dimensional height calculations, '//  &
       'too high surface height(s) in relation to ceiling height of zone(s).')
    call ShowContinueError('...Use OutputDiagnostics,DisplayExtraWarnings; to see details.')
    TotalWarningErrors=TotalWarningErrors+TotalRoomAirPatternTooHigh
  ENDIF
  ! now do one time setups from and checks on user data
  ! Find and set return and exhaust node ids
  DO I = 1, NumOfZones
    IF  (AirPatternZoneInfo(I)%IsUsed) THEN
      ! first get return and exhaust air node index
      found = FindItemInList(AirPatternZoneInfo(I)%ZoneName, ZoneEquipConfig%ZoneName, NumOfZones)
      IF (found /= 0) then
            AirPatternZoneInfo(I)%ReturnAirNodeID = ZoneEquipConfig(found)%ReturnAirNode
            AirPatternZoneInfo(I)%ZoneNodeID      = ZoneEquipConfig(found)%ZoneNode
            If (Allocated(ZoneEquipConfig(found)%ExhaustNode)) then
               Allocate(AirPatternZoneInfo(I)%ExhaustAirNodeID(ZoneEquipConfig(found)%NumExhaustNodes))
               AirPatternZoneInfo(I)%ExhaustAirNodeID = ZoneEquipConfig(found)%ExhaustNode
            ENDIF !exhaust nodes present
      ENDIF !found ZoneEquipConf
      ! second get zone height values
      AirPatternZoneInfo(I)%ZoneHeight = Zone(I)%CeilingHeight
    ENDIF !air pattern is used
  ENDDO
  RETURN
END SUBROUTINE GetUserDefinedPatternData