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

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

Type.Family.Either

Description

Convenient type families for working with type-level Eithers.

Synopsis

Documentation

type family EitherC ec :: Constraint Source

Take a Maybe Constraint to a Constraint.

Equations

EitherC (Left a) = ØC 
EitherC (Right c) = c 

type family IsLeft a :: Bool Source

Equations

IsLeft (Left a) = True 
IsLeft (Right b) = False 

type family IsRight a :: Bool Source

Equations

IsRight (Left a) = False 
IsRight (Right b) = True 

leftCong :: (a ~ b) :- (IsLeft a ~ IsLeft b) Source

rightCong :: (a ~ b) :- (IsRight a ~ IsRight b) Source

type family f <$> a :: Either m l infixr 4 Source

Map over a type-level Maybe.

Equations

f <$> (Left a) = Left a 
f <$> (Right b) = Right (f b) 

eitherFmapCong :: (f ~ g, a ~ b) :- ((f <$> a) ~ (g <$> b)) Source

type family f <&> a :: Either m l infixl 5 Source

Equations

(Left x) <&> a = Left x 
(Right f) <&> a = Right (f a) 

eitherPamfCong :: (f ~ g, a ~ b) :- ((f <&> a) ~ (g <&> b)) Source

type family f <*> a :: Either m l infixr 4 Source

Equations

(Left x) <*> (Left y) = Left (x <> y) 
(Left x) <*> a = Left x 
f <*> (Left x) = Left x 
(Right f) <*> (Right a) = Right (f a) 

eitherApCong :: (f ~ g, a ~ b) :- ((f <*> a) ~ (g <*> b)) Source

type family a <|> b :: Either m k infixr 4 Source

Equations

(Left x) <|> b = b 
(Right a) <|> b = Right a 

eitherAltCong :: (a ~ c, b ~ d) :- ((a <|> b) ~ (c <|> d)) Source

type family FromLeft e :: k Source

Equations

FromLeft (Left a) = a 

type family FromRight e :: l Source

Equations

FromRight (Right b) = b