tamarin-prover-utils-0.8.1.0: Utility library for the tamarin prover.

PortabilityGHC only
MaintainerSimon Meier <iridcode@gmail.com>
Safe HaskellSafe-Infered

Control.Monad.Bind

Contents

Description

Shallow monad transformer for dealing with bindings.

Synopsis

Bindings

type Bindings = MapSource

Type constructor for the state of the binding store.

noBindings :: Bindings v kSource

The empty binding store.

MonadBind class

class MonadState (Bindings k v) m => MonadBind k v m Source

Instances

MonadBind k v m => MonadBind k v (FreshT m) 
MonadBind k v m => MonadBind k v (FreshT m) 
Monad m => MonadBind k v (StateT (Bindings k v) m) 

Bind monad

type Bind k v = State (Bindings k v)Source

Managing just bindings.

runBind :: Bind k v a -> Bindings k v -> (a, Bindings k v)Source

Run a computation with bindings.

evalBind :: Bind k v a -> Bindings k v -> aSource

Evaluate a binding context computation.

execBind :: Bind k v a -> Bindings k v -> Bindings k vSource

Execute a binding context computation.

BindT monad transformer

type BindT k v = StateT (Bindings k v)Source

Managing bindings on top of another monad.

runBindT :: BindT k v m a -> Bindings k v -> m (a, Bindings k v)Source

Run a computation with bindings.

evalBindT :: Monad m => BindT k v m a -> Bindings k v -> m aSource

Evaluate a binding context computation.

execBindT :: Monad m => BindT k v m a -> Bindings k v -> m (Bindings k v)Source

Execute a binding context computation.

Binding operations

lookupBinding :: (MonadBind k v m, Ord k) => k -> m (Maybe v)Source

Lookup a stored binding.

insertBinding :: (MonadBind k v m, Ord k) => k -> v -> m ()Source

insertBinding k v inserts the binding of k to v, possibly overwriting the existing binding of k.

importBinding :: (MonadBind k v m, MonadFresh m, Show v, Show k, Ord k) => (String -> Integer -> v) -> k -> String -> m vSource

importBinding mkR d n checks if there is already a binding registered for the value d and if not it generates a fresh identifier using the name n as a hint and converting name and identifier to a value using $mkR$.