set-of-0.1.0.2: Sets of fixed size, with typelits

Safe HaskellNone
LanguageHaskell2010

Data.Set.Of

Synopsis

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 # 
Instance details

Defined in Data.Set.Of

Associated Types

type Item (Maybe (SetOf n a)) :: Type #

Methods

fromList :: [Item (Maybe (SetOf n a))] -> Maybe (SetOf n a) #

fromListN :: Int -> [Item (Maybe (SetOf n a))] -> Maybe (SetOf n a) #

toList :: Maybe (SetOf n a) -> [Item (Maybe (SetOf n a))] #

Foldable (SetOf n) Source # 
Instance details

Defined in Data.Set.Of

Methods

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 #

toList :: SetOf n a -> [a] #

null :: SetOf n a -> Bool #

length :: SetOf n a -> Int #

elem :: Eq a => a -> SetOf n a -> Bool #

maximum :: Ord a => SetOf n a -> a #

minimum :: Ord a => SetOf n a -> a #

sum :: Num a => SetOf n a -> a #

product :: Num a => SetOf n a -> a #

Eq a => Eq (SetOf n a) Source # 
Instance details

Defined in Data.Set.Of

Methods

(==) :: SetOf n a -> SetOf n a -> Bool #

(/=) :: SetOf n a -> SetOf n a -> Bool #

(KnownNat n, Data a, Ord a) => Data (SetOf n a) Source # 
Instance details

Defined in Data.Set.Of

Methods

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 # 
Instance details

Defined in Data.Set.Of

Methods

compare :: SetOf n a -> SetOf n a -> Ordering #

(<) :: SetOf n a -> SetOf n a -> Bool #

(<=) :: SetOf n a -> SetOf n a -> Bool #

(>) :: SetOf n a -> SetOf n a -> Bool #

(>=) :: SetOf n a -> SetOf n a -> Bool #

max :: SetOf n a -> SetOf n a -> SetOf n a #

min :: SetOf n a -> SetOf n a -> SetOf n a #

Show a => Show (SetOf n a) Source # 
Instance details

Defined in Data.Set.Of

Methods

showsPrec :: Int -> SetOf n a -> ShowS #

show :: SetOf n a -> String #

showList :: [SetOf n a] -> ShowS #

Generic (SetOf n a) Source # 
Instance details

Defined in Data.Set.Of

Associated Types

type Rep (SetOf n a) :: Type -> Type #

Methods

from :: SetOf n a -> Rep (SetOf n a) x #

to :: Rep (SetOf n a) x -> SetOf n a #

type Item (Maybe (SetOf n a)) Source # 
Instance details

Defined in Data.Set.Of

type Item (Maybe (SetOf n a)) = a
type Rep (SetOf n a) Source # 
Instance details

Defined in Data.Set.Of

type Rep (SetOf n a) = D1 (MetaData "SetOf" "Data.Set.Of" "set-of-0.1.0.2-KdN9KyOPeD7DyQefC44Gza" True) (C1 (MetaCons "SetOf" PrefixI True) (S1 (MetaSel (Just "toSet") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Set a))))

toSet :: SetOf n a -> Set a Source #

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

Associated Types

type TupOf n a :: Type Source #

The corrosponding tuple, as a family

Methods

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 # 
Instance details

Defined in Data.Set.Of

Associated Types

type TupOf 0 a :: Type Source #

Methods

fromTuple :: TupOf 0 a -> Maybe (SetOf 0 a) Source #

toTuple :: SetOf 0 a -> TupOf 0 a Source #

SetToTuple 1 a Source # 
Instance details

Defined in Data.Set.Of

Associated Types

type TupOf 1 a :: Type Source #

Methods

fromTuple :: TupOf 1 a -> Maybe (SetOf 1 a) Source #

toTuple :: SetOf 1 a -> TupOf 1 a Source #

SetToTuple 2 a Source # 
Instance details

Defined in Data.Set.Of

Associated Types

type TupOf 2 a :: Type Source #

Methods

fromTuple :: TupOf 2 a -> Maybe (SetOf 2 a) Source #

toTuple :: SetOf 2 a -> TupOf 2 a Source #

SetToTuple 3 a Source # 
Instance details

Defined in Data.Set.Of

Associated Types

type TupOf 3 a :: Type Source #

Methods

fromTuple :: TupOf 3 a -> Maybe (SetOf 3 a) Source #

