Use Foldable's all and any instead of allSet and anySet
[rootstock.git] / Util / Set.hs
bloba4aa6f2d707f144d30ac525a79dc82c5265fa2b4
1 module Util.Set where
2 import qualified Data.List as List
3 import Data.Maybe (fromJust)
4 import Data.Set (Set)
5 import qualified Data.Set as Set
6 import Data.Tuple (swap)
8 subsetsOfSize :: Ord a => Integer -> Set a -> Set (Set a)
9 subsetsOfSize n xs = case compare n 0 of
10 LT -> Set.empty
11 EQ -> Set.singleton Set.empty
12 GT -> case Set.minView xs of
13 Nothing -> Set.empty
14 Just (x, xs') -> Set.union
15 (subsetsOfSize n xs') $
16 Set.map (Set.insert x) $ subsetsOfSize (n - 1) xs'
18 distinctPairsOneWay :: Ord a => Set a -> Set (a, a)
19 distinctPairsOneWay =
20 Set.map (\xys -> let [x, y] = Set.toList xys in (x, y)) . subsetsOfSize 2
22 distinctPairs :: Ord a => Set a -> Set (a, a)
23 distinctPairs xs =
24 let dpow = distinctPairsOneWay xs in
25 Set.union dpow $ Set.map swap dpow
27 distinctTriplesOneWay :: Ord a => Set a -> Set (a, a, a)
28 distinctTriplesOneWay =
29 Set.map (\xyzs -> let [x, y, z] = Set.toList xyzs in (x, y, z))
30 . subsetsOfSize 3