hasmtlib-2.8.0: A monad for interfacing with external SMT solvers
Safe HaskellSafe-Inferred
LanguageGHC2021

Language.Hasmtlib.Codec

Description

This module provides the class Codec which takes care of marshalling data to and from external SMT-Solvers.

A generic default implementation with GCodec is possible.

Example

Expand
data V3 a = V3 a a a deriving Generic
instance Codec a => Codec (V3 a)

constantV3 :: V3 (Expr RealSort)
constantV3 = encode $ V3 7 69 42
Synopsis

Class

class Codec a where Source #

Lift values to SMT-Values or decode them.

You can derive an instance of this class if your type is Generic.

Minimal complete definition

Nothing

Associated Types

type Decoded a :: Type Source #

Result of decoding a.

Methods

decode :: Solution -> a -> Maybe (Decoded a) Source #

Decode a value using given solution.

default decode :: (Generic a, Generic (Decoded a), GCodec (Rep a), GDecoded (Rep a) x ~ Rep (Decoded a) x) => Solution -> a -> Maybe (Decoded a) Source #

encode :: Decoded a -> a Source #

Encode a value as constant.

default encode :: (Generic a, Generic (Decoded a), GCodec (Rep a), GDecoded (Rep a) x ~ Rep (Decoded a) x) => Decoded a -> a Source #

Instances

Instances details
Codec Int16 Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Int16 Source #

Codec Int32 Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Int32 Source #

Codec Int64 Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Int64 Source #

Codec Int8 Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Int8 Source #

Codec Word16 Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Word16 Source #

Codec Word32 Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Word32 Source #

Codec Word64 Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Word64 Source #

Codec Word8 Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Word8 Source #

Codec Ordering Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Ordering Source #

Codec Integer Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Integer Source #

Codec Natural Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Natural Source #

Codec () Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded () Source #

Methods

decode :: Solution -> () -> Maybe (Decoded ()) Source #

encode :: Decoded () -> () Source #

Codec Bool Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Bool Source #

Codec Char Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Char Source #

Codec Double Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Double Source #

Codec Float Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Float Source #

Codec Int Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Int Source #

Codec Word Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded Word Source #

Codec a => Codec (Identity a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Identity a) Source #

Codec a => Codec (First a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (First a) Source #

Codec a => Codec (Last a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Last a) Source #

Methods

decode :: Solution -> Last a -> Maybe (Decoded (Last a)) Source #

encode :: Decoded (Last a) -> Last a Source #

Codec a => Codec (Dual a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Dual a) Source #

Methods

decode :: Solution -> Dual a -> Maybe (Decoded (Dual a)) Source #

encode :: Decoded (Dual a) -> Dual a Source #

Codec a => Codec (Product a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Product a) Source #

Codec a => Codec (Sum a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Sum a) Source #

Methods

decode :: Solution -> Sum a -> Maybe (Decoded (Sum a)) Source #

encode :: Decoded (Sum a) -> Sum a Source #

Codec a => Codec (IntMap a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (IntMap a) Source #

Codec a => Codec (Seq a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Seq a) Source #

Methods

decode :: Solution -> Seq a -> Maybe (Decoded (Seq a)) Source #

encode :: Decoded (Seq a) -> Seq a Source #

Codec a => Codec (Tree a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Tree a) Source #

Methods

decode :: Solution -> Tree a -> Maybe (Decoded (Tree a)) Source #

encode :: Decoded (Tree a) -> Tree a Source #

KnownSMTSort t => Codec (Expr t) Source #

Decode and evaluate expressions

Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Expr t) Source #

Methods

decode :: Solution -> Expr t -> Maybe (Decoded (Expr t)) Source #

encode :: Decoded (Expr t) -> Expr t Source #

Codec a => Codec (Maybe a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Maybe a) Source #

Codec a => Codec [a] Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded [a] Source #

Methods

decode :: Solution -> [a] -> Maybe (Decoded [a]) Source #

encode :: Decoded [a] -> [a] Source #

(Codec a, Codec b) => Codec (Either a b) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Either a b) Source #

Methods

decode :: Solution -> Either a b -> Maybe (Decoded (Either a b)) Source #

encode :: Decoded (Either a b) -> Either a b Source #

(Ix i, Codec e) => Codec (Array i e) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Array i e) Source #

Methods

decode :: Solution -> Array i e -> Maybe (Decoded (Array i e)) Source #

encode :: Decoded (Array i e) -> Array i e Source #

Codec a => Codec (Map k a) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (Map k a) Source #

Methods

decode :: Solution -> Map k a -> Maybe (Decoded (Map k a)) Source #

encode :: Decoded (Map k a) -> Map k a Source #

(Ix a, Ix b) => Codec (Relation a b) Source # 
Instance details

Defined in Language.Hasmtlib.Type.Relation

Associated Types

type Decoded (Relation a b) Source #

(Codec a, Codec b) => Codec (a, b) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (a, b) Source #

Methods

decode :: Solution -> (a, b) -> Maybe (Decoded (a, b)) Source #

encode :: Decoded (a, b) -> (a, b) Source #

(Codec a, Codec b, Codec c) => Codec (a, b, c) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (a, b, c) Source #

Methods

decode :: Solution -> (a, b, c) -> Maybe (Decoded (a, b, c)) Source #

encode :: Decoded (a, b, c) -> (a, b, c) Source #

(Codec a, Codec b, Codec c, Codec d) => Codec (a, b, c, d) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (a, b, c, d) Source #

