first-class-families-0.8.0.1: First-class type families
Safe HaskellSafe-Inferred
LanguageHaskell2010

Fcf.Data.Common

Description

Common data types: tuples, Either, Maybe.

Synopsis

Pairs

data Uncurry :: (a -> b -> Exp c) -> (a, b) -> Exp c Source #

Instances

Instances details
type Eval (Uncurry f '(x, y) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (Uncurry f '(x, y) :: a2 -> Type) = Eval (f x y)

data Fst :: (a, b) -> Exp a Source #

Instances

Instances details
type Eval (Fst '(a2, _b) :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (Fst '(a2, _b) :: a1 -> Type) = a2

data Snd :: (a, b) -> Exp b Source #

Instances

Instances details
type Eval (Snd '(_a, b) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (Snd '(_a, b) :: a2 -> Type) = b

data (***) :: (b -> Exp c) -> (b' -> Exp c') -> (b, b') -> Exp (c, c') infixr 3 Source #

Specialization of Bimap for pairs.

Instances

Instances details
type Eval ((f *** f') '(b2, b'2) :: (k1, k2) -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval ((f *** f') '(b2, b'2) :: (k1, k2) -> Type) = '(Eval (f b2), Eval (f' b'2))

Either

data UnEither :: (a -> Exp c) -> (b -> Exp c) -> Either a b -> Exp c Source #

Instances

Instances details
type Eval (UnEither f g ('Right y :: Either a1 b) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (UnEither f g ('Right y :: Either a1 b) :: a2 -> Type) = Eval (g y)
type Eval (UnEither f g ('Left x :: Either a1 b) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (UnEither f g ('Left x :: Either a1 b) :: a2 -> Type) = Eval (f x)

data IsLeft :: Either a b -> Exp Bool Source #

Instances

Instances details
type Eval (IsLeft ('Right _a :: Either a b) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (IsLeft ('Right _a :: Either a b) :: Bool -> Type) = 'False
type Eval (IsLeft ('Left _a :: Either a b) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (IsLeft ('Left _a :: Either a b) :: Bool -> Type) = 'True

data IsRight :: Either a b -> Exp Bool Source #

Instances

Instances details
type Eval (IsRight ('Right _a :: Either a b) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (IsRight ('Right _a :: Either a b) :: Bool -> Type) = 'True
type Eval (IsRight ('Left _a :: Either a b) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (IsRight ('Left _a :: Either a b) :: Bool -> Type) = 'False

Maybe

data UnMaybe :: Exp b -> (a -> Exp b) -> Maybe a -> Exp b Source #

Instances

Instances details
type Eval (UnMaybe y f ('Just x) :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (UnMaybe y f ('Just x) :: a1 -> Type) = Eval (f x)
type Eval (UnMaybe y f ('Nothing :: Maybe a2) :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (UnMaybe y f ('Nothing :: Maybe a2) :: a1 -> Type) = Eval y

data FromMaybe :: k -> Maybe k -> Exp k Source #

Instances

Instances details
type Eval (FromMaybe _a ('Just b) :: a -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (FromMaybe _a ('Just b) :: a -> Type) = b
type Eval (FromMaybe a2 ('Nothing :: Maybe a1) :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (FromMaybe a2 ('Nothing :: Maybe a1) :: a1 -> Type) = a2

data IsNothing :: Maybe a -> Exp Bool Source #

Instances

Instances details
type Eval (IsNothing ('Nothing :: Maybe a) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (IsNothing ('Nothing :: Maybe a) :: Bool -> Type) = 'True
type Eval (IsNothing ('Just _a) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (IsNothing ('Just _a) :: Bool -> Type) = 'False

data IsJust :: Maybe a -> Exp Bool Source #

Instances

Instances details
type Eval (IsJust ('Nothing :: Maybe a) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (IsJust ('Nothing :: Maybe a) :: Bool -> Type) = 'False
type Eval (IsJust ('Just _a) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (IsJust ('Just _a) :: Bool -> Type) = 'True