web-rep-0.7.0: representations of a web page

Safe HaskellNone
LanguageHaskell2010

Web.Rep

Contents

Description

A haskell library for representing web pages.

This library is a collection of web page abstractions, together with a reimagining of suavemente.

I wanted to expose the server delivery mechanism, switch the streaming nature of the gap between a web page and a haskell server, and concentrate on getting a clean interface between pure haskell and the world that is a web page.

See app/examples.hs and Examples for usage.

Synopsis

Shared Representation

data RepF r a Source #

Information contained in a web page can usually be considered to be isomorphic to a map of named values - a HashMap. This is especially true when considering a differential of information contained in a web page. Looking at a page from the outside, it often looks like a streaming differential of a hashmap.

RepF consists of an underlying value being represented, and, given a hashmap state, a way to produce a representation of the underlying value (or error), in another domain, together with the potential to alter the hashmap state.

Constructors

Rep 

Fields

Instances
Bifunctor RepF Source # 
Instance details

Defined in Web.Rep.Shared

Methods

bimap :: (a -> b) -> (c -> d) -> RepF a c -> RepF b d #

first :: (a -> b) -> RepF a c -> RepF b c #

second :: (b -> c) -> RepF a b -> RepF a c #

Biapplicative RepF Source # 
Instance details

Defined in Web.Rep.Shared

Methods

bipure :: a -> b -> RepF a b #

(<<*>>) :: RepF (a -> b) (c -> d) -> RepF a c -> RepF b d #

biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> RepF a d -> RepF b e -> RepF c f #

(*>>) :: RepF a b -> RepF c d -> RepF c d #

(<<*) :: RepF a b -> RepF c d -> RepF a b #

Functor (RepF r) Source # 
Instance details

Defined in Web.Rep.Shared

Methods

fmap :: (a -> b) -> RepF r a -> RepF r b #

(<$) :: a -> RepF r b -> RepF r a #

Monoid r => Applicative (RepF r) Source # 
Instance details

Defined in Web.Rep.Shared

Methods

pure :: a -> RepF r a #

(<*>) :: RepF r (a -> b) -> RepF r a -> RepF r b #

liftA2 :: (a -> b -> c) -> RepF r a -> RepF r b -> RepF r c #

(*>) :: RepF r a -> RepF r b -> RepF r b #

(<*) :: RepF r a -> RepF r b -> RepF r a #

Semigroup r => Semigroup (RepF r a) Source # 
Instance details

Defined in Web.Rep.Shared

Methods

(<>) :: RepF r a -> RepF r a -> RepF r a #

sconcat :: NonEmpty (RepF r a) -> RepF r a #

stimes :: Integral b => b -> RepF r a -> RepF r a #

(Monoid a, Monoid r) => Monoid (RepF r a) Source # 
Instance details

Defined in Web.Rep.Shared

Methods

mempty :: RepF r a #

mappend :: RepF r a -> RepF r a -> RepF r a #

mconcat :: [RepF r a] -> RepF r a #

type Rep a = RepF (Html ()) a Source #

the common usage, where the representation domain is Html

oneRep :: (Monad m, MonadIO m) => Rep a -> (Rep a -> HashMap Text Text -> m ()) -> StateT (HashMap Text Text) m (HashMap Text Text, Either Text a) Source #

stateful result of one step, given a RepF, and a monadic action. Useful for testing and for initialising a page.

newtype SharedRepF m r a Source #

Driven by the architecture of the DOM, web page components are compositional, and tree-like, where components are often composed of other components, and values are thus shared across components.

This is sometimes referred to as "observable sharing". See data-reify as another library that reifies this (pun intended), and provided the initial inspiration for this implementation.

unshare should only be run once, which is a terrible flaw that might be fixed by linear types.

Constructors

SharedRep 

Fields

Instances
Functor m => Bifunctor (SharedRepF m) Source # 
Instance details

Defined in Web.Rep.Shared

Methods

bimap :: (a -> b) -> (c -> d) -> SharedRepF m a c -> SharedRepF m b d #

