Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data SetOf (n :: Nat) a
- toSet :: SetOf n a -> Set a
- fromFoldable :: forall (n :: Nat) f a. (KnownNat n, Ord a, Foldable f) => f a -> Maybe (SetOf n a)
- fromFoldable' :: forall f a (n :: Nat). (KnownNat n, Ord a, Foldable f) => Proxy n -> f a -> Maybe (SetOf n a)
- toList :: Ord a => SetOf n a -> [a]
- elems :: Ord a => SetOf n a -> [a]
- class SetToTuple (n :: Nat) a where
- member :: Ord a => a -> SetOf n a -> Bool
- notMember :: Ord a => a -> SetOf n a -> Bool
- fst :: Ord a => SetOf 2 a -> a
- snd :: Ord a => SetOf 2 a -> a
- lookupMax :: Ord a => SetOf 2 a -> a
- lookupMin :: Ord a => SetOf 2 a -> a
- map :: forall n a b. (KnownNat n, Ord b) => (a -> b) -> SetOf n a -> Maybe (SetOf n b)
- mapMonotonic :: (a -> b) -> SetOf n a -> SetOf n b
- fold :: (a -> b -> b) -> b -> SetOf n a -> b
- foldl' :: (a -> b -> a) -> a -> SetOf n b -> a
- foldr' :: (a -> b -> b) -> b -> SetOf n a -> b
- class KnownNat (n :: Nat)
- data Nat
- natVal :: KnownNat n => proxy n -> Integer
- empty :: SetOf 0 a
- singleton :: a -> SetOf 1 a
- doubleton :: Ord a => a -> a -> Maybe (SetOf 2 a)
- tripleton :: Ord a => a -> a -> a -> Maybe (SetOf 3 a)
- uncheckedmkSetOf :: Foldable f => f a -> SetOf n a
Documentation
data SetOf (n :: Nat) a Source #
A set of values a
with a size of n
Instances
(Ord a, KnownNat n) => IsList (Maybe (SetOf n a)) Source # | |
Foldable (SetOf n) Source # | |
Defined in Data.Set.Of fold :: Monoid m => SetOf n m -> m # foldMap :: Monoid m => (a -> m) -> SetOf n a -> m # foldr :: (a -> b -> b) -> b -> SetOf n a -> b # foldr' :: (a -> b -> b) -> b -> SetOf n a -> b # foldl :: (b -> a -> b) -> b -> SetOf n a -> b # foldl' :: (b -> a -> b) -> b -> SetOf n a -> b # foldr1 :: (a -> a -> a) -> SetOf n a -> a # foldl1 :: (a -> a -> a) -> SetOf n a -> a # elem :: Eq a => a -> SetOf n a -> Bool # maximum :: Ord a => SetOf n a -> a # minimum :: Ord a => SetOf n a -> a # | |
Eq a => Eq (SetOf n a) Source # | |
(KnownNat n, Data a, Ord a) => Data (SetOf n a) Source # | |
Defined in Data.Set.Of gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetOf n a -> c (SetOf n a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SetOf n a) # toConstr :: SetOf n a -> Constr # dataTypeOf :: SetOf n a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SetOf n a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SetOf n a)) # gmapT :: (forall b. Data b => b -> b) -> SetOf n a -> SetOf n a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetOf n a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetOf n a -> r # gmapQ :: (forall d. Data d => d -> u) -> SetOf n a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SetOf n a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetOf n a -> m (SetOf n a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetOf n a -> m (SetOf n a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetOf n a -> m (SetOf n a) # | |
Ord a => Ord (SetOf n a) Source # | |
Defined in Data.Set.Of | |
Show a => Show (SetOf n a) Source # | |
Generic (SetOf n a) Source # | |
type Item (Maybe (SetOf n a)) Source # | |
Defined in Data.Set.Of | |
type Rep (SetOf n a) Source # | |
Defined in Data.Set.Of |
fromFoldable :: forall (n :: Nat) f a. (KnownNat n, Ord a, Foldable f) => f a -> Maybe (SetOf n a) Source #
fromFoldable' :: forall f a (n :: Nat). (KnownNat n, Ord a, Foldable f) => Proxy n -> f a -> Maybe (SetOf n a) Source #
O(n*log n). Create a set from a list of elements.
toList :: Ord a => SetOf n a -> [a] Source #
O(n). Convert the set to a list of elements. Subject to list fusion.
elems :: Ord a => SetOf n a -> [a] Source #
O(n). Convert the set to a list of elements. Subject to list fusion.
class SetToTuple (n :: Nat) a where Source #
Type class to provide type safe, polymorphic mappings to and from tuples
fromTuple :: Ord a => TupOf n a -> Maybe (SetOf n a) Source #
Take a tuple, and potentially produce a Set of a the given size.
Nothing
is produced when the input tuple contains duplicate elements.
toTuple :: Ord a => SetOf n a -> TupOf n a Source #
Produce a tuple, where the elements a
are ordered left to right descending.
Instances
SetToTuple 0 a Source # | |
SetToTuple 1 a Source # | |
SetToTuple 2 a Source # | |
SetToTuple 3 a Source # | |
SetToTuple 4 a Source # | |
SetToTuple 5 a Source # | |
SetToTuple 6 a Source # | |
SetToTuple 7 a Source # | |
map :: forall n a b. (KnownNat n, Ord b) => (a -> b) -> SetOf n a -> Maybe (SetOf n b) Source #
O(n*log n).
is the set obtained by applying map
f sf
to each element of s
.
It's worth noting that the size of the result may be smaller if,
for some (x,y)
, x /= y && f x == f y
If the size changed, you will get Nothing
.
mapMonotonic :: (a -> b) -> SetOf n a -> SetOf n b Source #
O(n). The
, but works only when mapMonotonic
f s == map
f sf
is strictly increasing.
The precondition is not checked.
Semi-formally, we have:
and [x < y ==> f x < f y | x <- ls, y <- ls] ==> mapMonotonic f s == map f s where ls = toList s
fold :: (a -> b -> b) -> b -> SetOf n a -> b Source #
O(n). Fold the elements in the set using the given right-associative
binary operator. This function is an equivalent of foldr
and is present
for compatibility only.
Please note that fold will be deprecated in the future and removed.
foldr' :: (a -> b -> b) -> b -> SetOf n a -> b Source #
O(n). A strict version of foldr
. Each application of the operator is
evaluated before using the result in the next application. This
function is strict in the starting value.
This class gives the integer associated with a type-level natural. There are instances of the class for every concrete literal: 0, 1, 2, etc.
Since: base-4.7.0.0
natSing
uncheckedmkSetOf :: Foldable f => f a -> SetOf n a Source #