DataRootFinder.f90 Source File

This File Depends On

sourcefile~~datarootfinder.f90~~EfferentGraph sourcefile~datarootfinder.f90 DataRootFinder.f90 sourcefile~dataprecisionglobals.f90 DataPrecisionGlobals.f90 sourcefile~dataprecisionglobals.f90->sourcefile~datarootfinder.f90
Help

Files Dependent On This One

sourcefile~~datarootfinder.f90~~AfferentGraph sourcefile~datarootfinder.f90 DataRootFinder.f90 sourcefile~hvaccontrollers.f90 HVACControllers.f90 sourcefile~datarootfinder.f90->sourcefile~hvaccontrollers.f90 sourcefile~rootfinder.f90 RootFinder.f90 sourcefile~datarootfinder.f90->sourcefile~rootfinder.f90 sourcefile~simairservingzones.f90 SimAirServingZones.f90 sourcefile~hvaccontrollers.f90->sourcefile~simairservingzones.f90 sourcefile~hvacfurnace.f90 HVACFurnace.f90 sourcefile~hvaccontrollers.f90->sourcefile~hvacfurnace.f90 sourcefile~simulationmanager.f90 SimulationManager.f90 sourcefile~hvaccontrollers.f90->sourcefile~simulationmanager.f90 sourcefile~rootfinder.f90->sourcefile~hvaccontrollers.f90 sourcefile~sizingmanager.f90 SizingManager.f90 sourcefile~simairservingzones.f90->sourcefile~sizingmanager.f90 sourcefile~hvacmanager.f90 HVACManager.f90 sourcefile~simairservingzones.f90->sourcefile~hvacmanager.f90 sourcefile~hvacfurnace.f90->sourcefile~simairservingzones.f90 sourcefile~energyplus.f90 EnergyPlus.f90 sourcefile~simulationmanager.f90->sourcefile~energyplus.f90 sourcefile~utilityroutines.f90 UtilityRoutines.f90 sourcefile~simulationmanager.f90->sourcefile~utilityroutines.f90 sourcefile~sizingmanager.f90->sourcefile~simulationmanager.f90 sourcefile~hvacmanager.f90->sourcefile~simulationmanager.f90 sourcefile~heatbalanceairmanager.f90 HeatBalanceAirManager.f90 sourcefile~hvacmanager.f90->sourcefile~heatbalanceairmanager.f90 sourcefile~heatbalanceairmanager.f90->sourcefile~simulationmanager.f90 sourcefile~heatbalancesurfacemanager.f90 HeatBalanceSurfaceManager.f90 sourcefile~heatbalanceairmanager.f90->sourcefile~heatbalancesurfacemanager.f90 sourcefile~heatbalancesurfacemanager.f90->sourcefile~simulationmanager.f90 sourcefile~heatbalancemanager.f90 HeatBalanceManager.f90 sourcefile~heatbalancesurfacemanager.f90->sourcefile~heatbalancemanager.f90 sourcefile~heatbalancemanager.f90->sourcefile~simulationmanager.f90 sourcefile~heatbalancemanager.f90->sourcefile~sizingmanager.f90
Help

Source Code


Source Code

MODULE DataRootFinder   ! EnergyPlus Data-Only Module

          ! MODULE INFORMATION:
          !       AUTHOR         Dimitri Curtil
          !       DATE WRITTEN   February 2006
          !       MODIFIED       na
          !       RE-ENGINEERED  na

          ! PURPOSE OF THIS MODULE:
          ! This data-only module is a repository for variables and types used by the
          ! RootFinder module.

          ! METHODOLOGY EMPLOYED:
          ! na

          ! REFERENCES:
          ! na

          ! OTHER NOTES:
          ! na


          ! USE STATEMENTS:
USE DataPrecisionGlobals

IMPLICIT NONE   ! Enforce explicit typing of all variables

