cryptol-2.3.0: Cryptol: The Language of Cryptography

Copyright(c) 2014-2016 Galois, Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Cryptol.TypeCheck.Solver.Numeric.AST

Description

The sytnax of numeric propositions.

Synopsis

Documentation

ppName :: Name -> Doc Source

Pretty print a name.

data Prop Source

Propopsitions, representing Cryptol's numeric constraints (and a bit more).

Constructors

Fin Expr 
Expr :== Expr infix 4 
Expr :>= Expr infix 4 
Expr :> Expr infix 4 
Expr :==: Expr infix 4 
Expr :>: Expr infix 4 
Prop :&& Prop infixr 3 
Prop :|| Prop infixr 2 
Not Prop 
PFalse 
PTrue 

cryPropExprs :: Prop -> [Expr] Source

Compute all expressions in a property.

cryPropFVS :: Prop -> Set Name Source

Compute the free variables in a proposition.

ppProp :: Prop -> Doc Source

Pretty print a top-level property.

ppPropPrec :: Int -> Prop -> Doc Source

Pretty print a proposition, in the given precedence context.

data Expr Source

Expressions, representing Cryptol's numeric types.

zero :: Expr Source

The constant 0.

one :: Expr Source

The constant 1.

two :: Expr Source

The constant 2.

inf :: Expr Source

The constant infinity.

cryAnds :: [Prop] -> Prop Source

Make a conjucntion of the given properties.

cryOrs :: [Prop] -> Prop Source

Make a disjunction of the given properties.

cryExprExprs :: Expr -> [Expr] Source

Compute the immediate sub-expressions of an expression.

cryRebuildExpr :: Expr -> [Expr] -> Expr Source

Rebuild an expression, using the top-level strucutre of the first expression, but the second list of expressions as sub-expressions.

cryExprFVS :: Expr -> Set Name Source

Compute the free variables in an expression.

ppExpr :: Expr -> Doc Source

Pretty print an expression at the top level.

ppExprPrec :: Int -> Expr -> Doc Source

Pretty print an expression, in the given precedence context.

data Nat' Source

Natural numbers with an infinity element

Constructors

Nat Integer 
Inf 

data IfExpr' p a Source

Constructors

If p (IfExpr' p a) (IfExpr' p a) 
Return a 
Impossible 

Instances

ppIf :: (p -> Doc) -> (a -> Doc) -> IfExpr' p a -> Doc Source

Pretty print an experssion with ifs.

ppIfExpr :: IfExpr Expr -> Doc Source

Pretty print an experssion with ifs.

class HasVars ast where Source

Replaces occurances of the name with the expression. Returns Nothing if there were no occurances of the name.

Methods

apSubst :: Subst -> ast -> Maybe ast Source

Instances

HasVars Bool Source

This is used in the simplification to "apply" substitutions to Props.

HasVars Expr Source 
HasVars Prop Source 

cryLet :: HasVars e => Name -> Expr -> e -> Maybe e Source

doAppSubst :: HasVars a => Subst -> a -> a Source