toTuple :: SetOf 3 a -> TupOf 3 a Source #

SetToTuple 4 a Source # 
Instance details

Defined in Data.Set.Of

Associated Types

type TupOf 4 a :: Type Source #

Methods

fromTuple :: TupOf 4 a -> Maybe (SetOf 4 a) Source #

toTuple :: SetOf 4 a -> TupOf 4 a Source #

SetToTuple 5 a Source # 
Instance details

Defined in Data.Set.Of

Associated Types

type TupOf 5 a :: Type Source #

Methods

fromTuple :: TupOf 5 a -> Maybe (SetOf 5 a) Source #

toTuple :: SetOf 5 a -> TupOf 5 a Source #

SetToTuple 6 a Source # 
Instance details

Defined in Data.Set.Of

Associated Types

type TupOf 6 a :: Type Source #

Methods

fromTuple :: TupOf 6 a -> Maybe (SetOf 6 a) Source #

toTuple :: SetOf 6 a -> TupOf 6 a Source #

SetToTuple 7 a Source # 
Instance details

Defined in Data.Set.Of

Associated Types

type TupOf 7 a :: Type Source #

Methods

fromTuple :: TupOf 7 a -> Maybe (SetOf 7 a) Source #

toTuple :: SetOf 7 a -> TupOf 7 a Source #

member :: Ord a => a -> SetOf n a -> Bool Source #

O(log n). Is the element in the set?

notMember :: Ord a => a -> SetOf n a -> Bool Source #

O(log n). Is the element not in the set?

fst :: Ord a => SetOf 2 a -> a Source #

O(log n). The maximal element of a set.

snd :: Ord a => SetOf 2 a -> a Source #

O(log n). The minimal element of a set.

findMin :: SetOf (n + 1) a -> a Source #

Now typesafe!

findMax :: SetOf (n + 1) a -> a Source #

Now typesafe!

map :: forall n a b. (KnownNat n, Ord b) => (a -> b) -> SetOf n a -> Maybe (SetOf n b) Source #

O(n*log n). map f s is the set obtained by applying f 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

mapMonotonic f s == map f s, but works only when f 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.

foldl' :: (a -> b -> a) -> a -> SetOf n b -> a Source #

O(n). A strict version of foldl. Each application of the operator is evaluated before using the result in the next application. This function is strict in the starting value.Paste

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.

class KnownNat (n :: Nat) #

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

Minimal complete definition

natSing

data Nat #

(Kind) This is the kind of type-level natural numbers.

type family (a :: Nat) + (b :: Nat) :: Nat where ... infixl 6 #

Addition of type-level naturals.

Since: base-4.7.0.0

someNatVal :: Integer -> Maybe SomeNat #

Convert an integer into an unknown type-level natural.

Since: base-4.7.0.0

natVal :: KnownNat n => proxy n -> Integer #

Since: base-4.7.0.0

data SomeNat where #

This type represents unknown type-level natural numbers.

Since: base-4.10.0.0

Constructors

SomeNat :: forall (n :: Nat). KnownNat n => Proxy n -> SomeNat 
Instances
Eq SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Methods

(==) :: SomeNat -> SomeNat -> Bool #

(/=) :: SomeNat -> SomeNat -> Bool #

Ord SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Read SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Show SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

empty :: SetOf 0 a Source #

The empty set

singleton :: a -> SetOf 1 a Source #

O(1). Create a singleton set.

doubleton :: Ord a => a -> a -> Maybe (SetOf 2 a) Source #

tripleton :: Ord a => a -> a -> a -> Maybe (SetOf 3 a) Source #

data SomeSetOf a Source #

Constructors

SomeSetOf (SetOf n a) 
Instances
Eq a => Eq (SomeSetOf a) Source # 
Instance details

Defined in Data.Set.Of

Methods

(==) :: SomeSetOf a -> SomeSetOf a -> Bool #

(/=) :: SomeSetOf a -> SomeSetOf a -> Bool #

Ord a => Ord (SomeSetOf a) Source # 
Instance details

Defined in Data.Set.Of

Show a => Show (SomeSetOf a) Source # 
Instance details

Defined in Data.Set.Of

union :: Ord a => SetOf n a -> SetOf n' a -> SomeSetOf a Source #

withSomeSetOf :: forall a r. (forall n. Proxy n -> SetOf n a -> r) -> SomeSetOf a -> Maybe r Source #