PropaFP-0.1.2.0: Auto-active verification of floating-point programs
Safe HaskellSafe-Inferred
LanguageHaskell2010

PropaFP.Expression

Synopsis

Documentation

data BinOp Source #

Constructors

Add 
Sub 
Mul 
Div 
Min 
Max 
Pow 
Mod 

Instances

Instances details
Arbitrary BinOp Source # 
Instance details

Defined in PropaFP.Expression

Methods

arbitrary :: Gen BinOp #

shrink :: BinOp -> [BinOp] #

Show BinOp Source # 
Instance details

Defined in PropaFP.Expression

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Eq BinOp Source # 
Instance details

Defined in PropaFP.Expression

Methods

(==) :: BinOp -> BinOp -> Bool #

(/=) :: BinOp -> BinOp -> Bool #

Ord BinOp Source # 
Instance details

Defined in PropaFP.Expression

Methods

compare :: BinOp -> BinOp -> Ordering #

(<) :: BinOp -> BinOp -> Bool #

(<=) :: BinOp -> BinOp -> Bool #

(>) :: BinOp -> BinOp -> Bool #

(>=) :: BinOp -> BinOp -> Bool #

max :: BinOp -> BinOp -> BinOp #

min :: BinOp -> BinOp -> BinOp #

data UnOp Source #

Constructors

Sqrt 
Negate 
Abs 
Sin 
Cos 

Instances

Instances details
Arbitrary UnOp Source # 
Instance details

Defined in PropaFP.Expression

Methods

arbitrary :: Gen UnOp #

shrink :: UnOp -> [UnOp] #

Show UnOp Source # 
Instance details

Defined in PropaFP.Expression

Methods

showsPrec :: Int -> UnOp -> ShowS #

show :: UnOp -> String #

showList :: [UnOp] -> ShowS #

Eq UnOp Source # 
Instance details

Defined in PropaFP.Expression

Methods

(==) :: UnOp -> UnOp -> Bool #

(/=) :: UnOp -> UnOp -> Bool #

Ord UnOp Source # 
Instance details

Defined in PropaFP.Expression

Methods

compare :: UnOp -> UnOp -> Ordering #

(<) :: UnOp -> UnOp -> Bool #

(<=) :: UnOp -> UnOp -> Bool #

(>) :: UnOp -> UnOp -> Bool #

(>=) :: UnOp -> UnOp -> Bool #

max :: UnOp -> UnOp -> UnOp #

min :: UnOp -> UnOp -> UnOp #

data E Source #

The E type represents the inequality: expression :: E >= 0 TODO: Add rounding operator with certain epsilon/floating-point type

Instances

Instances details
Arbitrary E Source # 
Instance details

Defined in PropaFP.Expression

Methods

arbitrary :: Gen E #

shrink :: E -> [E] #

Show E Source # 
Instance details

Defined in PropaFP.Expression

Methods

showsPrec :: Int -> E -> ShowS #

show :: E -> String #

showList :: [E] -> ShowS #

Eq E Source # 
Instance details

Defined in PropaFP.Expression

Methods

(==) :: E -> E -> Bool #

(/=) :: E -> E -> Bool #

Ord E Source # 
Instance details

Defined in PropaFP.Expression

Methods

compare :: E -> E -> Ordering #

(<) :: E -> E -> Bool #

(<=) :: E -> E -> Bool #

(>) :: E -> E -> Bool #

(>=) :: E -> E -> Bool #

max :: E -> E -> E #

min :: E -> E -> E #

data ESafe Source #

Constructors

EStrict E 
ENonStrict E 

Instances

Instances details
Arbitrary ESafe Source # 
Instance details

Defined in PropaFP.Expression

Methods

arbitrary :: Gen ESafe #

shrink :: ESafe -> [ESafe] #

Show ESafe Source # 
Instance details

Defined in PropaFP.Expression

Methods

showsPrec :: Int -> ESafe -> ShowS #

show :: ESafe -> String #

showList :: [ESafe] -> ShowS #

Eq ESafe Source # 
Instance details

Defined in PropaFP.Expression

Methods

(==) :: ESafe -> ESafe -> Bool #

(/=) :: ESafe -> ESafe -> Bool #

Ord ESafe Source # 
Instance details

Defined in PropaFP.Expression

Methods

compare :: ESafe -> ESafe -> Ordering #

(<) :: ESafe -> ESafe -> Bool #

(<=) :: ESafe -> ESafe -> Bool #

(>) :: ESafe -> ESafe -> Bool #

(>=) :: ESafe -> ESafe -> Bool #

max :: ESafe -> ESafe -> ESafe #

min :: ESafe -> ESafe -> ESafe #

data Comp Source #

Constructors

Gt 
Ge 
Lt 
Le 
Eq 

Instances

Instances details
Arbitrary Comp Source # 
Instance details

Defined in PropaFP.Expression

Methods

arbitrary :: Gen Comp #

shrink :: Comp -> [Comp] #

Show Comp Source # 
Instance details

Defined in PropaFP.Expression

Methods

showsPrec :: Int -> Comp -> ShowS #

show :: Comp -> String #

showList :: [Comp] -> ShowS #

Eq Comp Source # 
Instance details

Defined in PropaFP.Expression

Methods

