functor-combinators-0.1.0.0: Tools for functor combinator-based program design

Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.HFunctor.Chain

Contents

Description

This module provides an Interpretable data type of "linked list of tensor applications".

The type Chain t, for any Monoidal t, is meant to be the same as MF t (the monoidal functor combinator for t), and represents "zero or more" applications of f to t.

The type Chain1 t, for any Semigroupoidal t, is meant to be the same as SF t (the semigroupoidal functor combinator for t) and represents "one or more" applications of f to t.

The advantage of using Chain and Chain1 over MF or SF is that they provide a universal interface for pattern matching and constructing such values, which may simplify working with new such functor combinators you might encounter.

Synopsis

Chain

data Chain t i f a Source #

A useful construction that works like a "linked list" of t f applied to itself multiple times. That is, it contains t f f, t f (t f f), t f (t f (t f f)), etc, with f occuring zero or more times. It is meant to be the same as MF t.

If t is Monoidal, then it means we can "collapse" this linked list into some final type MF t (rerollMF), and also extract it back into a linked list (unrollMF).

So, a value of type Chain t (I t) f a is one of either:

  • I t a
  • f a
  • t f f a
  • t f (t f f) a
  • t f (t f (t f f)) a
  • .. etc.

Note that this is exactly what an MF t is supposed to be. Using Chain allows us to work with all MF ts in a uniform way, with normal pattern matching and normal constructors.

This construction is inspired by http://oleg.fi/gists/posts/2018-02-21-single-free.html

Constructors

Done (i a) 
More (t f (Chain t i f) a) 
Instances
HBifunctor t => HFunctor (Chain t i :: (k1 -> Type) -> k2 -> Type) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

hmap :: (f ~> g) -> Chain t i f ~> Chain t i g Source #

