web-rep-0.1.2: representations of a web pag

Safe HaskellNone
LanguageHaskell2010

Web.Page.Types

Documentation

data Page Source #

Constructors

Page [Html ()] [Html ()] PageCss PageJs PageJs (Html ()) (Html ()) 
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 PageText Source #

Constructors

PageText [Text] [Text] Text Text Text Text Text 
Instances
Show PageText Source # 
Instance details

Defined in Web.Page.Types

Generic PageText Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep PageText :: Type -> Type #

Methods

from :: PageText -> Rep PageText x #

to :: Rep PageText x -> PageText #

type Rep PageText Source # 
Instance details

Defined in Web.Page.Types

data Concern Source #

Constructors

Css 
Js 
Html 
Instances
Eq Concern Source # 
Instance details

Defined in Web.Page.Types

Methods

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

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

Show Concern Source # 
Instance details

Defined in Web.Page.Types

Generic Concern Source # 
Instance details

Defined in Web.Page.Types

Associated Types

type Rep Concern :: Type -> Type #

Methods

from :: Concern -> Rep Concern x #

to :: Rep Concern x -> Concern #

type Rep Concern Source # 
Instance details

Defined in Web.Page.Types

type Rep Concern = D1 (MetaData "Concern" "Web.Page.Types" "web-rep-0.1.2-DZZ9ljrqQSJ9eWvBqn9RmN" False) (C1 (MetaCons "Css" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Js" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Html" PrefixI False) (U1 :: Type -> Type)))

data Concerns a Source #

Constructors

Concerns a a a 
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.1.2-DZZ9ljrqQSJ9eWvBqn9RmN" False) (C1 (MetaCons "Concerns" PrefixI True) (S1 (MetaSel (Just "css") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "js") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "html") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))))

data PageConcerns Source #

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.1.2-DZZ9ljrqQSJ9eWvBqn9RmN" False) (C1 (MetaCons "Inline" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Separated" PrefixI False) (U1 :: Type -> Type))

data PageStructure Source #

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.1.2-DZZ9ljrqQSJ9eWvBqn9RmN" 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 #

Constructors

Pretty 
Minified 
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.1.2-DZZ9ljrqQSJ9eWvBqn9RmN" False) (C1 (MetaCons "Pretty" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Minified" PrefixI False) (U1 :: Type -> Type))