Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Set operations on lists.
Synopsis
- set :: Ord a => [a] -> [a]
- n_powerset :: Integral n => n -> n
- powerset :: [a] -> [[a]]
- powerset_sorted :: Ord a => [a] -> [[a]]
- pairs :: [a] -> [(a, a)]
- triples :: [a] -> [(a, a, a)]
- expand_set :: Ord a => Int -> [a] -> [[a]]
- partitions :: Eq a => [a] -> [[[a]]]
- cartesian_product :: [a] -> [b] -> [(a, b)]
- nfold_cartesian_product :: [[a]] -> [[a]]
- multiset_cycles :: Ord t => [t] -> [[t]]
Documentation
n_powerset :: Integral n => n -> n Source #
Size of powerset of set of cardinality n, ie. 2
^
n.
map n_powerset [6..9] == [64,128,256,512]
powerset :: [a] -> [[a]] Source #
Powerset, ie. set of all subsets.
sort (powerset [1,2]) == [[],[1],[1,2],[2]] map length (map (\n -> powerset [1..n]) [6..9]) == [64,128,256,512]
powerset_sorted :: Ord a => [a] -> [[a]] Source #
Variant where result is sorted and the empty set is not given.
powerset_sorted [1,2,3] == [[1],[2],[3],[1,2],[1,3],[2,3],[1,2,3]]
triples :: [a] -> [(a, a, a)] Source #
Three element subsets.
triples [1..4] == [(1,2,3),(1,2,4),(1,3,4),(2,3,4)]
import Music.Theory.Combinations let f n = genericLength (triples [1..n]) == nk_combinations n 3 all f [1..15]
expand_set :: Ord a => Int -> [a] -> [[a]] Source #
Set expansion (ie. to multiset of degree n).
expand_set 4 [1,2,3] == [[1,1,2,3],[1,2,2,3],[1,2,3,3]]
partitions :: Eq a => [a] -> [[[a]]] Source #
All distinct multiset partitions, see partitions
.
partitions "aab" == [["aab"],["a","ab"],["b","aa"],["b","a","a"]] partitions "abc" == [["abc"],["bc","a"],["b","ac"],["c","ab"],["c","b","a"]]
cartesian_product :: [a] -> [b] -> [(a, b)] Source #
Cartesian product of two sets.
cartesian_product "abc" [1,2] == [('a',1),('a',2),('b',1),('b',2),('c',1),('c',2)] cartesian_product "abc" "" == []
nfold_cartesian_product :: [[a]] -> [[a]] Source #
List form of n-fold cartesian product.
length (nfold_cartesian_product [[1..13],[1..4]]) == 52 length (nfold_cartesian_product ["abc","de","fgh"]) == 3 * 2 * 3
multiset_cycles :: Ord t => [t] -> [[t]] Source #
Generate all distinct cycles, aka necklaces, with elements taken from a multiset.
concatMap multiset_cycles [replicate i 0 ++ replicate (6 - i) 1 | i <- [0 .. 6]]