pointless-haskell-0.0.5: Pointless Haskell library

Portabilitynon-portable
Stabilityexperimental
Maintainerhpacheco@di.uminho.pt

Generics.Pointless.Examples.Examples

Contents

Description

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

This module provides examples, examples and more examples.

Synopsis

Integers

Addition

add :: (Int, Int) -> IntSource

Pre-defined algebraic addition.

addAnaPW :: (Int, Int) -> IntSource

Definition of algebraic addition as an anamorphism in the point-wise style.

addAna :: (Int, Int) -> IntSource

Defition of algebraic addition as an anamorphism.

type From a = K a :+!: ISource

The fixpoint of the functor that is either a constant or defined recursively.

addHylo :: (Int, Int) -> IntSource

Definition of algebraic addition as an hylomorphism.

addAccum :: (Int, Int) -> IntSource

Definition of algebraic addition as an accumulation.

addApo :: (Int, Int) -> IntSource

Definition of algebraic addition as an apomorphism.

Product

prod :: (Int, Int) -> IntSource

Pre-defined algebraic product.

prodHylo :: (Int, Int) -> IntSource

Definition of algebraic product as an hylomorphism

'Greater than' comparison

gt :: Ord a => (a, a) -> BoolSource

Pre-defined 'greater than' comparison.

gtHylo :: (Int, Int) -> BoolSource

Definition of 'greater than' as an hylomorphism.

Factorial

fact :: Int -> IntSource

Native recursive definition of the factorial function.

factPF :: Int -> IntSource

Recursive definition of the factorial function in the point-free style.

factPF' :: Int -> IntSource

Recursive definition of the factorial function in the point-free style with structural recursion.

factHylo :: Int -> IntSource

Definition of the factorial function as an hylomorphism.

factPara :: Int -> IntSource

Definition of the factorial function as a paramorphism.

factZygo :: Int -> IntSource

Definition of the factorial function as a zygomorphism.

Fibonnaci

fib :: Int -> IntSource

Native recursive definition of the fibonacci function.

fibPF :: Int -> IntSource

Recursive definition of the fibonacci function in the point-free style.

fibPF' :: Int -> IntSource

Recursive definition of the fibonacci function in the point-free style with structural recursion.

type BSTree = K One :+!: (K One :+!: (I :*!: I))Source

The fixpoint of the functor for a binary shape tree.

fibHylo :: Int -> IntSource

Definition of the fibonacci function as an hylomorphism.

fibHisto :: Int -> IntSource

Definition of the fibonacci function as an histomorphism.

fibDyna :: Int -> IntSource

Definition of the fibonacci function as a dynamorphism.

Binary Partitioning

bp :: Int -> IntSource

Native recursive definition for the binary partitions of a number.

The number of binary partitions for a number n is the number of unique ways to partition this number (ignoring the order) into powers of 2. | Definition of the binary partitioning of a number as an hylomorphism.

type BTree = K One :+!: (I :+!: (I :*!: I))Source

The fixpoint of the functor representing trees with maximal branching factor of two.

bpHylo :: Int -> IntSource

Definition of the binary partitioning of a number as an hylomorphism.

bpDyna :: Int -> IntSource

Definition of the binary partitioning of a number as a dynamorphism.

Average

average :: [Int] -> IntSource

Recursive definition of the average of a set of integers.

averageCata :: [Int] -> IntSource

Definition of the average of a set of integers as a catamorphism.

Lists

Singleton list.

wrap :: a -> [a]Source

Pre-defined wrapping of an element into a list.

wrapPF :: a -> [a]Source

Definition of wrapping in the point-free style.

Tail

tail :: [a] -> [a]Source

Definition of the tail of a list as a total function.

tailPF :: [a] -> [a]Source

Definition of the tail of a list in the point-free style.

tailCata :: [a] -> [a]Source

Definition of the tail of a list as an anamorphism.

tailPara :: [a] -> [a]Source

Definition of the tail of a list as a paramorphism.

Length

length :: [a] -> IntSource

Native recursion definition of list length.

lengthPF :: [a] -> IntSource

Recursive definition of list length in the point-free style.

lengthPF' :: [a] -> IntSource

Recursive definition of list length in the point-free style with structural recursion.

lengthHylo :: [a] -> IntSource

Definition of list length as an hylomorphism.

lengthAna :: [a] -> IntSource

