Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2023 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
- Data.Hashable reexports
- Data.HashMap.Strict reexports
- Data.HashSet reexports
- Data.IntMap.Strict reexports
- Data.IntSet reexports
- Data.Map.Strict reexports
- Data.Sequence reexports
- Data.Set reexports
- Data.Tuple reexports
- GHC.Exts reexports
Reexports container-related data types, functions and typeclasses from base
,
containers
and unordered-containers
packages.
Synopsis
- class Eq a => Hashable a where
- hashWithSalt :: Int -> a -> Int
- data HashMap k v
- data HashSet a
- data IntMap a
- data IntSet
- data Map k a
- data Seq a
- data Set a
- curry :: ((a, b) -> c) -> a -> b -> c
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- swap :: (a, b) -> (b, a)
- uncurry :: (a -> b -> c) -> (a, b) -> c
- class IsList l where
Data.Hashable reexports
class Eq a => Hashable a where #
The class of types that can be converted to a hash value.
Minimal implementation: hashWithSalt
.
Note: the hash is not guaranteed to be stable across library versions, operating systems or architectures. For stable hashing use named hashes: SHA256, CRC32 etc.
If you are looking for Hashable
instance in time
package,
check time-compat
Nothing
hashWithSalt :: Int -> a -> Int infixl 0 #
Return a hash value for the argument, using the given salt.
The general contract of hashWithSalt
is:
- If two values are equal according to the
==
method, then applying thehashWithSalt
method on each of the two values must produce the same integer result if the same salt is used in each case. - It is not required that if two values are unequal
according to the
==
method, then applying thehashWithSalt
method on each of the two values must produce distinct integer results. However, the programmer should be aware that producing distinct integer results for unequal values may improve the performance of hashing-based data structures. - This method can be used to compute different hash values for
the same input by providing a different salt in each
application of the method. This implies that any instance
that defines
hashWithSalt
must make use of the salt in its implementation. hashWithSalt
may return negativeInt
values.
Instances
Data.HashMap.Strict reexports
A map from keys to values. A map cannot contain duplicate keys; each key can map to at most one value.
Instances
Bifoldable HashMap | Since: unordered-containers-0.2.11 |
Eq2 HashMap | |
Ord2 HashMap | |
Defined in Data.HashMap.Internal | |
Show2 HashMap | |
NFData2 HashMap | Since: unordered-containers-0.2.14.0 |
Defined in Data.HashMap.Internal | |
Hashable2 HashMap | |
Defined in Data.HashMap.Internal | |
(Lift k, Lift v) => Lift (HashMap k v :: Type) | Since: unordered-containers-0.2.17.0 |
Foldable (HashMap k) | |
Defined in Data.HashMap.Internal fold :: Monoid m => HashMap k m -> m # foldMap :: Monoid m => (a -> m) -> HashMap k a -> m # foldMap' :: Monoid m => (a -> m) -> HashMap k a -> m # foldr :: (a -> b -> b) -> b -> HashMap k a -> b # foldr' :: (a -> b -> b) -> b -> HashMap k a -> b # foldl :: (b -> a -> b) -> b -> HashMap k a -> b # foldl' :: (b -> a -> b) -> b -> HashMap k a -> b # foldr1 :: (a -> a -> a) -> HashMap k a -> a # foldl1 :: (a -> a -> a) -> HashMap k a -> a # toList :: HashMap k a -> [a] # length :: HashMap k a -> Int # elem :: Eq a => a -> HashMap k a -> Bool # maximum :: Ord a => HashMap k a -> a # minimum :: Ord a => HashMap k a -> a # | |
Eq k => Eq1 (HashMap k) | |
Ord k => Ord1 (HashMap k) | |
Defined in Data.HashMap.Internal | |
(Eq k, Hashable k, Read k) => Read1 (HashMap k) | |
Defined in Data.HashMap.Internal | |
Show k => Show1 (HashMap k) | |
Traversable (HashMap k) | |
Functor (HashMap k) | |
NFData k => NFData1 (HashMap k) | Since: unordered-containers-0.2.14.0 |
Defined in Data.HashMap.Internal | |
Hashable k => Hashable1 (HashMap k) | |
Defined in Data.HashMap.Internal | |
(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) | |
Defined in Data.HashMap.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashMap k v -> c (HashMap k v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashMap k v) # toConstr :: HashMap k v -> Constr # dataTypeOf :: HashMap k v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashMap k v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashMap k v)) # gmapT :: (forall b. Data b => b -> b) -> HashMap k v -> HashMap k v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashMap k v -> r # gmapQ :: (forall d. Data d => d -> u) -> HashMap k v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashMap k v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashMap k v -> m (HashMap k v) # | |
(Eq k, Hashable k) => Monoid (HashMap k v) | If a key occurs in both maps, the mapping from the first will be the mapping in the result. Examples
|
(Eq k, Hashable k) => Semigroup (HashMap k v) | If a key occurs in both maps, the mapping from the first will be the mapping in the result. Examples
|
(Eq k, Hashable k) => IsList (HashMap k v) | |
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) | |
(Show k, Show v) => Show (HashMap k v) | |
(NFData k, NFData v) => NFData (HashMap k v) | |
Defined in Data.HashMap.Internal | |
(Eq k, Eq v) => Eq (HashMap k v) | Note that, in the presence of hash collisions, equal
In general, the lack of substitutivity can be observed with any function that depends on the key ordering, such as folds and traversals. |
(Ord k, Ord v) => Ord (HashMap k v) | The ordering is total and consistent with the |
Defined in Data.HashMap.Internal | |
(Hashable k, Hashable v) => Hashable (HashMap k v) | |
Defined in Data.HashMap.Internal | |
Hashable k => One (HashMap k v) Source # | Create singleton
law> |
Hashable k => DynamicMap (HashMap k v) Source # | Since: 0.1.0 |
Defined in Relude.Extra.Map insert :: Key (HashMap k v) -> Val (HashMap k v) -> HashMap k v -> HashMap k v Source # insertWith :: (Val (HashMap k v) -> Val (HashMap k v) -> Val (HashMap k v)) -> Key (HashMap k v) -> Val (HashMap k v) -> HashMap k v -> HashMap k v Source # delete :: Key (HashMap k v) -> HashMap k v -> HashMap k v Source # alter :: (Maybe (Val (HashMap k v)) -> Maybe (Val (HashMap k v))) -> Key (HashMap k v) -> HashMap k v -> HashMap k v Source # | |
Hashable k => StaticMap (HashMap k v) Source # | Since: 0.1.0 |
type Item (HashMap k v) | |
Defined in Data.HashMap.Internal | |
type OneItem (HashMap k v) Source # | |
Defined in Relude.Container.One | |
type Key (HashMap k v) Source # | |
Defined in Relude.Extra.Map | |
type Val (HashMap k v) Source # | |
Defined in Relude.Extra.Map |
Data.HashSet reexports
A set of values. A set cannot contain duplicate values.
Instances
Foldable HashSet | |
Defined in Data.HashSet.Internal fold :: Monoid m => HashSet m -> m # foldMap :: Monoid m => (a -> m) -> HashSet a -> m # foldMap' :: Monoid m => (a -> m) -> HashSet a -> m # foldr :: (a -> b -> b) -> b -> HashSet a -> b # foldr' :: (a -> b -> b) -> b -> HashSet a -> b # foldl :: (b -> a -> b) -> b -> HashSet a -> b # foldl' :: (b -> a -> b) -> b -> HashSet a -> b # foldr1 :: (a -> a -> a) -> HashSet a -> a # foldl1 :: (a -> a -> a) -> HashSet a -> a # elem :: Eq a => a -> HashSet a -> Bool # maximum :: Ord a => HashSet a -> a # minimum :: Ord a => HashSet a -> a # | |
Eq1 HashSet | |
Ord1 HashSet | |
Defined in Data.HashSet.Internal | |
Show1 HashSet | |
NFData1 HashSet | Since: unordered-containers-0.2.14.0 |
Defined in Data.HashSet.Internal | |
Hashable1 HashSet | |
Defined in Data.HashSet.Internal | |
Lift a => Lift (HashSet a :: Type) | Since: unordered-containers-0.2.17.0 |
(Data a, Eq a, Hashable a) => Data (HashSet a) | |
Defined in Data.HashSet.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HashSet a -> c (HashSet a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HashSet a) # toConstr :: HashSet a -> Constr # dataTypeOf :: HashSet a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HashSet a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HashSet a)) # gmapT :: (forall b. Data b => b -> b) -> HashSet a -> HashSet a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HashSet a -> r # gmapQ :: (forall d. Data d => d -> u) -> HashSet a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HashSet a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HashSet a -> m (HashSet a) # | |
(Hashable a, Eq a) => Monoid (HashSet a) | \(O(n+m)\) To obtain good performance, the smaller set must be presented as the first argument. Examples
|
(Hashable a, Eq a) => Semigroup (HashSet a) | \(O(n+m)\) To obtain good performance, the smaller set must be presented as the first argument. Examples
|
(Eq a, Hashable a) => IsList (HashSet a) | |
(Eq a, Hashable a, Read a) => Read (HashSet a) | |
Show a => Show (HashSet a) | |
NFData a => NFData (HashSet a) | |
Defined in Data.HashSet.Internal | |
Eq a => Eq (HashSet a) | Note that, in the presence of hash collisions, equal
In general, the lack of substitutivity can be observed with any function that depends on the key ordering, such as folds and traversals. |
Ord a => Ord (HashSet a) | |
Defined in Data.HashSet.Internal | |
Hashable a => Hashable (HashSet a) | |
Defined in Data.HashSet.Internal | |
Hashable a => One (HashSet a) Source # | Create singleton
law> |
Hashable a => StaticMap (HashSet a) Source # | Since: 0.1.0 |
type Item (HashSet a) | |
Defined in Data.HashSet.Internal | |
type OneItem (HashSet a) Source # | |
Defined in Relude.Container.One | |
type Key (HashSet a) Source # | |
Defined in Relude.Extra.Map | |
type Val (HashSet a) Source # | |
Defined in Relude.Extra.Map |
Data.IntMap.Strict reexports
A map of integers to values a
.
Instances
Foldable IntMap | Folds in order of increasing key. |
Defined in Data.IntMap.Internal fold :: Monoid m => IntMap m -> m # foldMap :: Monoid m => (a -> m) -> IntMap a -> m # foldMap' :: Monoid m => (a -> m) -> IntMap a -> m # foldr :: (a -> b -> b) -> b -> IntMap a -> b # foldr' :: (a -> b -> b) -> b -> IntMap a -> b # foldl :: (b -> a -> b) -> b -> IntMap a -> b # foldl' :: (b -> a -> b) -> b -> IntMap a -> b # foldr1 :: (a -> a -> a) -> IntMap a -> a # foldl1 :: (a -> a -> a) -> IntMap a -> a # elem :: Eq a => a -> IntMap a -> Bool # maximum :: Ord a => IntMap a -> a # minimum :: Ord a => IntMap a -> a # | |
Eq1 IntMap | Since: containers-0.5.9 |
Ord1 IntMap | Since: containers-0.5.9 |
Defined in Data.IntMap.Internal | |
Read1 IntMap | Since: containers-0.5.9 |
Defined in Data.IntMap.Internal | |
Show1 IntMap | Since: containers-0.5.9 |
Traversable IntMap | Traverses in order of increasing key. |
Functor IntMap | |
Hashable1 IntMap | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Lift a => Lift (IntMap a :: Type) | Since: containers-0.6.6 |
Data a => Data (IntMap a) | |
Defined in Data.IntMap.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntMap a -> c (IntMap a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IntMap a) # toConstr :: IntMap a -> Constr # dataTypeOf :: IntMap a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IntMap a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IntMap a)) # gmapT :: (forall b. Data b => b -> b) -> IntMap a -> IntMap a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntMap a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntMap a -> r # gmapQ :: (forall d. Data d => d -> u) -> IntMap a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntMap a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMap a -> m (IntMap a) # | |
Monoid (IntMap a) | |
Semigroup (IntMap a) | Since: containers-0.5.7 |
IsList (IntMap a) | Since: containers-0.5.6.2 |
Read e => Read (IntMap e) | |
Show a => Show (IntMap a) | |
NFData a => NFData (IntMap a) | |
Defined in Data.IntMap.Internal | |
Eq a => Eq (IntMap a) | |
Ord a => Ord (IntMap a) | |
Defined in Data.IntMap.Internal | |
Hashable v => Hashable (IntMap v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
One (IntMap v) Source # | Create singleton
law> |
DynamicMap (IntMap v) Source # | Since: 0.1.0 |
Defined in Relude.Extra.Map insert :: Key (IntMap v) -> Val (IntMap v) -> IntMap v -> IntMap v Source # insertWith :: (Val (IntMap v) -> Val (IntMap v) -> Val (IntMap v)) -> Key (IntMap v) -> Val (IntMap v) -> IntMap v -> IntMap v Source # delete :: Key (IntMap v) -> IntMap v -> IntMap v Source # alter :: (Maybe (Val (IntMap v)) -> Maybe (Val (IntMap v))) -> Key (IntMap v) -> IntMap v -> IntMap v Source # | |
StaticMap (IntMap v) Source # | Since: 0.1.0 |
type Item (IntMap a) | |
Defined in Data.IntMap.Internal | |
type OneItem (IntMap v) Source # | |
Defined in Relude.Container.One | |
type Key (IntMap v) Source # | |
Defined in Relude.Extra.Map | |
type Val (IntMap v) Source # | |
Defined in Relude.Extra.Map |
Data.IntSet reexports
A set of integers.
Instances
Data IntSet | |
Defined in Data.IntSet.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntSet -> c IntSet # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntSet # toConstr :: IntSet -> Constr # dataTypeOf :: IntSet -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntSet) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntSet) # gmapT :: (forall b. Data b => b -> b) -> IntSet -> IntSet # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntSet -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntSet -> r # gmapQ :: (forall d. Data d => d -> u) -> IntSet -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntSet -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # | |
Monoid IntSet | |
Semigroup IntSet | Since: containers-0.5.7 |
IsList IntSet | Since: containers-0.5.6.2 |
Read IntSet | |
Show IntSet | |
NFData IntSet | |
Defined in Data.IntSet.Internal | |
Eq IntSet | |
Ord IntSet | |
Hashable IntSet | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
One IntSet Source # | Create singleton
law> |
StaticMap IntSet Source # | Since: 0.1.0 |
Lift IntSet | Since: containers-0.6.6 |
type Item IntSet | |
Defined in Data.IntSet.Internal | |
type OneItem IntSet Source # | |
Defined in Relude.Container.One | |
type Key IntSet Source # | |
Defined in Relude.Extra.Map | |
type Val IntSet Source # | |
Defined in Relude.Extra.Map |
Data.Map.Strict reexports
A Map from keys k
to values a
.
The Semigroup
operation for Map
is union
, which prefers
values from the left operand. If m1
maps a key k
to a value
a1
, and m2
maps the same key to a different value a2
, then
their union m1 <> m2
maps k
to a1
.
Instances
Bifoldable Map | Since: containers-0.6.3.1 |
Eq2 Map | Since: containers-0.5.9 |
Ord2 Map | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show2 Map | Since: containers-0.5.9 |
Hashable2 Map | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(Lift k, Lift a) => Lift (Map k a :: Type) | Since: containers-0.6.6 |
Foldable (Map k) | Folds in order of increasing key. |
Defined in Data.Map.Internal fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> m # foldMap' :: Monoid m => (a -> m) -> Map k a -> m # foldr :: (a -> b -> b) -> b -> Map k a -> b # foldr' :: (a -> b -> b) -> b -> Map k a -> b # foldl :: (b -> a -> b) -> b -> Map k a -> b # foldl' :: (b -> a -> b) -> b -> Map k a -> b # foldr1 :: (a -> a -> a) -> Map k a -> a # foldl1 :: (a -> a -> a) -> Map k a -> a # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |
Eq k => Eq1 (Map k) | Since: containers-0.5.9 |
Ord k => Ord1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
(Ord k, Read k) => Read1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show k => Show1 (Map k) | Since: containers-0.5.9 |
Traversable (Map k) | Traverses in order of increasing key. |
Functor (Map k) | |
Hashable k => Hashable1 (Map k) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(Data k, Data a, Ord k) => Data (Map k a) | |
Defined in Data.Map.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) # toConstr :: Map k a -> Constr # dataTypeOf :: Map k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) # gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # | |
Ord k => Monoid (Map k v) | |
Ord k => Semigroup (Map k v) | |
Ord k => IsList (Map k v) | Since: containers-0.5.6.2 |
(Ord k, Read k, Read e) => Read (Map k e) | |
(Show k, Show a) => Show (Map k a) | |
(NFData k, NFData a) => NFData (Map k a) | |
Defined in Data.Map.Internal | |
(Eq k, Eq a) => Eq (Map k a) | |
(Ord k, Ord v) => Ord (Map k v) | |
(Hashable k, Hashable v) => Hashable (Map k v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
One (Map k v) Source # | Create singleton
law> |
Ord k => DynamicMap (Map k v) Source # | Since: 0.1.0 |
Defined in Relude.Extra.Map insert :: Key (Map k v) -> Val (Map k v) -> Map k v -> Map k v Source # insertWith :: (Val (Map k v) -> Val (Map k v) -> Val (Map k v)) -> Key (Map k v) -> Val (Map k v) -> Map k v -> Map k v Source # delete :: Key (Map k v) -> Map k v -> Map k v Source # alter :: (Maybe (Val (Map k v)) -> Maybe (Val (Map k v))) -> Key (Map k v) -> Map k v -> Map k v Source # | |
Ord k => StaticMap (Map k v) Source # | Since: 0.1.0 |
type Item (Map k v) | |
Defined in Data.Map.Internal | |
type OneItem (Map k v) Source # | |
Defined in Relude.Container.One | |
type Key (Map k v) Source # | |
Defined in Relude.Extra.Map | |
type Val (Map k v) Source # | |
Defined in Relude.Extra.Map |
Data.Sequence reexports
General-purpose finite sequences.
Instances
MonadFix Seq | Since: containers-0.5.11 |
Defined in Data.Sequence.Internal | |
MonadZip Seq |
|
Foldable Seq | |
Defined in Data.Sequence.Internal fold :: Monoid m => Seq m -> m # foldMap :: Monoid m => (a -> m) -> Seq a -> m # foldMap' :: Monoid m => (a -> m) -> Seq a -> m # foldr :: (a -> b -> b) -> b -> Seq a -> b # foldr' :: (a -> b -> b) -> b -> Seq a -> b # foldl :: (b -> a -> b) -> b -> Seq a -> b # foldl' :: (b -> a -> b) -> b -> Seq a -> b # foldr1 :: (a -> a -> a) -> Seq a -> a # foldl1 :: (a -> a -> a) -> Seq a -> a # elem :: Eq a => a -> Seq a -> Bool # maximum :: Ord a => Seq a -> a # | |
Eq1 Seq | Since: containers-0.5.9 |
Ord1 Seq | Since: containers-0.5.9 |
Defined in Data.Sequence.Internal | |
Read1 Seq | Since: containers-0.5.9 |
Defined in Data.Sequence.Internal | |
Show1 Seq | Since: containers-0.5.9 |
Traversable Seq | |
Alternative Seq | Since: containers-0.5.4 |
Applicative Seq | Since: containers-0.5.4 |
Functor Seq | |
Monad Seq | |
MonadPlus Seq | |
UnzipWith Seq | |
Defined in Data.Sequence.Internal unzipWith' :: (x -> (a, b)) -> Seq x -> (Seq a, Seq b) | |
Hashable1 Seq | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Lift a => Lift (Seq a :: Type) | Since: containers-0.6.6 |
Data a => Data (Seq a) | |
Defined in Data.Sequence.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) # dataTypeOf :: Seq a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) # gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal fromString :: String -> Seq a # | |
Monoid (Seq a) | |
Semigroup (Seq a) | Since: containers-0.5.7 |
IsList (Seq a) | |
Read a => Read (Seq a) | |
Show a => Show (Seq a) | |
NFData a => NFData (Seq a) | |
Defined in Data.Sequence.Internal | |
Eq a => Eq (Seq a) | |
Ord a => Ord (Seq a) | |
Hashable v => Hashable (Seq v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
One (Seq a) Source # | Create singleton
law> |
type Item (Seq a) | |
Defined in Data.Sequence.Internal | |
type OneItem (Seq a) Source # | |
Defined in Relude.Container.One |
Data.Set reexports
A set of values a
.
Instances
Foldable Set | Folds in order of increasing key. |
Defined in Data.Set.Internal fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
Eq1 Set | Since: containers-0.5.9 |
Ord1 Set | Since: containers-0.5.9 |
Defined in Data.Set.Internal | |
Show1 Set | Since: containers-0.5.9 |
Hashable1 Set | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Lift a => Lift (Set a :: Type) | Since: containers-0.6.6 |
(Data a, Ord a) => Data (Set a) | |
Defined in Data.Set.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) # dataTypeOf :: Set a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) # gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # | |
Ord a => Monoid (Set a) | |
Ord a => Semigroup (Set a) | Since: containers-0.5.7 |
Ord a => IsList (Set a) | Since: containers-0.5.6.2 |
(Read a, Ord a) => Read (Set a) | |
Show a => Show (Set a) | |
NFData a => NFData (Set a) | |
Defined in Data.Set.Internal | |
Eq a => Eq (Set a) | |
Ord a => Ord (Set a) | |
Hashable v => Hashable (Set v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
One (Set a) Source # | Create singleton
law> |
Ord a => StaticMap (Set a) Source # | Since: 0.1.0 |
type Item (Set a) | |
Defined in Data.Set.Internal | |
type OneItem (Set a) Source # | |
Defined in Relude.Container.One | |
type Key (Set a) Source # | |
Defined in Relude.Extra.Map | |
type Val (Set a) Source # | |
Defined in Relude.Extra.Map |
Data.Tuple reexports
uncurry :: (a -> b -> c) -> (a, b) -> c #
uncurry
converts a curried function to a function on pairs.
Examples
>>>
uncurry (+) (1,2)
3
>>>
uncurry ($) (show, 1)
"1"
>>>
map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]
GHC.Exts reexports
The IsList
class and its methods are intended to be used in
conjunction with the OverloadedLists extension.
Since: base-4.7.0.0
The fromList
function constructs the structure l
from the given
list of Item l