| Copyright | (c) Junaid Rasheed 2021-2022 |
|---|---|
| License | MPL |
| Maintainer | jrasheed178@gmail.com |
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
LPPaver.Decide.Util
Description
Module defining useful utility functions for the LPPaver.Decide modules
Synopsis
- trace :: p -> p -> p
- applyExpression :: E -> VarMap -> Precision -> CN MPBall
- gradientExpression :: E -> VarMap -> Precision -> Vector (CN MPBall)
- applyExpressionList :: [E] -> VarMap -> Precision -> [CN MPBall]
- gradientExpressionList :: [E] -> VarMap -> Precision -> [Vector (CN MPBall)]
- applyExpressionDoubleList :: [[E]] -> VarMap -> Precision -> [[CN MPBall]]
- gradientExpressionDoubleList :: [[E]] -> VarMap -> Precision -> [[Vector (CN MPBall)]]
- applyESafeDoubleList :: [[ESafe]] -> VarMap -> Precision -> [[CN MPBall]]
- gradientESafeDoubleList :: [[ESafe]] -> VarMap -> Precision -> [[Vector (CN MPBall)]]
- checkFWithApply :: F -> VarMap -> Precision -> CN Kleenean
- filterOutFalseExpressions :: [((ESafe, BoxFun), CN MPBall)] -> [((ESafe, BoxFun), CN MPBall)]
- filterOutTrueExpressions :: [((ESafe, BoxFun), CN MPBall)] -> [((ESafe, BoxFun), CN MPBall)]
- decideRangesGEZero :: [((E, BoxFun), CN MPBall)] -> Bool
- mean :: [CN Dyadic] -> CN Rational
- safeMaximum :: (HasOrderAsymmetric a a, CanTestCertainly (OrderCompareType a a), CanTestErrorsPresent a) => a -> [a] -> a
- safeMaximumCentre :: [BoxFun] -> Box -> Maybe (CN Dyadic) -> Maybe (CN Dyadic)
- safeMaximumMinimum :: [BoxFun] -> Box -> Maybe (CN MPBall) -> Maybe (CN MPBall)
- safeMaximumMaximum :: [BoxFun] -> Box -> Maybe (CN MPBall) -> Maybe (CN MPBall)
- bisectWidestInterval :: VarMap -> (VarMap, VarMap)
- bisectWidestTypedInterval :: TypedVarMap -> (TypedVarMap, TypedVarMap)
- ensureVarMapWithinVarMap :: VarMap -> VarMap -> VarMap
- safelyComputeCornerValuesAndDerivatives :: [((ESafe, BoxFun), CN MPBall)] -> Box -> Maybe [(CN MPBall, CN MPBall, Vector (CN MPBall))]
- computeCornerValuesAndDerivatives :: [((ESafe, BoxFun), CN MPBall)] -> Box -> [(CN MPBall, CN MPBall, Vector (CN MPBall))]
- decideConjunctionRangesFalse :: [((ESafe, BoxFun), CN MPBall)] -> Bool
- decideConjunctionRangesTrue :: [((ESafe, BoxFun), CN MPBall)] -> Bool
- decideDisjunctionRangesTrue :: [((ESafe, BoxFun), CN MPBall)] -> Bool
- decideDisjunctionRangesFalse :: [((ESafe, BoxFun), CN MPBall)] -> Bool
- decideDisjunctionFalse :: [(ESafe, BoxFun)] -> TypedVarMap -> Precision -> Bool
- decideCNFFalse :: [[(ESafe, BoxFun)]] -> TypedVarMap -> Precision -> Bool
- decideConjunctionTrue :: [(ESafe, BoxFun)] -> TypedVarMap -> Precision -> Bool
- checkDisjunctionResults :: [(Maybe Bool, Maybe potentialModel)] -> Maybe potentialModel -> (Maybe Bool, Maybe potentialModel)
- checkConjunctionResults :: [(Maybe Bool, Maybe potentialModel)] -> Maybe potentialModel -> (Maybe Bool, Maybe potentialModel)
- substituteConjunctionEqualities :: [ESafe] -> [ESafe]
Documentation
applyExpressionList :: [E] -> VarMap -> Precision -> [CN MPBall] Source #
Run applyExpression on each E in a given list
gradientExpressionList :: [E] -> VarMap -> Precision -> [Vector (CN MPBall)] Source #
Run gradientExpression on each E in a given list
applyExpressionDoubleList :: [[E]] -> VarMap -> Precision -> [[CN MPBall]] Source #
Run applyExpressionList on each '[E.E]' in a given list
gradientExpressionDoubleList :: [[E]] -> VarMap -> Precision -> [[Vector (CN MPBall)]] Source #
Run gradientExpressionList on each '[E.E]' in a given list
applyESafeDoubleList :: [[ESafe]] -> VarMap -> Precision -> [[CN MPBall]] Source #
Run applyExpressionDoubleList on an [[ESafe]]
gradientESafeDoubleList :: [[ESafe]] -> VarMap -> Precision -> [[Vector (CN MPBall)]] Source #
Run gradientExpressionDoubleList on an [[ESafe]]
checkFWithApply :: F -> VarMap -> Precision -> CN Kleenean Source #
Evaluate an F over some VarMap with a given Precision using applyExpression
filterOutFalseExpressions :: [((ESafe, BoxFun), CN MPBall)] -> [((ESafe, BoxFun), CN MPBall)] Source #
Filter out expressions in a list which are certainly false. If an expression cannot be evaluated, do not filter it out.
filterOutTrueExpressions :: [((ESafe, BoxFun), CN MPBall)] -> [((ESafe, BoxFun), CN MPBall)] Source #
Filter out expressions in a list which are certainly true. If an expression cannot be evaluated, do not filter it out.
decideRangesGEZero :: [((E, BoxFun), CN MPBall)] -> Bool Source #
Returns true if any of the ranges of the given Expression have been evaluated to be greater than or equal to zero.
safeMaximum :: (HasOrderAsymmetric a a, CanTestCertainly (OrderCompareType a a), CanTestErrorsPresent a) => a -> [a] -> a Source #
Safely find the maximum of a list of ordered elements, avoiding exceptions by ignoring anything with errors
bisectWidestTypedInterval :: TypedVarMap -> (TypedVarMap, TypedVarMap) Source #
Bisect the widest interval in a TypedVarMap
ensureVarMapWithinVarMap :: VarMap -> VarMap -> VarMap Source #
Ensures that the first varMap is within the second varMap If it is, returns the first varMap. If it isn't modifies the varMap so that the returned varMap is within the second varMap Both varmaps must have the same number of vars in the same order (order of vars not checked)
safelyComputeCornerValuesAndDerivatives :: [((ESafe, BoxFun), CN MPBall)] -> Box -> Maybe [(CN MPBall, CN MPBall, Vector (CN MPBall))] Source #
Version of computeCornerValuesAndDerivatives that returns Nothing if a calculation contains an error
computeCornerValuesAndDerivatives :: [((ESafe, BoxFun), CN MPBall)] -> Box -> [(CN MPBall, CN MPBall, Vector (CN MPBall))] Source #
decideConjunctionRangesFalse :: [((ESafe, BoxFun), CN MPBall)] -> Bool Source #
Decide if the ranges of a conjunction of ESafe expressions is false in a standard manner
A range with an error is treated as false.
decideConjunctionRangesTrue :: [((ESafe, BoxFun), CN MPBall)] -> Bool Source #
Decide if the ranges of a conjunction of ESafe expressions is true in a standard manner
A range with an error is treated as false.
decideDisjunctionRangesTrue :: [((ESafe, BoxFun), CN MPBall)] -> Bool Source #
Decide if the ranges of a disjunction of ESafe expressions is true in a standard manner
A range with an error is treated as false.
decideDisjunctionRangesFalse :: [((ESafe, BoxFun), CN MPBall)] -> Bool Source #
Decide if the ranges of a disjunction of ESafe expressions is false in a standard manner
A range with an error is treated as false.
decideDisjunctionFalse :: [(ESafe, BoxFun)] -> TypedVarMap -> Precision -> Bool Source #
Evaluate the range of each ESafe expression in a disjunction and check if the disjunction is false in a standard manner.
decideCNFFalse :: [[(ESafe, BoxFun)]] -> TypedVarMap -> Precision -> Bool Source #
Evaluate the range of each ESafe expression in a CNF and check if the CNF is false in a standard manner.
decideConjunctionTrue :: [(ESafe, BoxFun)] -> TypedVarMap -> Precision -> Bool Source #
Evaluate the range of each ESafe expression in a conjunction and check if the conjunction is true in a standard manner.
checkDisjunctionResults :: [(Maybe Bool, Maybe potentialModel)] -> Maybe potentialModel -> (Maybe Bool, Maybe potentialModel) Source #
Check the results of a disjunction in a standard manner
checkConjunctionResults :: [(Maybe Bool, Maybe potentialModel)] -> Maybe potentialModel -> (Maybe Bool, Maybe potentialModel) Source #
Check the results of a conjunction in a standard manner
substituteConjunctionEqualities :: [ESafe] -> [ESafe] Source #
Substitute all variable-defining equalities in a given conjunction. Simplify the conjunction after substituting all variable-defining equalities.