web-rep-0.4.0: representations of a web page

Safe HaskellNone
LanguageHaskell2010

Web.Page

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.Page.Types

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.Page.Types

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.Page.Types

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.Page.Types

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.Page.Types

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.Page.Types

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.

Constructors

SharedRep 

Fields

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

Defined in Web.Page.Types

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.Page.Types

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.Page.Types

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.Page.Types

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

data Element Source #

A key-value Text pair as the realistic datatype that zips across the interface between a page and haskell.

Constructors

Element 

Fields

Instances
Eq Element Source # 
Instance details

Defined in Web.Page.Types

Methods

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

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

Show Element Source # 
Instance details

Defined in Web.Page.Types

Generic Element Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep Element :: Type -> Type #

Methods

from :: Element -> Rep Element x #

to :: Rep Element x -> Element #

ToJSON Element Source # 
Instance details

Defined in Web.Page.Types

FromJSON Element Source # 
Instance details

Defined in Web.Page.Types

type Rep Element Source # 
Instance details

Defined in Web.Page.Types

type Rep Element = D1 (MetaData "Element" "Web.Page.Types" "web-rep-0.4.0-1tSvqwxGHX6oFAw2f4hvL" False) (C1 (MetaCons "Element" PrefixI True) (S1 (MetaSel (Just "element") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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)

Web Page 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.Page.Types

Methods

showsPrec :: Int -> Page -> ShowS #

show :: Page -> String #

showList :: [Page] -> ShowS #

Generic Page Source # 
Instance details

Defined in Web.Page.Types

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.Page.Types

Methods

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

sconcat :: NonEmpty Page -> Page #

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

Monoid Page Source # 
Instance details

Defined in Web.Page.Types

Methods

mempty :: Page #

mappend :: Page -> Page -> Page #

mconcat :: [Page] -> Page #

type Rep Page Source # 
Instance details

Defined in Web.Page.Types

data PageConfig Source #

Configuration options when rendering a Page.

Instances
Eq PageConfig Source # 
Instance details

Defined in Web.Page.Types

Show PageConfig Source # 
Instance details

Defined in Web.Page.Types

Generic PageConfig Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep PageConfig :: Type -> Type #

type Rep PageConfig Source # 
Instance details

Defined in Web.Page.Types

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.Page.Types

Methods

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

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

Applicative Concerns Source # 
Instance details

Defined in Web.Page.Types

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.Page.Types

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.Page.Types

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.Page.Types

Methods

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

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

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

Defined in Web.Page.Types

Methods

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

show :: Concerns a -> String #

showList :: [Concerns a] -> ShowS #

Generic (Concerns a) Source # 
Instance details

Defined in Web.Page.Types

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.Page.Types

type Rep (Concerns a) = D1 (MetaData "Concerns" "Web.Page.Types" "web-rep-0.4.0-1tSvqwxGHX6oFAw2f4hvL" 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.Page.Types

Show PageConcerns Source # 
Instance details

Defined in Web.Page.Types

Generic PageConcerns Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep PageConcerns :: Type -> Type #

type Rep PageConcerns Source # 
Instance details

Defined in Web.Page.Types

type Rep PageConcerns = D1 (MetaData "PageConcerns" "Web.Page.Types" "web-rep-0.4.0-1tSvqwxGHX6oFAw2f4hvL" 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.Page.Types

Show PageStructure Source # 
Instance details

Defined in Web.Page.Types

Generic PageStructure Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep PageStructure :: Type -> Type #

type Rep PageStructure Source # 
Instance details

Defined in Web.Page.Types

type Rep PageStructure = D1 (MetaData "PageStructure" "Web.Page.Types" "web-rep-0.4.0-1tSvqwxGHX6oFAw2f4hvL" 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.Page.Types

Show PageRender Source # 
Instance details

Defined in Web.Page.Types

Generic PageRender Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep PageRender :: Type -> Type #

type Rep PageRender Source # 
Instance details

Defined in Web.Page.Types

type Rep PageRender = D1 (MetaData "PageRender" "Web.Page.Types" "web-rep-0.4.0-1tSvqwxGHX6oFAw2f4hvL" 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 PageCss Source #

Unifies css as either a Css or as Text.

Constructors

PageCss Css 
PageCssText Text 
Instances
Show PageCss Source # 
Instance details

Defined in Web.Page.Types

Generic PageCss Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep PageCss :: Type -> Type #

Methods

from :: PageCss -> Rep PageCss x #

to :: Rep PageCss x -> PageCss #

Semigroup PageCss Source # 
Instance details

Defined in Web.Page.Types

Monoid PageCss Source # 
Instance details

Defined in Web.Page.Types

type Rep PageCss Source # 
Instance details

Defined in Web.Page.Types

renderCss :: Css -> Text Source #

Render Css as text.

JS

newtype JS Source #

wrapper for JSAST

Constructors

JS 

Fields

Instances
Eq JS Source # 
Instance details

Defined in Web.Page.Types

Methods

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

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

Show JS Source # 
Instance details

Defined in Web.Page.Types

Methods

showsPrec :: Int -> JS -> ShowS #

show :: JS -> String #

showList :: [JS] -> ShowS #

Generic JS Source # 
Instance details

Defined in Web.Page.Types

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.Page.Types

Methods

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

sconcat :: NonEmpty JS -> JS #

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

Monoid JS Source # 
Instance details

Defined in Web.Page.Types

Methods

mempty :: JS #

mappend :: JS -> JS -> JS #

mconcat :: [JS] -> JS #

type Rep JS Source # 
Instance details

Defined in Web.Page.Types

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

data PageJs Source #

Unifies javascript as JSStatement and script as Text.

Constructors

PageJs JS 
PageJsText Text 
Instances
Eq PageJs Source # 
Instance details

Defined in Web.Page.Types

Methods

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

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

Show PageJs Source # 
Instance details

Defined in Web.Page.Types

Generic PageJs Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep PageJs :: Type -> Type #

Methods

from :: PageJs -> Rep PageJs x #

to :: Rep PageJs x -> PageJs #

Semigroup PageJs Source # 
Instance details

Defined in Web.Page.Types

Monoid PageJs Source # 
Instance details

Defined in Web.Page.Types

type Rep PageJs Source # 
Instance details

Defined in Web.Page.Types

onLoad :: PageJs -> PageJs 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 Value #

A JSON value represented as a Haskell value.

Instances
Eq Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

Data Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value #

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

Read Value 
Instance details

Defined in Data.Aeson.Types.Internal

Show Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

fromString :: String -> Value #

Generic Value 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Lift Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

lift :: Value -> Q Exp #

Hashable Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

ToJSON Value 
Instance details

Defined in Data.Aeson.Types.ToJSON

KeyValue Object

Constructs a singleton HashMap. For calling functions that demand an Object for constructing objects. To be used in conjunction with mconcat. Prefer to use object where possible.

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Object #

KeyValue Pair 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Pair #

FromJSON Value 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: Value -> () #

FromString Encoding 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromString Value 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

fromString :: String -> Value

GToJSON Encoding arity (U1 :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a -> U1 a -> Encoding

GToJSON Value arity (V1 :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a -> V1 a -> Value

GToJSON Value arity (U1 :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a -> U1 a -> Value

ToJSON1 f => GToJSON Encoding One (Rec1 f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding One a -> Rec1 f a -> Encoding

ToJSON1 f => GToJSON Value One (Rec1 f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value One a -> Rec1 f a -> Value

ToJSON a => GToJSON Encoding arity (K1 i a :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a0 -> K1 i a a0 -> Encoding

(EncodeProduct arity a, EncodeProduct arity b) => GToJSON Encoding arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a0 -> (a :*: b) a0 -> Encoding

ToJSON a => GToJSON Value arity (K1 i a :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a0 -> K1 i a a0 -> Value

(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON Value arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a0 -> (a :*: b) a0 -> Value

(ToJSON1 f, GToJSON Encoding One g) => GToJSON Encoding One (f :.: g) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding One a -> (f :.: g) a -> Encoding

(ToJSON1 f, GToJSON Value One g) => GToJSON Value One (f :.: g) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value One a -> (f :.: g) a -> Value

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

(GToJSON Encoding arity a, ConsToJSON Encoding arity a, Constructor c) => SumToJSON' TwoElemArray Encoding arity (C1 c a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

sumToJSON' :: Options -> ToArgs Encoding arity a0 -> C1 c a a0 -> Tagged TwoElemArray Encoding

(GToJSON Value arity a, ConsToJSON Value arity a, Constructor c) => SumToJSON' TwoElemArray Value arity (C1 c a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

sumToJSON' :: Options -> ToArgs Value arity a0 -> C1 c a a0 -> Tagged TwoElemArray Value

type Rep Value 
Instance details

Defined in Data.Aeson.Types.Internal

finally #

Arguments

:: IO a

computation to run first

-> IO b

computation to run afterward (even if an exception was raised)

-> IO a 

A specialised variant of bracket with just a computation to run afterward.

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
KeyValue Object

Constructs a singleton HashMap. For calling functions that demand an Object for constructing objects. To be used in conjunction with mconcat. Prefer to use object where possible.

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Object #

Eq2 HashMap 
Instance details

Defined in Data.HashMap.Base

Methods

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

Ord2 HashMap 
Instance details

Defined in Data.HashMap.Base

Methods

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

Show2 HashMap 
Instance details

Defined in Data.HashMap.Base

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.Base

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.Base

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.Base

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.Base

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

ToJSONKey k => ToJSON1 (HashMap k) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> HashMap k a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [HashMap k a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> HashMap k a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [HashMap k a] -> Encoding #

(FromJSONKey k, Eq k, Hashable k) => FromJSON1 (HashMap k) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

Eq k => Eq1 (HashMap k) 
Instance details

Defined in Data.HashMap.Base

Methods

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

Ord k => Ord1 (HashMap k) 
Instance details

Defined in Data.HashMap.Base

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.Base

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.Base

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.Base

Methods

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

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

Defined in Data.HashMap.Base

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) 
Instance details

Defined in Data.HashMap.Base

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.Base

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 order is total.

Note: Because the hash is not guaranteed to be stable across library versions, OSes, or architectures, neither is an actual order of elements in HashMap or an result of compare.is stable.

Instance details

Defined in Data.HashMap.Base

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.Base

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

Defined in Data.HashMap.Base

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) 
Instance details

Defined in Data.HashMap.Base

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) 
Instance details

Defined in Data.HashMap.Base

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.Base

Methods

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

hash :: HashMap k v -> Int #

(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.HashMap.Base

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.Base

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)]

fromList :: IsList l => [Item l] -> l #

The fromList function constructs the structure l from the given list of Item l

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Expand

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2

sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () #

Evaluate each action in the structure from left to right, and ignore the results. For a version that doesn't ignore the results see sequenceA.

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances
Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

KeyValue Object

Constructs a singleton HashMap. For calling functions that demand an Object for constructing objects. To be used in conjunction with mconcat. Prefer to use object where possible.

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Object #

KeyValue Pair 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Text -> v -> Pair #

ToJSONKey Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Chunk Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem Text :: Type #

Val Text 
Instance details

Defined in Clay.Property

Methods

value :: Text -> Value #

ShowQ Text 
Instance details

Defined in Text.InterpolatedString.Perl6

Methods

showQ :: Text -> String #

Ixed Text 
Instance details

Defined in Control.Lens.At

AsEmpty Text 
Instance details

Defined in Control.Lens.Empty

Methods

_Empty :: Prism' Text () #

Reversing Text 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversing :: Text -> Text #

ToHtml Text 
Instance details

Defined in Lucid.Base

Methods

toHtml :: Monad m => Text -> HtmlT m () #

toHtmlRaw :: Monad m => Text -> HtmlT m () #

Parsable Text 
Instance details

Defined in Web.Scotty.Action

Strict Text Text 
Instance details

Defined in Control.Lens.Iso

Methods

strict :: Iso' Text Text0 #

Term Text Attribute

Some terms (like style_, title_) can be used for attributes as well as elements.

Instance details

Defined in Lucid.Base

Methods

term :: Text -> Text -> Attribute #

termWith :: Text -> [Attribute] -> Text -> Attribute #

TermRaw Text Attribute

Some termRaws (like style_, title_) can be used for attributes as well as elements.

Instance details

Defined in Lucid.Base

(a ~ Char, b ~ Char) => Each Text Text a b
each :: Traversal Text Text Char Char
Instance details

Defined in Control.Lens.Each

Methods

each :: Traversal Text Text a b #

Cons Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Cons :: Prism Text Text (Char, Text) (Char, Text) #

Snoc Text Text Char Char 
Instance details

Defined in Control.Lens.Cons

Methods

_Snoc :: Prism Text Text (Text, Char) (Text, Char) #

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

(Monad m, a ~ ()) => TermRaw Text (HtmlT m a)

Given children immediately, just use that and expect no attributes.

Instance details

Defined in Lucid.Base

Methods

termRaw :: Text -> Text -> HtmlT m a #

termRawWith :: Text -> [Attribute] -> Text -> HtmlT m a #

type State Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State Text = Buffer
type ChunkElem Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char
type Index Text 
Instance details

Defined in Control.Lens.At

type Index Text = Int
type IxValue Text 
Instance details

Defined in Control.Lens.At

pack :: String -> Text #

O(n) Convert a String into a Text. Subject to fusion. Performs replacement on invalid scalar values.

unpack :: Text -> String #

O(n) Convert a Text into a String. Subject to fusion.

toStrict :: Text -> Text #

O(n) Convert a lazy Text into a strict Text.

bool :: a -> a -> Bool -> a #

Case analysis for the Bool type. bool x y p evaluates to x when p is False, and evaluates to y when p is True.

This is equivalent to if p then y else x; that is, one can think of it as an if-then-else construct with its arguments reordered.

Examples

Expand

Basic usage:

>>> bool "foo" "bar" True
"bar"
>>> bool "foo" "bar" False
"foo"

Confirm that bool x y p and if p then y else x are equivalent:

>>> let p = True; x = "bar"; y = "foo"
>>> bool x y p == if p then y else x
True
>>> let p = False
>>> bool x y p == if p then y else x
True

Since: base-4.7.0.0