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

Web.Rep.Page

Description

Representations of a web page, covering Html, CSS & JS artifacts.

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.12.1.0-mljk32nWcoKJWZerP610X" '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.12.1.0-mljk32nWcoKJWZerP610X" '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 

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.12.1.0-mljk32nWcoKJWZerP610X" '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)))

newtype Css Source #

css as a string.

Constructors

Css 

Instances

Instances details
Monoid Css Source # 
Instance details

Defined in Web.Rep.Page

Methods

mempty :: Css #

mappend :: Css -> Css -> Css #

mconcat :: [Css] -> Css #

Semigroup Css Source # 
Instance details

Defined in Web.Rep.Page

Methods

(<>) :: Css -> Css -> Css #

sconcat :: NonEmpty Css -> Css #

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

Generic Css Source # 
Instance details

Defined in Web.Rep.Page

Associated Types

type Rep Css :: Type -> Type #

Methods

from :: Css -> Rep Css x #

to :: Rep Css x -> Css #

Show Css Source # 
Instance details

Defined in Web.Rep.Page

Methods

showsPrec :: Int -> Css -> ShowS #

show :: Css -> String #

showList :: [Css] -> ShowS #

Eq Css Source # 
Instance details

Defined in Web.Rep.Page

Methods

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

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

type Rep Css Source # 
Instance details

Defined in Web.Rep.Page

type Rep Css = D1 ('MetaData "Css" "Web.Rep.Page" "web-rep-0.12.1.0-mljk32nWcoKJWZerP610X" 'True) (C1 ('MetaCons "Css" 'PrefixI 'True) (S1 ('MetaSel ('Just "cssByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

renderCss :: RenderStyle -> Css -> ByteString Source #

Render Css as text.

cssColorScheme :: Css Source #

Css snippet for reponsiveness to preferred color-scheme.

newtype Js Source #

Javascript as string

Constructors

Js 

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.12.1.0-mljk32nWcoKJWZerP610X" 'True) (C1 ('MetaCons "Js" 'PrefixI 'True) (S1 ('MetaSel ('Just "jsByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

onLoad :: Js -> Js Source #

Add the windows.onload assignment