first :: (a -> b) -> SharedRepF m a c -> SharedRepF m b c #

second :: (b -> c) -> SharedRepF m a b -> SharedRepF m a c #

Monad m => Biapplicative (SharedRepF m) Source # 
Instance details

Defined in Web.Rep.Shared

Methods

bipure :: a -> b -> SharedRepF m a b #

(<<*>>) :: SharedRepF m (a -> b) (c -> d) -> SharedRepF m a c -> SharedRepF m b d #

biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> SharedRepF m a d -> SharedRepF m b e -> SharedRepF m c f #

(*>>) :: SharedRepF m a b -> SharedRepF m c d -> SharedRepF m c d #

(<<*) :: SharedRepF m a b -> SharedRepF m c d -> SharedRepF m a b #

Functor m => Functor (SharedRepF m r) Source # 
Instance details

Defined in Web.Rep.Shared

Methods

fmap :: (a -> b) -> SharedRepF m r a -> SharedRepF m r b #

(<$) :: a -> SharedRepF m r b -> SharedRepF m r a #

(Monad m, Monoid r) => Applicative (SharedRepF m r) Source # 
Instance details

Defined in Web.Rep.Shared

Methods

pure :: a -> SharedRepF m r a #

(<*>) :: SharedRepF m r (a -> b) -> SharedRepF m r a -> SharedRepF m r b #

liftA2 :: (a -> b -> c) -> SharedRepF m r a -> SharedRepF m r b -> SharedRepF m r c #

(*>) :: SharedRepF m r a -> SharedRepF m r b -> SharedRepF m r b #

(<*) :: SharedRepF m r a -> SharedRepF m r b -> SharedRepF m r a #

type SharedRep m a = SharedRepF m (Html ()) a Source #

default representation type of Html ()

runOnce :: Monad m => SharedRep m a -> (Html () -> HashMap Text Text -> m ()) -> m (HashMap Text Text, Either Text a) Source #

Compute the initial state of a SharedRep and then run an action once (see tests).

zeroState :: Monad m => SharedRep m a -> m (Html (), (HashMap Text Text, Either Text a)) Source #

compute the initial state of a SharedRep (testing)

register Source #

Arguments

:: Monad m 
=> (Text -> Either Text a)

Parser

-> (a -> Text)

Printer

-> (Text -> a -> r)

create initial object from name and initial value

-> a

initial value

-> SharedRepF m r a 

Create a sharedRep

genName :: MonadState Int m => m Text Source #

name supply for elements of a SharedRepF

genNamePre :: MonadState Int m => Text -> m Text Source #

sometimes a number doesn't work properly in html (or js???), and an alpha prefix seems to help

Web Rep Components

data Page Source #

Components of a web page.

A web page can take many forms but still have the same underlying representation. For example, CSS can be linked to in a separate file, or can be inline within html, but still be the same css and have the same expected external effect. A Page represents the practical components of what makes up a static snapshot of a web page.

Constructors

Page 

Fields

Instances
Show Page Source # 
Instance details

Defined in Web.Rep.Page

Methods

showsPrec :: Int -> Page -> ShowS #

show :: Page -> String #

showList :: [Page] -> ShowS #

Generic Page Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep Page :: Type -> Type #

Methods

from :: Page -> Rep Page x #

to :: Rep Page x -> Page #

Semigroup Page Source # 
Instance details

Defined in Web.Rep.Page

Methods

(<>) :: Page -> Page -> Page #

sconcat :: NonEmpty Page -> Page #

stimes :: Integral b => b -> Page -> Page #

Monoid Page Source # 
Instance details

Defined in Web.Rep.Page

Methods

mempty :: Page #

mappend :: Page -> Page -> Page #

mconcat :: [Page] -> Page #

type Rep Page Source # 
Instance details

Defined in Web.Rep.Page

data PageConfig Source #

Configuration options when rendering a Page.

Instances
Eq PageConfig Source # 
Instance details

Defined in Web.Rep.Page

Show PageConfig Source # 
Instance details

Defined in Web.Rep.Page

