compdata-fixplate-0.1: Compdata basics implemented on top of Fixplate

Safe HaskellNone
LanguageHaskell2010

Data.Comp.Fixplate

Contents

Description

A replacement for the basic machinery in Compdata.

Differences and limitations

Deriving of type classes for base functors

Compdata's macros for deriving are replaced by similar macros from deriving-compat. See the documentation for defaultEqualF and similar functions in the same section.

Co-products and injections

Compdata and Fixplate use different names for equivalent things. For this reason, we export type and pattern synonyms to make the interface as similar to Compdata's as possible.

Unfortunately, :+: is defined as left-associative in Fixplate, which means that injections will look differently. For example, consider a compound base functor F :+: G :+: H. Elements from G are injected differently in the two libraries:

Inr (Inl ...) -- Compdata
InL (InR ...) -- Fixplate

(Note also the difference in capitalization.)

Smart constructors

There are no TemplateHaskell macros for making smart constructors, but the operators from Data.Composition (re-exported by this module) take us a long way towards the same goal. Consider the following base functors:

data Add a        = Add a a          deriving (Functor)
data IfThenElse a = IfThenElse a a a deriving (Functor)

Smart versions of these constructors can now be defined as follows:

(|+|) :: Add :<: f => Term f -> Term f -> Term f
(|+|) = inject .: Add

ite :: IfThenElse :<: f => Term f -> Term f -> Term f -> Term f
ite = inject .:. IfThenElse
Synopsis

Basic classes and operations on functors

class Eq1 (f :: * -> *) #

Lifting of the Eq class to unary type constructors.

Since: base-4.9.0.0

Minimal complete definition

liftEq

Instances
Eq1 []

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> [a] -> [b] -> Bool #

Eq1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool #

Eq1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool #

Eq1 Tree

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftEq :: (a -> b -> Bool) -> Tree a -> Tree b -> Bool #

Eq1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

liftEq :: (a -> b -> Bool) -> Seq a -> Seq b -> Bool #

Eq1 Set

Since: containers-0.5.9

Instance details

Defined in Data.Set.Internal

Methods

liftEq :: (a -> b -> Bool) -> Set a -> Set b -> Bool #

Eq a => Eq1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Either a a0 -> Either a b -> Bool #

Eq a => Eq1 ((,) a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> (a, a0) -> (a, b) -> Bool #

Eq1 (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Eq k => Eq1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftEq :: (a -> b -> Bool) -> Map k a -> Map k b -> Bool #

Eq a => Eq1 (Const a :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Const a a0 -> Const a b -> Bool #

(Eq e, Eq1 m) => Eq1 (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftEq :: (a -> b -> Bool) -> ErrorT e m a -> ErrorT e m b -> Bool #

class EqF (f :: * -> *) where #

"Functorised" versions of standard type classes. If you have your a structure functor, for example

Expr e 
  = Kst Int 
  | Var String 
  | Add e e 
  deriving (Eq,Ord,Read,Show,Functor,Foldable,Traversable)

you should make it an instance of these, so that the fixed-point type Mu Expr can be an instance of Eq, Ord and Show. Doing so is very easy:

instance EqF   Expr where equalF     = (==)
instance OrdF  Expr where compareF   = compare
instance ShowF Expr where showsPrecF = showsPrec

The Read instance depends on whether we are using GHC or not. The Haskell98 version is

instance ReadF Expr where readsPrecF = readsPrec

while the GHC version is

instance ReadF Expr where readPrecF  = readPrec

Minimal complete definition

equalF

Methods

equalF :: Eq a => f a -> f a -> Bool #

Instances
(EqF f, EqF g) => EqF (f :+: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

equalF :: Eq a => (f :+: g) a -> (f :+: g) a -> Bool #

(EqF f, EqF g) => EqF (f :*: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

equalF :: Eq a => (f :*: g) a -> (f :*: g) a -> Bool #

(Eq a, EqF f) => EqF (Ann f a)

NOTE: The EqF instance for annotations compares both the annotations and the original part.

Instance details

Defined in Data.Generics.Fixplate.Base

Methods

equalF :: Eq a0 => Ann f a a0 -> Ann f a a0 -> Bool #

(Eq a, EqF f) => EqF (CoAnn f a) 
Instance details

Defined in Data.Generics.Fixplate.Base

Methods

equalF :: Eq a0 => CoAnn f a a0 -> CoAnn f a a0 -> Bool #

class Show1 (f :: * -> *) #

Lifting of the Show class to unary type constructors.

Since: base-4.9.0.0

Minimal complete definition

liftShowsPrec

Instances
Show1 []

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Show1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Maybe a] -> ShowS #

Show1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identity a] -> ShowS #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

Show1 Tree

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tree a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tree a] -> ShowS #

Show1 Seq

Since: containers-0.5.9

Instance details

Defined in Data.Sequence.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Seq a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Seq a] -> ShowS #

Show1 Set

Since: containers-0.5.9

Instance details

Defined in Data.Set.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Set a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Set a] -> ShowS #

Show a => Show1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Either a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Either a a0] -> ShowS #

