Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Html = Markup
- shamlet :: QuasiQuoter
- shamletFile :: FilePath -> Q Exp
- xshamlet :: QuasiQuoter
- xshamletFile :: FilePath -> Q Exp
- type HtmlUrl url = Render url -> Html
- type Render url = url -> [(Text, Text)] -> Text
- hamlet :: QuasiQuoter
- hamletFile :: FilePath -> Q Exp
- hamletFileReload :: FilePath -> Q Exp
- xhamlet :: QuasiQuoter
- xhamletFile :: FilePath -> Q Exp
- type HtmlUrlI18n msg url = Translate msg -> Render url -> Html
- type Translate msg = msg -> Html
- ihamlet :: QuasiQuoter
- ihamletFile :: FilePath -> Q Exp
- ihamletFileReload :: 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
- hamletFromString :: Q HamletRules -> HamletSettings -> String -> Q Exp
Plain HTML
shamlet :: QuasiQuoter Source #
"Simple Hamlet" quasi-quoter. May only be used to generate expressions.
Generated expressions have type Html
.
>>>putStrLn
(renderHtml
[shamlet
|<div>Hello, world!|]) <div>Hello, world!</div>
xshamlet :: QuasiQuoter Source #
Like shamlet
, but produces XHTML.
xshamletFile :: FilePath -> Q Exp Source #
Like shamletFile
, but produces XHTML.
Hamlet
type HtmlUrl url = Render url -> Html Source #
A function generating an Html
given a URL-rendering function.
hamlet :: QuasiQuoter Source #
Hamlet quasi-quoter. May only be used to generate expressions.
Generated expression have type
, for some HtmlUrl
urlurl
.
data MyRoute = Home render ::Render
MyRoute render Home _ = "/home" >>>putStrLn
(renderHtml
([hamlet
|<a href=@{Home}>Home|] render)) <a href="/home">Home</a>
hamletFileReload :: FilePath -> Q Exp Source #
Like hamletFile
, but the external file is parsed at runtime. Allows for
more rapid development, but should not be used in production.
xhamlet :: QuasiQuoter Source #
Like hamlet
, but produces XHTML.
xhamletFile :: FilePath -> Q Exp Source #
Like hamletFile
, but produces XHTML.
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.
ihamlet :: QuasiQuoter Source #
Hamlet quasi-quoter with internationalization. May only be used to generate expressions.
Generated expressions have type
, for some HtmlUrlI18n
msg urlmsg
and
url
.
data MyMsg = Hi | Bye data MyRoute = Home renderEnglish ::Translate
MyMsg renderEnglish Hi = "hi" renderEnglish Bye = "bye" renderUrl ::Render
MyRoute renderUrl Home _ = "/home" >>>putStrLn
(renderHtml
([ihamlet
|@{Home} _{Hi} _{Bye}|] renderEnglish renderUrl)) <div>/home hi bye <div>
ihamletFileReload :: FilePath -> Q Exp Source #
Like ihamletFile
, but the external file is parsed at runtime. Allows for
more rapid development, but should not be used in production.
Type classes
class ToAttributes a where Source #
Convert some value to a list of attribute pairs.
toAttributes :: a -> [(Text, Text)] Source #
Instances
ToAttributes [(Text, Text)] Source # | |
Defined in Text.Hamlet | |
ToAttributes [(String, String)] Source # | |
Defined in Text.Hamlet | |
ToAttributes (Text, Text) Source # | |
Defined in Text.Hamlet | |
ToAttributes (String, String) Source # | |
Defined in Text.Hamlet |
Internal, for making more
data HamletSettings Source #
Settings for parsing of a hamlet document.
HamletSettings | |
|
Instances
Lift HamletSettings Source # | |
Defined in Text.Hamlet.Parse lift :: HamletSettings -> Q Exp # |
data NewlineStyle Source #
NoNewlines | never add newlines |
NewlinesText | add newlines between consecutive text lines |
AlwaysNewlines | add newlines everywhere |
DefaultNewlineStyle |
Instances
Show NewlineStyle Source # | |
Defined in Text.Hamlet.Parse showsPrec :: Int -> NewlineStyle -> ShowS # show :: NewlineStyle -> String # showList :: [NewlineStyle] -> ShowS # | |
Lift NewlineStyle Source # | |
Defined in Text.Hamlet.Parse lift :: NewlineStyle -> Q Exp # |
hamletFileWithSettings :: Q HamletRules -> HamletSettings -> FilePath -> Q Exp Source #
defaultHamletSettings :: HamletSettings Source #
Defaults settings: HTML5 doctype and HTML-style empty tags.
data HamletRules Source #
htmlRules :: Q HamletRules Source #
data CloseStyle Source #
Instances
Lift (String -> CloseStyle) Source # | |
Defined in Text.Hamlet.Parse |
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.
low-level
hamletFromString :: Q HamletRules -> HamletSettings -> String -> Q Exp Source #