universum-1.7.2: Custom prelude used in Serokell
Safe HaskellSafe
LanguageHaskell2010

Universum.Container

Description

This module exports all container-related stuff.

Synopsis

Documentation

class One x where Source #

Type class for types that can be created from one element. singleton is lone name for this function. Also constructions of different type differ: :[] for lists, two arguments for Maps. Also some data types are monomorphic.

>>> one True :: [Bool]
[True]
>>> one 'a' :: Text
"a"
>>> one (3, "hello") :: HashMap Int String
fromList [(3,"hello")]

Associated Types

type OneItem x Source #

Methods

one :: OneItem x -> x Source #

Create a list, map, Text, etc from a single element.

Instances

Instances details
One ByteString Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem ByteString Source #

One ByteString Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem ByteString Source #

One IntSet Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem IntSet Source #

One Text Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem Text Source #

Methods

one :: OneItem Text -> Text Source #

One Text Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem Text Source #

Methods

one :: OneItem Text -> Text Source #

One [a] Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem [a] Source #

Methods

one :: OneItem [a] -> [a] Source #

One (NonEmpty a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (NonEmpty a) Source #

Methods

one :: OneItem (NonEmpty a) -> NonEmpty a Source #

One (IntMap v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (IntMap v) Source #

Methods

one :: OneItem (IntMap v) -> IntMap v Source #

One (Seq a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Seq a) Source #

Methods

one :: OneItem (Seq a) -> Seq a Source #

One (Set v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Set v) Source #

Methods

one :: OneItem (Set v) -> Set v Source #

Hashable v => One (HashSet v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (HashSet v) Source #

Methods

one :: OneItem (HashSet v) -> HashSet v Source #

Unbox a => One (Vector a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Vector a) Source #

Methods

one :: OneItem (Vector a) -> Vector a Source #

Storable a => One (Vector a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Vector a) Source #

Methods

one :: OneItem (Vector a) -> Vector a Source #

Prim a => One (Vector a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Vector a) Source #

Methods

one :: OneItem (Vector a) -> Vector a Source #

One (Vector a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Vector a) Source #

Methods

one :: OneItem (Vector a) -> Vector a Source #

One (Map k v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Map k v) Source #

Methods

one :: OneItem (Map k v) -> Map k v Source #

Hashable k => One (HashMap k v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (HashMap k v) Source #

Methods

one :: OneItem (HashMap k v) -> HashMap k v Source #

class Container t where Source #

Very similar to Foldable but also allows instances for monomorphic types like Text but forbids instances for Maybe and similar. This class is used as a replacement for Foldable type class. It solves the following problems:

  1. length, foldr and other functions work on more types for which it makes sense.
  2. You can't accidentally use length on polymorphic Foldable (like list), replace list with Maybe and then debug error for two days.
  3. More efficient implementaions of functions for polymorphic types (like elem for Set).

The drawbacks:

  1. Type signatures of polymorphic functions look more scary.
  2. Orphan instances are involved if you want to use foldr (and similar) on types from libraries.

Minimal complete definition

Nothing

Associated Types

type Element t :: Type Source #

Type of element for some container. Implemented as an asscociated type family because some containers are monomorphic over element type (like Text, IntSet, etc.) so we can't implement nice interface using old higher-kinded types approach. Implementing this as an associated type family instead of top-level family gives you more control over element types.

type Element t = ElementDefault t

Methods

toList :: t -> [Element t] Source #

Convert container to list of elements.

>>> toList @Text "aba"
"aba"
>>> :t toList @Text "aba"
toList @Text "aba" :: [Char]

default toList :: (Foldable f, t ~ f a, Element t ~ a) => t -> [Element t] Source #

null :: t -> Bool Source #

Checks whether container is empty.

>>> null @Text ""
True
>>> null @Text "aba"
False

default null :: (Foldable f, t ~ f a) => t -> Bool Source #

foldr :: (Element t -> b -> b) -> b -> t -> b Source #

default foldr :: (Foldable f, t ~ f a, Element t ~ a) => (Element t -> b -> b) -> b -> t -> b Source #

foldl :: (b -> Element t -> b) -> b -> t -> b Source #

default foldl :: (Foldable f, t ~ f a, Element t ~ a) => (b -> Element t -> b) -> b -> t -> b Source #

foldl' :: (b -> Element t -> b) -> b -> t -> b Source #

default foldl' :: (Foldable f, t ~ f a, Element t ~ a) => (b -> Element t -> b) -> b -> t -> b Source #

length :: t -> Int Source #

default length :: (Foldable f, t ~ f a) => t -> Int Source #

elem :: Eq (Element t) => Element t -> t -> Bool Source #

default elem :: (Foldable f, t ~ f a, Element t ~ a, Eq a) => Element t -> t -> Bool Source #

foldMap :: Monoid m => (Element t -> m) -> t -> m Source #

fold :: Monoid (Element t) => t -> Element t Source #

foldr' :: (Element t -> b -> b) -> b -> t -> b Source #

notElem :: Eq (Element t) => Element t -> t -> Bool Source #

all :: (Element t -> Bool) -> t -> Bool Source #

any :: (Element t -> Bool) -> t -> Bool Source #

and :: Element t ~ Bool => t -> Bool Source #

or :: Element t ~ Bool => t -> Bool Source #

find :: (Element t -> Bool) -> t -> Maybe (Element t) Source #

safeHead :: t -> Maybe (Element t) Source #

safeMaximum :: Ord (Element t) => t -> Maybe (Element t) Source #

default safeMaximum :: (Foldable f, t ~ f a, Element t ~ a, Ord (Element t)) => t -> Maybe (Element t) Source #

safeMinimum :: Ord (Element t) => t -> Maybe (Element t) Source #

default safeMinimum :: (Foldable f, t ~ f a, Element t ~ a, Ord (Element t)) => t -> Maybe (Element t) Source #

safeFoldr1 :: (Element t -> Element t -> Element t) -> t -> Maybe (Element t) Source #

safeFoldl1 :: (Element t -> Element t -> Element t) -> t -> Maybe (Element t) Source #

Instances

Instances details
Container ByteString Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element ByteString Source #

Container ByteString Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element ByteString Source #

Container IntSet Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element IntSet Source #

Container Text Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element Text Source #

Container Text Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element Text Source #

Container [a] Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element [a] Source #

Methods

toList :: [a] -> [Element [a]] Source #

null :: [a] -> Bool Source #

foldr :: (Element [a] -> b -> b) -> b -> [a] -> b Source #

foldl :: (b -> Element [a] -> b) -> b -> [a] -> b Source #

foldl' :: (b -> Element [a] -> b) -> b -> [a] -> b Source #

length :: [a] -> Int Source #

elem :: Element [a] -> [a] -> Bool Source #

foldMap :: Monoid m => (Element [a] -> m) -> [a] -> m Source #

fold :: [a] -> Element [a] Source #

foldr' :: (Element [a] -> b -> b) -> b -> [a] -> b Source #

notElem :: Element [a] -> [a] -> Bool Source #

all :: (Element [a] -> Bool) -> [a] -> Bool Source #

any :: (Element [a] -> Bool) -> [a] -> Bool Source #

and :: [a] -> Bool Source #

or :: [a] -> Bool Source #

find :: (Element [a] -> Bool) -> [a] -> Maybe (Element [a]) Source #

safeHead :: [a] -> Maybe (Element [a]) Source #

safeMaximum :: [a] -> Maybe (Element [a]) Source #

safeMinimum :: [a] -> Maybe (Element [a]) Source #

safeFoldr1 :: (Element [a] -> Element [a] -> Element [a]) -> [a] -> Maybe (Element [a]) Source #

safeFoldl1 :: (Element [a] -> Element [a] -> Element [a]) -> [a] -> Maybe (Element [a]) Source #

(TypeError (DisallowInstance "Maybe") :: Constraint) => Container (Maybe a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Maybe a) Source #

Methods

toList :: Maybe a -> [Element (Maybe a)] Source #

null :: Maybe a -> Bool Source #

foldr :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b Source #

foldl :: (b -> Element (Maybe a) -> b) -> b -> Maybe a -> b Source #

foldl' :: (b -> Element (Maybe a) -> b) -> b -> Maybe a -> b Source #

length :: Maybe a -> Int Source #

elem :: Element (Maybe a) -> Maybe a -> Bool Source #

foldMap :: Monoid m => (Element (Maybe a) -> m) -> Maybe a -> m Source #

fold :: Maybe a -> Element (Maybe a) Source #

foldr' :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b Source #

notElem :: Element (Maybe a) -> Maybe a -> Bool Source #

all :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool Source #

any :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool Source #

and :: Maybe a -> Bool Source #

or :: Maybe a -> Bool Source #

find :: (Element (Maybe a) -> Bool) -> Maybe a -> Maybe (Element (Maybe a)) Source #

safeHead :: Maybe a -> Maybe (Element (Maybe a)) Source #

safeMaximum :: Maybe a -> Maybe (Element (Maybe a)) Source #

safeMinimum :: Maybe a -> Maybe (Element (Maybe a)) Source #

safeFoldr1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Maybe (Element (Maybe a)) Source #

safeFoldl1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Maybe (Element (Maybe a)) Source #

Container (ZipList a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (ZipList a) Source #

Methods

toList :: ZipList a -> [Element (ZipList a)] Source #

null :: ZipList a -> Bool Source #

foldr :: (Element (ZipList a) -> b -> b) -> b -> ZipList a -> b Source #

foldl :: (b -> Element (ZipList a) -> b) -> b -> ZipList a -> b Source #

foldl' :: (b -> Element (ZipList a) -> b) -> b -> ZipList a -> b Source #

length :: ZipList a -> Int Source #

elem :: Element (ZipList a) -> ZipList a -> Bool Source #

foldMap :: Monoid m => (Element (ZipList a) -> m) -> ZipList a -> m Source #

fold :: ZipList a -> Element (ZipList a) Source #

foldr' :: (Element (ZipList a) -> b -> b) -> b -> ZipList a -> b Source #

notElem :: Element (ZipList a) -> ZipList a -> Bool Source #

all :: (Element (ZipList a) -> Bool) -> ZipList a -> Bool Source #

any :: (Element (ZipList a) -> Bool) -> ZipList a -> Bool Source #

and :: ZipList a -> Bool Source #

or :: ZipList a -> Bool Source #

find :: (Element (ZipList a) -> Bool) -> ZipList a -> Maybe (Element (ZipList a)) Source #

safeHead :: ZipList a -> Maybe (Element (ZipList a)) Source #

safeMaximum :: ZipList a -> Maybe (Element (ZipList a)) Source #

safeMinimum :: ZipList a -> Maybe (Element (ZipList a)) Source #

safeFoldr1 :: (Element (ZipList a) -> Element (ZipList a) -> Element (ZipList a)) -> ZipList a -> Maybe (Element (ZipList a)) Source #

safeFoldl1 :: (Element (ZipList a) -> Element (ZipList a) -> Element (ZipList a)) -> ZipList a -> Maybe (Element (ZipList a)) Source #

(TypeError (DisallowInstance "Identity") :: Constraint) => Container (Identity a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Identity a) Source #

Container (First a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (First a) Source #

Methods

toList :: First a -> [Element (First a)] Source #

null :: First a -> Bool Source #

foldr :: (Element (First a) -> b -> b) -> b -> First a -> b Source #

foldl :: (b -> Element (First a) -> b) -> b -> First a -> b Source #

foldl' :: (b -> Element (First a) -> b) -> b -> First a -> b Source #

length :: First a -> Int Source #

elem :: Element (First a) -> First a -> Bool Source #

foldMap :: Monoid m => (Element (First a) -> m) -> First a -> m Source #

fold :: First a -> Element (First a) Source #

foldr' :: (Element (First a) -> b -> b) -> b -> First a -> b Source #

notElem :: Element (First a) -> First a -> Bool Source #

all :: (Element (First a) -> Bool) -> First a -> Bool Source #

any :: (Element (First a) -> Bool) -> First a -> Bool Source #

and :: First a -> Bool Source #

or :: First a -> Bool Source #

find :: (Element (First a) -> Bool) -> First a -> Maybe (Element (First a)) Source #

safeHead :: First a -> Maybe (Element (First a)) Source #

safeMaximum :: First a -> Maybe (Element (First a)) Source #

safeMinimum :: First a -> Maybe (Element (First a)) Source #

safeFoldr1 :: (Element (First a) -> Element (First a) -> Element (First a)) -> First a -> Maybe (Element (First a)) Source #

safeFoldl1 :: (Element (First a) -> Element (First a) -> Element (First a)) -> First a -> Maybe (Element (First a)) Source #

Container (Last a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Last a) Source #

Methods

toList :: Last a -> [Element (Last a)] Source #

null :: Last a -> Bool Source #

foldr :: (Element (Last a) -> b -> b) -> b -> Last a -> b Source #

foldl :: (b -> Element (Last a) -> b) -> b -> Last a -> b Source #

foldl' :: (b -> Element (Last a) -> b) -> b -> Last a -> b Source #

length :: Last a -> Int Source #

elem :: Element (Last a) -> Last a -> Bool Source #

foldMap :: Monoid m => (Element (Last a) -> m) -> Last a -> m Source #

fold :: Last a -> Element (Last a) Source #

foldr' :: (Element (Last a) -> b -> b) -> b -> Last a -> b Source #

notElem :: Element (Last a) -> Last a -> Bool Source #

all :: (Element (Last a) -> Bool) -> Last a -> Bool Source #

any :: (Element (Last a) -> Bool) -> Last a -> Bool Source #

and :: Last a -> Bool Source #

or :: Last a -> Bool Source #

find :: (Element (Last a) -> Bool) -> Last a -> Maybe (Element (Last a)) Source #

safeHead :: Last a -> Maybe (Element (Last a)) Source #

safeMaximum :: Last a -> Maybe (Element (Last a)) Source #

safeMinimum :: Last a -> Maybe (Element (Last a)) Source #

safeFoldr1 :: (Element (Last a) -> Element (Last a) -> Element (Last a)) -> Last a -> Maybe (Element (Last a)) Source #

safeFoldl1 :: (Element (Last a) -> Element (Last a) -> Element (Last a)) -> Last a -> Maybe (Element (Last a)) Source #

Container (Dual a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Dual a) Source #

Methods

toList :: Dual a -> [Element (Dual a)] Source #

null :: Dual a -> Bool Source #

foldr :: (Element (Dual a) -> b -> b) -> b -> Dual a -> b Source #

foldl :: (b -> Element (Dual a) -> b) -> b -> Dual a -> b Source #

foldl' :: (b -> Element (Dual a) -> b) -> b -> Dual a -> b Source #

length :: Dual a -> Int Source #

elem :: Element (Dual a) -> Dual a -> Bool Source #

foldMap :: Monoid m => (Element (Dual a) -> m) -> Dual a -> m Source #

fold :: Dual a -> Element (Dual a) Source #

foldr' :: (Element (Dual a) -> b -> b) -> b -> Dual a -> b Source #

notElem :: Element (Dual a) -> Dual a -> Bool Source #

all :: (Element (Dual a) -> Bool) -> Dual a -> Bool Source #

any :: (Element (Dual a) -> Bool) -> Dual a -> Bool Source #

and :: Dual a -> Bool Source #

or :: Dual a -> Bool Source #

find :: (Element (Dual a) -> Bool) -> Dual a -> Maybe (Element (Dual a)) Source #

safeHead :: Dual a -> Maybe (Element (Dual a)) Source #

safeMaximum :: Dual a -> Maybe (Element (Dual a)) Source #

safeMinimum :: Dual a -> Maybe (Element (Dual a)) Source #

safeFoldr1 :: (Element (Dual a) -> Element (Dual a) -> Element (Dual a)) -> Dual a -> Maybe (Element (Dual a)) Source #

safeFoldl1 :: (Element (Dual a) -> Element (Dual a) -> Element (Dual a)) -> Dual a -> Maybe (Element (Dual a)) Source #

Container (Sum a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Sum a) Source #

Methods

toList :: Sum a -> [Element (Sum a)] Source #

null :: Sum a -> Bool Source #

foldr :: (Element (Sum a) -> b -> b) -> b -> Sum a -> b Source #

foldl :: (b -> Element (Sum a) -> b) -> b -> Sum a -> b Source #

foldl' :: (b -> Element (Sum a) -> b) -> b -> Sum a -> b Source #

length :: Sum a -> Int Source #

elem :: Element (Sum a) -> Sum a -> Bool Source #

foldMap :: Monoid m => (Element (Sum a) -> m) -> Sum a -> m Source #

fold :: Sum a -> Element (Sum a) Source #

foldr' :: (Element (Sum a) -> b -> b) -> b -> Sum a -> b Source #

notElem :: Element (Sum a) -> Sum a -> Bool Source #

all :: (Element (Sum a) -> Bool) -> Sum a -> Bool Source #

any :: (Element (Sum a) -> Bool) -> Sum a -> Bool Source #

and :: Sum a -> Bool Source #

or :: Sum a -> Bool Source #

find :: (Element (Sum a) -> Bool) -> Sum a -> Maybe (Element (Sum a)) Source #

safeHead :: Sum a -> Maybe (Element (Sum a)) Source #

safeMaximum :: Sum a -> Maybe (Element (Sum a)) Source #

safeMinimum :: Sum a -> Maybe (Element (Sum a)) Source #

safeFoldr1 :: (Element (Sum a) -> Element (Sum a) -> Element (Sum a)) -> Sum a -> Maybe (Element (Sum a)) Source #

safeFoldl1 :: (Element (Sum a) -> Element (Sum a) -> Element (Sum a)) -> Sum a -> Maybe (Element (Sum a)) Source #

Container (Product a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Product a) Source #

Methods

toList :: Product a -> [Element (Product a)] Source #

null :: Product a -> Bool Source #

foldr :: (Element (Product a) -> b -> b) -> b -> Product a -> b Source #

foldl :: (b -> Element (Product a) -> b) -> b -> Product a -> b Source #

foldl' :: (b -> Element (Product a) -> b) -> b -> Product a -> b Source #

length :: Product a -> Int Source #

elem :: Element (Product a) -> Product a -> Bool Source #

foldMap :: Monoid m => (Element (Product a) -> m) -> Product a -> m Source #

fold :: Product a -> Element (Product a) Source #

foldr' :: (Element (Product a) -> b -> b) -> b -> Product a -> b Source #

notElem :: Element (Product a) -> Product a -> Bool Source #

all :: (Element (Product a) -> Bool) -> Product a -> Bool Source #

any :: (Element (Product a) -> Bool) -> Product a -> Bool Source #

and :: Product a -> Bool Source #

or :: Product a -> Bool Source #

find :: (Element (Product a) -> Bool) -> Product a -> Maybe (Element (Product a)) Source #

safeHead :: Product a -> Maybe (Element (Product a)) Source #

safeMaximum :: Product a -> Maybe (Element (Product a)) Source #

safeMinimum :: Product a -> Maybe (Element (Product a)) Source #

safeFoldr1 :: (Element (Product a) -> Element (Product a) -> Element (Product a)) -> Product a -> Maybe (Element (Product a)) Source #

safeFoldl1 :: (Element (Product a) -> Element (Product a) -> Element (Product a)) -> Product a -> Maybe (Element (Product a)) Source #

Container (NonEmpty a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (NonEmpty a) Source #

Container (IntMap v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (IntMap v) Source #

Methods

toList :: IntMap v -> [Element (IntMap v)] Source #

null :: IntMap v -> Bool Source #

foldr :: (Element (IntMap v) -> b -> b) -> b -> IntMap v -> b Source #

foldl :: (b -> Element (IntMap v) -> b) -> b -> IntMap v -> b Source #

foldl' :: (b -> Element (IntMap v) -> b) -> b -> IntMap v -> b Source #

length :: IntMap v -> Int Source #

elem :: Element (IntMap v) -> IntMap v -> Bool Source #

foldMap :: Monoid m => (Element (IntMap v) -> m) -> IntMap v -> m Source #

fold :: IntMap v -> Element (IntMap v) Source #

foldr' :: (Element (IntMap v) -> b -> b) -> b -> IntMap v -> b Source #

notElem :: Element (IntMap v) -> IntMap v -> Bool Source #

all :: (Element (IntMap v) -> Bool) -> IntMap v -> Bool Source #

any :: (Element (IntMap v) -> Bool) -> IntMap v -> Bool Source #

and :: IntMap v -> Bool Source #

or :: IntMap v -> Bool Source #

find :: (Element (IntMap v) -> Bool) -> IntMap v -> Maybe (Element (IntMap v)) Source #

safeHead :: IntMap v -> Maybe (Element (IntMap v)) Source #

safeMaximum :: IntMap v -> Maybe (Element (IntMap v)) Source #

safeMinimum :: IntMap v -> Maybe (Element (IntMap v)) Source #

safeFoldr1 :: (Element (IntMap v) -> Element (IntMap v) -> Element (IntMap v)) -> IntMap v -> Maybe (Element (IntMap v)) Source #

safeFoldl1 :: (Element (IntMap v) -> Element (IntMap v) -> Element (IntMap v)) -> IntMap v -> Maybe (Element (IntMap v)) Source #

Container (Seq a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Seq a) Source #

Methods

toList :: Seq a -> [Element (Seq a)] Source #

null :: Seq a -> Bool Source #

foldr :: (Element (Seq a) -> b -> b) -> b -> Seq a -> b Source #

foldl :: (b -> Element (Seq a) -> b) -> b -> Seq a -> b Source #

foldl' :: (b -> Element (Seq a) -> b) -> b -> Seq a -> b Source #

length :: Seq a -> Int Source #

elem :: Element (Seq a) -> Seq a -> Bool Source #

foldMap :: Monoid m => (Element (Seq a) -> m) -> Seq a -> m Source #

fold :: Seq a -> Element (Seq a) Source #

foldr' :: (Element (Seq a) -> b -> b) -> b -> Seq a -> b Source #

notElem :: Element (Seq a) -> Seq a -> Bool Source #

all :: (Element (Seq a) -> Bool) -> Seq a -> Bool Source #

any :: (Element (Seq a) -> Bool) -> Seq a -> Bool Source #

and :: Seq a -> Bool Source #

or :: Seq a -> Bool Source #

find :: (Element (Seq a) -> Bool) -> Seq a -> Maybe (Element (Seq a)) Source #

safeHead :: Seq a -> Maybe (Element (Seq a)) Source #

safeMaximum :: Seq a -> Maybe (Element (Seq a)) Source #

safeMinimum :: Seq a -> Maybe (Element (Seq a)) Source #

safeFoldr1 :: (Element (Seq a) -> Element (Seq a) -> Element (Seq a)) -> Seq a -> Maybe (Element (Seq a)) Source #

safeFoldl1 :: (Element (Seq a) -> Element (Seq a) -> Element (Seq a)) -> Seq a -> Maybe (Element (Seq a)) Source #

Ord v => Container (Set v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Set v) Source #

Methods

toList :: Set v -> [Element (Set v)] Source #

null :: Set v -> Bool Source #

foldr :: (Element (Set v) -> b -> b) -> b -> Set v -> b Source #

foldl :: (b -> Element (Set v) -> b) -> b -> Set v -> b Source #

foldl' :: (b -> Element (Set v) -> b) -> b -> Set v -> b Source #

length :: Set v -> Int Source #

elem :: Element (Set v) -> Set v -> Bool Source #

foldMap :: Monoid m => (Element (Set v) -> m) -> Set v -> m Source #

fold :: Set v -> Element (Set v) Source #

foldr' :: (Element (Set v) -> b -> b) -> b -> Set v -> b Source #

notElem :: Element (Set v) -> Set v -> Bool Source #

all :: (Element (Set v) -> Bool) -> Set v -> Bool Source #

any :: (Element (Set v) -> Bool) -> Set v -> Bool Source #

and :: Set v -> Bool Source #

or :: Set v -> Bool Source #

find :: (Element (Set v) -> Bool) -> Set v -> Maybe (Element (Set v)) Source #

safeHead :: Set v -> Maybe (Element (Set v)) Source #

safeMaximum :: Set v -> Maybe (Element (Set v)) Source #

safeMinimum :: Set v -> Maybe (Element (Set v)) Source #

safeFoldr1 :: (Element (Set v) -> Element (Set v) -> Element (Set v)) -> Set v -> Maybe (Element (Set v)) Source #

safeFoldl1 :: (Element (Set v) -> Element (Set v) -> Element (Set v)) -> Set v -> Maybe (Element (Set v)) Source #

(Eq v, Hashable v) => Container (HashSet v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (HashSet v) Source #

Methods

toList :: HashSet v -> [Element (HashSet v)] Source #

null :: HashSet v -> Bool Source #

foldr :: (Element (HashSet v) -> b -> b) -> b -> HashSet v -> b Source #

foldl :: (b -> Element (HashSet v) -> b) -> b -> HashSet v -> b Source #

foldl' :: (b -> Element (HashSet v) -> b) -> b -> HashSet v -> b Source #

length :: HashSet v -> Int Source #

elem :: Element (HashSet v) -> HashSet v -> Bool Source #

foldMap :: Monoid m => (Element (HashSet v) -> m) -> HashSet v -> m Source #

fold :: HashSet v -> Element (HashSet v) Source #

foldr' :: (Element (HashSet v) -> b -> b) -> b -> HashSet v -> b Source #

notElem :: Element (HashSet v) -> HashSet v -> Bool Source #

all :: (Element (HashSet v) -> Bool) -> HashSet v -> Bool Source #

any :: (Element (HashSet v) -> Bool) -> HashSet v -> Bool Source #

and :: HashSet v -> Bool Source #

or :: HashSet v -> Bool Source #

find :: (Element (HashSet v) -> Bool) -> HashSet v -> Maybe (Element (HashSet v)) Source #

safeHead :: HashSet v -> Maybe (Element (HashSet v)) Source #

safeMaximum :: HashSet v -> Maybe (Element (HashSet v)) Source #

safeMinimum :: HashSet v -> Maybe (Element (HashSet v)) Source #

safeFoldr1 :: (Element (HashSet v) -> Element (HashSet v) -> Element (HashSet v)) -> HashSet v -> Maybe (Element (HashSet v)) Source #

safeFoldl1 :: (Element (HashSet v) -> Element (HashSet v) -> Element (HashSet v)) -> HashSet v -> Maybe (Element (HashSet v)) Source #

Container (Vector a) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Vector a) Source #

Methods

toList :: Vector a -> [Element (Vector a)] Source #

null :: Vector a -> Bool Source #

foldr :: (Element (Vector a) -> b -> b) -> b -> Vector a -> b Source #

foldl :: (b -> Element (Vector a) -> b) -> b -> Vector a -> b Source #

foldl' :: (b -> Element (Vector a) -> b) -> b -> Vector a -> b Source #

length :: Vector a -> Int Source #

elem :: Element (Vector a) -> Vector a -> Bool Source #

foldMap :: Monoid m => (Element (Vector a) -> m) -> Vector a -> m Source #

fold :: Vector a -> Element (Vector a) Source #

foldr' :: (Element (Vector a) -> b -> b) -> b -> Vector a -> b Source #

notElem :: Element (Vector a) -> Vector a -> Bool Source #

all :: (Element (Vector a) -> Bool) -> Vector a -> Bool Source #

any :: (Element (Vector a) -> Bool) -> Vector a -> Bool Source #

and :: Vector a -> Bool Source #

or :: Vector a -> Bool Source #

find :: (Element (Vector a) -> Bool) -> Vector a -> Maybe (Element (Vector a)) Source #

safeHead :: Vector a -> Maybe (Element (Vector a)) Source #

safeMaximum :: Vector a -> Maybe (Element (Vector a)) Source #

safeMinimum :: Vector a -> Maybe (Element (Vector a)) Source #

safeFoldr1 :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a)) -> Vector a -> Maybe (Element (Vector a)) Source #

safeFoldl1 :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a)) -> Vector a -> Maybe (Element (Vector a)) Source #

(TypeError (DisallowInstance "Either") :: Constraint) => Container (Either a b) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Either a b) Source #

Methods

toList :: Either a b -> [Element (Either a b)] Source #

null :: Either a b -> Bool Source #

foldr :: (Element (Either a b) -> b0 -> b0) -> b0 -> Either a b -> b0 Source #

foldl :: (b0 -> Element (Either a b) -> b0) -> b0 -> Either a b -> b0 Source #

foldl' :: (b0 -> Element (Either a b) -> b0) -> b0 -> Either a b -> b0 Source #

length :: Either a b -> Int Source #

elem :: Element (Either a b) -> Either a b -> Bool Source #

foldMap :: Monoid m => (Element (Either a b) -> m) -> Either a b -> m Source #

fold :: Either a b -> Element (Either a b) Source #

foldr' :: (Element (Either a b) -> b0 -> b0) -> b0 -> Either a b -> b0 Source #

notElem :: Element (Either a b) -> Either a b -> Bool Source #

all :: (Element (Either a b) -> Bool) -> Either a b -> Bool Source #

any :: (Element (Either a b) -> Bool) -> Either a b -> Bool Source #

and :: Either a b -> Bool Source #

or :: Either a b -> Bool Source #

find :: (Element (Either a b) -> Bool) -> Either a b -> Maybe (Element (Either a b)) Source #

safeHead :: Either a b -> Maybe (Element (Either a b)) Source #

safeMaximum :: Either a b -> Maybe (Element (Either a b)) Source #

safeMinimum :: Either a b -> Maybe (Element (Either a b)) Source #

safeFoldr1 :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Maybe (Element (Either a b)) Source #

safeFoldl1 :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Maybe (Element (Either a b)) Source #

(TypeError (DisallowInstance "tuple") :: Constraint) => Container (a, b) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (a, b) Source #

Methods

toList :: (a, b) -> [Element (a, b)] Source #

null :: (a, b) -> Bool Source #

foldr :: (Element (a, b) -> b0 -> b0) -> b0 -> (a, b) -> b0 Source #

foldl :: (b0 -> Element (a, b) -> b0) -> b0 -> (a, b) -> b0 Source #

foldl' :: (b0 -> Element (a, b) -> b0) -> b0 -> (a, b) -> b0 Source #

length :: (a, b) -> Int Source #

elem :: Element (a, b) -> (a, b) -> Bool Source #

foldMap :: Monoid m => (Element (a, b) -> m) -> (a, b) -> m Source #

fold :: (a, b) -> Element (a, b) Source #

foldr' :: (Element (a, b) -> b0 -> b0) -> b0 -> (a, b) -> b0 Source #

notElem :: Element (a, b) -> (a, b) -> Bool Source #

all :: (Element (a, b) -> Bool) -> (a, b) -> Bool Source #

any :: (Element (a, b) -> Bool) -> (a, b) -> Bool Source #

and :: (a, b) -> Bool Source #

or :: (a, b) -> Bool Source #

find :: (Element (a, b) -> Bool) -> (a, b) -> Maybe (Element (a, b)) Source #

safeHead :: (a, b) -> Maybe (Element (a, b)) Source #

safeMaximum :: (a, b) -> Maybe (Element (a, b)) Source #

safeMinimum :: (a, b) -> Maybe (Element (a, b)) Source #

safeFoldr1 :: (Element (a, b) -> Element (a, b) -> Element (a, b)) -> (a, b) -> Maybe (Element (a, b)) Source #

safeFoldl1 :: (Element (a, b) -> Element (a, b) -> Element (a, b)) -> (a, b) -> Maybe (Element (a, b)) Source #

Container (Map k v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Map k v) Source #

Methods

toList :: Map k v -> [Element (Map k v)] Source #

null :: Map k v -> Bool Source #

foldr :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b Source #

foldl :: (b -> Element (Map k v) -> b) -> b -> Map k v -> b Source #

foldl' :: (b -> Element (Map k v) -> b) -> b -> Map k v -> b Source #

length :: Map k v -> Int Source #

elem :: Element (Map k v) -> Map k v -> Bool Source #

foldMap :: Monoid m => (Element (Map k v) -> m) -> Map k v -> m Source #

fold :: Map k v -> Element (Map k v) Source #

foldr' :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b Source #

notElem :: Element (Map k v) -> Map k v -> Bool Source #

all :: (Element (Map k v) -> Bool) -> Map k v -> Bool Source #

any :: (Element (Map k v) -> Bool) -> Map k v -> Bool Source #

and :: Map k v -> Bool Source #

or :: Map k v -> Bool Source #

find :: (Element (Map k v) -> Bool) -> Map k v -> Maybe (Element (Map k v)) Source #

safeHead :: Map k v -> Maybe (Element (Map k v)) Source #

safeMaximum :: Map k v -> Maybe (Element (Map k v)) Source #

safeMinimum :: Map k v -> Maybe (Element (Map k v)) Source #

safeFoldr1 :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Maybe (Element (Map k v)) Source #

safeFoldl1 :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Maybe (Element (Map k v)) Source #

Container (HashMap k v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (HashMap k v) Source #

Methods

toList :: HashMap k v -> [Element (HashMap k v)] Source #

null :: HashMap k v -> Bool Source #

foldr :: (Element (HashMap k v) -> b -> b) -> b -> HashMap k v -> b Source #

foldl :: (b -> Element (HashMap k v) -> b) -> b -> HashMap k v -> b Source #

foldl' :: (b -> Element (HashMap k v) -> b) -> b -> HashMap k v -> b Source #

length :: HashMap k v -> Int Source #

elem :: Element (HashMap k v) -> HashMap k v -> Bool Source #

foldMap :: Monoid m => (Element (HashMap k v) -> m) -> HashMap k v -> m Source #

fold :: HashMap k v -> Element (HashMap k v) Source #

foldr' :: (Element (HashMap k v) -> b -> b) -> b -> HashMap k v -> b Source #

notElem :: Element (HashMap k v) -> HashMap k v -> Bool Source #

all :: (Element (HashMap k v) -> Bool) -> HashMap k v -> Bool Source #

any :: (Element (HashMap k v) -> Bool) -> HashMap k v -> Bool Source #

and :: HashMap k v -> Bool Source #

or :: HashMap k v -> Bool Source #

find :: (Element (HashMap k v) -> Bool) -> HashMap k v -> Maybe (Element (HashMap k v)) Source #

safeHead :: HashMap k v -> Maybe (Element (HashMap k v)) Source #

safeMaximum :: HashMap k v -> Maybe (Element (HashMap k v)) Source #

safeMinimum :: HashMap k v -> Maybe (Element (HashMap k v)) Source #

safeFoldr1 :: (Element (HashMap k v) -> Element (HashMap k v) -> Element (HashMap k v)) -> HashMap k v -> Maybe (Element (HashMap k v)) Source #

safeFoldl1 :: (Element (HashMap k v) -> Element (HashMap k v) -> Element (HashMap k v)) -> HashMap k v -> Maybe (Element (HashMap k v)) Source #

Container (Const a b) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Const a b) Source #

Methods

toList :: Const a b -> [Element (Const a b)] Source #

null :: Const a b -> Bool Source #

foldr :: (Element (Const a b) -> b0 -> b0) -> b0 -> Const a b -> b0 Source #

foldl :: (b0 -> Element (Const a b) -> b0) -> b0 -> Const a b -> b0 Source #

foldl' :: (b0 -> Element (Const a b) -> b0) -> b0 -> Const a b -> b0 Source #

length :: Const a b -> Int Source #

elem :: Element (Const a b) -> Const a b -> Bool Source #

foldMap :: Monoid m => (Element (Const a b) -> m) -> Const a b -> m Source #

fold :: Const a b -> Element (Const a b) Source #

foldr' :: (Element (Const a b) -> b0 -> b0) -> b0 -> Const a b -> b0 Source #

notElem :: Element (Const a b) -> Const a b -> Bool Source #

all :: (Element (Const a b) -> Bool) -> Const a b -> Bool Source #

any :: (Element (Const a b) -> Bool) -> Const a b -> Bool Source #

and :: Const a b -> Bool Source #

or :: Const a b -> Bool Source #

find :: (Element (Const a b) -> Bool) -> Const a b -> Maybe (Element (Const a b)) Source #

safeHead :: Const a b -> Maybe (Element (Const a b)) Source #

safeMaximum :: Const a b -> Maybe (Element (Const a b)) Source #

safeMinimum :: Const a b -> Maybe (Element (Const a b)) Source #

safeFoldr1 :: (Element (Const a b) -> Element (Const a b) -> Element (Const a b)) -> Const a b -> Maybe (Element (Const a b)) Source #

safeFoldl1 :: (Element (Const a b) -> Element (Const a b) -> Element (Const a b)) -> Const a b -> Maybe (Element (Const a b)) Source #

class ToPairs t where Source #

Type class for data types that can be converted to List of Pairs. You can define ToPairs by just defining toPairs function.

But the following laws should be met:

toPairs m ≡ zip (keys m) (elems m)
keysmap fst . toPairs
elemsmap snd . toPairs

Minimal complete definition

toPairs

Associated Types

type Key t :: Type Source #

Type of keys of the mapping.

type Val t :: Type Source #

Type of value of the mapping.

Methods

toPairs :: t -> [(Key t, Val t)] Source #

Converts the structure to the list of the key-value pairs. >>> toPairs (HashMap.fromList [(a, "xxx"), (b, "yyy")]) [(a,"xxx"),(b,"yyy")]

keys :: t -> [Key t] Source #

Converts the structure to the list of the keys.

>>> keys (HashMap.fromList [('a', "xxx"), ('b', "yyy")])
"ab"

elems :: t -> [Val t] Source #

Converts the structure to the list of the values.

>>> elems (HashMap.fromList [('a', "xxx"), ('b', "yyy")])
["xxx","yyy"]

Instances

Instances details
ToPairs (IntMap v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Key (IntMap v) Source #

type Val (IntMap v) Source #

Methods

toPairs :: IntMap v -> [(Key (IntMap v), Val (IntMap v))] Source #

keys :: IntMap v -> [Key (IntMap v)] Source #

elems :: IntMap v -> [Val (IntMap v)] Source #

ToPairs (Map k v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Key (Map k v) Source #

type Val (Map k v) Source #

Methods

toPairs :: Map k v -> [(Key (Map k v), Val (Map k v))] Source #

keys :: Map k v -> [Key (Map k v)] Source #

elems :: Map k v -> [Val (Map k v)] Source #

ToPairs (HashMap k v) Source # 
Instance details

Defined in Universum.Container.Class

Associated Types

type Key (HashMap k v) Source #

type Val (HashMap k v) Source #

Methods

toPairs :: HashMap k v -> [(Key (HashMap k v), Val (HashMap k v))] Source #

keys :: HashMap k v -> [Key (HashMap k v)] Source #

elems :: HashMap k v -> [Val (HashMap k v)] Source #

flipfoldl' :: (Container t, Element t ~ a) => (a -> b -> b) -> b -> t -> b Source #

Similar to foldl' but takes a function with its arguments flipped.

>>> flipfoldl' (/) 5 [2,3] :: Rational
15 % 2

sum :: (Container t, Num (Element t)) => t -> Element t Source #

Stricter version of sum.

>>> sum [1..10]
55
>>> sum (Just 3)
...
    • Do not use 'Foldable' methods on Maybe
      Suggestions:
          Instead of
              for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
          use
              whenJust  :: Applicative f => Maybe a    -> (a -> f ()) -> f ()
              whenRight :: Applicative f => Either l r -> (r -> f ()) -> f ()
...
          Instead of
              fold :: (Foldable t, Monoid m) => t m -> m
          use
              maybeToMonoid :: Monoid m => Maybe m -> m
...

product :: (Container t, Num (Element t)) => t -> Element t Source #

Stricter version of product.

>>> product [1..10]
3628800
>>> product (Right 3)
...
    • Do not use 'Foldable' methods on Either
      Suggestions:
          Instead of
              for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f ()
          use
              whenJust  :: Applicative f => Maybe a    -> (a -> f ()) -> f ()
              whenRight :: Applicative f => Either l r -> (r -> f ()) -> f ()
...
          Instead of
              fold :: (Foldable t, Monoid m) => t m -> m
          use
              maybeToMonoid :: Monoid m => Maybe m -> m
...

traverse_ :: (Container t, Applicative f) => (Element t -> f b) -> t -> f () Source #

Constrained to Container version of traverse_.

>>> traverse_ putTextLn ["foo", "bar"]
foo
bar

for_ :: (Container t, Applicative f) => t -> (Element t -> f b) -> f () Source #

Constrained to Container version of for_.

>>> for_ [1 .. 5 :: Int] $ \i -> when (even i) (print i)
2
4

mapM_ :: (Container t, Monad m) => (Element t -> m b) -> t -> m () Source #

Constrained to Container version of mapM_.

>>> mapM_ print [True, False]
True
False

forM_ :: (Container t, Monad m) => t -> (Element t -> m b) -> m () Source #

Constrained to Container version of forM_.

>>> forM_ [True, False] print
True
False

sequenceA_ :: (Container t, Applicative f, Element t ~ f a) => t -> f () Source #

Constrained to Container version of sequenceA_.

>>> sequenceA_ [putTextLn "foo", print True]
foo
True

sequence_ :: (Container t, Monad m, Element t ~ m a) => t -> m () Source #

Constrained to Container version of sequence_.

>>> sequence_ [putTextLn "foo", print True]
foo
True

asum :: (Container t, Alternative f, Element t ~ f a) => t -> f a Source #

Constrained to Container version of asum.

>>> asum [Nothing, Just [False, True], Nothing, Just [True]]
Just [False,True]