planet-mitchell-0.1.0: Planet Mitchell

Safe HaskellSafe
LanguageHaskell2010

List.Builder

Contents

Synopsis

List builder

data DList a where #

A difference list is a function that, given a list, returns the original contents of the difference list prepended to the given list.

This structure supports O(1) append and snoc operations on lists, making it very useful for append-heavy uses (esp. left-nested uses of ++), such as logging and pretty printing.

Here is an example using DList as the state type when printing a tree with the Writer monad:

import Control.Monad.Writer
import Data.DList

data Tree a = Leaf a | Branch (Tree a) (Tree a)

flatten_writer :: Tree x -> DList x
flatten_writer = snd . runWriter . flatten
    where
      flatten (Leaf x)     = tell (singleton x)
      flatten (Branch x y) = flatten x >> flatten y

Bundled Patterns

pattern Nil :: forall a. DList a

A unidirectional pattern synonym using toList in a view pattern and matching on []

pattern Cons :: forall a. a -> [a] -> DList a

A unidirectional pattern synonym using toList in a view pattern and matching on x:xs such that you have the pattern Cons x xs

Instances
Monad DList 
Instance details

Defined in Data.DList

Methods

(>>=) :: DList a -> (a -> DList b) -> DList b #

(>>) :: DList a -> DList b -> DList b #

return :: a -> DList a #

fail :: String -> DList a #

Functor DList 
Instance details

Defined in Data.DList

Methods

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

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

Applicative DList 
Instance details

Defined in Data.DList

Methods

pure :: a -> DList a #

(<*>) :: DList (a -> b) -> DList a -> DList b #

liftA2 :: (a -> b -> c) -> DList a -> DList b -> DList c #

(*>) :: DList a -> DList b -> DList b #

(<*) :: DList a -> DList b -> DList a #

Foldable DList 
Instance details

Defined in Data.DList

Methods

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

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

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

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

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

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

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

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

toList :: DList a -> [a] #

null :: DList a -> Bool #

length :: DList a -> Int #

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

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

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

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

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

Alternative DList 
Instance details

Defined in Data.DList

Methods

empty :: DList a #

(<|>) :: DList a -> DList a -> DList a #

some :: DList a -> DList [a] #

many :: DList a -> DList [a] #

ToJSON1 DList 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> DList a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [DList a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> DList a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [DList a] -> Encoding #

FromJSON1 DList 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (DList a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [DList a] #

MonadPlus DList 
Instance details

Defined in Data.DList

Methods

mzero :: DList a #

mplus :: DList a -> DList a -> DList a #

FromPairs Value (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

fromPairs :: DList Pair -> Value

v ~ Value => KeyValuePair v (DList Pair) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

pair :: String -> v -> DList Pair

IsList (DList a) 
Instance details

Defined in Data.DList

Associated Types

type Item (DList a) :: * #

Methods

fromList :: [Item (DList a)] -> DList a #

fromListN :: Int -> [Item (DList a)] -> DList a #

toList :: DList a -> [Item (DList a)] #

Eq a => Eq (DList a) 
Instance details

Defined in Data.DList

Methods

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

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

Ord a => Ord (DList a) 
Instance details

Defined in Data.DList

Methods

compare :: DList a -> DList a -> Ordering #

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

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

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

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

max :: DList a -> DList a -> DList a #

min :: DList a -> DList a -> DList a #

Read a => Read (DList a) 
Instance details

Defined in Data.DList

Show a => Show (DList a) 
Instance details

Defined in Data.DList

Methods

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

show :: DList a -> String #

showList :: [DList a] -> ShowS #

a ~ Char => IsString (DList a) 
Instance details

Defined in Data.DList

Methods

fromString :: String -> DList a #

Semigroup (DList a) 
Instance details

Defined in Data.DList

Methods

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

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

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

Monoid (DList a) 
Instance details

Defined in Data.DList

Methods

mempty :: DList a #

mappend :: DList a -> DList a -> DList a #

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

ToJSON a => ToJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON a => FromJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData a => NFData (DList a) 
Instance details

Defined in Data.DList

Methods

rnf :: DList a -> () #

type Item (DList a) 
Instance details

Defined in Data.DList

type Item (DList a) = a

fromList :: [a] -> DList a #

Convert a list to a dlist

toList :: DList a -> [a] #

Convert a dlist to a list

apply :: DList a -> [a] -> [a] #

Apply a dlist to a list to get the underlying list with an extension

apply (fromList xs) ys = xs ++ ys

empty :: DList a #

Create a dlist containing no elements

singleton :: a -> DList a #

Create dlist with a single element

cons :: a -> DList a -> DList a infixr 9 #

O(1). Prepend a single element to a dlist

snoc :: DList a -> a -> DList a infixl 9 #

O(1). Append a single element to a dlist

append :: DList a -> DList a -> DList a #

O(1). Append dlists

concat :: [DList a] -> DList a #

O(spine). Concatenate dlists

replicate :: Int -> a -> DList a #

O(n). Create a dlist of the given number of elements

list :: b -> (a -> DList a -> b) -> DList a -> b #

O(n). List elimination for dlists

unfoldr :: (b -> Maybe (a, b)) -> b -> DList a #

O(n). Unfoldr for dlists

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

O(n). Foldr over difference lists

map :: (a -> b) -> DList a -> DList b #

O(n). Map over difference lists.