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

Web.Rep.Page

Synopsis

Documentation

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

Instances details
Monoid Page Source # 
Instance details

Defined in Web.Rep.Page

Methods

mempty :: Page #

mappend :: Page -> Page -> Page #

mconcat :: [Page] -> 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 #

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 #

Show Page Source # 
Instance details

Defined in Web.Rep.Page

Methods

showsPrec :: Int -> Page -> ShowS #

show :: Page -> String #

showList :: [Page] -> ShowS #

type Rep Page Source # 
Instance details

Defined in Web.Rep.Page

data PageConfig Source #

Configuration options when rendering a Page.

Instances

Instances details
Generic PageConfig Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep PageConfig :: Type -> Type #

Show PageConfig Source # 
Instance details

Defined in Web.Rep.Page

Eq PageConfig Source # 
Instance details

Defined in Web.Rep.Page

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

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

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

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 #

Functor Concerns Source # 
Instance details

Defined in Web.Rep.Page

Methods

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

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

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 #

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 #

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

Defined in Web.Rep.Page

Methods

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

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

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.10.2.0-B2YHxkxT2gHDHhcJpNYihj" '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

Instances details
Generic PageConcerns Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep PageConcerns :: Type -> Type #

Show PageConcerns Source # 
Instance details

Defined in Web.Rep.Page

Eq PageConcerns Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageConcerns Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageConcerns = D1 ('MetaData "PageConcerns" "Web.Rep.Page" "web-rep-0.10.2.0-B2YHxkxT2gHDHhcJpNYihj" '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

Instances details
Generic PageStructure Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep PageStructure :: Type -> Type #

Show PageStructure Source # 
Instance details

Defined in Web.Rep.Page

Eq PageStructure Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageStructure Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageStructure = D1 ('MetaData "PageStructure" "Web.Rep.Page" "web-rep-0.10.2.0-B2YHxkxT2gHDHhcJpNYihj" '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

Instances details
Generic PageRender Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep PageRender :: Type -> Type #

Show PageRender Source # 
Instance details

Defined in Web.Rep.Page

Eq PageRender Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageRender Source # 
Instance details

Defined in Web.Rep.Page

type Rep PageRender = D1 ('MetaData "PageRender" "Web.Rep.Page" "web-rep-0.10.2.0-B2YHxkxT2gHDHhcJpNYihj" '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)))

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

Instances details
Monoid RepCss Source # 
Instance details

Defined in Web.Rep.Page

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

Show RepCss Source # 
Instance details

Defined in Web.Rep.Page

type Rep RepCss Source # 
Instance details

Defined in Web.Rep.Page

type Rep RepCss = D1 ('MetaData "RepCss" "Web.Rep.Page" "web-rep-0.10.2.0-B2YHxkxT2gHDHhcJpNYihj" 'False) (C1 ('MetaCons "RepCss" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Css)) :+: C1 ('MetaCons "RepCssText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

renderCss :: Css -> Text Source #

Render Css as text.

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

Render RepCss as text.

newtype JS Source #

wrapper for JSAST

Constructors

JS 

Fields

Instances

Instances details
Monoid JS Source # 
Instance details

Defined in Web.Rep.Page

Methods

mempty :: JS #

mappend :: JS -> JS -> JS #

mconcat :: [JS] -> 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 #

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 #

Show JS Source # 
Instance details

Defined in Web.Rep.Page

Methods

showsPrec :: Int -> JS -> ShowS #

show :: JS -> String #

showList :: [JS] -> ShowS #

Eq JS Source # 
Instance details

Defined in Web.Rep.Page

Methods

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

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

type Rep JS Source # 
Instance details

Defined in Web.Rep.Page

type Rep JS = D1 ('MetaData "JS" "Web.Rep.Page" "web-rep-0.10.2.0-B2YHxkxT2gHDHhcJpNYihj" '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

Instances details
Monoid RepJs Source # 
Instance details

Defined in Web.Rep.Page

Methods

mempty :: RepJs #

mappend :: RepJs -> RepJs -> RepJs #

mconcat :: [RepJs] -> 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 #

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 #

Show RepJs Source # 
Instance details

Defined in Web.Rep.Page

Methods

showsPrec :: Int -> RepJs -> ShowS #

show :: RepJs -> String #

showList :: [RepJs] -> ShowS #

Eq RepJs Source # 
Instance details

Defined in Web.Rep.Page

Methods

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

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

type Rep RepJs Source # 
Instance details

Defined in Web.Rep.Page

type Rep RepJs = D1 ('MetaData "RepJs" "Web.Rep.Page" "web-rep-0.10.2.0-B2YHxkxT2gHDHhcJpNYihj" 'False) (C1 ('MetaCons "RepJs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JS)) :+: C1 ('MetaCons "RepJsText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

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.