Generic PageConfig Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep PageConfig :: Type -> Type #

type Rep PageConfig Source # 
Instance details

Defined in Web.Rep.Page

defaultPageConfig :: FilePath -> PageConfig Source #

Default configuration is inline ecma and css, separate html header and body, minified code, with the suggested filename prefix.

data Concerns a Source #

A web page typically is composed of some css, javascript and html.

Concerns abstracts this structural feature of a web page.

Constructors

Concerns 

Fields

Instances
Functor Concerns Source # 
Instance details

Defined in Web.Rep.Page

Methods

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

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

Applicative Concerns Source # 
Instance details

Defined in Web.Rep.Page

Methods

pure :: a -> Concerns a #

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

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

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

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

Foldable Concerns Source # 
Instance details

Defined in Web.Rep.Page

Methods

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

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

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

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

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

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

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

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

toList :: Concerns a -> [a] #

null :: Concerns a -> Bool #

length :: Concerns a -> Int #

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

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

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

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

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

Traversable Concerns Source # 
Instance details

Defined in Web.Rep.Page

Methods

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

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

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

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

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

Defined in Web.Rep.Page

Methods

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

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

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

Defined in Web.Rep.Page

Methods

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

show :: Concerns a -> String #

showList :: [Concerns a] -> ShowS #

Generic (Concerns a) Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

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

Methods

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

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

type Rep (Concerns a) Source # 
Instance details

Defined in Web.Rep.Page

