| IsBitVector BVUntyped Source # | |
|
| SMTOrd Integer Source # | |
|
| SMTArith Integer Source # | |
|
| SMTValue Bool Source # | |
|
| SMTValue Integer Source # | |
|
| SMTValue UntypedValue Source # | |
|
| SMTType Bool Source # | |
|
| SMTType Integer Source # | |
|
| SMTType UntypedValue Source # | |
|
| SMTType Untyped Source # | |
|
| Extractable BVUntyped BVUntyped Source # | |
|
| Concatable BVUntyped BVUntyped Source # | |
|
| TypeableNat n => Extractable BVUntyped (BVTyped n) Source # | |
|
| TypeableNat n2 => Concatable BVUntyped (BVTyped n2) Source # | |
|
| Enum (SMTExpr Integer) Source # | |
|
| Eq a => Eq (SMTExpr a) Source # | |
|
| Fractional (SMTExpr (Ratio Integer)) Source # | |
|
| TypeableNat n => Num (BitVector (BVTyped n)) Source # | |
|
| Num (SMTExpr Integer) Source # | |
|
| Num (SMTExpr (Ratio Integer)) Source # | |
|
| TypeableNat n => Num (SMTExpr (BitVector (BVTyped n))) Source # | |
|
| SMTType t => Ord (SMTExpr t) Source # | |
|
| LiftArgs a => LiftArgs [a] Source # | |
|
| LiftArgs a => LiftArgs (Maybe a) Source # | |
|
| SMTValue a => LiftArgs (SMTExpr a) Source # | |
|
| SMTType a => Liftable [SMTExpr a] Source # | |
|
| SMTType a => Liftable (SMTExpr a) Source # | |
|
| Args a => Args [a] Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> [a] -> ArgAnnotation [a] -> m (s, [a]) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [([a], b)] -> ArgAnnotation [a] -> m (s, [[a]], [a]) Source # extractArgAnnotation :: [a] -> ArgAnnotation [a] Source # toArgs :: ArgAnnotation [a] -> [SMTExpr Untyped] -> Maybe ([a], [SMTExpr Untyped]) Source # fromArgs :: [a] -> [SMTExpr Untyped] Source # getTypes :: [a] -> ArgAnnotation [a] -> [ProxyArg] Source # getArgAnnotation :: [a] -> [Sort] -> (ArgAnnotation [a], [Sort]) Source # |
| Args a => Args (Maybe a) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> Maybe a -> ArgAnnotation (Maybe a) -> m (s, Maybe a) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [(Maybe a, b)] -> ArgAnnotation (Maybe a) -> m (s, [Maybe a], Maybe a) Source # extractArgAnnotation :: Maybe a -> ArgAnnotation (Maybe a) Source # toArgs :: ArgAnnotation (Maybe a) -> [SMTExpr Untyped] -> Maybe (Maybe a, [SMTExpr Untyped]) Source # fromArgs :: Maybe a -> [SMTExpr Untyped] Source # getTypes :: Maybe a -> ArgAnnotation (Maybe a) -> [ProxyArg] Source # getArgAnnotation :: Maybe a -> [Sort] -> (ArgAnnotation (Maybe a), [Sort]) Source # |
| SMTType a => Args (SMTExpr a) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> SMTExpr a -> ArgAnnotation (SMTExpr a) -> m (s, SMTExpr a) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [(SMTExpr a, b)] -> ArgAnnotation (SMTExpr a) -> m (s, [SMTExpr a], SMTExpr a) Source # extractArgAnnotation :: SMTExpr a -> ArgAnnotation (SMTExpr a) Source # toArgs :: ArgAnnotation (SMTExpr a) -> [SMTExpr Untyped] -> Maybe (SMTExpr a, [SMTExpr Untyped]) Source # fromArgs :: SMTExpr a -> [SMTExpr Untyped] Source # getTypes :: SMTExpr a -> ArgAnnotation (SMTExpr a) -> [ProxyArg] Source # getArgAnnotation :: SMTExpr a -> [Sort] -> (ArgAnnotation (SMTExpr a), [Sort]) Source # |
| TypeableNat n => IsBitVector (BVTyped n) Source # | |
|
| SMTOrd (Ratio Integer) Source # | |
|
| SMTArith (Ratio Integer) Source # | |
|
| (Typeable * a, SMTValue a) => SMTValue [a] Source # | |
|
| SMTValue a => SMTValue (Maybe a) Source # | |
|
| SMTValue (Ratio Integer) Source # | |
|
| TypeableNat n => SMTValue (BitVector (BVTyped n)) Source # | |
|
| SMTValue (BitVector BVUntyped) Source # | |
|
| (Typeable * a, SMTType a) => SMTType [a] Source # | |
|
| SMTType a => SMTType (Maybe a) Source # | |
|
| SMTType (Ratio Integer) Source # | |
|
| TypeableNat n => SMTType (BitVector (BVTyped n)) Source # | |
|
| SMTType (BitVector BVUntyped) Source # | |
|
| TypeableNat n => Extractable (BVTyped n) BVUntyped Source # | |
|
| TypeableNat n1 => Concatable (BVTyped n1) BVUntyped Source # | |
|
| (TypeableNat n1, TypeableNat n2) => Extractable (BVTyped n1) (BVTyped n2) Source # | |
|
| (TypeableNat n1, TypeableNat n2, TypeableNat (Add n1 n2)) => Concatable (BVTyped n1) (BVTyped n2) Source # | |
|
| Eq (Field a f) Source # | |
|
| Eq (Constructor arg res) Source # | |
|
| Args arg => Eq (SMTFunction arg res) Source # | |
|
| Ord (Field a f) Source # | |
|
| Ord (Constructor arg res) Source # | |
|
| Args arg => Ord (SMTFunction arg res) Source # | |
|
| (LiftArgs a, LiftArgs b) => LiftArgs (Either a b) Source # | |
|
| (LiftArgs a, LiftArgs b) => LiftArgs (a, b) Source # | |
|
| (Typeable * a, Show a, Ord a, LiftArgs b) => LiftArgs (Map a b) Source # | |
|
| (Liftable a, Liftable b) => Liftable (a, b) Source # | |
Methods getLiftedArgumentAnn :: (a, b) -> i -> ArgAnnotation (a, b) -> ArgAnnotation i -> ArgAnnotation (Lifted (a, b) i) Source # inferLiftedAnnotation :: (a, b) -> i -> ArgAnnotation (Lifted (a, b) i) -> (ArgAnnotation i, ArgAnnotation (a, b)) Source # getConstraint :: Args i => p ((a, b), i) -> Dict (Liftable (Lifted (a, b) i)) Source # |
| (Args a, Args b) => Args (Either a b) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> Either a b -> ArgAnnotation (Either a b) -> m (s, Either a b) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [(Either a b, b)] -> ArgAnnotation (Either a b) -> m (s, [Either a b], Either a b) Source # extractArgAnnotation :: Either a b -> ArgAnnotation (Either a b) Source # toArgs :: ArgAnnotation (Either a b) -> [SMTExpr Untyped] -> Maybe (Either a b, [SMTExpr Untyped]) Source # fromArgs :: Either a b -> [SMTExpr Untyped] Source # getTypes :: Either a b -> ArgAnnotation (Either a b) -> [ProxyArg] Source # getArgAnnotation :: Either a b -> [Sort] -> (ArgAnnotation (Either a b), [Sort]) Source # |
| (Args a, Args b) => Args (a, b) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> (a, b) -> ArgAnnotation (a, b) -> m (s, (a, b)) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [((a, b), b)] -> ArgAnnotation (a, b) -> m (s, [(a, b)], (a, b)) Source # extractArgAnnotation :: (a, b) -> ArgAnnotation (a, b) Source # toArgs :: ArgAnnotation (a, b) -> [SMTExpr Untyped] -> Maybe ((a, b), [SMTExpr Untyped]) Source # fromArgs :: (a, b) -> [SMTExpr Untyped] Source # getTypes :: (a, b) -> ArgAnnotation (a, b) -> [ProxyArg] Source # getArgAnnotation :: (a, b) -> [Sort] -> (ArgAnnotation (a, b), [Sort]) Source # |
| (Typeable * a, Show a, Args b, Ord a) => Args (Map a b) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> Map a b -> ArgAnnotation (Map a b) -> m (s, Map a b) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [(Map a b, b)] -> ArgAnnotation (Map a b) -> m (s, [Map a b], Map a b) Source # extractArgAnnotation :: Map a b -> ArgAnnotation (Map a b) Source # toArgs :: ArgAnnotation (Map a b) -> [SMTExpr Untyped] -> Maybe (Map a b, [SMTExpr Untyped]) Source # fromArgs :: Map a b -> [SMTExpr Untyped] Source # getTypes :: Map a b -> ArgAnnotation (Map a b) -> [ProxyArg] Source # getArgAnnotation :: Map a b -> [Sort] -> (ArgAnnotation (Map a b), [Sort]) Source # |
| (Args idx, SMTType val) => SMTType (SMTArray idx val) Source # | |
|
| (LiftArgs a, LiftArgs b, LiftArgs c) => LiftArgs (a, b, c) Source # | |
Methods liftArgs :: Unpacked (a, b, c) -> ArgAnnotation (a, b, c) -> (a, b, c) Source # unliftArgs :: Monad m => (a, b, c) -> (forall t. SMTValue t => SMTExpr t -> m t) -> m (Unpacked (a, b, c)) Source # |
| (Liftable a, Liftable b, Liftable c) => Liftable (a, b, c) Source # | |
Methods getLiftedArgumentAnn :: (a, b, c) -> i -> ArgAnnotation (a, b, c) -> ArgAnnotation i -> ArgAnnotation (Lifted (a, b, c) i) Source # inferLiftedAnnotation :: (a, b, c) -> i -> ArgAnnotation (Lifted (a, b, c) i) -> (ArgAnnotation i, ArgAnnotation (a, b, c)) Source # getConstraint :: Args i => p ((a, b, c), i) -> Dict (Liftable (Lifted (a, b, c) i)) Source # |
| (Args a, Args b, Args c) => Args (a, b, c) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> (a, b, c) -> ArgAnnotation (a, b, c) -> m (s, (a, b, c)) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [((a, b, c), b)] -> ArgAnnotation (a, b, c) -> m (s, [(a, b, c)], (a, b, c)) Source # extractArgAnnotation :: (a, b, c) -> ArgAnnotation (a, b, c) Source # toArgs :: ArgAnnotation (a, b, c) -> [SMTExpr Untyped] -> Maybe ((a, b, c), [SMTExpr Untyped]) Source # fromArgs :: (a, b, c) -> [SMTExpr Untyped] Source # getTypes :: (a, b, c) -> ArgAnnotation (a, b, c) -> [ProxyArg] Source # getArgAnnotation :: (a, b, c) -> [Sort] -> (ArgAnnotation (a, b, c), [Sort]) Source # |
| (LiftArgs a, LiftArgs b, LiftArgs c, LiftArgs d) => LiftArgs (a, b, c, d) Source # | |
Methods liftArgs :: Unpacked (a, b, c, d) -> ArgAnnotation (a, b, c, d) -> (a, b, c, d) Source # unliftArgs :: Monad m => (a, b, c, d) -> (forall t. SMTValue t => SMTExpr t -> m t) -> m (Unpacked (a, b, c, d)) Source # |
| (Liftable a, Liftable b, Liftable c, Liftable d) => Liftable (a, b, c, d) Source # | |
Methods getLiftedArgumentAnn :: (a, b, c, d) -> i -> ArgAnnotation (a, b, c, d) -> ArgAnnotation i -> ArgAnnotation (Lifted (a, b, c, d) i) Source # inferLiftedAnnotation :: (a, b, c, d) -> i -> ArgAnnotation (Lifted (a, b, c, d) i) -> (ArgAnnotation i, ArgAnnotation (a, b, c, d)) Source # getConstraint :: Args i => p ((a, b, c, d), i) -> Dict (Liftable (Lifted (a, b, c, d) i)) Source # |
| (Args a, Args b, Args c, Args d) => Args (a, b, c, d) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> (a, b, c, d) -> ArgAnnotation (a, b, c, d) -> m (s, (a, b, c, d)) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [((a, b, c, d), b)] -> ArgAnnotation (a, b, c, d) -> m (s, [(a, b, c, d)], (a, b, c, d)) Source # extractArgAnnotation :: (a, b, c, d) -> ArgAnnotation (a, b, c, d) Source # toArgs :: ArgAnnotation (a, b, c, d) -> [SMTExpr Untyped] -> Maybe ((a, b, c, d), [SMTExpr Untyped]) Source # fromArgs :: (a, b, c, d) -> [SMTExpr Untyped] Source # getTypes :: (a, b, c, d) -> ArgAnnotation (a, b, c, d) -> [ProxyArg] Source # getArgAnnotation :: (a, b, c, d) -> [Sort] -> (ArgAnnotation (a, b, c, d), [Sort]) Source # |
| (LiftArgs a, LiftArgs b, LiftArgs c, LiftArgs d, LiftArgs e) => LiftArgs (a, b, c, d, e) Source # | |
Methods liftArgs :: Unpacked (a, b, c, d, e) -> ArgAnnotation (a, b, c, d, e) -> (a, b, c, d, e) Source # unliftArgs :: Monad m => (a, b, c, d, e) -> (forall t. SMTValue t => SMTExpr t -> m t) -> m (Unpacked (a, b, c, d, e)) Source # |
| (Liftable a, Liftable b, Liftable c, Liftable d, Liftable e) => Liftable (a, b, c, d, e) Source # | |
Methods getLiftedArgumentAnn :: (a, b, c, d, e) -> i -> ArgAnnotation (a, b, c, d, e) -> ArgAnnotation i -> ArgAnnotation (Lifted (a, b, c, d, e) i) Source # inferLiftedAnnotation :: (a, b, c, d, e) -> i -> ArgAnnotation (Lifted (a, b, c, d, e) i) -> (ArgAnnotation i, ArgAnnotation (a, b, c, d, e)) Source # getConstraint :: Args i => p ((a, b, c, d, e), i) -> Dict (Liftable (Lifted (a, b, c, d, e) i)) Source # |
| (Args a, Args b, Args c, Args d, Args e) => Args (a, b, c, d, e) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> (a, b, c, d, e) -> ArgAnnotation (a, b, c, d, e) -> m (s, (a, b, c, d, e)) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [((a, b, c, d, e), b)] -> ArgAnnotation (a, b, c, d, e) -> m (s, [(a, b, c, d, e)], (a, b, c, d, e)) Source # extractArgAnnotation :: (a, b, c, d, e) -> ArgAnnotation (a, b, c, d, e) Source # toArgs :: ArgAnnotation (a, b, c, d, e) -> [SMTExpr Untyped] -> Maybe ((a, b, c, d, e), [SMTExpr Untyped]) Source # fromArgs :: (a, b, c, d, e) -> [SMTExpr Untyped] Source # getTypes :: (a, b, c, d, e) -> ArgAnnotation (a, b, c, d, e) -> [ProxyArg] Source # getArgAnnotation :: (a, b, c, d, e) -> [Sort] -> (ArgAnnotation (a, b, c, d, e), [Sort]) Source # |
| (LiftArgs a, LiftArgs b, LiftArgs c, LiftArgs d, LiftArgs e, LiftArgs f) => LiftArgs (a, b, c, d, e, f) Source # | |
Methods liftArgs :: Unpacked (a, b, c, d, e, f) -> ArgAnnotation (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source # unliftArgs :: Monad m => (a, b, c, d, e, f) -> (forall t. SMTValue t => SMTExpr t -> m t) -> m (Unpacked (a, b, c, d, e, f)) Source # |
| (Liftable a, Liftable b, Liftable c, Liftable d, Liftable e, Liftable f) => Liftable (a, b, c, d, e, f) Source # | |
Methods getLiftedArgumentAnn :: (a, b, c, d, e, f) -> i -> ArgAnnotation (a, b, c, d, e, f) -> ArgAnnotation i -> ArgAnnotation (Lifted (a, b, c, d, e, f) i) Source # inferLiftedAnnotation :: (a, b, c, d, e, f) -> i -> ArgAnnotation (Lifted (a, b, c, d, e, f) i) -> (ArgAnnotation i, ArgAnnotation (a, b, c, d, e, f)) Source # getConstraint :: Args i => p ((a, b, c, d, e, f), i) -> Dict (Liftable (Lifted (a, b, c, d, e, f) i)) Source # |
| (Args a, Args b, Args c, Args d, Args e, Args f) => Args (a, b, c, d, e, f) Source # | |
Methods foldExprs :: Monad m => (forall t. SMTType t => s -> SMTExpr t -> SMTAnnotation t -> m (s, SMTExpr t)) -> s -> (a, b, c, d, e, f) -> ArgAnnotation (a, b, c, d, e, f) -> m (s, (a, b, c, d, e, f)) Source # foldsExprs :: Monad m => (forall t. SMTType t => s -> [(SMTExpr t, b)] -> SMTAnnotation t -> m (s, [SMTExpr t], SMTExpr t)) -> s -> [((a, b, c, d, e, f), b)] -> ArgAnnotation (a, b, c, d, e, f) -> m (s, [(a, b, c, d, e, f)], (a, b, c, d, e, f)) Source # extractArgAnnotation :: (a, b, c, d, e, f) -> ArgAnnotation (a, b, c, d, e, f) Source # toArgs :: ArgAnnotation (a, b, c, d, e, f) -> [SMTExpr Untyped] -> Maybe ((a, b, c, d, e, f), [SMTExpr Untyped]) Source # fromArgs :: (a, b, c, d, e, f) -> [SMTExpr Untyped] Source # getTypes :: (a, b, c, d, e, f) -> ArgAnnotation (a, b, c, d, e, f) -> [ProxyArg] Source # getArgAnnotation :: (a, b, c, d, e, f) -> [Sort] -> (ArgAnnotation (a, b, c, d, e, f), [Sort]) Source # |