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

Fcf.Data.Function

Description

Simple combinators for functions.

Synopsis

Documentation

data (&) :: a -> (a -> Exp b) -> Exp b infixl 1 Source #

Reverse function application, argument first.

Example

Expand
>>> :kind! Eval ('(True, Nothing) & Fst)
Eval ('(True, Nothing) & Fst) :: Bool
= True

Instances

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

Defined in Fcf.Data.Function

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

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

Lift a binary function to the domain of a projection.

Example

Expand
>>> :kind! Eval (((&&) `On` Fst) '(True, Nothing) '(False, Just '()))
Eval (((&&) `On` Fst) '(True, Nothing) '(False, Just '())) :: Bool
= False

Instances

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

Defined in Fcf.Data.Function

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

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

Pre-compose a binary function with a function for each argument.

Example

Expand
>>> :kind! Eval (Bicomap Fst Pure (||) '(False, Nothing) True)
Eval (Bicomap Fst Pure (||) '(False, Nothing) True) :: Bool
= True

Instances

Instances details
type Eval (Bicomap f g r x y :: a4 -> Type) Source # 
Instance details

Defined in Fcf.Data.Function

type Eval (Bicomap f g r x y :: a4 -> Type) = Eval (r (Eval (f x)) (Eval (g y)))