type-combinators-0.2.4.3: A collection of data types for type-level programming

CopyrightCopyright (C) 2015 Kyle Carter
LicenseBSD3
MaintainerKyle Carter <kylcarte@indiana.edu>
Stabilityexperimental
PortabilityRankNTypes
Safe HaskellSafe
LanguageHaskell2010

Type.Family.Monoid

Description

Type-level Monoid, defined as an open type family.

Documentation

type family Mempty :: k Source #

Instances

type Mempty [k] Source # 
type Mempty [k] = Ø k
type Mempty (Maybe a) Source # 
type Mempty (Maybe a) = Nothing a
type Mempty (Either a b) Source # 
type Mempty (Either a b) = Left a b (Mempty a)
type Mempty (a, b) Source # 
type Mempty (a, b) = (#) a b (Mempty a) (Mempty b)
type Mempty (k, k1, k2) Source # 
type Mempty (k, k1, k2) = (,,) k k1 k2 (Mempty k) (Mempty k1) (Mempty k2)

type family (a :: k) <> (b :: k) :: k Source #

Instances

type (<>) [k] a b Source # 
type (<>) [k] a b = (++) k a b
type (<>) (Maybe k) a b Source # 
type (<>) (Maybe k) a b = (<|>) k a b
type (<>) (Either m k) a b Source # 
type (<>) (Either m k) a b = (<|>) m k a b
type (<>) (a, b) ((#) a b r a1) ((#) a b s b1) Source # 
type (<>) (a, b) ((#) a b r a1) ((#) a b s b1) = (#) a b ((<>) a r s) ((<>) b a1 b1)
type (<>) (k, k1, k2) ((,,) k k1 k2 a b c) ((,,) k k1 k2 d e f) Source # 
type (<>) (k, k1, k2) ((,,) k k1 k2 a b c) ((,,) k k1 k2 d e f) = (,,) k k1 k2 ((<>) k a d) ((<>) k1 b e) ((<>) k2 c f)