(==) :: Comp -> Comp -> Bool #

(/=) :: Comp -> Comp -> Bool #

Ord Comp Source # 
Instance details

Defined in PropaFP.Expression

Methods

compare :: Comp -> Comp -> Ordering #

(<) :: Comp -> Comp -> Bool #

(<=) :: Comp -> Comp -> Bool #

(>) :: Comp -> Comp -> Bool #

(>=) :: Comp -> Comp -> Bool #

max :: Comp -> Comp -> Comp #

min :: Comp -> Comp -> Comp #

data Conn Source #

Constructors

And 
Or 
Impl 

Instances

Instances details
Arbitrary Conn Source # 
Instance details

Defined in PropaFP.Expression

Methods

arbitrary :: Gen Conn #

shrink :: Conn -> [Conn] #

Show Conn Source # 
Instance details

Defined in PropaFP.Expression

Methods

showsPrec :: Int -> Conn -> ShowS #

show :: Conn -> String #

showList :: [Conn] -> ShowS #

Eq Conn Source # 
Instance details

Defined in PropaFP.Expression

Methods

(==) :: Conn -> Conn -> Bool #

(/=) :: Conn -> Conn -> Bool #

Ord Conn Source # 
Instance details

Defined in PropaFP.Expression

Methods

compare :: Conn -> Conn -> Ordering #

(<) :: Conn -> Conn -> Bool #

(<=) :: Conn -> Conn -> Bool #

(>) :: Conn -> Conn -> Bool #

(>=) :: Conn -> Conn -> Bool #

max :: Conn -> Conn -> Conn #

min :: Conn -> Conn -> Conn #

data F Source #

The F type is used to specify comparisons between E types and logical connectives between F types

Constructors

FComp Comp E E 
FConn Conn F F 
FNot F 
FTrue 
FFalse 

Instances

Instances details
Arbitrary F Source # 
Instance details

Defined in PropaFP.Expression

Methods

arbitrary :: Gen F #

shrink :: F -> [F] #

Show F Source # 
Instance details

Defined in PropaFP.Expression

Methods

showsPrec :: Int -> F -> ShowS #

show :: F -> String #

showList :: [F] -> ShowS #

Eq F Source # 
Instance details

Defined in PropaFP.Expression

Methods

(==) :: F -> F -> Bool #

(/=) :: F -> F -> Bool #

Ord F Source # 
Instance details

Defined in PropaFP.Expression

Methods

compare :: F -> F -> Ordering #

(<) :: F -> F -> Bool #

(<=) :: F -> F -> Bool #

(>) :: F -> F -> Bool #

(>=) :: F -> F -> Bool #

max :: F -> F -> F #

min :: F -> F -> F #

newtype Name Source #

Constructors

Name String 

Instances

Instances details
Arbitrary Name Source # 
Instance details

Defined in PropaFP.Expression

Methods

arbitrary :: Gen Name #

shrink :: Name -> [Name] #

Show Name Source # 
Instance details

Defined in PropaFP.Expression

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

negateSafeE :: ESafe -> ESafe Source #

Equivalent to E * -1 Example: ENonStrict e == e >= 0. negateSafeE (ENonStrict e) == e == -e 0 == (EStrict (EUnOp Negate e))

fmapESafe :: (E -> E) -> ESafe -> ESafe Source #

fToECNF :: F -> [[ESafe]] Source #

fToEDNF :: F -> [[ESafe]] Source #

fToFDNF :: F -> [[F]] Source #

simplifyE :: E -> E Source #

Add bounds for any Float expressions addRoundingBounds :: E -> [[E]] addRoundingBounds (Float e significand) = [[exactExpression - machineEpsilon], [exactExpression + machineEpsilon]] where exactExpression = addRoundingBounds e machineEpsilon = 2^(-23) addRoundingBounds e = e

Various rules to simplify expressions

simplifyFDNF :: [[F]] -> [[F]] Source #

fDNFToFDNFWithoutEq :: [[F]] -> [[F]] -> [[F]] Source #

fDNFToEDNF :: [[F]] -> [[ESafe]] Source #

computeE :: E -> [(String, Rational)] -> CN Double Source #

compute the value of E with Vars at specified points

computeQualifiedEs :: [([E], E)] -> [(String, Rational)] -> [CN Double] Source #

Given a list of qualified Es and points for all Vars, compute a list of valid values.

A value is the computed result of the second element of the tuple and is valid if all the expressions in the list at the first element of the tuple compute to be above 0.

computeECNF :: [[E]] -> [(String, Rational)] -> [[CN Double]] Source #

prettyShowE :: E -> String Source #

Show an expression in a human-readable format Rationals are converted into doubles

prettyShowECNF :: [[E]] -> String Source #

Show a conjunction of expressions in a human-readable format This is shown as an AND with each disjunction tabbed in with an OR If there is only one term in a disjunction, the expression is shown without an OR

extractVariablesE :: E -> [String] Source #

Extract all variables in an expression Will not return duplicationes

extractVariablesF :: F -> [String] Source #

Extract all variables in an expression Will not return duplicationes

replaceEInE :: E -> E -> E -> E Source #

replaceEInF :: F -> E -> E -> F Source #

normalizeBoolean :: F -> F Source #

Normalize to and/or aggressively apply elimination rules