Safe Haskell | None |
---|---|
Language | Haskell98 |
- type Html = Markup
- shamlet :: QuasiQuoter
- shamletFile :: FilePath -> Q Exp
- xshamlet :: QuasiQuoter
- xshamletFile :: FilePath -> Q Exp
- type HtmlUrl url = Render url -> Html
- hamlet :: QuasiQuoter
- hamletFile :: FilePath -> Q Exp
- hamletFileReload :: FilePath -> Q Exp
- ihamletFileReload :: FilePath -> Q Exp
- xhamlet :: QuasiQuoter
- xhamletFile :: FilePath -> Q Exp
- type HtmlUrlI18n msg url = Translate msg -> Render url -> Html
- ihamlet :: QuasiQuoter
- ihamletFile :: FilePath -> Q Exp
- class ToAttributes a where
- toAttributes :: a -> [(Text, Text)]
- data HamletSettings = HamletSettings {}
- data NewlineStyle
- hamletWithSettings :: Q HamletRules -> HamletSettings -> QuasiQuoter
- hamletFileWithSettings :: Q HamletRules -> HamletSettings -> FilePath -> Q Exp
- defaultHamletSettings :: HamletSettings
- xhtmlHamletSettings :: HamletSettings
- data Env = Env {}
- data HamletRules = HamletRules {}
- hamletRules :: Q HamletRules
- ihamletRules :: Q HamletRules
- htmlRules :: Q HamletRules
- data CloseStyle
- condH :: Monad m => [(Bool, m ())] -> Maybe (m ()) -> m ()
- maybeH :: Monad m => Maybe v -> (v -> m ()) -> Maybe (m ()) -> m ()
- asHtmlUrl :: HtmlUrl url -> HtmlUrl url
- attrsToHtml :: [(Text, Text)] -> Html
Plain HTML
shamletFile :: FilePath -> Q Exp Source
xshamletFile :: FilePath -> Q Exp Source
Hamlet
type HtmlUrl url = Render url -> Html Source
A function generating an Html
given a URL-rendering function.
hamletFile :: FilePath -> Q Exp Source
hamletFileReload :: FilePath -> Q Exp Source
ihamletFileReload :: FilePath -> Q Exp Source
xhamletFile :: FilePath -> Q Exp Source
I18N Hamlet
type HtmlUrlI18n msg url = Translate msg -> Render url -> Html Source
A function generating an Html
given a message translator and a URL rendering function.
ihamletFile :: FilePath -> Q Exp Source
Type classes
class ToAttributes a where Source
Convert some value to a list of attribute pairs.
toAttributes :: a -> [(Text, Text)] Source
ToAttributes [(String, String)] | |
ToAttributes [(Text, Text)] | |
ToAttributes (String, String) | |
ToAttributes (Text, Text) |
Internal, for making more
data HamletSettings Source
Settings for parsing of a hamlet document.
HamletSettings | |
|
data NewlineStyle Source
NoNewlines | never add newlines |
NewlinesText | add newlines between consecutive text lines |
AlwaysNewlines | add newlines everywhere |
DefaultNewlineStyle |
hamletFileWithSettings :: Q HamletRules -> HamletSettings -> FilePath -> Q Exp Source
defaultHamletSettings :: HamletSettings Source
Defaults settings: HTML5 doctype and HTML-style empty tags.
data HamletRules Source
Used by generated code
condH :: Monad m => [(Bool, m ())] -> Maybe (m ()) -> m () Source
Checks for truth in the left value in each pair in the first argument. If a true exists, then the corresponding right action is performed. Only the first is performed. In there are no true values, then the second argument is performed, if supplied.
maybeH :: Monad m => Maybe v -> (v -> m ()) -> Maybe (m ()) -> m () Source
Runs the second argument with the value in the first, if available. Otherwise, runs the third argument, if available.
attrsToHtml :: [(Text, Text)] -> Html Source