Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | hpacheco@di.uminho.pt |
Pointless Haskell: point-free programming with recursion patterns as hylomorphisms
This module provides examples, examples and more examples.
- add :: (Int, Int) -> Int
- addAnaPW :: (Int, Int) -> Int
- addAna :: (Int, Int) -> Int
- type From a = K a :+!: I
- addHylo :: (Int, Int) -> Int
- addAccum :: (Int, Int) -> Int
- addApoPW :: (Int, Int) -> Int
- addApo :: (Int, Int) -> Int
- prod :: (Int, Int) -> Int
- prodHylo :: (Int, Int) -> Int
- gt :: Ord a => (a, a) -> Bool
- gtHylo :: (Int, Int) -> Bool
- fact :: Int -> Int
- factPF :: Int -> Int
- factPF' :: Int -> Int
- factHylo :: Int -> Int
- factPara :: Int -> Int
- factZygo :: Int -> Int
- fib :: Int -> Int
- fibPF :: Int -> Int
- fibPF' :: Int -> Int
- type BSTree = K One :+!: (K One :+!: (I :*!: I))
- fibHylo :: Int -> Int
- fibHisto :: Int -> Int
- fibDyna :: Int -> Int
- bp :: Int -> Int
- type BTree = K One :+!: (I :+!: (I :*!: I))
- bpHylo :: Int -> Int
- bpDyna :: Int -> Int
- average :: [Int] -> Int
- averageCata :: [Int] -> Int
- wrap :: a -> [a]
- wrapPF :: a -> [a]
- tail :: [a] -> [a]
- tailPF :: [a] -> [a]
- tailCata :: [a] -> [a]
- tailPara :: [a] -> [a]
- length :: [a] -> Int
- lengthPF :: [a] -> Int
- lengthPF' :: [a] -> Int
- lengthHylo :: [a] -> Int
- lengthAna :: [a] -> Int
- lengthCata :: [a] -> Int
- filter :: (a -> Bool) -> [a] -> [a]
- filterCata :: (a -> Bool) -> [a] -> [a]
- repeatAna :: a -> [a]
- replicateAna :: (Int, a) -> [a]
- downtoAna :: Int -> [Int]
- insertApo :: Ord a => (a, [a]) -> [a]
- insertPara :: Ord a => (a, [a]) -> [a]
- snoc :: (a, [a]) -> [a]
- snocApo :: (a, [a]) -> [a]
- bubble :: Ord a => [a] -> Either One (a, [a])
- takeAna :: (Int, [a]) -> [a]
- partition :: Ord a => (a, [a]) -> ([a], [a])
- partitionHylo :: Ord a => (a, [a]) -> ([a], [a])
- isum :: [Int] -> [Int]
- fisum :: [Int] -> Int -> [Int]
- data NeLis a
- isumsAccum :: ([Int], Int) -> NeLis Int
- isumsAna :: ([Int], Int) -> NeLis Int
- mapCata :: [a] -> (a -> b) -> [b]
- reverseCata :: [a] -> [a]
- reverseAccum' :: ([a], [a]) -> [a]
- reverseHylo :: ([a], [a]) -> [a]
- qsort :: Ord a => [a] -> [a]
- bsort :: Ord a => [a] -> [a]
- isort :: Ord a => [a] -> [a]
- msplit :: [a] -> ([a], [a])
- msort :: Ord a => [a] -> [a]
- hsort :: Ord a => [a] -> [a]
- hsplit :: Ord a => [a] -> (a, ([a], [a]))
- malcolm :: ((b, a) -> a) -> a -> [b] -> [a]
- malcolmAna :: ((b, a) -> a) -> a -> [b] -> [a]
- malcolmAna' :: ((b, a) -> a) -> ([b], a) -> [a]
- zipAna :: ([a], [b]) -> [(a, b)]
- subsequences :: Eq a => [a] -> [[a]]
- cat :: ([a], [a]) -> [a]
- catCata :: [a] -> [a] -> [a]
- type NeList a b = K a :+!: (K b :*!: I)
- catHylo :: ([a], [a]) -> [a]
- concat :: [[a]] -> [a]
- concatCata :: [[a]] -> [a]
- merge :: Ord a => ([a], [a]) -> [a]
- sumCata :: [Int] -> Int
- mult :: [Int] -> Int
- multCata :: [Int] -> Int
- sorted :: Ord a => [a] -> Bool
- editdist :: Eq a => ([a], [a]) -> Int
- type EditDist a = K [a] :+!: ((K a :*!: K a) :*!: (I :*!: (I :*!: I)))
- type EditDistL a = (K [a] :*!: K [a]) :*!: (K One :+!: I)
- editdistHylo :: Eq a => ([a], [a]) -> Int
- editDistDyna :: Eq a => ([a], [a]) -> Int
- type Stream a = K a :*!: I
- headS :: Stream a -> a
- tailS :: Stream a -> Stream a
- generate :: Int -> Stream Int
- idStream :: Stream a -> Stream a
- mapStream :: (a -> b) -> Stream a -> Stream b
- malcolmS :: ((b, a) -> a) -> a -> Stream b -> Stream a
- malcolmSAna :: ((b, a) -> a) -> a -> Stream b -> Stream a
- malcolmSAna' :: ((b, a) -> a) -> (Stream b, a) -> Stream a
- inits :: Stream a -> Stream [a]
- exchFutu :: Stream a -> Stream a
- data Tree a
- nleaves :: Tree a -> Int
- nnodes :: Tree a -> Int
- genTree :: Int -> Tree Int
- preTree :: Tree a -> [a]
- postTree :: Tree a -> [a]
- data LTree a
- leaves :: LTree a -> [a]
- genLTree :: Int -> LTree Int
- height :: LTree a -> Int
- data Rose a = Forest a [Rose a]
- preRose :: Rose a -> [a]
- postRose :: Rose a -> [a]
- genRose :: Int -> Rose Int
Integers
Addition
addAnaPW :: (Int, Int) -> IntSource
Definition of algebraic addition as an anamorphism in the point-wise style.
type From a = K a :+!: ISource
The fixpoint of the functor that is either a constant or defined recursively.
Product
'Greater than' comparison
Factorial
Recursive definition of the factorial function in the point-free style with structural recursion.
Fibonnaci
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.
Binary Partitioning
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.
Average
averageCata :: [Int] -> IntSource
Definition of the average of a set of integers as a catamorphism.
Lists
Singleton list.
Tail
Length
Recursive definition of list length in the point-free style with structural recursion.
lengthHylo :: [a] -> IntSource
Definition of list length as an hylomorphism.
lengthCata :: [a] -> IntSource
Definition of list length as a catamorphism.
Filtering
filterCata :: (a -> Bool) -> [a] -> [a]Source
Definition of list filtering as an catamorphism.
Generation
replicateAna :: (Int, a) -> [a]Source
Finite replication of an element as an anamorphism.
insertPara :: Ord a => (a, [a]) -> [a]Source
Ordered list insertion as a paramorphism.
Extraction
bubble :: Ord a => [a] -> Either One (a, [a])Source
Creates a bubble from a list. Used in the bubble sort algorithm.
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
fisum :: [Int] -> Int -> [Int]Source
Incrementation the elements of a list by a specified value as a catamorphism.
isumsAccum :: ([Int], Int) -> NeLis IntSource
Incrementation the elements of a list by a specified value as an accumulation. The result is always a non-empty list
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
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
Subsequencing
subsequences :: Eq a => [a] -> [[a]]Source
Definition of the subsequences of a list as a catamorphism.
Concatenation
type NeList a b = K a :+!: (K b :*!: I)Source
The fixpoint of the list functor with a specific terminal element.
concatCata :: [[a]] -> [a]Source
Definition of lists-of-lists concatenation as an anamorphism.
Summation
Multiplication
Predicates
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.
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
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.
Binary Tree
Datatype declaration of a binary tree.
genTree :: Int -> Tree IntSource
Generation of a binary tree with a specified height as an anamorphism.
Leaf Trees
Datatype declaration of a leaf tree.
genLTree :: Int -> LTree IntSource
Generation of a leaft tree of a specified height as an anamorphism.
Rose Trees
Datatype declaration of a rose tree.