Copyright | (c) Murdoch J. Gabbay 2020 |
---|---|
License | GPL-3 |
Maintainer | murdoch.gabbay@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Typeclass and instances for a "suspended" monoid action. Three examples will be of particular interest:
- Suspend a permutation (
). (This is familiar from the theory of nominal rewriting, where swappings suspend on unknowns.)XSwp
s - Suspend a binding (
; we use this to defineXRes
s
).KNom
- Suspend a capture-avoiding binding (
).KNom
s
Intuitively, KNom
is just XRes
plus Swappable
plus IO
(for fresh IDs).
Synopsis
- class Monoid i => SMonad i m | m -> i where
- (+<<) :: SMonad i m => (i -> a -> m b) -> m a -> m b
- imap :: SMonad i m => (i -> a -> b) -> m a -> m b
- pami :: SMonad i m => m a -> (i -> a -> b) -> m b
- exitWith :: SMonad i m => (i -> a -> b) -> m a -> b
- withExit :: SMonad i m => m a -> (i -> a -> b) -> b
- iact :: (Monad m, SMonad i m) => i -> m a -> m a
- newtype ViaSMonad m a = ViaSMonad {
- runViaSMonad :: m a
- data XSuspend i a = Suspend i a
- type XSwp s a = XSuspend (KPerm s) a
- getSwp :: (Typeable s, Swappable a) => XSwp s a -> a
- type XRes s a = XSuspend [KAtom s] a
- getRes :: KRestrict s a => XRes s a -> a
- transposeMF :: (Functor f, SMonad i m) => m (f a) -> f (m a)
- transposeFM :: (Traversable f, Applicative m, SMonad i m) => f (m a) -> m (f a)
Documentation
class Monoid i => SMonad i m | m -> i where Source #
A typeclass for computing under a monoid action.
RULES:
exit . enter mempty == id flip >>+ . const == >== i.e. a' >>= f = a' >>+ const f enter mempty == return
In other words:
+<< . const
andenter mempty
form a monad.enter mempty
followed byexit
is a noop.
(>>+) :: m a -> (i -> a -> m b) -> m b Source #
Move from one suspended environment to another via a function i -> a -> m b
.
enter :: i -> a -> m a Source #
Enter the suspended environment, by suspending i
on a
.
Exit the suspended environment, discarding any suspended actions.
Use exitWith
to exit while folding actions into the computation.
imap :: SMonad i m => (i -> a -> b) -> m a -> m b Source #
An equivalent to fmap
, with access to the monoid.
pami :: SMonad i m => m a -> (i -> a -> b) -> m b Source #
An equivalent to <&>
, with access to the monoid.
exitWith :: SMonad i m => (i -> a -> b) -> m a -> b Source #
Exit the SMonad
, with a function to fold the monoid into the computation. So:
exit = exitWith (,)
newtype ViaSMonad m a Source #
ViaSMonad | |
|
A generic type for suspended monoid operations
Suspend i a |
Instances
Monoid i => SMonad i (XSuspend i) Source # | |
Monoid i => Monad (XSuspend i) Source # | |
Monoid i => Functor (XSuspend i) Source # | |
Monoid i => Applicative (XSuspend i) Source # | |
Defined in Language.Nominal.SMonad | |
(Eq i, Eq a) => Eq (XSuspend i a) Source # | |
(Show i, Show a) => Show (XSuspend i a) Source # | |
Generic (XSuspend i a) Source # | |
(Swappable i, Swappable a) => Swappable (XSuspend i a) Source # | |
type Rep (XSuspend i a) Source # | |
Defined in Language.Nominal.SMonad type Rep (XSuspend i a) = D1 (MetaData "XSuspend" "Language.Nominal.SMonad" "nom-0.1.0.2-Cei0dwnsIrWHLKrPA11A4S" False) (C1 (MetaCons "Suspend" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 i) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) |
getSwp :: (Typeable s, Swappable a) => XSwp s a -> a Source #
Exit with a swapping action, if available
Transpose an SMonad
with other constructors.
transposeMF :: (Functor f, SMonad i m) => m (f a) -> f (m a) Source #
Transpose an SMonad
with a Functor
Note: if m
is instantiated to
then note there is no capture-avoidance here; local bindings are just moved around. A stronger version (with correspondingly stronger typeclass assumptions) is in KNom
stransposeNomF
.
transposeFM :: (Traversable f, Applicative m, SMonad i m) => f (m a) -> m (f a) Source #
This is just an instance of a more general principle, since f
is Traversable
and we assume m
applicative.