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

Grisette.Internal.SymPrim.AllSyms

Description

 
Synopsis

Documentation

symSize :: forall con sym. LinkedRep con sym => sym -> Int Source #

Get the size of a symbolic term. Duplicate sub-terms are counted for only once.

>>> symSize (1 :: SymInteger)
1
>>> symSize ("a" :: SymInteger)
1
>>> symSize ("a" + 1 :: SymInteger)
3
>>> symSize (("a" + 1) * ("a" + 1) :: SymInteger)
4

symsSize :: forall con sym. LinkedRep con sym => [sym] -> Int Source #

Get the sum of the sizes of a list of symbolic terms. Duplicate sub-terms are counted for only once.

>>> symsSize [1, "a" :: SymInteger, "a" + 1 :: SymInteger]
3

data SomeSym where Source #

Some symbolic value with LinkedRep constraint.

Constructors

SomeSym :: LinkedRep con sym => sym -> SomeSym 

class AllSyms a where Source #

Extract all symbolic primitive values that are represented as SMT terms.

Note: This type class can be derived for algebraic data types. You may need the DerivingVia and DerivingStrategies extenstions.

data X = ... deriving Generic deriving AllSyms via (Default X)

Minimal complete definition

allSymsS | allSyms

Methods

allSymsS :: a -> [SomeSym] -> [SomeSym] Source #

Convert a value to a list of symbolic primitive values. It should prepend to an existing list of symbolic primitive values.

allSyms :: a -> [SomeSym] Source #

Specialized allSymsS that prepends to an empty list.

Instances

Instances details
AllSyms Int16 Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Int32 Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Int64 Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Int8 Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Word16 Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Word32 Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Word64 Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Word8 Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms ByteString Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms AssertionError Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms VerificationConditions Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms SymBool Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SymBool

AllSyms SymInteger Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SymInteger

AllSyms Text Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Integer Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms () Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: () -> [SomeSym] -> [SomeSym] Source #

allSyms :: () -> [SomeSym] Source #

AllSyms Bool Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Char Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Int Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms Word Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

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

Defined in Grisette.Internal.SymPrim.AllSyms

(Generic a, AllSyms' (Rep a)) => AllSyms (Default a) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms a => AllSyms (UnionM a) Source # 
Instance details

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

AllSyms a => AllSyms (Union a) Source # 
Instance details

Defined in Grisette.Internal.Core.Data.Union

Methods

allSymsS :: Union a -> [SomeSym] -> [SomeSym] Source #

allSyms :: Union a -> [SomeSym] Source #

(forall (n :: Nat). (KnownNat n, 1 <= n) => AllSyms (bv n)) => AllSyms (SomeBV bv) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.SomeBV

Methods

allSymsS :: SomeBV bv -> [SomeSym] -> [SomeSym] Source #

allSyms :: SomeBV bv -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.SymBV

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

Defined in Grisette.Internal.SymPrim.SymBV

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: Maybe a -> [SomeSym] -> [SomeSym] Source #

allSyms :: Maybe a -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: [a] -> [SomeSym] -> [SomeSym] Source #

allSyms :: [a] -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: Either a b -> [SomeSym] -> [SomeSym] Source #

allSyms :: Either a b -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.SymGeneralFun

Methods

allSymsS :: (sa -~> sb) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (sa -~> sb) -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.SymTabularFun

Methods

allSymsS :: (sa =~> sb) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (sa =~> sb) -> [SomeSym] Source #

AllSyms (m (Maybe a)) => AllSyms (MaybeT m a) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: MaybeT m a -> [SomeSym] -> [SomeSym] Source #

allSyms :: MaybeT m a -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: (a, b) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (a, b) -> [SomeSym] Source #

AllSyms (m (Either e a)) => AllSyms (ExceptT e m a) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: ExceptT e m a -> [SomeSym] -> [SomeSym] Source #

allSyms :: ExceptT e m a -> [SomeSym] Source #

AllSyms (m a) => AllSyms (IdentityT m a) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

AllSyms (m (a, s)) => AllSyms (WriterT s m a) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: WriterT s m a -> [SomeSym] -> [SomeSym] Source #

allSyms :: WriterT s m a -> [SomeSym] Source #

AllSyms (m (a, s)) => AllSyms (WriterT s m a) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: WriterT s m a -> [SomeSym] -> [SomeSym] Source #

allSyms :: WriterT s m a -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: (a, b, c) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (a, b, c) -> [SomeSym] Source #

(AllSyms (f a), AllSyms (g a)) => AllSyms (Sum f g a) Source # 
Instance details

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: Sum f g a -> [SomeSym] -> [SomeSym] Source #

allSyms :: Sum f g a -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: (a, b, c, d) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (a, b, c, d) -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: (a, b, c, d, e) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (a, b, c, d, e) -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: (a, b, c, d, e, f) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (a, b, c, d, e, f) -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: (a, b, c, d, e, f, g) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (a, b, c, d, e, f, g) -> [SomeSym] Source #

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

Defined in Grisette.Internal.SymPrim.AllSyms

Methods

allSymsS :: (a, b, c, d, e, f, g, h) -> [SomeSym] -> [SomeSym] Source #

allSyms :: (a, b, c, d, e, f, g, h) -> [SomeSym] Source #

allSymsSize :: AllSyms a => a -> Int Source #

Get the total size of symbolic terms in a value. Duplicate sub-terms are counted for only once.

>>> allSymsSize ("a" :: SymInteger, "a" + "b" :: SymInteger, ("a" + "b") * "c" :: SymInteger)
5