graphql-1.0.1.0: Haskell GraphQL implementation
Safe HaskellNone
LanguageHaskell2010

Language.GraphQL.Execute.OrderedMap

Description

This module contains a map data structure, that preserves insertion order. Some definitions conflict with functions from prelude, so this module should probably be imported qualified.

Synopsis

Documentation

data OrderedMap v Source #

This map associates values with the given text keys. Insertion order is preserved. When inserting a value with a key, that is already available in the map, the existing value isn't overridden, but combined with the new value using its Semigroup instance.

Internally this map uses an array with keys to preserve the order and an unorded map with key-value pairs.

Instances

Instances details
Functor OrderedMap Source # 
Instance details

Defined in Language.GraphQL.Execute.OrderedMap

Methods

fmap :: (a -> b) -> OrderedMap a -> OrderedMap b #

(<$) :: a -> OrderedMap b -> OrderedMap a #

Foldable OrderedMap Source # 
Instance details

Defined in Language.GraphQL.Execute.OrderedMap

Methods

fold :: Monoid m => OrderedMap m -> m #

foldMap :: Monoid m => (a -> m) -> OrderedMap a -> m #

foldMap' :: Monoid m => (a -> m) -> OrderedMap a -> m #

foldr :: (a -> b -> b) -> b -> OrderedMap a -> b #

foldr' :: (a -> b -> b) -> b -> OrderedMap a -> b #

foldl :: (b -> a -> b) -> b -> OrderedMap a -> b #

foldl' :: (b -> a -> b) -> b -> OrderedMap a -> b #

foldr1 :: (a -> a -> a) -> OrderedMap a -> a #

foldl1 :: (a -> a -> a) -> OrderedMap a -> a #

toList :: OrderedMap a -> [a] #

null :: OrderedMap a -> Bool #

length :: OrderedMap a -> Int #

elem :: Eq a => a -> OrderedMap a -> Bool #

maximum :: Ord a => OrderedMap a -> a #

minimum :: Ord a => OrderedMap a -> a #

sum :: Num a => OrderedMap a -> a #

product :: Num a => OrderedMap a -> a #

Traversable OrderedMap Source # 
Instance details

Defined in Language.GraphQL.Execute.OrderedMap

Methods

traverse :: Applicative f => (a -> f b) -> OrderedMap a -> f (OrderedMap b) #

sequenceA :: Applicative f => OrderedMap (f a) -> f (OrderedMap a) #

mapM :: Monad m => (a -> m b) -> OrderedMap a -> m (OrderedMap b) #

sequence :: Monad m => OrderedMap (m a) -> m (OrderedMap a) #

Eq v => Eq (OrderedMap v) Source # 
Instance details

Defined in Language.GraphQL.Execute.OrderedMap

Methods

(==) :: OrderedMap v -> OrderedMap v -> Bool #

(/=) :: OrderedMap v -> OrderedMap v -> Bool #

Show v => Show (OrderedMap v) Source # 
Instance details

Defined in Language.GraphQL.Execute.OrderedMap

Semigroup v => Semigroup (OrderedMap v) Source # 
Instance details

Defined in Language.GraphQL.Execute.OrderedMap

Semigroup v => Monoid (OrderedMap v) Source # 
Instance details

Defined in Language.GraphQL.Execute.OrderedMap

elems :: forall v. OrderedMap v -> [v] Source #

Returns a list with all elements in this map.

empty :: forall v. OrderedMap v Source #

Constructs an empty map.

insert :: Semigroup v => Text -> v -> OrderedMap v -> OrderedMap v Source #

Associates the specified value with the specified key in this map. If this map previously contained a mapping for the key, the existing and new values are combined.

foldlWithKey' :: forall v a. (a -> Text -> v -> a) -> a -> OrderedMap v -> a Source #

Reduces this map by applying a binary operator from left to right to all elements, using the given starting value.

keys :: forall v. OrderedMap v -> [Text] Source #

Returns a list with all keys in this map.

lookup :: forall v. Text -> OrderedMap v -> Maybe v Source #

Looks up a value in this map by key.

replace :: Text -> v -> OrderedMap v -> OrderedMap v Source #

Associates the specified value with the specified key in this map. If this map previously contained a mapping for the key, the existing value is replaced by the new one.

singleton :: forall v. Text -> v -> OrderedMap v Source #

Constructs a map with a single element.

size :: forall v. OrderedMap v -> Int Source #

Gives the size of this map, i.e. number of elements in it.

toList :: forall v. OrderedMap v -> [(Text, v)] Source #

Converts this map to the list of key-value pairs.

traverseMaybe :: Applicative f => forall a. (a -> f (Maybe b)) -> OrderedMap a -> f (OrderedMap b) Source #

Traverse over the elements and collect the Just results.