Safe Haskell | Trustworthy |
---|---|
Language | GHC2021 |
Language.Hasmtlib.Internal.Sharing
Synopsis
- class Sharing s where
- type SharingMonad s :: (Type -> Type) -> Constraint
- stableMap :: Lens' s (HashMap (StableName ()) (SomeKnownSMTSort Expr))
- assertSharedNode :: (MonadState s m, SharingMonad s m) => StableName () -> Expr BoolSort -> m ()
- setSharingMode :: MonadState s m => SharingMode -> m ()
- data SharingMode
- = None
- | StableNames
- runSharing :: (KnownSMTSort t, MonadSMT s m, Sharing s, SharingMonad s m) => SharingMode -> Expr t -> m (Expr t)
- share :: (Equatable (Expr t), KnownSMTSort t, MonadSMT s m, Sharing s, SharingMonad s m) => Expr t -> m (Expr t) -> m (Expr t)
Documentation
class Sharing s where Source #
States that can share expressions by comparing their StableName
s.
Associated Types
type SharingMonad s :: (Type -> Type) -> Constraint Source #
A constraint on the monad used when asserting the shared node in assertSharedNode
.
Methods
stableMap :: Lens' s (HashMap (StableName ()) (SomeKnownSMTSort Expr)) Source #
A Lens'
on a mapping between a StableName
and it's Expr
we may share.
assertSharedNode :: (MonadState s m, SharingMonad s m) => StableName () -> Expr BoolSort -> m () Source #
Asserts that a node-expression is represented by it's auxiliary node-variable: nodeExpr :: Expr t === nodeVar
.
Also gives access to the StableName
of the original expression.
setSharingMode :: MonadState s m => SharingMode -> m () Source #
Sets the mode used for sharing common expressions. Defaults to StableNames
.
Instances
data SharingMode Source #
Mode used for sharing.
Constructors
None | Common expressions are not shared at all |
StableNames | Expressions that resolve to the same |
Instances
Show SharingMode Source # | |
Defined in Language.Hasmtlib.Internal.Sharing Methods showsPrec :: Int -> SharingMode -> ShowS # show :: SharingMode -> String # showList :: [SharingMode] -> ShowS # | |
Default SharingMode Source # | |
Defined in Language.Hasmtlib.Internal.Sharing Methods def :: SharingMode # |
runSharing :: (KnownSMTSort t, MonadSMT s m, Sharing s, SharingMonad s m) => SharingMode -> Expr t -> m (Expr t) Source #
Shares all possible sub-expressions in given expression.
Replaces each node in the expression-tree with an auxiliary variable.
All nodes x
y
where makeStableName x == makeStableName y
are replaced with the same auxiliary variable.
Therefore this creates a DAG.
share :: (Equatable (Expr t), KnownSMTSort t, MonadSMT s m, Sharing s, SharingMonad s m) => Expr t -> m (Expr t) -> m (Expr t) Source #
Returns an auxiliary variable representing this expression node. If such a shared auxiliary variable exists already, returns that. Otherwise creates one and returns it.