bencoding-0.4.5.3: A library for encoding and decoding of BEncode data.
Copyright(c) Sam Truzjan 2013
LicenseBSD3
Maintainerpxqr.sta@gmail.com
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.BEncode.BDict

Description

This module defines a simple key/value list ordered by keys which both faster and more suitable for bencode dictionaries than just [(k,v)].

Synopsis

Documentation

data BDictMap a Source #

BDictMap is an ascending list of key/value pairs sorted by keys.

Constructors

Cons !BKey a !(BDictMap a) 
Nil 

Instances

Instances details
Functor BDictMap Source # 
Instance details

Defined in Data.BEncode.BDict

Methods

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

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

Foldable BDictMap Source # 
Instance details

Defined in Data.BEncode.BDict

Methods

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

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

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

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

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

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

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

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

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

toList :: BDictMap a -> [a] #

null :: BDictMap a -> Bool #

length :: BDictMap a -> Int #

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

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

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

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

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

BEncode BDict Source # 
Instance details

Defined in Data.BEncode

Eq a => Eq (BDictMap a) Source # 
Instance details

Defined in Data.BEncode.BDict

Methods

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

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

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

Defined in Data.BEncode.BDict

Methods

compare :: BDictMap a -> BDictMap a -> Ordering #

(<) :: BDictMap a -> BDictMap a -> Bool #

(<=) :: BDictMap a -> BDictMap a -> Bool #

(>) :: BDictMap a -> BDictMap a -> Bool #

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

max :: BDictMap a -> BDictMap a -> BDictMap a #

min :: BDictMap a -> BDictMap a -> BDictMap a #

Read a => Read (BDictMap a) Source # 
Instance details

Defined in Data.BEncode.BDict

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

Defined in Data.BEncode.BDict

Methods

showsPrec :: Int -> BDictMap a -> ShowS #

show :: BDictMap a -> String #

showList :: [BDictMap a] -> ShowS #

Generic (BDictMap a) Source # 
Instance details

Defined in Data.BEncode.BDict

Associated Types

type Rep (BDictMap a) :: Type -> Type #

Methods

from :: BDictMap a -> Rep (BDictMap a) x #

to :: Rep (BDictMap a) x -> BDictMap a #

Semigroup (BDictMap a) Source # 
Instance details

Defined in Data.BEncode.BDict

Methods

(<>) :: BDictMap a -> BDictMap a -> BDictMap a #

sconcat :: NonEmpty (BDictMap a) -> BDictMap a #

stimes :: Integral b => b -> BDictMap a -> BDictMap a #

Monoid (BDictMap a) Source # 
Instance details

Defined in Data.BEncode.BDict

Methods

mempty :: BDictMap a #

mappend :: BDictMap a -> BDictMap a -> BDictMap a #

mconcat :: [BDictMap a] -> BDictMap a #

NFData a => NFData (BDictMap a) Source # 
Instance details

Defined in Data.BEncode.BDict

Methods

rnf :: BDictMap a -> () #

type Rep (BDictMap a) Source # 
Instance details

Defined in Data.BEncode.BDict

type Rep (BDictMap a) = D1 ('MetaData "BDictMap" "Data.BEncode.BDict" "bencoding-0.4.5.3-3C5sORAAFvX3pierLOBPg9" 'False) (C1 ('MetaCons "Cons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BKey) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BDictMap a)))) :+: C1 ('MetaCons "Nil" 'PrefixI 'False) (U1 :: Type -> Type))

Construction

empty :: BDictMap a Source #

O(1). The empty dicionary.

singleton :: BKey -> a -> BDictMap a Source #

O(1). Dictionary of one key-value pair.

Query

null :: BDictMap a -> Bool Source #

O(1). Is the dictionary empty?

member :: BKey -> BDictMap a -> Bool Source #

O(n). Is the key a member of the dictionary?

lookup :: BKey -> BDictMap a -> Maybe a Source #

O(n). Lookup the value at a key in the dictionary.

Combine

union :: BDictMap a -> BDictMap a -> BDictMap a Source #

O(n + m). Merge two dictionaries by taking pair from both given dictionaries. Dublicated keys are not filtered.

Maps

map :: (a -> b) -> BDictMap a -> BDictMap b Source #

O(n). Map a function over all values in the dictionary.

mapWithKey :: (BKey -> a -> b) -> BDictMap a -> BDictMap b Source #

O(n). Map a function over all keys/value pairs in the dictionary.

Folds

foldMapWithKey :: Monoid m => (BKey -> a -> m) -> BDictMap a -> m Source #

O(n). Map each key/value pair to a monoid and fold resulting sequnce using mappend.

bifoldMap :: Monoid m => (BKey -> a -> m) -> BDictMap a -> m Source #

Deprecated: Use foldMapWithKey instead

O(n). Map each key/value pair to a monoid and fold resulting sequnce using mappend.

Conversion

fromAscList :: [(BKey, a)] -> BDictMap a Source #

O(n). Build a dictionary from a list of key/value pairs where the keys are in ascending order.

toAscList :: BDictMap a -> [(BKey, a)] Source #

O(n). Convert the dictionary to a list of key/value pairs where the keys are in ascending order.