Methods

decode :: Solution -> (a, b, c, d) -> Maybe (Decoded (a, b, c, d)) Source #

encode :: Decoded (a, b, c, d) -> (a, b, c, d) Source #

(Codec a, Codec b, Codec c, Codec d, Codec e) => Codec (a, b, c, d, e) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (a, b, c, d, e) Source #

Methods

decode :: Solution -> (a, b, c, d, e) -> Maybe (Decoded (a, b, c, d, e)) Source #

encode :: Decoded (a, b, c, d, e) -> (a, b, c, d, e) Source #

(Codec a, Codec b, Codec c, Codec d, Codec e, Codec f) => Codec (a, b, c, d, e, f) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (a, b, c, d, e, f) Source #

Methods

decode :: Solution -> (a, b, c, d, e, f) -> Maybe (Decoded (a, b, c, d, e, f)) Source #

encode :: Decoded (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

(Codec a, Codec b, Codec c, Codec d, Codec e, Codec f, Codec g) => Codec (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (a, b, c, d, e, f, g) Source #

Methods

decode :: Solution -> (a, b, c, d, e, f, g) -> Maybe (Decoded (a, b, c, d, e, f, g)) Source #

encode :: Decoded (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

(Codec a, Codec b, Codec c, Codec d, Codec e, Codec f, Codec g, Codec h) => Codec (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type Decoded (a, b, c, d, e, f, g, h) Source #

Methods

decode :: Solution -> (a, b, c, d, e, f, g, h) -> Maybe (Decoded (a, b, c, d, e, f, g, h)) Source #

encode :: Decoded (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

Generics

class GCodec f where Source #

Associated Types

type GDecoded f :: Type -> Type Source #

Methods

gdecode :: Solution -> f a -> Maybe (GDecoded f a) Source #

gencode :: GDecoded f a -> f a Source #

Instances

Instances details
GCodec (U1 :: Type -> Type) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type GDecoded U1 :: Type -> Type Source #

Methods

gdecode :: Solution -> U1 a -> Maybe (GDecoded U1 a) Source #

gencode :: GDecoded U1 a -> U1 a Source #

GCodec (V1 :: Type -> Type) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type GDecoded V1 :: Type -> Type Source #

Methods

gdecode :: Solution -> V1 a -> Maybe (GDecoded V1 a) Source #

gencode :: GDecoded V1 a -> V1 a Source #

(GCodec f, GCodec g) => GCodec (f :*: g) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type GDecoded (f :*: g) :: Type -> Type Source #

Methods

gdecode :: Solution -> (f :*: g) a -> Maybe (GDecoded (f :*: g) a) Source #

gencode :: GDecoded (f :*: g) a -> (f :*: g) a Source #

(GCodec f, GCodec g) => GCodec (f :+: g) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type GDecoded (f :+: g) :: Type -> Type Source #

Methods

gdecode :: Solution -> (f :+: g) a -> Maybe (GDecoded (f :+: g) a) Source #

gencode :: GDecoded (f :+: g) a -> (f :+: g) a Source #

Codec a => GCodec (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type GDecoded (K1 i a) :: Type -> Type Source #

Methods

gdecode :: Solution -> K1 i a a0 -> Maybe (GDecoded (K1 i a) a0) Source #

gencode :: GDecoded (K1 i a) a0 -> K1 i a a0 Source #

GCodec f => GCodec (M1 i c f) Source # 
Instance details

Defined in Language.Hasmtlib.Codec

Associated Types

type GDecoded (M1 i c f) :: Type -> Type Source #

Methods

gdecode :: Solution -> M1 i c f a -> Maybe (GDecoded (M1 i c f) a) Source #

gencode :: GDecoded (M1 i c f) a -> M1 i c f a Source #

type family DefaultDecoded a :: Type where ... Source #

Computes a default Decoded Type by distributing Decoded over it's type arguments.

Equations

DefaultDecoded (t a b c d e f g h) = t (Decoded a) (Decoded b) (Decoded c) (Decoded d) (Decoded e) (Decoded f) (Decoded g) (Decoded h) 
DefaultDecoded (t a b c d e f g) = t (Decoded a) (Decoded b) (Decoded c) (Decoded d) (Decoded e) (Decoded f) (Decoded g) 
DefaultDecoded (t a b c d e f) = t (Decoded a) (Decoded b) (Decoded c) (Decoded d) (Decoded e) (Decoded f) 
DefaultDecoded (t a b c d e) = t (Decoded a) (Decoded b) (Decoded c) (Decoded d) (Decoded e) 
DefaultDecoded (t a b c d) = t (Decoded a) (Decoded b) (Decoded c) (Decoded d) 
DefaultDecoded (t a b c) = t (Decoded a) (Decoded b) (Decoded c) 
DefaultDecoded (t a b) = t (Decoded a) (Decoded b) 
DefaultDecoded (t a) = t (Decoded a) 
DefaultDecoded x = TypeError (((((Text "DefaultDecoded (" :<>: ShowType x) :<>: Text ") is not allowed.") :$$: ((Text "Try providing the associated Type Decoded (" :<>: ShowType x) :<>: Text ") manually:")) :$$: ((Text "instance Codec (" :<>: ShowType x) :<>: Text ") where ")) :$$: ((Text " type Decoded (" :<>: ShowType x) :<>: Text ") = ... "))