Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Page = Page {}
- data PageConfig = PageConfig {}
- defaultPageConfig :: FilePath -> PageConfig
- data Concerns a = Concerns {
- cssConcern :: a
- jsConcern :: a
- htmlConcern :: a
- suffixes :: Concerns FilePath
- concernNames :: FilePath -> FilePath -> Concerns FilePath
- data PageConcerns
- data PageStructure
- = HeaderBody
- | Headless
- | Snippet
- | Svg
- data PageRender
- type Css = StyleM ()
- data PageCss
- renderCss :: Css -> Text
- renderPageCss :: PageRender -> PageCss -> Text
- newtype JS = JS {}
- data PageJs
- = PageJs JS
- | PageJsText Text
- onLoad :: PageJs -> PageJs
- renderPageJs :: PageRender -> PageJs -> Text
- parseJs :: Text -> JS
- renderJs :: JS -> Text
- data Element = Element {}
- data RepF r a = Rep {}
- type Rep a = RepF (Html ()) a
- oneRep :: (Monad m, MonadIO m) => Rep a -> (Rep a -> HashMap Text Text -> m ()) -> StateT (HashMap Text Text) m (HashMap Text Text, Either Text a)
- newtype SharedRepF m r a = SharedRep {}
- type SharedRep m a = SharedRepF m (Html ()) a
- runOnce :: Monad m => SharedRep m a -> (Html () -> HashMap Text Text -> m ()) -> m (HashMap Text Text, Either Text a)
- zeroState :: Monad m => SharedRep m a -> m (Html (), (HashMap Text Text, Either Text a))
Documentation
Components of a web page.
A web page typically can take many forms but still be the same web page. For example, css can be linked to in a separate file, or can be inline within html, but still be the same css. This type represents the practical components of what makes up a web page.
Instances
Show Page Source # | |
Generic Page Source # | |
Semigroup Page Source # | |
Monoid Page Source # | |
type Rep Page Source # | |
Defined in Web.Page.Types type Rep Page = D1 (MetaData "Page" "Web.Page.Types" "web-rep-0.2.0-FIwogXICtLkCMjX6u6XK6R" False) (C1 (MetaCons "Page" PrefixI True) ((S1 (MetaSel (Just "libsCss") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Html ()]) :*: (S1 (MetaSel (Just "libsJs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Html ()]) :*: S1 (MetaSel (Just "cssBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PageCss))) :*: ((S1 (MetaSel (Just "jsGlobal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PageJs) :*: S1 (MetaSel (Just "jsOnLoad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PageJs)) :*: (S1 (MetaSel (Just "htmlHeader") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Html ())) :*: S1 (MetaSel (Just "htmlBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Html ())))))) |
data PageConfig Source #
Configuration of the rendering of a web page
PageConfig | |
|
Instances
A web page typically is composed of css, javascript and html
Concerns
abstracts this compositional feature of a web page.
Concerns | |
|
Instances
concernNames :: FilePath -> FilePath -> Concerns FilePath Source #
create filenames for each Concern element.
data PageConcerns Source #
Is the rendering to include all Concerns or be separated?
Instances
Eq PageConcerns Source # | |
Defined in Web.Page.Types (==) :: PageConcerns -> PageConcerns -> Bool # (/=) :: PageConcerns -> PageConcerns -> Bool # | |
Show PageConcerns Source # | |
Defined in Web.Page.Types showsPrec :: Int -> PageConcerns -> ShowS # show :: PageConcerns -> String # showList :: [PageConcerns] -> ShowS # | |
Generic PageConcerns Source # | |
Defined in Web.Page.Types type Rep PageConcerns :: Type -> Type # from :: PageConcerns -> Rep PageConcerns x # to :: Rep PageConcerns x -> PageConcerns # | |
type Rep PageConcerns Source # | |
data PageStructure Source #
Various ways that a Html file can be structured.
Instances
Eq PageStructure Source # | |
Defined in Web.Page.Types (==) :: PageStructure -> PageStructure -> Bool # (/=) :: PageStructure -> PageStructure -> Bool # | |
Show PageStructure Source # | |
Defined in Web.Page.Types showsPrec :: Int -> PageStructure -> ShowS # show :: PageStructure -> String # showList :: [PageStructure] -> ShowS # | |
Generic PageStructure Source # | |
Defined in Web.Page.Types type Rep PageStructure :: Type -> Type # from :: PageStructure -> Rep PageStructure x # to :: Rep PageStructure x -> PageStructure # | |
type Rep PageStructure Source # | |
Defined in Web.Page.Types type Rep PageStructure = D1 (MetaData "PageStructure" "Web.Page.Types" "web-rep-0.2.0-FIwogXICtLkCMjX6u6XK6R" 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
Instances
Eq PageRender Source # | |
Defined in Web.Page.Types (==) :: PageRender -> PageRender -> Bool # (/=) :: PageRender -> PageRender -> Bool # | |
Show PageRender Source # | |
Defined in Web.Page.Types showsPrec :: Int -> PageRender -> ShowS # show :: PageRender -> String # showList :: [PageRender] -> ShowS # | |
Generic PageRender Source # | |
Defined in Web.Page.Types type Rep PageRender :: Type -> Type # from :: PageRender -> Rep PageRender x # to :: Rep PageRender x -> PageRender # | |
type Rep PageRender Source # | |
Defined in Web.Page.Types |
unifies css as a Clay.Css and css as Text
Instances
Show PageCss Source # | |
Generic PageCss Source # | |
Semigroup PageCss Source # | |
Monoid PageCss Source # | |
type Rep PageCss Source # | |
Defined in Web.Page.Types type Rep PageCss = D1 (MetaData "PageCss" "Web.Page.Types" "web-rep-0.2.0-FIwogXICtLkCMjX6u6XK6R" False) (C1 (MetaCons "PageCss" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Css)) :+: C1 (MetaCons "PageCssText" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
renderPageCss :: PageRender -> PageCss -> Text Source #
render PageCss as text
wrapper for JSAST
unify JSStatement javascript and text-rendered script
Instances
Eq PageJs Source # | |
Show PageJs Source # | |
Generic PageJs Source # | |
Semigroup PageJs Source # | |
Monoid PageJs Source # | |
type Rep PageJs Source # | |
Defined in Web.Page.Types type Rep PageJs = D1 (MetaData "PageJs" "Web.Page.Types" "web-rep-0.2.0-FIwogXICtLkCMjX6u6XK6R" False) (C1 (MetaCons "PageJs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JS)) :+: C1 (MetaCons "PageJsText" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
renderPageJs :: PageRender -> PageJs -> Text Source #
render PageJs as text
Abstracted message event element
Instances
Eq Element Source # | |
Show Element Source # | |
Generic Element Source # | |
ToJSON Element Source # | |
Defined in Web.Page.Types | |
FromJSON Element Source # | |
type Rep Element Source # | |
Defined in Web.Page.Types type Rep Element = D1 (MetaData "Element" "Web.Page.Types" "web-rep-0.2.0-FIwogXICtLkCMjX6u6XK6R" False) (C1 (MetaCons "Element" PrefixI True) (S1 (MetaSel (Just "element") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "value") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
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 #
type SharedRep m a = SharedRepF m (Html ()) a Source #