(Tensor t, i ~ I t) => Inject (Chain t i :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

inject :: f ~> Chain t i f Source #

(Monoidal t, i ~ I t) => Interpret (Chain t i) Source #

We can collapse and interpret an Chain t i if we have Tensor t.

Instance details

Defined in Data.HFunctor.Chain

Associated Types

type C (Chain t i) :: (Type -> Type) -> Constraint Source #

Methods

retract :: C (Chain t i) f => Chain t i f ~> f Source #

interpret :: C (Chain t i) g => (f ~> g) -> Chain t i f ~> g Source #

(Functor i, Functor (t f (Chain t i f))) => Functor (Chain t i f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

fmap :: (a -> b) -> Chain t i f a -> Chain t i f b #

(<$) :: a -> Chain t i f b -> Chain t i f a #

(Foldable i, Foldable (t f (Chain t i f))) => Foldable (Chain t i f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

fold :: Monoid m => Chain t i f m -> m #

foldMap :: Monoid m => (a -> m) -> Chain t i f a -> m #

foldr :: (a -> b -> b) -> b -> Chain t i f a -> b #

foldr' :: (a -> b -> b) -> b -> Chain t i f a -> b #

foldl :: (b -> a -> b) -> b -> Chain t i f a -> b #

foldl' :: (b -> a -> b) -> b -> Chain t i f a -> b #

foldr1 :: (a -> a -> a) -> Chain t i f a -> a #

foldl1 :: (a -> a -> a) -> Chain t i f a -> a #

toList :: Chain t i f a -> [a] #

null :: Chain t i f a -> Bool #

length :: Chain t i f a -> Int #

elem :: Eq a => a -> Chain t i f a -> Bool #

maximum :: Ord a => Chain t i f a -> a #

minimum :: Ord a => Chain t i f a -> a #

sum :: Num a => Chain t i f a -> a #

product :: Num a => Chain t i f a -> a #

(Traversable i, Traversable (t f (Chain t i f))) => Traversable (Chain t i f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Chain t i f a -> f0 (Chain t i f b) #

sequenceA :: Applicative f0 => Chain t i f (f0 a) -> f0 (Chain t i f a) #

mapM :: Monad m => (a -> m b) -> Chain t i f a -> m (Chain t i f b) #

sequence :: Monad m => Chain t i f (m a) -> m (Chain t i f a) #

(Eq1 i, Eq1 (t f (Chain t i f))) => Eq1 (Chain t i f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

liftEq :: (a -> b -> Bool) -> Chain t i f a -> Chain t i f b -> Bool #

(Ord1 i, Ord1 (t f (Chain t i f))) => Ord1 (Chain t i f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

liftCompare :: (a -> b -> Ordering) -> Chain t i f a -> Chain t i f b -> Ordering #

(Functor i, Read1 (t f (Chain t i f)), Read1 i) => Read1 (Chain t i f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Chain t i f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Chain t i f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Chain t i f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Chain t i f a] #

(Show1 (t f (Chain t i f)), Show1 i) => Show1 (Chain t i f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Chain t i f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Chain t i f a] -> ShowS #

(Eq (i a), Eq (t f (Chain t i f) a)) => Eq (Chain t i f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

(==) :: Chain t i f a -> Chain t i f a -> Bool #

(/=) :: Chain t i f a -> Chain t i f a -> Bool #

(Ord (i a), Ord (t f (Chain t i f) a)) => Ord (Chain t i f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

compare :: Chain t i f a -> Chain t i f a -> Ordering #

(<) :: Chain t i f a -> Chain t i f a -> Bool #

(<=) :: Chain t i f a -> Chain t i f a -> Bool #

(>) :: Chain t i f a -> Chain t i f a -> Bool #

(>=) :: Chain t i f a -> Chain t i f a -> Bool #

max :: Chain t i f a -> Chain t i f a -> Chain t i f a #

min :: Chain t i f a -> Chain t i f a -> Chain t i f a #

(Read (i a), Read (t f (Chain t i f) a)) => Read (Chain t i f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

readsPrec :: Int -> ReadS (Chain t i f a) #

readList :: ReadS [Chain t i f a] #

readPrec :: ReadPrec (Chain t i f a) #

readListPrec :: ReadPrec [Chain t i f a] #

(Show (i a), Show (t f (Chain t i f) a)) => Show (Chain t i f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

showsPrec :: Int -> Chain t i f a -> ShowS #

show :: Chain t i f a -> String #

showList :: [Chain t i f a] -> ShowS #

type C (Chain t i) Source # 
Instance details

Defined in Data.HFunctor.Chain

type C (Chain t i) = CM t

foldChain Source #

Arguments

:: HBifunctor t 
=> (i ~> g)

Handle Done

-> (t f g ~> g)

Handle More

-> Chain t i f ~> g 

Recursively fold down a Chain. Provide a function on how to handle the "single f case" (nilMF), and how to handle the "combined t f g case", and this will fold the entire Chain t i) f into a single g.

This is a catamorphism.

unfoldChain :: forall t f (g :: Type -> Type) i. HBifunctor t => (g ~> (i :+: t f g)) -> g ~> Chain t i f Source #

Recursively build up a Chain. Provide a function that takes some starting seed g and returns either "done" (i) or "continue further" (t f g), and it will create a Chain t i f from a g.

This is an anamorphism.

unrollMF :: Monoidal t => MF t f ~> Chain t (I t) f Source #

A type MF t is supposed to represent the successive application of ts to itself. unrollMF makes that successive application explicit, buy converting it to a literal Chain of applications of t to itself.

unrollMF = unfoldChain unconsMF

rerollMF :: forall t f. Monoidal t => Chain t (I t) f ~> MF t f Source #

A type MF t is supposed to represent the successive application of ts to itself. rerollSF takes an explicit Chain of applications of t to itself and rolls it back up into an MF t.

rerollMF = foldChain nilMF consMF

Because t cannot be inferred from the input or output, you should call this with -XTypeApplications:

rerollMF @Comp
    :: Chain Comp Identity f a -> Free f a

unrollingMF :: Monoidal t => MF t f <~> Chain t (I t) f Source #

A type MF t is supposed to represent the successive application of ts to itself. The type Chain t (I t) f is an actual concrete ADT that contains successive applications of t to itself, and you can pattern match on each layer.

unrollingMF states that the two types are isormorphic. Use unrollMF and rerollMF to convert between the two.

Chain1

data Chain1 t f a Source #

A useful construction that works like a "non-empty linked list" of t f applied to itself multiple times. That is, it contains t f f, t f (t f f), t f (t f (t f f)), etc, with f occuring one or more times. It is meant to be the same as SF t.

A Chain1 t f a is explicitly one of:

  • f a
  • t f f a
  • t f (t f f) a
  • t f (t f (t f f)) a
  • .. etc

Note that this is exactly the description of SF t. And that's "the point": for all instances of Semigroupoidal, Chain1 t is isomorphic to SF t (witnessed by unrollingSF). That's big picture of SF: it's supposed to be a type that consists of all possible self-applications of f to t.

Chain1 gives you a way to work with all SF t in a uniform way. Unlike for SF t f in general, you can always explicitly /pattern match/ on a Chain1 (with its two constructors) and do what you please with it. You can also construct Chain1 using normal constructors and functions.

You can convert in between SF t f and Chain1 t f with unrollSF and rerollSF.

See Chain for a version that has an "empty" value.

This construction is inspired by iteratees and machines.

Constructors

Done1 (f a) 
More1 (t f (Chain1 t f) a) 
Instances
HBifunctor t => HFunctor (Chain1 t :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

hmap :: (f ~> g) -> Chain1 t f ~> Chain1 t g Source #

HBifunctor t => Inject (Chain1 t :: (k -> Type) -> k -> Type) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

inject :: f ~> Chain1 t f Source #

(HBifunctor t, Semigroupoidal t) => Interpret (Chain1 t) Source # 
Instance details

Defined in Data.HFunctor.Chain

Associated Types

type C (Chain1 t) :: (Type -> Type) -> Constraint Source #

Methods

retract :: C (Chain1 t) f => Chain1 t f ~> f Source #

interpret :: C (Chain1 t) g => (f ~> g) -> Chain1 t f ~> g Source #

(Functor f, Functor (t f (Chain1 t f))) => Functor (Chain1 t f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

fmap :: (a -> b) -> Chain1 t f a -> Chain1 t f b #

(<$) :: a -> Chain1 t f b -> Chain1 t f a #

(Foldable f, Foldable (t f (Chain1 t f))) => Foldable (Chain1 t f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

fold :: Monoid m => Chain1 t f m -> m #

foldMap :: Monoid m => (a -> m) -> Chain1 t f a -> m #

foldr :: (a -> b -> b) -> b -> Chain1 t f a -> b #

foldr' :: (a -> b -> b) -> b -> Chain1 t f a -> b #

foldl :: (b -> a -> b) -> b -> Chain1 t f a -> b #

foldl' :: (b -> a -> b) -> b -> Chain1 t f a -> b #

foldr1 :: (a -> a -> a) -> Chain1 t f a -> a #

foldl1 :: (a -> a -> a) -> Chain1 t f a -> a #

toList :: Chain1 t f a -> [a] #

null :: Chain1 t f a -> Bool #

length :: Chain1 t f a -> Int #

elem :: Eq a => a -> Chain1 t f a -> Bool #

maximum :: Ord a => Chain1 t f a -> a #

minimum :: Ord a => Chain1 t f a -> a #

sum :: Num a => Chain1 t f a -> a #

product :: Num a => Chain1 t f a -> a #

(Traversable f, Traversable (t f (Chain1 t f))) => Traversable (Chain1 t f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Chain1 t f a -> f0 (Chain1 t f b) #

sequenceA :: Applicative f0 => Chain1 t f (f0 a) -> f0 (Chain1 t f a) #

mapM :: Monad m => (a -> m b) -> Chain1 t f a -> m (Chain1 t f b) #

sequence :: Monad m => Chain1 t f (m a) -> m (Chain1 t f a) #

(Eq1 f, Eq1 (t f (Chain1 t f))) => Eq1 (Chain1 t f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

liftEq :: (a -> b -> Bool) -> Chain1 t f a -> Chain1 t f b -> Bool #

(Ord1 f, Ord1 (t f (Chain1 t f))) => Ord1 (Chain1 t f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

liftCompare :: (a -> b -> Ordering) -> Chain1 t f a -> Chain1 t f b -> Ordering #

(Functor f, Read1 (t f (Chain1 t f)), Read1 f) => Read1 (Chain1 t f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Chain1 t f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Chain1 t f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Chain1 t f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Chain1 t f a] #

(Show1 (t f (Chain1 t f)), Show1 f) => Show1 (Chain1 t f) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Chain1 t f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Chain1 t f a] -> ShowS #

(Eq (f a), Eq (t f (Chain1 t f) a)) => Eq (Chain1 t f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

(==) :: Chain1 t f a -> Chain1 t f a -> Bool #

(/=) :: Chain1 t f a -> Chain1 t f a -> Bool #

(Ord (f a), Ord (t f (Chain1 t f) a)) => Ord (Chain1 t f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

compare :: Chain1 t f a -> Chain1 t f a -> Ordering #

(<) :: Chain1 t f a -> Chain1 t f a -> Bool #

(<=) :: Chain1 t f a -> Chain1 t f a -> Bool #

(>) :: Chain1 t f a -> Chain1 t f a -> Bool #

(>=) :: Chain1 t f a -> Chain1 t f a -> Bool #

max :: Chain1 t f a -> Chain1 t f a -> Chain1 t f a #

min :: Chain1 t f a -> Chain1 t f a -> Chain1 t f a #

(Read (f a), Read (t f (Chain1 t f) a)) => Read (Chain1 t f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

readsPrec :: Int -> ReadS (Chain1 t f a) #

readList :: ReadS [Chain1 t f a] #

readPrec :: ReadPrec (Chain1 t f a) #

readListPrec :: ReadPrec [Chain1 t f a] #

(Show (f a), Show (t f (Chain1 t f) a)) => Show (Chain1 t f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Methods

showsPrec :: Int -> Chain1 t f a -> ShowS #

show :: Chain1 t f a -> String #

showList :: [Chain1 t f a] -> ShowS #

Generic (Chain1 t f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

Associated Types

type Rep (Chain1 t f a) :: Type -> Type #

Methods

from :: Chain1 t f a -> Rep (Chain1 t f a) x #

to :: Rep (Chain1 t f a) x -> Chain1 t f a #

type C (Chain1 t) Source # 
Instance details

Defined in Data.HFunctor.Chain

type C (Chain1 t) = CS t
type Rep (Chain1 t f a) Source # 
Instance details

Defined in Data.HFunctor.Chain

type Rep (Chain1 t f a) = D1 (MetaData "Chain1" "Data.HFunctor.Chain" "functor-combinators-0.1.0.0-1Dw8a8tI1Rr1Hp1DFwH5I6" False) (C1 (MetaCons "Done1" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))) :+: C1 (MetaCons "More1" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (t f (Chain1 t f) a))))

foldChain1 Source #

Arguments

:: HBifunctor t 
=> (f ~> g)

handle Done1

-> (t f g ~> g)

handle More1

-> Chain1 t f ~> g 

Recursively fold down a Chain1. Provide a function on how to handle the "single f case" (inject), and how to handle the "combined t f g case", and this will fold the entire Chain1 t f into a single g.

This is a catamorphism.

unfoldChain1 :: forall t f (g :: Type -> Type). HBifunctor t => (g ~> (f :+: t f g)) -> g ~> Chain1 t f Source #

Recursively build up a Chain1. Provide a function that takes some starting seed g and returns either "done" (f) or "continue further" (t f g), and it will create a Chain1 t f from a g.

This is an anamorphism.

unrollingSF :: forall t f. (Semigroupoidal t, Functor f) => SF t f <~> Chain1 t f Source #

A type SF t is supposed to represent the successive application of ts to itself. The type Chain1 t f is an actual concrete ADT that contains successive applications of t to itself, and you can pattern match on each layer.

unrollingSF states that the two types are isormorphic. Use unrollSF and rerollSF to convert between the two.

unrollSF :: (Semigroupoidal t, Functor f) => SF t f ~> Chain1 t f Source #

A type SF t is supposed to represent the successive application of ts to itself. unrollSF makes that successive application explicit, buy converting it to a literal Chain1 of applications of t to itself.

unrollSF = unfoldChain1 matchSF

rerollSF :: Semigroupoidal t => Chain1 t f ~> SF t f Source #

A type SF t is supposed to represent the successive application of ts to itself. rerollSF takes an explicit Chain1 of applications of t to itself and rolls it back up into an SF t.

rerollSF = foldChain1 inject consSF

fromChain1 :: Tensor t => Chain1 t f ~> Chain t (I t) f Source #

A Chain1 is "one or more linked fs", and a Chain is "zero or more linked fs". So, we can convert from a Chain1 to a Chain that always has at least one f.

The result of this function always is made with More at the top level.

Matchable

The following conversions between Chain and Chain1 are only possible if t is Matchable

splittingChain1 :: forall t f. (Matchable t, Functor f) => Chain1 t f <~> t f (Chain t (I t) f) Source #

A Chain1 t f is like a non-empty linked list of fs, and a Chain t (I t) f is a possibly-empty linked list of fs. This witnesses the fact that the former is isomorphic to f consed to the latter.

splitChain1 :: forall t f. Matchable t => Chain1 t f ~> t f (Chain t (I t) f) Source #

The "forward" function representing splittingChain1. Provided here as a separate function because it does not require Functor f.

matchingChain :: forall t f. (Matchable t, Functor f) => Chain t (I t) f <~> (I t :+: Chain1 t f) Source #

A Chain t (I t) f is a linked list of fs, and a Chain1 t f is a non-empty linked list of fs. This witnesses the fact that a Chain t (I t) f is either empty (I t) or non-empty (Chain1 t f).

unmatchChain :: forall t f. Matchable t => (I t :+: Chain1 t f) ~> Chain t (I t) f Source #

The "reverse" function representing matchingChain. Provided here as a separate function because it does not require Functor f.