type Rep (Concerns a) = D1 (MetaData "Concerns" "Web.Rep.Page" "web-rep-0.7.0-FbnLiBhVUXzFOFUBGflJ1L" False) (C1 (MetaCons "Concerns" PrefixI True) (S1 (MetaSel (Just "cssConcern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "jsConcern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "htmlConcern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

suffixes :: Concerns FilePath Source #

The common file suffixes of the three concerns.

concernNames :: FilePath -> FilePath -> Concerns FilePath Source #

Create filenames for each Concern element.

data PageConcerns Source #

Is the rendering to include all Concerns (typically in a html file) or be separated (tyypically into separate files and linked in the html file)?

Constructors

Inline 
Separated 
Instances
Eq PageConcerns Source # 
Instance details

Defined in Web.Rep.Page

Show PageConcerns Source # 
Instance details

Defined in Web.Rep.Page

Generic PageConcerns Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep PageConcerns :: Type -> Type #

type Rep PageConcerns Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageConcerns = D1 (MetaData "PageConcerns" "Web.Rep.Page" "web-rep-0.7.0-FbnLiBhVUXzFOFUBGflJ1L" False) (C1 (MetaCons "Inline" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Separated" PrefixI False) (U1 :: Type -> Type))

data PageStructure Source #

Various ways that a Html file can be structured.

Constructors

HeaderBody 
Headless 
Snippet 
Svg 
Instances
Eq PageStructure Source # 
Instance details

Defined in Web.Rep.Page

Show PageStructure Source # 
Instance details

Defined in Web.Rep.Page

Generic PageStructure Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep PageStructure :: Type -> Type #

type Rep PageStructure Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageStructure = D1 (MetaData "PageStructure" "Web.Rep.Page" "web-rep-0.7.0-FbnLiBhVUXzFOFUBGflJ1L" False) ((C1 (MetaCons "HeaderBody" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Headless" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Snippet" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Svg" PrefixI False) (U1 :: Type -> Type)))

data PageRender Source #

Post-processing of page concerns

Constructors

Pretty 
Minified 
NoPost 
Instances
Eq PageRender Source # 
Instance details

Defined in Web.Rep.Page

Show PageRender Source # 
Instance details

Defined in Web.Rep.Page

Generic PageRender Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep PageRender :: Type -> Type #

type Rep PageRender Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageRender = D1 (MetaData "PageRender" "Web.Rep.Page" "web-rep-0.7.0-FbnLiBhVUXzFOFUBGflJ1L" False) (C1 (MetaCons "Pretty" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Minified" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoPost" PrefixI False) (U1 :: Type -> Type)))

Css

type Css = StyleM () #

The Css context is used to collect style rules which are mappings from selectors to style properties. The Css type is a computation in the StyleM monad that just collects and doesn't return anything.

data RepCss Source #

Unifies css as either a Css or as Text.

Constructors

RepCss Css 
RepCssText Text 
Instances
Show RepCss Source # 
Instance details

Defined in Web.Rep.Page

Generic RepCss Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep RepCss :: Type -> Type #

Methods

from :: RepCss -> Rep RepCss x #

to :: Rep RepCss x -> RepCss #

Semigroup RepCss Source # 
Instance details

Defined in Web.Rep.Page

Monoid RepCss Source # 
Instance details

Defined in Web.Rep.Page

type Rep RepCss Source # 
Instance details

Defined in Web.Rep.Page

renderCss :: Css -> Text Source #

Render Css as text.

renderRepCss :: PageRender -> RepCss -> Text Source #

Render RepCss as text.

JS

newtype JS Source #

wrapper for JSAST

Constructors

JS 

Fields

Instances
Eq JS Source # 
Instance details

Defined in Web.Rep.Page

Methods

(==) :: JS -> JS -> Bool #

(/=) :: JS -> JS -> Bool #

Show JS Source # 
Instance details

Defined in Web.Rep.Page

Methods

showsPrec :: Int -> JS -> ShowS #

show :: JS -> String #

showList :: [JS] -> ShowS #

Generic JS Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep JS :: Type -> Type #

Methods

from :: JS -> Rep JS x #

to :: Rep JS x -> JS #

Semigroup JS Source # 
Instance details

Defined in Web.Rep.Page

Methods

(<>) :: JS -> JS -> JS #

sconcat :: NonEmpty JS -> JS #

stimes :: Integral b => b -> JS -> JS #

Monoid JS Source # 
Instance details

Defined in Web.Rep.Page

Methods

mempty :: JS #

mappend :: JS -> JS -> JS #

mconcat :: [JS] -> JS #

type Rep JS Source # 
Instance details

Defined in Web.Rep.Page

type Rep JS = D1 (MetaData "JS" "Web.Rep.Page" "web-rep-0.7.0-FbnLiBhVUXzFOFUBGflJ1L" True) (C1 (MetaCons "JS" PrefixI True) (S1 (MetaSel (Just "unJS") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JSAST)))

data RepJs Source #

Unifies javascript as JSStatement and script as Text.

Constructors

RepJs JS 
RepJsText Text 
Instances
Eq RepJs Source # 
Instance details

Defined in Web.Rep.Page

Methods

(==) :: RepJs -> RepJs -> Bool #

(/=) :: RepJs -> RepJs -> Bool #

Show RepJs Source # 
Instance details

Defined in Web.Rep.Page

Methods

showsPrec :: Int -> RepJs -> ShowS #

show :: RepJs -> String #

showList :: [RepJs] -> ShowS #

Generic RepJs Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep RepJs :: Type -> Type #

Methods

from :: RepJs -> Rep RepJs x #

to :: Rep RepJs x -> RepJs #

Semigroup RepJs Source # 
Instance details

Defined in Web.Rep.Page

Methods

(<>) :: RepJs -> RepJs -> RepJs #

sconcat :: NonEmpty RepJs -> RepJs #

stimes :: Integral b => b -> RepJs -> RepJs #

Monoid RepJs Source # 
Instance details

Defined in Web.Rep.Page

Methods

mempty :: RepJs #

mappend :: RepJs -> RepJs -> RepJs #

mconcat :: [RepJs] -> RepJs #

type Rep RepJs Source # 
Instance details

Defined in Web.Rep.Page

onLoad :: RepJs -> RepJs Source #

Wrap js in standard DOM window loader.

parseJs :: Text -> JS Source #

Convert Text to JS, throwing an error on incorrectness.

renderJs :: JS -> Text Source #

Render JS as Text.

re-export modules

re-exports

data HashMap k v #

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

Instance details

Defined in Data.HashMap.Internal

Methods

bifold :: Monoid m => HashMap m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> HashMap a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> HashMap a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> HashMap a b -> c #

Eq2 HashMap 
Instance details

Defined in Data.HashMap.Internal

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> HashMap a c -> HashMap b d -> Bool #

Ord2 HashMap 
Instance details

Defined in Data.HashMap.Internal

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> HashMap a c -> HashMap b d -> Ordering #

Show2 HashMap 
Instance details

Defined in Data.HashMap.Internal

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> HashMap a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [HashMap a b] -> ShowS #

Hashable2 HashMap 
Instance details

Defined in Data.HashMap.Internal

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> HashMap a b -> Int #

FunctorWithIndex k (HashMap k) 
Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (k -> a -> b) -> HashMap k a -> HashMap k b #

imapped :: IndexedSetter k (HashMap k a) (HashMap k b) a b #

FoldableWithIndex k (HashMap k) 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (k -> a -> m) -> HashMap k a -> m #

ifolded :: IndexedFold k (HashMap k a) a #

ifoldr :: (k -> a -> b -> b) -> b -> HashMap k a -> b #

ifoldl :: (k -> b -> a -> b) -> b -> HashMap k a -> b #

ifoldr' :: (k -> a -> b -> b) -> b -> HashMap k a -> b #

ifoldl' :: (k -> b -> a -> b) -> b -> HashMap k a -> b #

TraversableWithIndex k (HashMap k) 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (k -> a -> f b) -> HashMap k a -> f (HashMap k b) #

itraversed :: IndexedTraversal k (HashMap k a) (HashMap k b) a b #

Functor (HashMap k) 
Instance details

Defined in Data.HashMap.Internal

Methods

fmap :: (a -> b) -> HashMap k a -> HashMap k b #

(<$) :: a -> HashMap k b -> HashMap k a #

Foldable (HashMap k) 
Instance details

Defined in Data.HashMap.Internal

Methods

fold :: Monoid m => HashMap k m -> 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] #

null :: HashMap k a -> Bool #

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 #

sum :: Num a => HashMap k a -> a #

product :: Num a => HashMap k a -> a #

Traversable (HashMap k) 
Instance details

Defined in Data.HashMap.Internal

Methods

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

sequenceA :: Applicative f => HashMap k (f a) -> f (HashMap k a) #

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

sequence :: Monad m => HashMap k (m a) -> m (HashMap k a) #

Eq k => Eq1 (HashMap k) 
Instance details

Defined in Data.HashMap.Internal

Methods

liftEq :: (a -> b -> Bool) -> HashMap k a -> HashMap k b -> Bool #

Ord k => Ord1 (HashMap k) 
Instance details

Defined in Data.HashMap.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> HashMap k a -> HashMap k b -> Ordering #

(Eq k, Hashable k, Read k) => Read1 (HashMap k) 
Instance details

Defined in Data.HashMap.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (HashMap k a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [HashMap k a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (HashMap k a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [HashMap k a] #

Show k => Show1 (HashMap k) 
Instance details

Defined in Data.HashMap.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> HashMap k a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [HashMap k a] -> ShowS #

Hashable k => Hashable1 (HashMap k) 
Instance details

Defined in Data.HashMap.Internal

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> HashMap k a -> Int #

(Eq k, Hashable k) => IsList (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Associated Types

type Item (HashMap k v) :: Type #

Methods

fromList :: [Item (HashMap k v)] -> HashMap k v #

fromListN :: Int -> [Item (HashMap k v)] -> HashMap k v #

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

(Eq k, Eq v) => Eq (HashMap k v)

Note that, in the presence of hash collisions, equal HashMaps may behave differently, i.e. substitutivity may be violated:

>>> data D = A | B deriving (Eq, Show)
>>> instance Hashable D where hashWithSalt salt _d = salt
>>> x = fromList [(A,1), (B,2)]
>>> y = fromList [(B,2), (A,1)]
>>> x == y
True
>>> toList x
[(A,1),(B,2)]
>>> toList y
[(B,2),(A,1)]

In general, the lack of substitutivity can be observed with any function that depends on the key ordering, such as folds and traversals.

Instance details

Defined in Data.HashMap.Internal

Methods

(==) :: HashMap k v -> HashMap k v -> Bool #

(/=) :: HashMap k v -> HashMap k v -> Bool #

(Data k, Data v, Eq k, Hashable k) => Data (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

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 :: (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) #

(Ord k, Ord v) => Ord (HashMap k v)

The ordering is total and consistent with the Eq instance. However, nothing else about the ordering is specified, and it may change from version to version of either this package or of hashable.

Instance details

Defined in Data.HashMap.Internal

Methods

compare :: HashMap k v -> HashMap k v -> Ordering #

(<) :: HashMap k v -> HashMap k v -> Bool #

(<=) :: HashMap k v -> HashMap k v -> Bool #

(>) :: HashMap k v -> HashMap k v -> Bool #

(>=) :: HashMap k v -> HashMap k v -> Bool #

max :: HashMap k v -> HashMap k v -> HashMap k v #

min :: HashMap k v -> HashMap k v -> HashMap k v #

(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) 
Instance details

Defined in Data.HashMap.Internal

(Show k, Show v) => Show (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

showsPrec :: Int -> HashMap k v -> ShowS #

show :: HashMap k v -> String #

showList :: [HashMap k v] -> ShowS #

(Eq k, Hashable k) => Semigroup (HashMap k v)

<> = union

If a key occurs in both maps, the mapping from the first will be the mapping in the result.

Examples

Expand
>>> fromList [(1,'a'),(2,'b')] <> fromList [(2,'c'),(3,'d')]
fromList [(1,'a'),(2,'b'),(3,'d')]
Instance details

Defined in Data.HashMap.Internal

Methods

(<>) :: HashMap k v -> HashMap k v -> HashMap k v #

sconcat :: NonEmpty (HashMap k v) -> HashMap k v #

stimes :: Integral b => b -> HashMap k v -> HashMap k v #

(Eq k, Hashable k) => Monoid (HashMap k v)

mempty = empty

mappend = union

If a key occurs in both maps, the mapping from the first will be the mapping in the result.

Examples

Expand
>>> mappend (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')])
fromList [(1,'a'),(2,'b'),(3,'d')]
Instance details

Defined in Data.HashMap.Internal

Methods

mempty :: HashMap k v #

mappend :: HashMap k v -> HashMap k v -> HashMap k v #

mconcat :: [HashMap k v] -> HashMap k v #

(Hashable k, Hashable v) => Hashable (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

hashWithSalt :: Int -> HashMap k v -> Int #

hash :: HashMap k v -> Int #

(NFData k, NFData v) => NFData (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

rnf :: HashMap k v -> () #

(Eq k, Hashable k) => Ixed (HashMap k a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (HashMap k a) -> Traversal' (HashMap k a) (IxValue (HashMap k a)) #

(Eq k, Hashable k) => At (HashMap k a) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (HashMap k a) -> Lens' (HashMap k a) (Maybe (IxValue (HashMap k a))) #

(Hashable k, Eq k) => Wrapped (HashMap k a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (HashMap k a) :: Type #

Methods

_Wrapped' :: Iso' (HashMap k a) (Unwrapped (HashMap k a)) #

AsEmpty (HashMap k a) 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' (HashMap k a) () #

(t ~ HashMap k' a', Hashable k, Eq k) => Rewrapped (HashMap k a) t

Use wrapping fromList. Unwrapping returns some permutation of the list.

Instance details

Defined in Control.Lens.Wrapped

c ~ d => Each (HashMap c a) (HashMap d b) a b
each :: Traversal (HashMap c a) (HashMap c b) a b
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal (HashMap c a) (HashMap d b) a b #

type Item (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

type Item (HashMap k v) = (k, v)
type Index (HashMap k a) 
Instance details

Defined in Control.Lens.At

type Index (HashMap k a) = k
type IxValue (HashMap k a) 
Instance details

Defined in Control.Lens.At

type IxValue (HashMap k a) = a
type Unwrapped (HashMap k a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (HashMap k a) = [(k, a)]