grisette-0.5.0.0: Symbolic evaluation as a library
Copyright(c) Sirui Lu 2021-2023
LicenseBSD-3-Clause (see the LICENSE file)
Maintainersiruilu@cs.washington.edu
StabilityExperimental
PortabilityGHC only
Safe HaskellTrustworthy
LanguageHaskell2010

Grisette.Internal.Core.Data.Class.Solvable

Description

 
Synopsis

Solvable type interface

class IsString t => Solvable c t | t -> c where Source #

The class defines the creation and pattern matching of solvable type values.

Minimal complete definition

con, conView, sym

Methods

con :: c -> t Source #

Wrap a concrete value in a symbolic value.

>>> con True :: SymBool
true

conView :: t -> Maybe c Source #

Extract the concrete value from a symbolic value.

>>> conView (con True :: SymBool)
Just True
>>> conView (ssym "a" :: SymBool)
Nothing

sym :: Symbol -> t Source #

Generate symbolic constants.

Two symbolic constants with the same symbol are the same symbolic constant, and will always be assigned with the same value by the solver.

>>> sym "a" :: SymBool
a
>>> (sym "a" :: SymBool) == sym "a"
True
>>> (sym "a" :: SymBool) == sym "b"
False
>>> (sym "a" :: SymBool) .&& sym "a"
a
>>> (sym "a" :: SymBool) == isym "a" 1
False

ssym :: Identifier -> t Source #

Generate simply-named symbolic constants.

Two symbolic constants with the same identifier are the same symbolic constant, and will always be assigned with the same value by the solver.

>>> ssym "a" :: SymBool
a
>>> (ssym "a" :: SymBool) == ssym "a"
True
>>> (ssym "a" :: SymBool) == ssym "b"
False
>>> (ssym "a" :: SymBool) .&& ssym "a"
a

isym :: Identifier -> Int -> t Source #

Generate indexed symbolic constants.

Two symbolic constants with the same identifier but different indices are not the same symbolic constants.

>>> isym "a" 1 :: SymBool
a@1

Instances

Instances details
Solvable Integer SymInteger Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SymInteger

Solvable Bool SymBool Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SymBool

(Solvable c t, Mergeable t) => Solvable c (UnionM t) Source # 
Instance details

Defined in Grisette.Internal.Core.Control.Monad.UnionM

(KnownNat n, 1 <= n) => Solvable (IntN n) (SymIntN n) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SymBV

(KnownNat n, 1 <= n) => Solvable (WordN n) (SymWordN n) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SymBV

(SupportedPrim ca, SupportedPrim cb, LinkedRep ca sa, LinkedRep cb sb, SupportedPrim (ca --> cb)) => Solvable (ca --> cb) (sa -~> sb) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SymGeneralFun

Methods

con :: (ca --> cb) -> sa -~> sb Source #

conView :: (sa -~> sb) -> Maybe (ca --> cb) Source #

sym :: Symbol -> sa -~> sb Source #

ssym :: Identifier -> sa -~> sb Source #

isym :: Identifier -> Int -> sa -~> sb Source #

(SupportedPrim ca, SupportedPrim cb, LinkedRep ca sa, LinkedRep cb sb, SupportedPrim (ca =-> cb)) => Solvable (ca =-> cb) (sa =~> sb) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SymTabularFun

Methods

con :: (ca =-> cb) -> sa =~> sb Source #

conView :: (sa =~> sb) -> Maybe (ca =-> cb) Source #

sym :: Symbol -> sa =~> sb Source #

ssym :: Identifier -> sa =~> sb Source #

isym :: Identifier -> Int -> sa =~> sb Source #

pattern Con :: Solvable c t => c -> t Source #

Extract the concrete value from a solvable value with conView.

>>> case con True :: SymBool of Con v -> v
True

slocsym :: Solvable c s => Identifier -> SpliceQ s Source #

Generate simply-named symbolic variables. The file location will be attached to the identifier.

>>> $$(slocsym "a") :: SymBool
a:<interactive>:...

Calling slocsym with the same name at different location will always generate different symbolic constants. Calling slocsym at the same location for multiple times will generate the same symbolic constants.

>>> ($$(slocsym "a") :: SymBool) == $$(slocsym "a")
False
>>> let f _ = $$(slocsym "a") :: SymBool
>>> f () == f ()
True

ilocsym :: Solvable c s => Identifier -> Int -> SpliceQ s Source #

Generate indexed symbolic variables. The file location will be attached to identifier.

>>> $$(ilocsym "a" 1) :: SymBool
a:<interactive>:...@1

Calling ilocsym with the same name and index at different location will always generate different symbolic constants. Calling slocsym at the same location for multiple times will generate the same symbolic constants.