Definition of list length as an anamorphism.

lengthCata :: [a] -> IntSource

Definition of list length as a catamorphism.

Filtering

filter :: (a -> Bool) -> [a] -> [a]Source

Native recursive definition of list filtering.

filterCata :: (a -> Bool) -> [a] -> [a]Source

Definition of list filtering as an catamorphism.

Generation

repeatAna :: a -> [a]Source

Generation of infinite lists as an anamorphism.

replicateAna :: (Int, a) -> [a]Source

Finite replication of an element as an anamorphism.

downtoAna :: Int -> [Int]Source

Generation of a downwards list as an anamorphism.

insertApo :: Ord a => (a, [a]) -> [a]Source

Ordered list insertion as an apomorphism.

insertPara :: Ord a => (a, [a]) -> [a]Source

Ordered list insertion as a paramorphism.

snoc :: (a, [a]) -> [a]Source

Append an element to the end of a list as an hylomorphism.

snocApo :: (a, [a]) -> [a]Source

Append an element to the end of a list as an apomorphism.

Extraction

bubble :: Ord a => [a] -> Either One (a, [a])Source

Creates a bubble from a list. Used in the bubble sort algorithm.

takeAna :: (Int, [a]) -> [a]Source

Extraction of a number of elements from a list as an anamorphism.

Partition

partition :: Ord a => (a, [a]) -> ([a], [a])Source

Native recursive definition for partitioning a list at a specified element.

partitionHylo :: Ord a => (a, [a]) -> ([a], [a])Source

Definition for partitioning a list at a specified element as an hylomorphism.

Transformations

isum :: [Int] -> [Int]Source

Incremental summation as a catamorphism.

fisum :: [Int] -> Int -> [Int]Source

Incrementation the elements of a list by a specified value as a catamorphism.

data Some a Source

Constructors

Wrap a 
Insert a (Some a) 

Instances

Eq a => Eq (Some a) 
Show a => Show (Some a) 
Mu (Some a) 

isumsAccum :: ([Int], Int) -> Some IntSource

Incrementation the elements of a list by a specified value as an accumulation. The result is always a non-empty list

mapCata :: [a] -> (a -> b) -> [b]Source

Definition of list mapping as a catamorphism.

reverseCata :: [a] -> [a]Source

Definition of list reversion as a catamorphism.

reverseAccum' :: ([a], [a]) -> [a]Source

Linear version of reverse using accumulations

reverseHylo :: ([a], [a]) -> [a]Source

qsort :: Ord a => [a] -> [a]Source

Definition of the quicksort algorithm as an hylomorphism.

bsort :: Ord a => [a] -> [a]Source

Definition of the bubble sort algorithm as an anamorphism.

isort :: Ord a => [a] -> [a]Source

Definition of the insertion sort algorithm as a catamorphism.

msplit :: [a] -> ([a], [a])Source

msort :: Ord a => [a] -> [a]Source

hsort :: Ord a => [a] -> [a]Source

Definition of the heap sort algorithm as an hylomorphism.

hsplit :: Ord a => [a] -> (a, ([a], [a]))Source

malcolm :: ((b, a) -> a) -> a -> [b] -> [a]Source

Malcolm downwards accumulations on lists.

malcolmAna :: ((b, a) -> a) -> a -> [b] -> [a]Source

Malcom downwards accumulations on lists as an anamorphism.

malcolmAna' :: ((b, a) -> a) -> ([b], a) -> [a]Source

Uncurried version of Malcom downwards accumulations on lists as an anamorphism.

Zipping

zipAna :: ([a], [b]) -> [(a, b)]Source

Definition of the zip for lists of pairs as an anamorphism.

Subsequencing

subsequences :: Eq a => [a] -> [[a]]Source

Definition of the subsequences of a list as a catamorphism.

Concatenation

cat :: ([a], [a]) -> [a]Source

Pre-defined list concatenation.

catCata :: [a] -> [a] -> [a]Source

List concatenation as a catamorphism.

type NeList a b = K a :+!: (K b :*!: I)Source

The fixpoint of the list functor with a specific terminal element.

catHylo :: ([a], [a]) -> [a]Source

List concatenation as an hylomorphism.

concat :: [[a]] -> [a]Source

Native recursive definition of lists-of-lists concatenation.

concatCata :: [[a]] -> [a]Source