PUBLIC          ! By definition, all variables which are placed in this data
                ! -only module should be available to other modules and routines.
                ! Thus, all variables in this module must be PUBLIC.

          ! MODULE PARAMETER DEFINITIONS
  INTEGER, PARAMETER :: iSlopeNone        = 0  ! Undefined slope specification
  INTEGER, PARAMETER :: iSlopeIncreasing  = 1  ! For overall increasing function F(X) between min and max points
  INTEGER, PARAMETER :: iSlopeDecreasing  = -1 ! For overall decreasing function F(X) between min and max points


  ! Error because the overall slope appears to be flat between the min and max points,
  ! implying that the function might be singular over the interval:
  ! F(XMin) == F(XMax)
  INTEGER, PARAMETER :: iStatusErrorSingular      = -4
  ! Error because the overall slope assumption is not observed at the min and max points:
  ! - for an increasing function F(X), we expect F(XMin) < F(XMax)  otherwise error
  ! - for a decreasing function F(X),  we expect F(XMin) > F(XMax)  otherwise error
  ! Note that this error status does not detect strict monotonicity at points
  ! between the min and max points.
  INTEGER, PARAMETER :: iStatusErrorSlope          = -3
  ! Error because the current candidate X does not lie within the current lower an upper points:
  ! X < XLower or X > XUpper
  INTEGER, PARAMETER :: iStatusErrorBracket        = -2
  ! Error because the current candidate X does not lie within the min and max points:
  ! X < XMin or X > XMax
  INTEGER, PARAMETER :: iStatusErrorRange          = -1


  INTEGER, PARAMETER :: iStatusNone       =  0   ! Indeterminate error state (not converged), also default state
  INTEGER, PARAMETER :: iStatusOK         =  1   ! Unconstrained convergence achieved with root solution so that:
                                                 ! XMin < XRoot < XMax
  INTEGER, PARAMETER :: iStatusOKMin      =  2   ! Constrained convergence achieved with solution XRoot==XMin
  INTEGER, PARAMETER :: iStatusOKMax      =  3   ! Constrained convergence achieved with solution XRoot==XMax
  INTEGER, PARAMETER :: iStatusOKRoundOff =  4   ! Reached requested tolerance in X variables although Y=F(X) does not
                                                 ! satisfy unconstrained convergence check

  INTEGER, PARAMETER :: iStatusWarningNonMonotonic = 10  ! Error because F(X) is not strictly monotonic between the
                                                         ! lower and upper points
  INTEGER, PARAMETER :: iStatusWarningSingular     = 11  ! Error because F(X) == YLower or F(X) == YUpper


  INTEGER, PARAMETER :: iMethodNone          = -1 ! No solution method (used internally only when root finder is reset)
  INTEGER, PARAMETER :: iMethodBracket       = 0  ! Bracketting mode (used internally only to bracket root)
  INTEGER, PARAMETER :: iMethodBisection     = 1  ! Step performed using bisection method (aka interval halving)
  INTEGER, PARAMETER :: iMethodFalsePosition = 2  ! Step performed using false position method (aka regula falsi)
  INTEGER, PARAMETER :: iMethodSecant        = 3  ! Step performed using secant method
  INTEGER, PARAMETER :: iMethodBrent         = 4  ! Step performed using Brent's method
  ! Names for each solution method type
  CHARACTER(LEN=*), PARAMETER, DIMENSION(-1:4) :: SolutionMethodTypes =  &
                     (/'No solution method   ',  &
                       'Bracketting method   ',  &
                       'Bisection method     ',  &
                       'False position method',  &
                       'Secant method        ',  &
                       'Brent method         '/)


          ! DERIVED TYPE DEFINITIONS
  ! Type declaration for the numerical controls.
  TYPE ControlsType
    INTEGER           :: SlopeType  = iSlopeNone   ! Set to any of the iSlope<...> codes
    INTEGER           :: MethodType = iMethodNone  ! Desired solution method.
                                ! Set to any of the iMethod<...> codes except for iMethodNone and iMethodBracket
    REAL(r64)         :: TolX   = 1.0d-3           ! Relative tolerance for variable X
    REAL(r64)         :: ATolX  = 1.0d-3           ! Absolute tolerance for variable X
    REAL(r64)         :: ATolY  = 1.0d-3           ! Absolute tolerance for variable Y
  END TYPE ControlsType

  ! Type declaration for iterate tracking.
  TYPE PointType
    LOGICAL           :: DefinedFlag = .FALSE.     ! Set to true if point has been set; false otherwise
    REAL(r64)         :: X = 0.0d0                   ! X value
    REAL(r64)         :: Y = 0.0d0                   ! Y value = F(X)
  END TYPE PointType

  ! Type declaration for the root finder solution technique.
  TYPE RootFinderDataType
    TYPE (ControlsType)       :: Controls
    INTEGER                   :: StatusFlag = iStatusNone     ! Current status of root finder
                                                ! Valid values are any of the STATUS_<code> constants
    INTEGER                   :: CurrentMethodType = iMethodNone ! Solution method used to perform current step
    REAL(r64)                 :: XCandidate = 0.0d0       ! Candidate X value to use next when evaluating F(X)
    REAL(r64)                 :: ConvergenceRate = 0.0d0  ! Convergence rate achieved over the last 2 successive iterations
    TYPE (PointType)          :: Increment              ! Increment between last 2 iterations
    TYPE (PointType)          :: MinPoint               ! Point { XMin, F(XMin) }
    TYPE (PointType)          :: MaxPoint               ! Point { XMax, F(XMax) }
    TYPE (PointType)          :: LowerPoint             ! Point { XLower, F(XLower) } so that XLower <= XRoot
    TYPE (PointType)          :: UpperPoint             ! Point { XUpper, F(XUpper) } so that XRoot <= YUpper
    TYPE (PointType)          :: CurrentPoint           ! Last evaluated point { X, F(X) }
    INTEGER                   :: NumHistory = 0         ! Number of points stored in History
    TYPE (PointType)          :: History(3)             ! Vector containing last 3 best iterates
  END TYPE RootFinderDataType

          ! INTERFACE BLOCK SPECIFICATIONS:
          ! na

          ! MODULE VARIABLE DECLARATIONS:
          ! na


