first-class-families-0.5.0.0: First class type families

Safe HaskellSafe
LanguageHaskell2010

Fcf

Contents

Description

First-class type families

For example, here is a regular type family:

type family   FromMaybe (a :: k) (m :: Maybe k) :: k
type instance FromMaybe a 'Nothing  = a
type instance FromMaybe a ('Just b) = b

With Fcf, it translates to a data declaration:

data FromMaybe :: k -> Maybe k -> Exp k
type instance Eval (FromMaybe a 'Nothing)  = a
type instance Eval (FromMaybe a ('Just b)) = b
  • Fcfs can be higher-order.
  • The kind constructor Exp is a monad: there's (=<<) and Pure.

Essential language extensions for Fcf:

{-# LANGUAGE
    DataKinds,
    PolyKinds,
    TypeFamilies,
    TypeInType,
    TypeOperators,
    UndecidableInstances #-}
Synopsis

First-class type families

type Exp a = a -> Type Source #

Kind of type-level expressions indexed by their result type.

type family Eval (e :: Exp a) :: a Source #

Expression evaluator.

Instances
type Eval (Not False) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Not False) = True
type Eval (Not True) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Not True) = False
type Eval (Constraints (a ': as) :: Constraint -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Constraints (a ': as) :: Constraint -> Type) = (a, Eval (Constraints as))
type Eval (Constraints ([] :: [Constraint])) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Constraints ([] :: [Constraint])) = ()
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
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
type Eval (False && b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (False && b :: Bool -> Type) = False
type Eval (True && b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (True && b :: Bool -> Type) = b
type Eval (a && True :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a && True :: Bool -> Type) = a
type Eval (a && False :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a && False :: Bool -> Type) = False
type Eval (False || b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (False || b :: Bool -> Type) = b
type Eval (True || b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (True || b :: Bool -> Type) = True
type Eval (a || False :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a || False :: Bool -> Type) = a
type Eval (a || True :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a || True :: Bool -> Type) = True
type Eval (a > b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a > b :: Bool -> Type) = Eval (Not =<< (a <= b))
type Eval (a < b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a < b :: Bool -> Type) = Eval (Not =<< (a >= b))
type Eval (a >= b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a >= b :: Bool -> Type) = b <=? a
type Eval (a <= b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a <= b :: Bool -> Type) = a <=? b
type Eval (Null (a2 ': as) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Null (a2 ': as) :: Bool -> Type) = False
type Eval (Null ([] :: [a]) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Null ([] :: [a]) :: Bool -> Type) = True
type Eval (a ^ b :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a ^ b :: Nat -> Type) = a ^ b
type Eval (a * b :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a * b :: Nat -> Type) = a * b
type Eval (a - b :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a - b :: Nat -> Type) = a - b
type Eval (a + b :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a + b :: Nat -> Type) = a + b
type Eval (Length (a2 ': as) :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Length (a2 ': as) :: Nat -> Type) = 1 + Eval (Length as)
type Eval (Length ([] :: [a]) :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Length ([] :: [a]) :: Nat -> Type) = 0
type Eval (Pure x :: a -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (Pure x :: a -> Type) = x
type Eval (Join e :: a -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (Join e :: a -> Type) = Eval (Eval e)
type Eval (Error msg :: a -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Error msg :: a -> Type) = (TypeError (Text msg) :: a)
type Eval (TError msg :: a -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (TError msg :: a -> Type) = (TypeError msg :: a)
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
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
type Eval (Fst ((,) a2 _b) :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (Fst ((,) a2 _b) :: a1 -> Type) = a2
type Eval (Snd ((,) _a b) :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

type Eval (Snd ((,) _a b) :: a1 -> Type) = b
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
type Eval (TyEq a b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (TyEq a b :: Bool -> Type)
type Eval (Pure1 f x :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (Pure1 f x :: a2 -> Type) = f x
type Eval (k =<< e :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (k =<< e :: a2 -> Type) = Eval (k (Eval e))
type Eval (f <$> e :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (f <$> e :: a2 -> Type) = f (Eval e)
type Eval (f <*> e :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (f <*> e :: a2 -> Type) = Eval f (Eval e)
type Eval (ConstFn a2 _b :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (ConstFn a2 _b :: a1 -> Type) = a2
type Eval (f $ a3 :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (f $ a3 :: a2 -> Type) = Eval (f a3)
type Eval (UnBool fal tru True :: a -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (UnBool fal tru True :: a -> Type) = Eval tru
type Eval (UnBool fal tru False :: a -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (UnBool fal tru False :: a -> Type) = Eval fal
type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) = Eval (If (Eval (p x)) y (Guarded x ys))
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)
type Eval (UnMaybe y f (Just x) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.List

type Eval (Foldr f y (x ': xs) :: a2 -> Type) = Eval (f x (Eval (Foldr f y xs)))
type Eval (Foldr f y ([] :: [a1]) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Foldr f y ([] :: [a1]) :: a2 -> Type) = y
type Eval (UnList y f xs :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (UnList y f xs :: a2 -> Type) = Eval (Foldr f y xs)
type Eval (Pure2 f x y :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (Pure2 f x y :: a2 -> Type) = f x y
type Eval ((f <=< g) x :: a3 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval ((f <=< g) x :: a3 -> Type) = Eval (f (Eval (g x)))
type Eval (LiftM2 f x y :: a3 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (LiftM2 f x y :: a3 -> Type) = Eval (f (Eval x) (Eval y))
type Eval (Flip f y x :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Combinators

type Eval (Pure3 f x y z :: a2 -> Type) = f x y z
type Eval (LiftM3 f x y z :: a4 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (LiftM3 f x y z :: a4 -> Type) = Eval (f (Eval x) (Eval y) (Eval z))
type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) = Eval ((Map (Cons a2) :: Maybe [a1] -> Maybe [a1] -> Type) =<< Init (b ': as))
type Eval (Init (a2 ': ([] :: [a1])) :: Maybe [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Init (a2 ': ([] :: [a1])) :: Maybe [a1] -> Type) = Just ([] :: [a1])
type Eval (Init ([] :: [a]) :: Maybe [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Init ([] :: [a]) :: Maybe [a] -> Type) = (Nothing :: Maybe [a])
type Eval (Tail (_a ': as) :: Maybe [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Tail (_a ': as) :: Maybe [a] -> Type) = Just as
type Eval (Tail ([] :: [a]) :: Maybe [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Tail ([] :: [a]) :: Maybe [a] -> Type) = (Nothing :: Maybe [a])
type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) = Just a2
type Eval (Head ([] :: [a]) :: Maybe a -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Head ([] :: [a]) :: Maybe a -> Type) = (Nothing :: Maybe a)
type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) = Eval (Last (b ': as))
type Eval (Last (a2 ': ([] :: [a1])) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Last (a2 ': ([] :: [a1])) :: Maybe a1 -> Type) = Just a2
type Eval (Last ([] :: [a]) :: Maybe a -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Last ([] :: [a]) :: Maybe a -> Type) = (Nothing :: Maybe a)
type Eval (Cons a2 as :: [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Cons a2 as :: [a1] -> Type) = a2 ': as
type Eval ((x ': xs) ++ ys :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval ((x ': xs) ++ ys :: [a] -> Type) = x ': Eval (xs ++ ys)
type Eval (([] :: [a]) ++ ys :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (([] :: [a]) ++ ys :: [a] -> Type) = ys
type Eval (Filter p (a2 ': as) :: [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Filter p (a2 ': as) :: [a1] -> Type) = If (Eval (p a2)) (a2 ': Eval (Filter p as)) (Eval (Filter p as))
type Eval (Filter _p ([] :: [a]) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Filter _p ([] :: [a]) :: [a] -> Type) = ([] :: [a])
type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) = Eval (If (Eval (p a2)) (Pure (Just 0)) ((Map ((+) 1) :: Maybe Nat -> Maybe Nat -> Type) =<< FindIndex p as))
type Eval (FindIndex _p ([] :: [a]) :: Maybe Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex _p ([] :: [a]) :: Maybe Nat -> Type) = (Nothing :: Maybe Nat)
type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) = If (Eval (p a2)) (Just a2) (Eval (Find p as))
type Eval (Find _p ([] :: [a]) :: Maybe a -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Find _p ([] :: [a]) :: Maybe a -> Type) = (Nothing :: Maybe a)
type Eval (SetIndex n a' as :: [k] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (SetIndex n a' as :: [k] -> Type)
type Eval (Map f (a2 ': as) :: [b] -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (a2 ': as) :: [b] -> Type) = Eval (f a2) ': Eval (Map f as)
type Eval (Map f ([] :: [a]) :: [b] -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ([] :: [a]) :: [b] -> Type) = ([] :: [b])
type Eval (Map f (Just a3) :: Maybe a2 -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (Just a3) :: Maybe a2 -> Type) = Just (Eval (f a3))
type Eval (Map f (Nothing :: Maybe a) :: Maybe b -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (Nothing :: Maybe a) :: Maybe b -> Type) = (Nothing :: Maybe b)
type Eval (ZipWith f (a2 ': as) (b2 ': bs) :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith f (a2 ': as) (b2 ': bs) :: [c] -> Type) = Eval (f a2 b2) ': Eval (ZipWith f as bs)
type Eval (ZipWith _f _as ([] :: [b]) :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith _f _as ([] :: [b]) :: [c] -> Type) = ([] :: [c])
type Eval (ZipWith _f ([] :: [a]) _bs :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith _f ([] :: [a]) _bs :: [c] -> Type) = ([] :: [c])
type Eval (Unzip as :: ([a], [b]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Unzip as :: ([a], [b]) -> Type) = Eval (Foldr (Cons2 :: (a, b) -> ([a], [b]) -> ([a], [b]) -> Type) ((,) ([] :: [a]) ([] :: [b])) (Eval as))
type Eval (Cons2 ((,) a3 b) ((,) as bs) :: ([a2], [a1]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Cons2 ((,) a3 b) ((,) as bs) :: ([a2], [a1]) -> Type) = (,) (a3 ': as) (b ': bs)
type Eval (Map f (Right a3 :: Either a2 a1) :: Either a2 b -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (Right a3 :: Either a2 a1) :: Either a2 b -> Type) = (Right (Eval (f a3)) :: Either a2 b)
type Eval (Map f (Left x :: Either a2 a1) :: Either a2 b -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (Left x :: Either a2 a1) :: Either a2 b -> Type) = (Left x :: Either a2 b)
type Eval (Map f ((,) x a2) :: (k2, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

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

Defined in Fcf.Data.Common

type Eval ((f *** f') ((,) b2 b'2) :: (k2, k1) -> Type) = (,) (Eval (f b2)) (Eval (f' b'2))
type Eval (Bimap f g (Right y :: Either a b1) :: Either a' b2 -> Type) Source # 
Instance details

Defined in Fcf.Classes

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

Defined in Fcf.Classes

type Eval (Bimap f g (Left x :: Either a1 b) :: Either a2 b' -> Type) = (Left (Eval (f x)) :: Either a2 b')
type Eval (Bimap f g ((,) x y) :: (k2, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Bimap f g ((,) x y) :: (k2, k1) -> Type) = (,) (Eval (f x)) (Eval (g y))
type Eval (Map f ((,,) x y a2) :: (k2, k3, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ((,,) x y a2) :: (k2, k3, k1) -> Type) = (,,) x y (Eval (f a2))
type Eval (Map f ((,,,) x y z a2) :: (k2, k3, k4, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ((,,,) x y z a2) :: (k2, k3, k4, k1) -> Type) = (,,,) x y z (Eval (f a2))
type Eval (Map f ((,,,,) x y z w a2) :: (k2, k3, k4, k5, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ((,,,,) x y z w a2) :: (k2, k3, k4, k5, k1) -> Type) = (,,,,) x y z w (Eval (f a2))

type (@@) f x = Eval (f x) Source #

Apply and evaluate a unary type function.

Functional combinators

data Pure :: a -> Exp a Source #

Instances
type Eval (Pure x :: a -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (Pure x :: a -> Type) = x

data Pure1 :: (a -> b) -> a -> Exp b Source #

Instances
type Eval (Pure1 f x :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (Pure1 f x :: a2 -> Type) = f x

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

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

Defined in Fcf.Combinators

type Eval (Pure2 f x y :: a2 -> Type) = f x y

data Pure3 :: (a -> b -> c -> d) -> a -> b -> c -> Exp d Source #

Instances
type Eval (Pure3 f x y z :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (Pure3 f x y z :: a2 -> Type) = f x y z

data (=<<) :: (a -> Exp b) -> Exp a -> Exp b infixr 1 Source #

Instances
type Eval (k =<< e :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (k =<< e :: a2 -> Type) = Eval (k (Eval e))

data (<=<) :: (b -> Exp c) -> (a -> Exp b) -> a -> Exp c infixr 1 Source #

Instances
type Eval ((f <=< g) x :: a3 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval ((f <=< g) x :: a3 -> Type) = Eval (f (Eval (g x)))

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

Instances
type Eval (LiftM2 f x y :: a3 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (LiftM2 f x y :: a3 -> Type) = Eval (f (Eval x) (Eval y))

data LiftM3 :: (a -> b -> c -> Exp d) -> Exp a -> Exp b -> Exp c -> Exp d Source #

Instances
type Eval (LiftM3 f x y z :: a4 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (LiftM3 f x y z :: a4 -> Type) = Eval (f (Eval x) (Eval y) (Eval z))

data Join :: Exp (Exp a) -> Exp a Source #

Instances
type Eval (Join e :: a -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (Join e :: a -> Type) = Eval (Eval e)

data (<$>) :: (a -> b) -> Exp a -> Exp b infixl 4 Source #

Instances
type Eval (f <$> e :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (f <$> e :: a2 -> Type) = f (Eval e)

data (<*>) :: Exp (a -> b) -> Exp a -> Exp b infixl 4 Source #

Instances
type Eval (f <*> e :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (f <*> e :: a2 -> Type) = Eval f (Eval e)

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

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

Defined in Fcf.Combinators

type Eval (Flip f y x :: a2 -> Type) = Eval (f x y)

data ConstFn :: a -> b -> Exp a Source #

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

Defined in Fcf.Combinators

type Eval (ConstFn a2 _b :: a1 -> Type) = a2

data ($) :: (a -> Exp b) -> a -> Exp b infixr 0 Source #

Note that this denotes the identity function, so ($) f can usually be replaced with f.

Instances
type Eval (f $ a3 :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Combinators

type Eval (f $ a3 :: a2 -> Type) = Eval (f a3)

Operations on common types

Pairs

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

Instances
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
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
type Eval (Snd ((,) _a b) :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

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

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

Equivalent to Bimap for pairs.

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

Defined in Fcf.Data.Common

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

Either

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

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

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

Instances
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
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
type Eval (UnMaybe y f (Just x) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

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

Instances
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
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
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

Lists

data Foldr :: (a -> b -> Exp b) -> b -> [a] -> Exp b Source #

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

Defined in Fcf.Data.List

type Eval (Foldr f y (x ': xs) :: a2 -> Type) = Eval (f x (Eval (Foldr f y xs)))
type Eval (Foldr f y ([] :: [a1]) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Foldr f y ([] :: [a1]) :: a2 -> Type) = y

data UnList :: b -> (a -> b -> Exp b) -> [a] -> Exp b Source #

N.B.: This is equivalent to a Foldr flipped.

Instances
type Eval (UnList y f xs :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (UnList y f xs :: a2 -> Type) = Eval (Foldr f y xs)

data (++) :: [a] -> [a] -> Exp [a] Source #

Instances
type Eval ((x ': xs) ++ ys :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval ((x ': xs) ++ ys :: [a] -> Type) = x ': Eval (xs ++ ys)
type Eval (([] :: [a]) ++ ys :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (([] :: [a]) ++ ys :: [a] -> Type) = ys

data Filter :: (a -> Exp Bool) -> [a] -> Exp [a] Source #

Instances
type Eval (Filter p (a2 ': as) :: [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Filter p (a2 ': as) :: [a1] -> Type) = If (Eval (p a2)) (a2 ': Eval (Filter p as)) (Eval (Filter p as))
type Eval (Filter _p ([] :: [a]) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Filter _p ([] :: [a]) :: [a] -> Type) = ([] :: [a])

data Head :: [a] -> Exp (Maybe a) Source #

Instances
type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) = Just a2
type Eval (Head ([] :: [a]) :: Maybe a -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Head ([] :: [a]) :: Maybe a -> Type) = (Nothing :: Maybe a)

data Tail :: [a] -> Exp (Maybe [a]) Source #

Instances
type Eval (Tail (_a ': as) :: Maybe [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Tail (_a ': as) :: Maybe [a] -> Type) = Just as
type Eval (Tail ([] :: [a]) :: Maybe [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Tail ([] :: [a]) :: Maybe [a] -> Type) = (Nothing :: Maybe [a])

data Null :: [a] -> Exp Bool Source #

Instances
type Eval (Null (a2 ': as) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Null (a2 ': as) :: Bool -> Type) = False
type Eval (Null ([] :: [a]) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Null ([] :: [a]) :: Bool -> Type) = True

data Length :: [a] -> Exp Nat Source #

Instances
type Eval (Length (a2 ': as) :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Length (a2 ': as) :: Nat -> Type) = 1 + Eval (Length as)
type Eval (Length ([] :: [a]) :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Length ([] :: [a]) :: Nat -> Type) = 0

data Find :: (a -> Exp Bool) -> [a] -> Exp (Maybe a) Source #

Instances
type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) = If (Eval (p a2)) (Just a2) (Eval (Find p as))
type Eval (Find _p ([] :: [a]) :: Maybe a -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Find _p ([] :: [a]) :: Maybe a -> Type) = (Nothing :: Maybe a)

data FindIndex :: (a -> Exp Bool) -> [a] -> Exp (Maybe Nat) Source #

Find the index of an element satisfying the predicate.

Instances
type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) = Eval (If (Eval (p a2)) (Pure (Just 0)) ((Map ((+) 1) :: Maybe Nat -> Maybe Nat -> Type) =<< FindIndex p as))
type Eval (FindIndex _p ([] :: [a]) :: Maybe Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex _p ([] :: [a]) :: Maybe Nat -> Type) = (Nothing :: Maybe Nat)

type Lookup (a :: k) (as :: [(k, b)]) = (Map Snd (Eval (Find (TyEq a <=< Fst) as)) :: Exp (Maybe b)) Source #

Find an element associated with a key. Lookup :: k -> [(k, b)] -> Exp (Maybe b)

data SetIndex :: Nat -> a -> [a] -> Exp [a] Source #

Modify an element at a given index.

The list is unchanged if the index is out of bounds.

Instances
type Eval (SetIndex n a' as :: [k] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (SetIndex n a' as :: [k] -> Type)

data ZipWith :: (a -> b -> Exp c) -> [a] -> [b] -> Exp [c] Source #

Instances
type Eval (ZipWith f (a2 ': as) (b2 ': bs) :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith f (a2 ': as) (b2 ': bs) :: [c] -> Type) = Eval (f a2 b2) ': Eval (ZipWith f as bs)
type Eval (ZipWith _f _as ([] :: [b]) :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith _f _as ([] :: [b]) :: [c] -> Type) = ([] :: [c])
type Eval (ZipWith _f ([] :: [a]) _bs :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith _f ([] :: [a]) _bs :: [c] -> Type) = ([] :: [c])

type Zip = ZipWith (Pure2 (,)) Source #

Zip :: [a] -> [b] -> Exp [(a, b)]

data Unzip :: Exp [(a, b)] -> Exp ([a], [b]) Source #

Instances
type Eval (Unzip as :: ([a], [b]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Unzip as :: ([a], [b]) -> Type) = Eval (Foldr (Cons2 :: (a, b) -> ([a], [b]) -> ([a], [b]) -> Type) ((,) ([] :: [a]) ([] :: [b])) (Eval as))

data Cons2 :: (a, b) -> ([a], [b]) -> Exp ([a], [b]) Source #

Instances
type Eval (Cons2 ((,) a3 b) ((,) as bs) :: ([a2], [a1]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Cons2 ((,) a3 b) ((,) as bs) :: ([a2], [a1]) -> Type) = (,) (a3 ': as) (b ': bs)

Bool

data UnBool :: Exp a -> Exp a -> Bool -> Exp a Source #

N.B.: The order of the two branches is the opposite of "if": UnBool ifFalse ifTrue bool.

This mirrors the default order of constructors:

data Bool = False | True
----------- False < True
Instances
type Eval (UnBool fal tru True :: a -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (UnBool fal tru True :: a -> Type) = Eval tru
type Eval (UnBool fal tru False :: a -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (UnBool fal tru False :: a -> Type) = Eval fal

data (||) :: Bool -> Bool -> Exp Bool infixr 2 Source #

Instances
type Eval (False || b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (False || b :: Bool -> Type) = b
type Eval (True || b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (True || b :: Bool -> Type) = True
type Eval (a || False :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a || False :: Bool -> Type) = a
type Eval (a || True :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a || True :: Bool -> Type) = True

data (&&) :: Bool -> Bool -> Exp Bool infixr 3 Source #

Instances
type Eval (False && b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (False && b :: Bool -> Type) = False
type Eval (True && b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (True && b :: Bool -> Type) = b
type Eval (a && True :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a && True :: Bool -> Type) = a
type Eval (a && False :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (a && False :: Bool -> Type) = False

data Not :: Bool -> Exp Bool Source #

Instances
type Eval (Not False) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Not False) = True
type Eval (Not True) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Not True) = False

Multi-way if

data Guarded :: a -> [Guard (a -> Exp Bool) (Exp b)] -> Exp b Source #

A conditional choosing the first branch whose guard a -> Exp Bool accepts a given value a.

Example

type UnitPrefix n = Eval (Guarded n
  '[ TyEq 0 ':= Pure ""
   , TyEq 1 ':= Pure "deci"
   , TyEq 2 ':= Pure "hecto"
   , TyEq 3 ':= Pure "kilo"
   , TyEq 6 ':= Pure "mega"
   , TyEq 9 ':= Pure "giga"
   , Otherwise ':= Error "Something else"
   ])
Instances
type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) = Eval (If (Eval (p x)) y (Guarded x ys))

data Guard a b Source #

A fancy-looking pair type to use with Guarded.

Constructors

a := b infixr 0 
Instances
type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Data.Bool

type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) = Eval (If (Eval (p x)) y (Guarded x ys))

type Otherwise = ConstFn True Source #

A catch-all guard for Guarded.

Nat

data (+) :: Nat -> Nat -> Exp Nat Source #

Instances
type Eval (a + b :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a + b :: Nat -> Type) = a + b

data (-) :: Nat -> Nat -> Exp Nat Source #

Instances
type Eval (a - b :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a - b :: Nat -> Type) = a - b

data * :: Nat -> Nat -> Exp Nat Source #

Instances
type Eval (a * b :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a * b :: Nat -> Type) = a * b

data (^) :: Nat -> Nat -> Exp Nat Source #

Instances
type Eval (a ^ b :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a ^ b :: Nat -> Type) = a ^ b

data (<=) :: Nat -> Nat -> Exp Bool Source #

Instances
type Eval (a <= b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a <= b :: Bool -> Type) = a <=? b

data (>=) :: Nat -> Nat -> Exp Bool Source #

Instances
type Eval (a >= b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a >= b :: Bool -> Type) = b <=? a

data (<) :: Nat -> Nat -> Exp Bool Source #

Instances
type Eval (a < b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a < b :: Bool -> Type) = Eval (Not =<< (a >= b))

data (>) :: Nat -> Nat -> Exp Bool Source #

Instances
type Eval (a > b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.Nat

type Eval (a > b :: Bool -> Type) = Eval (Not =<< (a <= b))

Overloaded operations

data Map :: (a -> Exp b) -> f a -> Exp (f b) Source #

Type-level fmap for type-level functors.

Instances
type Eval (Map f (a2 ': as) :: [b] -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (a2 ': as) :: [b] -> Type) = Eval (f a2) ': Eval (Map f as)
type Eval (Map f ([] :: [a]) :: [b] -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ([] :: [a]) :: [b] -> Type) = ([] :: [b])
type Eval (Map f (Just a3) :: Maybe a2 -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (Just a3) :: Maybe a2 -> Type) = Just (Eval (f a3))
type Eval (Map f (Nothing :: Maybe a) :: Maybe b -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (Nothing :: Maybe a) :: Maybe b -> Type) = (Nothing :: Maybe b)
type Eval (Map f (Right a3 :: Either a2 a1) :: Either a2 b -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (Right a3 :: Either a2 a1) :: Either a2 b -> Type) = (Right (Eval (f a3)) :: Either a2 b)
type Eval (Map f (Left x :: Either a2 a1) :: Either a2 b -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f (Left x :: Either a2 a1) :: Either a2 b -> Type) = (Left x :: Either a2 b)
type Eval (Map f ((,) x a2) :: (k2, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ((,) x a2) :: (k2, k1) -> Type) = (,) x (Eval (f a2))
type Eval (Map f ((,,) x y a2) :: (k2, k3, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ((,,) x y a2) :: (k2, k3, k1) -> Type) = (,,) x y (Eval (f a2))
type Eval (Map f ((,,,) x y z a2) :: (k2, k3, k4, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ((,,,) x y z a2) :: (k2, k3, k4, k1) -> Type) = (,,,) x y z (Eval (f a2))
type Eval (Map f ((,,,,) x y z w a2) :: (k2, k3, k4, k5, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Map f ((,,,,) x y z w a2) :: (k2, k3, k4, k5, k1) -> Type) = (,,,,) x y z w (Eval (f a2))

data Bimap :: (a -> Exp a') -> (b -> Exp b') -> f a b -> Exp (f a' b') Source #

Type-level bimap.

Instances
type Eval (Bimap f g (Right y :: Either a b1) :: Either a' b2 -> Type) Source # 
Instance details

Defined in Fcf.Classes

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

Defined in Fcf.Classes

type Eval (Bimap f g (Left x :: Either a1 b) :: Either a2 b' -> Type) = (Left (Eval (f x)) :: Either a2 b')
type Eval (Bimap f g ((,) x y) :: (k2, k1) -> Type) Source # 
Instance details

Defined in Fcf.Classes

type Eval (Bimap f g ((,) x y) :: (k2, k1) -> Type) = (,) (Eval (f x)) (Eval (g y))

Miscellaneous

data Error :: Symbol -> Exp a Source #

Type-level error.

Instances
type Eval (Error msg :: a -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Error msg :: a -> Type) = (TypeError (Text msg) :: a)

data Constraints :: [Constraint] -> Exp Constraint Source #

Conjunction of a list of constraints.

Instances
type Eval (Constraints (a ': as) :: Constraint -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Constraints (a ': as) :: Constraint -> Type) = (a, Eval (Constraints as))
type Eval (Constraints ([] :: [Constraint])) Source # 
Instance details

Defined in Fcf.Utils

type Eval (Constraints ([] :: [Constraint])) = ()

data TyEq :: a -> b -> Exp Bool Source #

Type equality.

Instances
type Eval (TyEq a b :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Utils

type Eval (TyEq a b :: Bool -> Type)

type family Stuck :: a Source #

A stuck type that can be used like a type-level undefined.

class IsBool (b :: Bool) where Source #

Methods

_If :: (b ~ True => r) -> (b ~ False => r) -> r Source #

Instances
IsBool False Source # 
Instance details

Defined in Fcf.Utils

Methods

_If :: ((False ~ True) -> r) -> ((False ~ False) -> r) -> r Source #

IsBool True Source # 
Instance details

Defined in Fcf.Utils

Methods

_If :: ((True ~ True) -> r) -> ((True ~ False) -> r) -> r Source #

type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ... #

Type-level If. If True a b ==> a; If False a b ==> b

Equations

If True (tru :: k) (fls :: k) = tru 
If False (tru :: k) (fls :: k) = fls