Safe Haskell | None |
---|---|
Language | Haskell2010 |
- trace :: String -> a -> a
- traceM :: Monad m => String -> m ()
- type DList a = Endo [a]
- type AttrSet = HashMap Text
- type Alg f a = f a -> a
- type AlgM f m a = f a -> m a
- type Transform f a = (Fix f -> a) -> Fix f -> a
- (<&>) :: Functor f => f a -> (a -> c) -> f c
- (??) :: Functor f => f (a -> b) -> a -> f b
- loeb :: Functor f => f (f a -> a) -> f a
- loebM :: (MonadFix m, Traversable t) => t (t a -> m a) -> m (t a)
- para :: Functor f => (f (Fix f, a) -> a) -> Fix f -> a
- paraM :: (Traversable f, Monad m) => (f (Fix f, a) -> m a) -> Fix f -> m a
- cataP :: Functor f => (Fix f -> f a -> a) -> Fix f -> a
- cataPM :: (Traversable f, Monad m) => (Fix f -> f a -> m a) -> Fix f -> m a
- transport :: Functor g => (forall x. f x -> g x) -> Fix f -> Fix g
- adi :: Functor f => (f a -> a) -> ((Fix f -> a) -> Fix f -> a) -> Fix f -> a
- adiM :: (Traversable t, Monad m) => (t a -> m a) -> ((Fix t -> m a) -> Fix t -> m a) -> Fix t -> m a
- class Has a b where
- toEncodingSorted :: Value -> Encoding
Documentation
type Alg f a = f a -> a Source #
An f-algebra defines how to reduced the fixed-point of a functor to a value.
type Transform f a = (Fix f -> a) -> Fix f -> a Source #
An "transform" here is a modification of a catamorphism.
loebM :: (MonadFix m, Traversable t) => t (t a -> m a) -> m (t a) Source #
adi :: Functor f => (f a -> a) -> ((Fix f -> a) -> Fix f -> a) -> Fix f -> a Source #
adi is Abstracting Definitional Interpreters:
https://arxiv.org/abs/1707.04755
Essentially, it does for evaluation what recursion schemes do for representation: allows threading layers through existing structure, only in this case through behavior.
adiM :: (Traversable t, Monad m) => (t a -> m a) -> ((Fix t -> m a) -> Fix t -> m a) -> Fix t -> m a Source #
toEncodingSorted :: Value -> Encoding Source #