web-rep-0.10.2.0: representations of a web page
Safe HaskellSafe-Inferred
LanguageGHC2021

Web.Rep.Shared

Synopsis

Documentation

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

Instances details
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 #

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 #

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

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 #

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

the common usage, where the representation domain is Html

oneRep :: Monad 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

Instances details
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 #

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

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 #

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

message Source #

Arguments

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

Parser

-> (Text -> a -> r)

create initial object from name and initial value

-> a

initial value

-> a

default value

-> SharedRepF m r a 

Like register, but does not put a value into the HashMap on instantiation, consumes the value when found in the HashMap, and substitutes a default on lookup failure

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