Safe Haskell | None |
---|---|
Language | Haskell98 |
- data BasicExpr
- data THType
- liftNat :: Nat -> ExpQ
- liftNatType :: Nat -> TypeQ
- liftTypeRepr :: Type -> ExpQ
- liftType' :: Type -> TypeQ
- liftList :: [ExpQ] -> ExpQ
- liftTHType :: THType -> ExpQ
- liftTHTypes :: [THType] -> ExpQ
- liftNumType :: Type -> ExpQ
- natLength :: [a] -> Nat
- natInt :: Integer -> Nat
- data THFunction = THFun {}
- data THExpression = THExpr {
- deriveType :: THType
- getExpr' :: ExpQ
- type THBind = Map String THExpression
- deriveAllEqType :: [THExpression] -> THType
- toFunction :: BasicExpr -> THFunction
- toOrd :: Name -> THFunction
- toArith :: Name -> THFunction
- toArithBin :: Name -> THFunction
- toLogic :: Name -> THFunction
- toExpression :: THBind -> BasicExpr -> THExpression
- toQuantifier :: Quantifier -> THBind -> [BasicExpr] -> BasicExpr -> THExpression
- parseList :: String -> Maybe ([BasicExpr], String)
- parseExpr :: String -> Maybe (BasicExpr, String)
- parseName :: String -> Maybe (String, String)
- parseHs :: String -> Maybe (String, String)
- parseArgs :: String -> Maybe [BasicExpr]
- parseSingleExpr :: String -> Maybe BasicExpr
- expr :: QuasiQuoter
- declare :: QuasiQuoter
- define :: QuasiQuoter
- toFunDef :: [(String, THType)] -> BasicExpr -> THBind -> [ExpQ] -> ExpQ
- entypeExpr :: Proxy (t :: Type) -> e t -> e t
- toExpr :: THBind -> BasicExpr -> ExpQ
- enforceTypes :: Proxy tps -> (List e tps -> a) -> List e tps -> a
- toVarSig :: [BasicExpr] -> [(String, THType)]
- toQuant :: [(String, Type)] -> Map String Exp -> Q (Exp, Map String Exp)
- quantSig :: [(String, Type)] -> TypeQ
- asSig :: Proxy sig -> (List e sig -> a) -> List e sig -> a
- toPat :: BasicExpr -> PatQ
- distinct' :: Embed m e => [e t] -> m (e BoolType)
- arith' :: (Embed m e, SMTArith t) => ArithOp -> [e t] -> m (e t)
- logic' :: Embed m e => LogicOp -> [e BoolType] -> m (e BoolType)
- and' :: Embed m e => [e BoolType] -> m (e BoolType)
- or' :: Embed m e => [e BoolType] -> m (e BoolType)
- xor' :: Embed m e => [e BoolType] -> m (e BoolType)
- implies' :: Embed m e => [e BoolType] -> m (e BoolType)
- plus' :: (Embed m e, SMTArith t) => [e t] -> m (e t)
- minus' :: (Embed m e, SMTArith t) => [e t] -> m (e t)
- mult' :: (Embed m e, SMTArith t) => [e t] -> m (e t)
- toType :: BasicExpr -> THType
- thElementType :: THType -> THType
- thIndexType :: THType -> Either [Type] ExpQ
- thMakeArray :: Either [Type] ExpQ -> THType -> THType
- mkArgsPat :: [BasicExpr] -> PatQ
- mkAllEqPat :: [BasicExpr] -> PatQ
- mkNum :: Integer -> TypeQ
Documentation
liftNatType :: Nat -> TypeQ Source
liftTypeRepr :: Type -> ExpQ Source
liftTHType :: THType -> ExpQ Source
liftTHTypes :: [THType] -> ExpQ Source
liftNumType :: Type -> ExpQ Source
data THFunction Source
data THExpression Source
THExpr | |
|
type THBind = Map String THExpression Source
deriveAllEqType :: [THExpression] -> THType Source
toFunction :: BasicExpr -> THFunction Source
toOrd :: Name -> THFunction Source
toArith :: Name -> THFunction Source
toArithBin :: Name -> THFunction Source
toLogic :: Name -> THFunction Source
toExpression :: THBind -> BasicExpr -> THExpression Source
toQuantifier :: Quantifier -> THBind -> [BasicExpr] -> BasicExpr -> THExpression Source
This quasiquoter can be used to generate SMTLib2 expressions or pattern matches.
For example, to assert the fact that variable x
is equal to variable y
we can use
[expr| (= x y) |] >>= assert
To perform pattern matching against an expression e
, we can use:
analyze e >>= \re -> case re of [expr| (+ x y) |] -> ...
Types can also be generated using for example:
myExpr :: Backend b => SMT b (Expr b [expr| (Array Int Bool) |]) myExpr = [expr| ((as const (Array Int Bool)) False) |]
entypeExpr :: Proxy (t :: Type) -> e t -> e t Source
enforceTypes :: Proxy tps -> (List e tps -> a) -> List e tps -> a Source
thElementType :: THType -> THType Source
mkAllEqPat :: [BasicExpr] -> PatQ Source