tip-lib-0.2.2: tons of inductive problems - support library and tools

Safe HaskellNone
LanguageHaskell2010

Tip.Passes

Contents

Description

Passes

Synopsis

Running passes in the Fresh monad

freshPass :: (Foldable f, Name a) => (f a -> Fresh b) -> f a -> b Source

Continues making unique names after the highest numbered name in a foldable value.

Simplifications

simplifyTheory :: Name a => SimplifyOpts a -> Theory a -> Fresh (Theory a) Source

Simplify an entire theory

gently :: SimplifyOpts a Source

Gentle options: if there is risk for code duplication, only inline atomic expressions

aggressively :: Name a => SimplifyOpts a Source

Aggressive options: inline everything that might plausibly lead to simplification

data SimplifyOpts a Source

Options for the simplifier

Constructors

SimplifyOpts 

Fields

touch_lets :: Bool

Allow simplifications on lets

remove_variable_scrutinee_in_branches :: Bool

transform (match x (case (K y) (e x y))) to (match x (case (K y) (e (K y) y)) This is useful for triggering other known-case simplifications, and is therefore on by default.

should_inline :: Occurrences -> Maybe (Scope a) -> Expr a -> Bool

Inlining predicate

inline_match :: Bool

Allow function inlining to introduce match

removeNewtype :: Name a => Theory a -> Theory a Source

Remove datatypes that have only one constructor with one field. Can only be run after the addMatch pass.

uncurryTheory :: Name a => Theory a -> Fresh (Theory a) Source

Replace "fat arrow", =>, functions with normal functions wherever possible.

Simplifyng conjectures

splitConjecture :: Theory a -> [Theory a] Source

Splits a theory with many goals into many theories each with one goal

skolemiseConjecture :: Name a => Theory a -> Fresh [Theory a] Source

Splits, type skolems and skolemises conjectures!

skolemiseConjecture' :: Name a => Theory a -> Fresh (Theory a) Source

Skolemises a conjecture, assuming that there is just one goal and that it has no type variables.

skolemise :: Expr a -> Writer ([Local a], [Expr a]) (Expr a) Source

negateConjecture :: Name a => Theory a -> Fresh (Theory a) Source

Negates the conjecture: changes assert-not into assert, and introduce skolem types in case the goal is polymorphic. (runs typeSkolemConjecture)

typeSkolemConjecture :: Name a => Theory a -> Fresh (Theory a) Source

Introduce skolem types in case the goal is polymorphic.

intToNat :: forall a. Name a => Theory a -> Fresh (Theory a) Source

Replaces the builtin Int to natural numbers, if the only operations performed on are related to int ordering

sortsToNat :: forall a. Name a => Theory a -> Fresh (Theory a) Source

Replaces abstract sorts with natural numbers

Changing status of conjectures

Boolean builtins

ifToBoolOp :: TransformBi (Expr a) (f a) => f a -> f a Source

Transforms ite (match) on boolean literals in the branches into the corresponding builtin boolean function.

boolOpToIf :: (Ord a, TransformBi (Expr a) (f a)) => f a -> f a Source

Transforms and, or, =>, not and = and distinct on Bool into ite (i.e. match)

theoryBoolOpToIf :: Ord a => Theory a -> Theory a Source

Transforms boolean operators to if, but not in expression contexts.

boolOpLift :: Name a => Theory a -> Fresh (Theory a) Source

Lifts boolean operators to the top level

replaces (and r s t) with f r s t and f x y z = and x y z

Run CollapseEqual and BoolOpToIf afterwards

Match expressions

addMatch :: Name a => Theory a -> Fresh (Theory a) Source

Replace SMTLIB-style selector and discriminator functions (is-nil, head, tail) with case expressions.

commuteMatch :: forall a f. (Name a, TransformBiM Fresh (Expr a) (f a)) => Maybe (Theory a) -> f a -> Fresh (f a) Source

Makes an effort to move match statements upwards: moves match above function applications, and moves matches inside scrutinees outside.

Does not move past quantifiers, lets, and lambdas.

removeMatch :: Name a => Theory a -> Fresh (Theory a) Source

Turn case expressions into is-Cons, head, tail etc.

cseMatch :: Name a => CSEMatchOpts -> Theory a -> Theory a Source

Look for expressions of the form (match x (case P ...P...) ...) and replace them with (match x (case P ...x...) ...). This helps Why3's termination checker in some cases.

cseMatchNormal :: CSEMatchOpts Source

cseMatchWhy3 :: CSEMatchOpts Source

fillInCases :: (Ord a, PrettyVar a) => (Type a -> Expr a) -> Theory a -> Theory a Source

Duplicated functions

collapseEqual :: forall a. Ord a => Theory a -> Theory a Source

If we have

f x = E[x]
g y = E[y]

then we remove g and replace it with f everywhere

removeAliases :: Ord a => Theory a -> Theory a Source

If we have

g [a] x y = f [T1 a,T2 a] x y

then we remove g [t] and replace it with f [T1 t,T2 t] everywhere

Lambda and let lifting

lambdaLift :: Name a => Theory a -> Fresh (Theory a) Source

Defunctionalization.

f x = ... \ y -> e [ x ] ...

becomes

f x = ... g x ...
g x = \ y -> e [ x ]

where g is a fresh function.

After this pass, lambdas only exist at the top level of functions.

letLift :: Name a => Theory a -> Fresh (Theory a) Source

Lift lets to the top level.

let x = b[fvs] in e[x]

becomes

e[f fvs]
f fvs = b[fvs]

axiomatizeLambdas :: forall a. Name a => Theory a -> Fresh (Theory a) Source

Axiomatize lambdas.

f x = \ y -> E[x,y]

becomes

declare-fun f ...
assert (forall x y . @ (f x) y = E[x,y])

Function definitions

axiomatizeFuncdefs :: Theory a -> Theory a Source

Transforms define-fun to declare-fun in the most straightforward way. All parts of the right hand side is preserved, including match and if-then-else.

axiomatizeFuncdefs2 :: Name a => Theory a -> Theory a Source

Makes function definitions into case by converting case to left hand side pattern matching.

Data types

Monomorphisation

monomorphise :: forall a. Name a => Bool -> Theory a -> Fresh (Theory a) Source

Induction

induction :: (Name a, Ord a) => [Int] -> Theory a -> Fresh [Theory a] Source

Applies induction at the given coordinates to the first goal

Miscellaneous

uniqLocals :: forall a. Name a => Theory a -> Fresh (Theory a) Source

dropSuffix :: forall f a. (Traversable f, Name a) => String -> f a -> Fresh (f a) Source

Building pass pipelines

class Pass p where Source

Methods

runPass :: Name a => p -> Theory a -> Fresh [Theory a] Source

passName :: p -> String Source

parsePass :: Parser p Source

Instances

unitPass :: Pass p => p -> Mod FlagFields () -> Parser p Source

lintMany :: (Name a, Monad m) => String -> [Theory a] -> m [Theory a] Source

runPassLinted :: (Pass p, Name a) => p -> Theory a -> Fresh [Theory a] Source

data Choice a b Source

A sum type that supports Enum and Bounded

Constructors

First a 
Second b 

Instances

(Eq a, Eq b) => Eq (Choice a b) Source 
(Ord a, Ord b) => Ord (Choice a b) Source 
(Show a, Show b) => Show (Choice a b) Source 
(Pass a, Pass b) => Pass (Choice a b) Source 

choice :: (a -> c) -> (b -> c) -> Choice a b -> c Source

runPasses :: (Pass p, Name a) => [p] -> Theory a -> Fresh [Theory a] Source

continuePasses :: forall p a. (Pass p, Name a) => [p] -> [Theory a] -> Fresh [Theory a] Source