first-class-families-0.8.0.0: First class type families

Safe HaskellSafe
LanguageHaskell2010

Fcf.Combinators

Description

General fcf combinators.

See also Fcf.Data.Function for more.

Synopsis

Documentation

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)