Show a => Show1 ((,) a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> (a, a0) -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [(a, a0)] -> ShowS #

Show1 (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Show k => Show1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Map k a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Map k a] -> ShowS #

Show a => Show1 (Const a :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Const a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Const a a0] -> ShowS #

(Show e, Show1 m) => Show1 (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ErrorT e m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ErrorT e m a] -> ShowS #

class ShowF (f :: * -> *) where #

Minimal complete definition

showsPrecF

Methods

showsPrecF :: Show a => Int -> f a -> ShowS #

Instances
ShowF f => ShowF (HideInj f) # 
Instance details

Defined in Data.Comp.Fixplate

Methods

showsPrecF :: Show a => Int -> HideInj f a -> ShowS #

(ShowF (HideInj f), ShowF (HideInj g)) => ShowF (HideInj (f :+: g)) # 
Instance details

Defined in Data.Comp.Fixplate

Methods

showsPrecF :: Show a => Int -> HideInj (f :+: g) a -> ShowS #

(ShowF f, ShowF g) => ShowF (f :+: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

showsPrecF :: Show a => Int -> (f :+: g) a -> ShowS #

(ShowF f, ShowF g) => ShowF (f :*: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

showsPrecF :: Show a => Int -> (f :*: g) a -> ShowS #

(Show a, ShowF f) => ShowF (Ann f a) 
Instance details

Defined in Data.Generics.Fixplate.Base

Methods

showsPrecF :: Show a0 => Int -> Ann f a a0 -> ShowS #

(Show a, ShowF f) => ShowF (CoAnn f a) 
Instance details

Defined in Data.Generics.Fixplate.Base

Methods

showsPrecF :: Show a0 => Int -> CoAnn f a a0 -> ShowS #

deriveEq1 :: Name -> Q [Dec] #

Generates an Eq1 instance declaration for the given data type or data family instance.

deriveShow1 :: Name -> Q [Dec] #

Generates a Show1 instance declaration for the given data type or data family instance.

defaultEqualF :: (Eq1 f, Eq a) => f a -> f a -> Bool Source #

Default implementation of equalF

Use as follows:

data F = ...

deriveEq1 ''F -- Requires TemplateHaskell
instance EqF F where equalF = defaultEqualF

defaultShowsPrecF :: (Show1 f, Show a) => Int -> f a -> ShowS Source #

Default implementation of showsPrecF

Use as follows:

data F = ...

deriveShow1 ''F -- Requires TemplateHaskell
instance ShowF F where showsPrecF = defaultShowsPrecF

eqMod :: (EqF f, Functor f, Foldable f) => f a -> f b -> Maybe [(a, b)] Source #

Compositional data types

type Term = Mu Source #

pattern Term :: f (Term f) -> Term f Source #

unTerm :: Term f -> f (Term f) Source #

type (:&:) f a = Ann f a Source #

pattern (:&:) :: f b -> a -> (f :&: a) b Source #

data ((f :: * -> *) :+: (g :: * -> *)) a infixl 6 #

Sum of two functors

Constructors

InL (f a) 
InR (g a) 
Instances
f :<: h => f :<: (h :+: g) Source #

Unlike standard Data Types à la Carte, this instance recurses into the left term. This is due to the left-associativity of :+: in Fixplate.

Instance details

Defined in Data.Comp.Fixplate

Methods

inj :: f a -> (h :+: g) a Source #

prj :: (h :+: g) a -> Maybe (f a) Source #

f :<: f => f :<: (g :+: f) Source # 
Instance details

Defined in Data.Comp.Fixplate

Methods

inj :: f a -> (g :+: f) a Source #

prj :: (g :+: f) a -> Maybe (f a) Source #

(ShowF (HideInj f), ShowF (HideInj g)) => ShowF (HideInj (f :+: g)) # 
Instance details

Defined in Data.Comp.Fixplate

Methods

showsPrecF :: Show a => Int -> HideInj (f :+: g) a -> ShowS #

(Functor f, Functor g) => Functor (f :+: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b #

(<$) :: a -> (f :+: g) b -> (f :+: g) a #

(Foldable f, Foldable g) => Foldable (f :+: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

fold :: Monoid m => (f :+: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :+: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :+: g) a -> a #

toList :: (f :+: g) a -> [a] #

null :: (f :+: g) a -> Bool #

length :: (f :+: g) a -> Int #

elem :: Eq a => a -> (f :+: g) a -> Bool #

maximum :: Ord a => (f :+: g) a -> a #

minimum :: Ord a => (f :+: g) a -> a #

sum :: Num a => (f :+: g) a -> a #

product :: Num a => (f :+: g) a -> a #

(Traversable f, Traversable g) => Traversable (f :+: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) #

sequenceA :: Applicative f0 => (f :+: g) (f0 a) -> f0 ((f :+: g) a) #

mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) #

sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) #

(EqF f, EqF g) => EqF (f :+: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

equalF :: Eq a => (f :+: g) a -> (f :+: g) a -> Bool #

(OrdF f, OrdF g) => OrdF (f :+: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

compareF :: Ord a => (f :+: g) a -> (f :+: g) a -> Ordering #

(ShowF f, ShowF g) => ShowF (f :+: g) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

showsPrecF :: Show a => Int -> (f :+: g) a -> ShowS #

(Eq (f a), Eq (g a)) => Eq ((f :+: g) a) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

(==) :: (f :+: g) a -> (f :+: g) a -> Bool #

(/=) :: (f :+: g) a -> (f :+: g) a -> Bool #

(Ord (f a), Ord (g a)) => Ord ((f :+: g) a) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

compare :: (f :+: g) a -> (f :+: g) a -> Ordering #

(<) :: (f :+: g) a -> (f :+: g) a -> Bool #

(<=) :: (f :+: g) a -> (f :+: g) a -> Bool #

(>) :: (f :+: g) a -> (f :+: g) a -> Bool #

(>=) :: (f :+: g) a -> (f :+: g) a -> Bool #

max :: (f :+: g) a -> (f :+: g) a -> (f :+: g) a #

min :: (f :+: g) a -> (f :+: g) a -> (f :+: g) a #

(Show (f a), Show (g a)) => Show ((f :+: g) a) 
Instance details

Defined in Data.Generics.Fixplate.Functor

Methods

showsPrec :: Int -> (f :+: g) a -> ShowS #

show :: (f :+: g) a -> String #

showList :: [(f :+: g) a] -> ShowS #

class f :<: g where infix 7 Source #

Minimal complete definition

inj, prj

Methods

inj :: f a -> g a Source #

prj :: g a -> Maybe (f a) Source #

Instances
f :<: f Source # 
Instance details

Defined in Data.Comp.Fixplate

Methods

inj :: f a -> f a Source #

prj :: f a -> Maybe (f a) Source #

f :<: h => f :<: (h :+: g) Source #

Unlike standard Data Types à la Carte, this instance recurses into the left term. This is due to the left-associativity of :+: in Fixplate.

Instance details

Defined in Data.Comp.Fixplate

Methods

inj :: f a -> (h :+: g) a Source #

prj :: (h :+: g) a -> Maybe (f a) Source #

f :<: f => f :<: (g :+: f) Source # 
Instance details

Defined in Data.Comp.Fixplate

Methods

inj :: f a -> (g :+: f) a Source #

prj :: (g :+: f) a -> Maybe (f a) Source #

inject :: f :<: g => f (Term g) -> Term g Source #

project :: f :<: g => Term g -> Maybe (f (Term g)) Source #

Rendering

data HideInj f a Source #

Instances
Functor f => Functor (HideInj f) Source # 
Instance details

Defined in Data.Comp.Fixplate

Methods

fmap :: (a -> b) -> HideInj f a -> HideInj f b #

(<$) :: a -> HideInj f b -> HideInj f a #

Foldable f => Foldable (HideInj f) Source # 
Instance details

Defined in Data.Comp.Fixplate

Methods

fold :: Monoid m => HideInj f m -> m #

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

foldr :: (a -> b -> b) -> b -> HideInj f a -> b #

foldr' :: (a -> b -> b) -> b -> HideInj f a -> b #

foldl :: (b -> a -> b) -> b -> HideInj f a -> b #

foldl' :: (b -> a -> b) -> b -> HideInj f a -> b #

foldr1 :: (a -> a -> a) -> HideInj f a -> a #

foldl1 :: (a -> a -> a) -> HideInj f a -> a #

toList :: HideInj f a -> [a] #

null :: HideInj f a -> Bool #

length :: HideInj f a -> Int #

elem :: Eq a => a -> HideInj f a -> Bool #

maximum :: Ord a => HideInj f a -> a #

minimum :: Ord a => HideInj f a -> a #

sum :: Num a => HideInj f a -> a #

product :: Num a => HideInj f a -> a #

Traversable f => Traversable (HideInj f) Source # 
Instance details

Defined in Data.Comp.Fixplate

Methods

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

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

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

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

ShowF f => ShowF (HideInj f) Source # 
Instance details

Defined in Data.Comp.Fixplate

Methods

showsPrecF :: Show a => Int -> HideInj f a -> ShowS #

(ShowF (HideInj f), ShowF (HideInj g)) => ShowF (HideInj (f :+: g)) Source # 
Instance details

Defined in Data.Comp.Fixplate

Methods

showsPrecF :: Show a => Int -> HideInj (f :+: g) a -> ShowS #

showTerm :: (Functor f, Foldable f, ShowF (HideInj f)) => Term f -> String Source #

Represent a Term as an ASCII drawing

showTermU :: (Functor f, Foldable f, ShowF (HideInj f)) => Term f -> String Source #

Represent a Term as a Unicode drawing

drawTerm :: (Functor f, Foldable f, ShowF (HideInj f)) => Term f -> IO () Source #

Display a Term as an ASCII drawing

drawTermU :: (Functor f, Foldable f, ShowF (HideInj f)) => Term f -> IO () Source #

Display a Term as a Unicode drawing

Making smart constructors

(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d infixr 8 #

Compose two functions. f .: g is similar to f . g except that g will be fed two arguments instead of one before handing its result to f.

This function is defined as

(f .: g) x y = f (g x y)

Example usage:

concatMap :: (a -> b) -> [a] -> [b]
concatMap = concat .: map

Notice how two arguments (the function and the list) will be given to map before the result is passed to concat. This is equivalent to:

concatMap f xs = concat (map f xs)

(.:.) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e infixr 8 #

One compact pattern for composition operators is to "count the dots after the first one", which begins with the common .:, and proceeds by first appending another . and then replacing it with :

(.::) :: (d -> e) -> (a1 -> a2 -> b -> c -> d) -> a1 -> a2 -> b -> c -> e infixr 8 #

(.::.) :: (d -> e) -> (a1 -> a2 -> a3 -> b -> c -> d) -> a1 -> a2 -> a3 -> b -> c -> e infixr 8 #

(.:::) :: (d -> e) -> (a1 -> a2 -> a3 -> a4 -> b -> c -> d) -> a1 -> a2 -> a3 -> a4 -> b -> c -> e infixr 8 #