pointless-haskell-0.0.5: Pointless Haskell library

Portabilitynon-portable
Stabilityexperimental
Maintainerhpacheco@di.uminho.pt

Generics.Pointless.Combinators

Contents

Description

Pointless Haskell: point-free programming with recursion patterns as hylomorphisms

This module defines many standard combinators used for point-free programming.

Synopsis

Terminal object

_L :: aSource

The bottom value for any type. It is many times used just for type annotations.

data One Source

The final object. The only possible value of type One is _L.

Points

bang :: a -> OneSource

Creates a point to the terminal object.

pnt :: a -> One -> aSource

Converts elements into points.

Products

(/\) :: (a -> b) -> (a -> c) -> a -> (b, c)Source

The infix split combinator.

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

Sums

inl :: a -> Either a bSource

Injects a value to the left of a sum.

inr :: b -> Either a bSource

Injects a value to the right of a sum.

(\/) :: (b -> a) -> (c -> a) -> Either b c -> aSource

The infix either combinator.

(-|-) :: (a -> b) -> (c -> d) -> Either a c -> Either b dSource

The infix sum combinator.

(<>) :: (a -> b) -> (c -> d) -> Either a c -> Either b dSource

Alias for the infix sum combinator.

Exponentials

app :: (a -> b, a) -> bSource

The application combinator.

lexp :: (a -> b) -> (b -> c) -> a -> cSource

The left exponentiation combinator.

rexp :: (b -> c) -> (a -> b) -> a -> cSource

The right exponentiation combinator.

(!) :: a -> b -> aSource

The infix combinator for a constant point.

Guards

grd :: (a -> Bool) -> a -> Either a aSource

Guard combinator that operates on Haskell booleans.

(?) :: (a -> Bool) -> a -> Either a aSource

Infix guard combinator that simulates the postfix syntax.

(??) :: (a -> Either One One) -> a -> Either a aSource

Point-free definitions of uncurried versions of the basic combinators

split :: (a -> b, a -> c) -> a -> (b, c)Source

The uncurried split combinator.

eithr :: (a -> c, b -> c) -> Either a b -> cSource

The uncurried either combinator.

comp :: (b -> c, a -> b) -> a -> cSource

The uncurried composition combinator.

orf :: (a -> Bool, a -> Bool) -> a -> BoolSource

Binary or of boolean functions.

andf :: (a -> Bool, a -> Bool) -> a -> BoolSource

Binary and of boolean functions.

or :: (Bool, Bool) -> BoolSource

Binary or point-free combinator.

and :: (Bool, Bool) -> BoolSource

Binary and point-free combinator.

eq :: Eq a => (a, a) -> BoolSource

Binary equality point-free combinator.

neq :: Eq a => (a, a) -> BoolSource

Binary inequality point-free combinator.

Point-free isomorphic combinators

swap :: (a, b) -> (b, a)Source

Swap the elements of a product.

coswap :: Either a b -> Either b aSource

Swap the elements of a sum.

distl :: (Either a b, c) -> Either (a, c) (b, c)Source

Distribute products over the left of sums.

undistl :: Either (a, c) (b, c) -> (Either a b, c)Source

Distribute sums over the left of products.

distr :: (c, Either a b) -> Either (c, a) (c, b)Source

Distribute products over the right of sums.

undistr :: Either (c, a) (c, b) -> (c, Either a b)Source

Distribute sums over the right of products.

assocl :: (a, (b, c)) -> ((a, b), c)Source

Associate nested products to the left.

assocr :: ((a, b), c) -> (a, (b, c))Source

Associates nested products to the right.

coassocl :: Either a (Either b c) -> Either (Either a b) cSource

Associates nested sums to the left.

coassocr :: Either (Either a b) c -> Either a (Either b c)Source

Associates nested sums to the right.

subr :: (a, (b, c)) -> (b, (a, c))Source

Shifts the an element to the right of a nested pair.

subl :: ((a, b), c) -> ((a, c), b)Source

Shifts the an element to the left of a nested pair.

cosubr :: Either a (Either b c) -> Either b (Either a c)Source

Shifts an option to the right of a nested sum.

cosubl :: Either (Either a b) c -> Either (Either a c) bSource

Shifts an option to the left of a nested sum.

distp :: ((c, d), (a, b)) -> ((c, a), (d, b))Source

The product distribution combinator

dists :: (Either a b, Either c d) -> Either (Either (a, c) (a, d)) (Either (b, c) (b, d))Source

The sum distribution combinator.