shakespeare-2.0.11: A toolkit for making compile-time interpolated templates

Safe HaskellNone
LanguageHaskell98

Text.Hamlet

Contents

Synopsis

Plain HTML

type Html = Markup #

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.

type Render url = url -> [(Text, Text)] -> Text Source #

hamlet :: QuasiQuoter Source #

Hamlet quasi-quoter. May only be used to generate expressions.

Generated expression have type HtmlUrl url, for some url.

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.

type Translate msg = msg -> Html Source #

ihamlet :: QuasiQuoter Source #

Hamlet quasi-quoter with internationalization. May only be used to generate expressions.

Generated expressions have type HtmlUrlI18n msg url, for some msg 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.

Minimal complete definition

toAttributes

Methods

toAttributes :: a -> [(Text, Text)] Source #

Internal, for making more

data HamletSettings Source #

Settings for parsing of a hamlet document.

Constructors

HamletSettings 

Fields

Instances

data NewlineStyle Source #

Constructors

NoNewlines

never add newlines

NewlinesText

add newlines between consecutive text lines

AlwaysNewlines

add newlines everywhere

DefaultNewlineStyle 

defaultHamletSettings :: HamletSettings Source #

Defaults settings: HTML5 doctype and HTML-style empty tags.

data Env Source #

Constructors

Env 

Fields

data HamletRules Source #

Constructors

HamletRules 

Fields

data CloseStyle Source #

Instances

Lift (String -> CloseStyle) Source # 

Methods

lift :: (String -> CloseStyle) -> Q Exp #

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