!     NOTICE
!
!     Copyright © 1996-2013 The Board of Trustees of the University of Illinois
!     and The Regents of the University of California through Ernest Orlando Lawrence
!     Berkeley National Laboratory.  All rights reserved.
!
!     Portions of the EnergyPlus software package have been developed and copyrighted
!     by other individuals, companies and institutions.  These portions have been
!     incorporated into the EnergyPlus software package under license.   For a complete
!     list of contributors, see "Notice" located in EnergyPlus.f90.
!
!     NOTICE: The U.S. Government is granted for itself and others acting on its
!     behalf a paid-up, nonexclusive, irrevocable, worldwide license in this data to
!     reproduce, prepare derivative works, and perform publicly and display publicly.
!     Beginning five (5) years after permission to assert copyright is granted,
!     subject to two possible five year renewals, the U.S. Government is granted for
!     itself and others acting on its behalf a paid-up, non-exclusive, irrevocable
!     worldwide license in this data to reproduce, prepare derivative works,
!     distribute copies to the public, perform publicly and display publicly, and to
!     permit others to do so.
!
!     TRADEMARKS: EnergyPlus is a trademark of the US Department of Energy.
!

END MODULE DataRootFinder

AirflowNetworkBalanceManager.f90 AirflowNetworkSolver.f90 BaseboardRadiator.f90 BaseboardRadiatorElectric.f90 BaseboardRadiatorSteam.f90 BaseboardRadiatorWater.f90 BranchInputManager.f90 BranchNodeConnections.f90 ConductionTransferFunctionCalc.f90 CoolTower.f90 CostEstimateManager.f90 CurveManager.f90 CVFOnlyRoutines.f90 DataAirflowNetwork.f90 DataAirLoop.f90 DataAirSystems.f90 DataBranchAirLoopPlant.f90 DataBranchNodeConnections.f90 DataBSDFWindow.f90 DataComplexFenestration.f90 DataContaminantBalance.f90 DataConvergParams.f90 DataConversions.f90 DataCostEstimate.f90 DataDaylighting.f90 DataDaylightingDevices.f90 Datadefineequip.f90 DataDElight.f90 DataEnvironment.f90 DataEquivalentLayerWindow.f90 DataErrorTracking.f90 DataGenerators.f90 DataGlobalConstants.f90 DataGlobals.f90 DataHeatBalance.f90 DataHeatBalFanSys.f90 DataHeatBalSurface.f90 DataHVACControllers.f90 DataHVACGlobals.f90 DataInterfaces.f90 DataIPShortCuts.f90 DataLoopNode.f90 DataMoistureBalance.f90 DataMoistureBalanceEMPD.f90 DataOutputs.f90 DataPhotovoltaics.f90 DataPlant.f90 DataPlantPipingSystems.f90 DataPrecisionGlobals.f90 DataReportingFlags.f90 DataRoomAir.f90 DataRootFinder.f90 DataRuntimeLanguage.f90 DataShadowingCombinations.f90 DataSizing.f90 DataStringGlobals.f90 DataSurfaceColors.f90 DataSurfaceLists.f90 DataSurfaces.f90 DataSystemVariables.f90 DataTimings.f90 DataUCSDSharedData.f90 DataVectorTypes.f90 DataViewFactorInformation.f90 DataWater.f90 DataZoneControls.f90 DataZoneEnergyDemands.f90 DataZoneEquipment.f90 DaylightingDevices.f90 DaylightingManager.f90 DElightManagerF.f90 DElightManagerF_NO.f90 DemandManager.f90 DesiccantDehumidifiers.f90 DirectAir.f90 DisplayRoutines.f90 DXCoil.f90 EarthTube.f90 EconomicLifeCycleCost.f90 EconomicTariff.f90 EcoRoof.f90 ElectricPowerGenerators.f90 ElectricPowerManager.f90 EMSManager.f90 EnergyPlus.f90 ExteriorEnergyUseManager.f90 ExternalInterface_NO.f90 FanCoilUnits.f90 FaultsManager.f90 FluidProperties.f90 General.f90 GeneralRoutines.f90 GlobalNames.f90 HeatBalanceAirManager.f90 HeatBalanceConvectionCoeffs.f90 HeatBalanceHAMTManager.f90 HeatBalanceInternalHeatGains.f90 HeatBalanceIntRadExchange.f90 HeatBalanceManager.f90 HeatBalanceMovableInsulation.f90 HeatBalanceSurfaceManager.f90 HeatBalFiniteDifferenceManager.f90 HeatRecovery.f90 Humidifiers.f90 HVACControllers.f90 HVACCooledBeam.f90 HVACDualDuctSystem.f90 HVACDuct.f90 HVACDXSystem.f90 HVACEvapComponent.f90 HVACFanComponent.f90 HVACFurnace.f90 HVACHeatingCoils.f90 HVACHXAssistedCoolingCoil.f90 HVACInterfaceManager.f90 HVACManager.f90 HVACMixerComponent.f90 HVACMultiSpeedHeatPump.f90 HVACSingleDuctInduc.f90 HVACSingleDuctSystem.f90 HVACSplitterComponent.f90 HVACStandAloneERV.f90 HVACSteamCoilComponent.f90 HVACTranspiredCollector.f90 HVACUnitaryBypassVAV.f90 HVACUnitarySystem.f90 HVACVariableRefrigerantFlow.f90 HVACWaterCoilComponent.f90 HVACWatertoAir.f90 HVACWatertoAirMultiSpeedHP.f90 InputProcessor.f90 MatrixDataManager.f90 MixedAir.f90 MoistureBalanceEMPDManager.f90 NodeInputManager.f90 NonZoneEquipmentManager.f90 OutAirNodeManager.f90 OutdoorAirUnit.f90 OutputProcessor.f90 OutputReportPredefined.f90 OutputReports.f90 OutputReportTabular.f90 PackagedTerminalHeatPump.f90 PackagedThermalStorageCoil.f90 Photovoltaics.f90 PhotovoltaicThermalCollectors.f90 PlantAbsorptionChillers.f90 PlantBoilers.f90 PlantBoilersSteam.f90 PlantCentralGSHP.f90 PlantChillers.f90 PlantCondLoopOperation.f90 PlantCondLoopTowers.f90 PlantEIRChillers.f90 PlantEvapFluidCoolers.f90 PlantExhaustAbsorptionChiller.f90 PlantFluidCoolers.f90 PlantGasAbsorptionChiller.f90 PlantGroundHeatExchangers.f90 PlantHeatExchanger.f90 PlantIceThermalStorage.f90 PlantLoadProfile.f90 PlantLoopEquipment.f90 PlantLoopSolver.f90 PlantManager.f90 PlantOutsideEnergySources.f90 PlantPipeHeatTransfer.f90 PlantPipes.f90 PlantPipingSystemManager.f90 PlantPondGroundHeatExchanger.f90 PlantPressureSystem.f90 PlantPumps.f90 PlantSolarCollectors.f90 PlantSurfaceGroundHeatExchanger.f90 PlantUtilities.f90 PlantValves.f90 PlantWaterSources.f90 PlantWaterThermalTank.f90 PlantWatertoWaterGSHP.f90 PlantWaterUse.f90 PollutionAnalysisModule.f90 PoweredInductionUnits.f90 PsychRoutines.f90 Purchasedairmanager.f90 RadiantSystemHighTemp.f90 RadiantSystemLowTemp.f90 RefrigeratedCase.f90 ReportSizingManager.f90 ReturnAirPath.f90 RoomAirManager.f90 RoomAirModelCrossVent.f90 RoomAirModelDisplacementVent.f90 RoomAirModelMundt.f90 RoomAirModelUFAD.f90 RoomAirModelUserTempPattern.f90 RootFinder.f90 RuntimeLanguageProcessor.f90 ScheduleManager.f90 SetPointManager.f90 SimAirServingZones.f90 SimulationManager.f90 SizingManager.f90 SolarReflectionManager.f90 SolarShading.f90 SortAndStringUtilities.f90 sqlite3.c SQLiteCRoutines.c SQLiteFortranRoutines.f90 SQLiteFortranRoutines_NO.f90 StandardRatings.f90 SurfaceGeometry.f90 SystemAvailabilityManager.f90 SystemReports.f90 TarcogComplexFenestration.f90 ThermalChimney.f90 ThermalComfort.f90 UnitHeater.f90 UnitVentilator.f90 UserDefinedComponents.f90 UtilityRoutines.f90 VectorUtilities.f90 VentilatedSlab.f90 WaterManager.f90 WeatherManager.f90 WindowAC.f90 WindowComplexManager.f90 WindowEquivalentLayer.f90 WindowManager.f90 WindTurbine.f90 Zoneairloopequipmentmanager.f90 ZoneContaminantPredictorCorrector.f90 ZoneDehumidifier.f90 Zoneequipmentmanager.f90 ZonePlenumComponent.f90 ZoneTempPredictorCorrector.f90