monoid-extras-0.6.2: Various extra monoid-related definitions and utilities
Copyright(c) 2011 diagrams-core team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Monoid.MList

Description

Heterogeneous lists of monoids.

Synopsis

Heterogeneous monoidal lists

The idea of heterogeneous lists has been around for a long time. Here, we adopt heterogeneous lists where the element types are all monoids: this allows us to leave out identity values, so that a heterogeneous list containing only a single non-identity value can be created without incurring constraints due to all the other types, by leaving all the other values out.

type (:::) a l = (Maybe a, l) infixr 5 Source #

(*:) :: a -> l -> a ::: l infixr 5 Source #

class MList l where Source #

Type class for heterogeneous monoidal lists, with a single method allowing construction of an empty list.

Methods

empty :: l Source #

The empty heterogeneous list of type l. Of course, empty == mempty, but unlike mempty, empty does not require Monoid constraints on all the elements of l.

Instances

Instances details
MList () Source # 
Instance details

Defined in Data.Monoid.MList

Methods

empty :: () Source #

MList l => MList (a ::: l) Source # 
Instance details

Defined in Data.Monoid.MList

Methods

empty :: a ::: l Source #

Accessing embedded values

class l :>: a where Source #

The relation l :>: a holds when a is the type of an element in l. For example, (Char ::: Int ::: Bool ::: Nil) :>: Int.

Methods

inj :: a -> l Source #

Inject a value into an otherwise empty heterogeneous list.

get :: l -> Maybe a Source #

Get the value of type a from a heterogeneous list, if there is one.

alt :: (Maybe a -> Maybe a) -> l -> l Source #

Alter the value of type a by applying the given function to it.

Instances

Instances details
MList t => (a ::: t) :>: a Source # 
Instance details

Defined in Data.Monoid.MList

Methods

inj :: a -> a ::: t Source #

get :: (a ::: t) -> Maybe a Source #

alt :: (Maybe a -> Maybe a) -> (a ::: t) -> a ::: t Source #

t :>: a => (b ::: t) :>: a Source # 
Instance details

Defined in Data.Monoid.MList

Methods

inj :: a -> b ::: t Source #

get :: (b ::: t) -> Maybe a Source #

alt :: (Maybe a -> Maybe a) -> (b ::: t) -> b ::: t Source #

Monoid actions of heterogeneous lists

Monoidal heterogeneous lists may act on one another as you would expect, with each element in the first list acting on each in the second. Unfortunately, coding this up in type class instances is a bit fiddly.

newtype SM m Source #

SM, an abbreviation for "single monoid" (as opposed to a heterogeneous list of monoids), is only used internally to help guide instance selection when defining the action of heterogeneous monoidal lists on each other.

Constructors

SM m 

Instances

Instances details
Show m => Show (SM m) Source # 
Instance details

Defined in Data.Monoid.MList

Methods

showsPrec :: Int -> SM m -> ShowS #

show :: SM m -> String #

showList :: [SM m] -> ShowS #

Action (SM a) () Source # 
Instance details

Defined in Data.Monoid.MList

Methods

act :: SM a -> () -> () Source #

(Action a a', Action (SM a) l) => Action (SM a) (Maybe a', l) Source # 
Instance details

Defined in Data.Monoid.MList

Methods

act :: SM a -> (Maybe a', l) -> (Maybe a', l) Source #

Orphan instances

(Action (SM a) l2, Action l1 l2) => Action (a, l1) l2 Source # 
Instance details

Methods

act :: (a, l1) -> l2 -> l2 Source #