| Copyright | © Jonathan Lorimer 2023 |
|---|---|
| License | MIT |
| Maintainer | jonathanlorimer@pm.me |
| Stability | stable |
| Safe Haskell | None |
| Language | Haskell2010 |
KeyTree
Description
This module contains types for our internal tree representation of types and configurations. It also contains some helper functions for working with these trees. This should make it easier to implement different source providers.
Since: 0.0.2.0
Synopsis
- type KeyTree key value = Free (Map key) value
- type KeyForest key value = Map key (Free (Map key) value)
- foldKeyTree :: (Eq k, Eq v) => (v -> a) -> (k -> Free (Map k) v -> a -> a) -> a -> KeyTree k v -> a
- appendFold :: (Eq k, Eq v) => (a -> v -> v') -> (a -> v') -> (k -> a -> Map k (Free (Map k) v) -> a) -> a -> KeyTree k v -> KeyTree k v'
- mayAppendFold :: (Eq k, Eq v) => (a -> v -> Maybe v') -> (a -> Maybe v') -> (k -> a -> Map k (Free (Map k) v) -> a) -> a -> KeyTree k v -> KeyTree k v'
- appendTraverse :: (Applicative f, Eq k, Eq v) => (a -> v -> f v') -> (a -> f v') -> (k -> a -> Map k (Free (Map k) v) -> a) -> a -> KeyTree k v -> f (KeyTree k v')
- mayAppendTraverse :: (Applicative f, Eq k, Eq v) => (a -> v -> f v') -> (a -> f (Maybe v')) -> (k -> a -> Map k (Free (Map k) v) -> a) -> a -> KeyTree k v -> f (KeyTree k v')
- data Map k a
- data Free (f :: Type -> Type) a
Types
type KeyTree key value = Free (Map key) value Source #
Type alias for our internal tree structure. If this was written directly as a sum type it would look like this:
Pure value | Free (Map key (KeyTree key value))
Since: 0.0.2.0
type KeyForest key value = Map key (Free (Map key) value) Source #
Type alias for a subtree
Since: 0.0.2.0
Helper Functions
Arguments
| :: (Eq k, Eq v) | |
| => (v -> a) | Function to run on |
| -> (k -> Free (Map k) v -> a -> a) | Step function for fold |
| -> a | Initial accumulator |
| -> KeyTree k v | KeyTree to fold |
| -> a |
Right fold on a KeyTree. Uses foldrWithKey under the hood.
Since: 0.0.2.0
Arguments
| :: (Eq k, Eq v) | |
| => (a -> v -> v') | Function to run on existing |
| -> (a -> v') | Function from accumulator |
| -> (k -> a -> Map k (Free (Map k) v) -> a) | Step function for fold with key |
| -> a | Accumulator. |
| -> KeyTree k v | KeyTree to append values to. |
| -> KeyTree k v' |
A fold that appends a value at the leaf of the KeyTree, identifies what to
insert at the leaf by running a function on an accumulated value.
Since: 0.0.2.0
Arguments
| :: (Eq k, Eq v) | |
| => (a -> v -> Maybe v') | Function to run on existing |
| -> (a -> Maybe v') | Function to run when an empty node is found. |
| -> (k -> a -> Map k (Free (Map k) v) -> a) | Step function for fold with key |
| -> a | Accumulator. |
| -> KeyTree k v | Tree to be folded. |
| -> KeyTree k v' |
A fold that appends a value at the leaf of the KeyTree (like
appendFold), but the function on the accumulator can return a Maybe. In
the Nothing case we just append a Free full of an empty Map.
Since: 0.0.2.0
Arguments
| :: (Applicative f, Eq k, Eq v) | |
| => (a -> v -> f v') | Function to run on existing |
| -> (a -> f v') | Function to run when an empty node is found. |
| -> (k -> a -> Map k (Free (Map k) v) -> a) | Step function for fold with key |
| -> a | Accumulator. |
| -> KeyTree k v | Tree to be folded. |
| -> f (KeyTree k v') |
Like appendFold but with functions that return a value wrapped in an
Applicative effect f. The function is suffixed with "Traverse" because
we use the sequenceA to wrap the entire tree in a single Applicative
effect.
Since: 0.0.2.0
mayAppendTraverse :: (Applicative f, Eq k, Eq v) => (a -> v -> f v') -> (a -> f (Maybe v')) -> (k -> a -> Map k (Free (Map k) v) -> a) -> a -> KeyTree k v -> f (KeyTree k v') Source #
Similar to appendTraverse except the Applicative effect can optionally
return a result. The function is manually implemented rather than using
Traversable methods so that we don't have to require Traversable on f.
This allows consumers to use effects like IO that don't have a
Traversable instance.
Since: 0.0.2.0
Type Re-exports
A Map from keys k to values a.
The Semigroup operation for Map is union, which prefers
values from the left operand. If m1 maps a key k to a value
a1, and m2 maps the same key to a different value a2, then
their union m1 <> m2 maps k to a1.
Instances
| Bifoldable Map | Since: containers-0.6.3.1 |
| Eq2 Map | Since: containers-0.5.9 |
| Ord2 Map | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
| Show2 Map | Since: containers-0.5.9 |
| Hashable2 Map | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
| (Lift k, Lift a) => Lift (Map k a :: Type) | Since: containers-0.6.6 |
| Foldable (Map k) | Folds in order of increasing key. |
Defined in Data.Map.Internal Methods fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> m # foldMap' :: Monoid m => (a -> m) -> Map k a -> m # foldr :: (a -> b -> b) -> b -> Map k a -> b # foldr' :: (a -> b -> b) -> b -> Map k a -> b # foldl :: (b -> a -> b) -> b -> Map k a -> b # foldl' :: (b -> a -> b) -> b -> Map k a -> b # foldr1 :: (a -> a -> a) -> Map k a -> a # foldl1 :: (a -> a -> a) -> Map k a -> a # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |
| Eq k => Eq1 (Map k) | Since: containers-0.5.9 |
| Ord k => Ord1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
| (Ord k, Read k) => Read1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
| Show k => Show1 (Map k) | Since: containers-0.5.9 |
| Traversable (Map k) | Traverses in order of increasing key. |
| Functor (Map k) | |
| Hashable k => Hashable1 (Map k) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
| (Data k, Data a, Ord k) => Data (Map k a) | |
Defined in Data.Map.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) # toConstr :: Map k a -> Constr # dataTypeOf :: Map k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) # gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # | |
| Ord k => Monoid (Map k v) | |
| Ord k => Semigroup (Map k v) | |
| Ord k => IsList (Map k v) | Since: containers-0.5.6.2 |
| (Ord k, Read k, Read e) => Read (Map k e) | |
| (Show k, Show a) => Show (Map k a) | |
| (NFData k, NFData a) => NFData (Map k a) | |
Defined in Data.Map.Internal | |
| (Eq k, Eq a) => Eq (Map k a) | |
| (Ord k, Ord v) => Ord (Map k v) | |
| (Hashable k, Hashable v) => Hashable (Map k v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
| type Item (Map k v) | |
Defined in Data.Map.Internal | |
data Free (f :: Type -> Type) a #
The Free Monad for a Functor f.
Formally
A Monad n is a free Monad for f if every monad homomorphism
from n to another monad m is equivalent to a natural transformation
from f to m.
Why Free?
Every "free" functor is left adjoint to some "forgetful" functor.
If we define a forgetful functor U from the category of monads to the category of functors
that just forgets the Monad, leaving only the Functor. i.e.
U (M,return,join) = M
then Free is the left adjoint to U.
Free being left adjoint to U means that there is an isomorphism between
in the category of monads and Free f -> mf -> U m in the category of functors.
Morphisms in the category of monads are Monad homomorphisms (natural transformations that respect return and join).
Morphisms in the category of functors are Functor homomorphisms (natural transformations).
Given this isomorphism, every monad homomorphism from to Free fm is equivalent to a natural transformation from f to m
Showing that this isomorphism holds is left as an exercise.
In practice, you can just view a as many layers of Free f af wrapped around values of type a, where
( performs substitution and grafts new layers of >>=)f in for each of the free variables.
This can be very useful for modeling domain specific languages, trees, or other constructs.
This instance of MonadFree is fairly naive about the encoding. For more efficient free monad implementation see Control.Monad.Free.Church, in particular note the improve combinator.
You may also want to take a look at the kan-extensions package (http://hackage.haskell.org/package/kan-extensions).
A number of common monads arise as free monads,
Instances
| MonadTrans Free | This is not a true monad transformer. It is only a monad transformer "up to | ||||
Defined in Control.Monad.Free | |||||
| Functor f => Generic1 (Free f :: Type -> Type) | |||||
Defined in Control.Monad.Free Associated Types
| |||||
| Functor f => MonadFree f (Free f) | |||||
Defined in Control.Monad.Free | |||||
| MonadError e m => MonadError e (Free m) | |||||
Defined in Control.Monad.Free | |||||
| MonadReader e m => MonadReader e (Free m) | |||||
| MonadState s m => MonadState s (Free m) | |||||
| MonadWriter e m => MonadWriter e (Free m) | |||||
| Functor f => MonadFix (Free f) | |||||
Defined in Control.Monad.Free | |||||
| Foldable f => Foldable (Free f) | |||||
Defined in Control.Monad.Free Methods fold :: Monoid m => Free f m -> m # foldMap :: Monoid m => (a -> m) -> Free f a -> m # foldMap' :: Monoid m => (a -> m) -> Free f a -> m # foldr :: (a -> b -> b) -> b -> Free f a -> b # foldr' :: (a -> b -> b) -> b -> Free f a -> b # foldl :: (b -> a -> b) -> b -> Free f a -> b # foldl' :: (b -> a -> b) -> b -> Free f a -> b # foldr1 :: (a -> a -> a) -> Free f a -> a # foldl1 :: (a -> a -> a) -> Free f a -> a # elem :: Eq a => a -> Free f a -> Bool # maximum :: Ord a => Free f a -> a # minimum :: Ord a => Free f a -> a # | |||||
| Foldable1 f => Foldable1 (Free f) | |||||
Defined in Control.Monad.Free Methods fold1 :: Semigroup m => Free f m -> m # foldMap1 :: Semigroup m => (a -> m) -> Free f a -> m # foldMap1' :: Semigroup m => (a -> m) -> Free f a -> m # toNonEmpty :: Free f a -> NonEmpty a # maximum :: Ord a => Free f a -> a # minimum :: Ord a => Free f a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> Free f a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> Free f a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> Free f a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> Free f a -> b # | |||||
| Eq1 f => Eq1 (Free f) | |||||
| Ord1 f => Ord1 (Free f) | |||||
Defined in Control.Monad.Free | |||||
| Read1 f => Read1 (Free f) | |||||
Defined in Control.Monad.Free | |||||
| Show1 f => Show1 (Free f) | |||||
| Traversable f => Traversable (Free f) | |||||
| Alternative v => Alternative (Free v) | This violates the Alternative laws, handle with care. | ||||
| Functor f => Applicative (Free f) | |||||
| Functor f => Functor (Free f) | |||||
| Functor f => Monad (Free f) | |||||
| MonadPlus v => MonadPlus (Free v) | This violates the MonadPlus laws, handle with care. | ||||
| MonadCont m => MonadCont (Free m) | |||||
| Functor f => Apply (Free f) | |||||
| Functor f => Bind (Free f) | |||||
| Traversable1 f => Traversable1 (Free f) | |||||
| FoldableWithIndex i f => FoldableWithIndex [i] (Free f) | |||||
Defined in Control.Monad.Free | |||||
| FunctorWithIndex i f => FunctorWithIndex [i] (Free f) | |||||
Defined in Control.Monad.Free | |||||
| TraversableWithIndex i f => TraversableWithIndex [i] (Free f) | |||||
Defined in Control.Monad.Free Methods itraverse :: Applicative f0 => ([i] -> a -> f0 b) -> Free f a -> f0 (Free f b) # | |||||
| (Typeable f, Data (f (Free f a)), Data a) => Data (Free f a) | |||||
Defined in Control.Monad.Free Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Free f a -> c (Free f a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Free f a) # toConstr :: Free f a -> Constr # dataTypeOf :: Free f a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Free f a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Free f a)) # gmapT :: (forall b. Data b => b -> b) -> Free f a -> Free f a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Free f a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Free f a -> r # gmapQ :: (forall d. Data d => d -> u) -> Free f a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Free f a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Free f a -> m (Free f a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Free f a -> m (Free f a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Free f a -> m (Free f a) # | |||||
| Generic (Free f a) | |||||
Defined in Control.Monad.Free Associated Types
| |||||
| (Read1 f, Read a) => Read (Free f a) | |||||
| (Show1 f, Show a) => Show (Free f a) | |||||
| (Eq1 f, Eq a) => Eq (Free f a) | |||||
| (Ord1 f, Ord a) => Ord (Free f a) | |||||
Defined in Control.Monad.Free | |||||
| type Rep1 (Free f :: Type -> Type) | |||||
Defined in Control.Monad.Free type Rep1 (Free f :: Type -> Type) = D1 ('MetaData "Free" "Control.Monad.Free" "free-5.2-HYM0gD1Fq69B83fsZa2Ny8" 'False) (C1 ('MetaCons "Pure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1) :+: C1 ('MetaCons "Free" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (f :.: Rec1 (Free f)))) | |||||
| type Rep (Free f a) | |||||
Defined in Control.Monad.Free type Rep (Free f a) = D1 ('MetaData "Free" "Control.Monad.Free" "free-5.2-HYM0gD1Fq69B83fsZa2Ny8" 'False) (C1 ('MetaCons "Pure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Free" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Free f a))))) | |||||