Definition of lists-of-lists concatenation as an anamorphism.

merge :: Ord a => ([a], [a]) -> [a]Source

Sorted concatenation of two lists as an hylomorphism.

Summation

sumCata :: [Int] -> IntSource

Definition of inter addition as a catamorphism.

Multiplication

mult :: [Int] -> IntSource

Native recursive definition of integer multiplication.

multCata :: [Int] -> IntSource

Definition of integer multiplication as a catamorphism.

Predicates

sorted :: Ord a => [a] -> BoolSource

Edit distance

editdist :: Eq a => ([a], [a]) -> IntSource

Native recursive definition of the edit distance algorithm.

Edit distance is a classical dynamic programming algorithm that calculates a measure of distance or dierence between lists with comparable elements.

type EditDist a = K [a] :+!: ((K a :*!: K a) :*!: (I :*!: (I :*!: I)))Source

The fixpoint of the functor that represents a virtual matrix used to accumulate and look up values for the edit distance algorithm.

Since matrixes are not inductive types, a walk-through of a matrix is used, consisting in a list of values from the matrix ordered predictability.

For a more detailed explanation, please refer to http://math.ut.ee/~eugene/kabanov-vene-mpc-06.pdf.

type EditDistL a = (K [a] :*!: K [a]) :*!: (K One :+!: I)Source

editdistHylo :: Eq a => ([a], [a]) -> IntSource

The edit distance algorithm as an hylomorphism.

editDistDyna :: Eq a => ([a], [a]) -> IntSource

The edit distance algorithm as a dynamorphism.

Streams

type Stream a = K a :*!: ISource

The fixpoint of the functor of streams.

headS :: Stream a -> aSource

Stream head.

tailS :: Stream a -> Stream aSource

Stream tail.

generate :: Int -> Stream IntSource

Definition of a stream sequence generator as an anamorphism.

idStream :: Stream a -> Stream aSource

Identity o streams as an anamorphism.

mapStream :: (a -> b) -> Stream a -> Stream bSource

Mapping over streams as an anamorphism.

malcolmS :: ((b, a) -> a) -> a -> Stream b -> Stream aSource

Malcolm downwards accumulations on streams.

malcolmSAna :: ((b, a) -> a) -> a -> Stream b -> Stream aSource

Malcom downwards accumulations on streams as an anamorphism.

malcolmSAna' :: ((b, a) -> a) -> (Stream b, a) -> Stream aSource

Uncurried version of Malcom downwards accumulations on streams as an anamorphism.

inits :: Stream a -> Stream [a]Source

Promotes streams elements to streams of singleton elements.

exchFutu :: Stream a -> Stream aSource

Definition of parwise exchange on streams as a futumorphism.

Binary Tree

data Tree a Source

Datatype declaration of a binary tree.

Constructors

Empty 
Node a (Tree a) (Tree a) 

Instances

Show a => Show (Tree a) 
Mu (Tree a) 

nleaves :: Tree a -> IntSource

Counting the number of leaves in a binary tree as a catamorphism.

nnodes :: Tree a -> IntSource

Counting the number of nodes in a binary tree as a catamorphism.

genTree :: Int -> Tree IntSource

Generation of a binary tree with a specified height as an anamorphism.

preTree :: Tree a -> [a]Source

The preorder traversal on binary trees as a catamorphism.

postTree :: Tree a -> [a]Source

The postorder traversal on binary trees as a catamorphism.

Leaf Trees

data LTree a Source

Datatype declaration of a leaf tree.

Constructors

Leaf a 
Branch (LTree a) (LTree a) 

Instances

Mu (LTree a) 

leaves :: LTree a -> [a]Source

Extract the leaves of a leaf tree as a catamorphism.

genLTree :: Int -> LTree IntSource

Generation of a leaft tree of a specified height as an anamorphism.

height :: LTree a -> IntSource

Calculate the height of a leaf tree as a catamorphism.

Rose Trees

data Rose a Source

Datatype declaration of a rose tree.

Constructors

Forest a [Rose a] 

Instances

Show a => Show (Rose a) 
Mu (Rose a) 

preRose :: Rose a -> [a]Source

postRose :: Rose a -> [a]Source

The postorder traversal on rose trees as a catamorphism.

genRose :: Int -> Rose IntSource

Generation of a rose tree of a specified height as an anamorphism.