hamlet-0.2.3.1: Haml-like template files that are compile-time checked

Text.Hamlet.Monad

Contents

Synopsis

Generalized enumerator

type Iteratee val seed m = seed -> val -> m (Either seed seed)Source

Something to be run for each val. Returns Left when enumeration should terminate immediately, Right when it can receive more input.

newtype Enumerator val m Source

Generates a stream of values to be passed to an Iteratee.

Constructors

Enumerator 

Fields

runEnumerator :: forall seed. Iteratee val seed m -> seed -> m (Either seed seed)
 

fromList :: Monad m => [a] -> Enumerator a mSource

Convert a list into an Enumerator.

Datatypes

newtype Hamlet url m a Source

Hamlet is a monad that has two features:

  • It passes along a function to convert a URL to a String.
  • It keeps an Iteratee and a seed value so that it can output values. Output is all done through a strict Text value.

The URL to String function makes it very convenient to write templates without knowing the absolute URLs for all referenced resources. For more information on this approach, please see the web-routes package.

For efficiency, the Hamlet monad halts execution as soon as the underlying Iteratee returns a Left value. This is normally what you want; this might cause a problem if you are relying on the side effects of a Hamlet action. However, it is not recommended to rely on side-effects. Though a Hamlet monad may perform IO actions, this should only be used for read-only behavior for efficiency.

Constructors

Hamlet 

Fields

runHamlet :: forall seed. (url -> String) -> seed -> Iteratee Text seed m -> m (Either seed (a, seed))
 

Instances

Monad m => Monad (Hamlet url m) 
Monad m => Functor (Hamlet url m) 
Monad m => Applicative (Hamlet url m) 

data HtmlContent Source

Content for an HTML document. Encoded content should not be entity escaped; Unencoded should be.

Constructors

Encoded Text 
Unencoded Text 

Output

output :: Monad m => Text -> Hamlet url m ()Source

Directly output strict Text without any escaping.

outputHtml :: Monad m => HtmlContent -> Hamlet url m ()Source

Outputs the given HtmlContent, entity encoding any Unencoded data.

outputString :: Monad m => String -> Hamlet url m ()Source

pack a String and call output; this will not perform any escaping.

outputUrl :: Monad m => url -> Hamlet url m ()Source

Uses the URL rendering function to convert the given URL to a String and then calls outputString.

outputUrlParams :: Monad m => (url, [(String, String)]) -> Hamlet url m ()Source

Same as outputUrl, but appends a query-string with given keys and values.

outputEmbed :: Monad m => Hamlet url m () -> Hamlet url m ()Source

Only really used to ensure that the argument has the right type.

Utility functions

htmlContentToText :: HtmlContent -> TextSource

Returns HTML-ready text (ie, all entities are escaped properly).

showUrl :: Monad m => url -> Hamlet url m StringSource

Use the URL to String rendering function to convert a URL to a String.

liftHamlet :: Monad m => m a -> Hamlet url m aSource

Lift a monadic action into the Hamlet monad.

mapH :: Monad m => (val -> Hamlet url m ()) -> Enumerator val m -> Hamlet url m ()Source

Perform the given Hamlet action for all values generated by the given Enumerator.

condH :: Monad m => [(m Bool, Hamlet url m ())] -> Maybe (Hamlet url m ()) -> Hamlet url 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 -> Hamlet url m ()) -> Hamlet url m ()Source

Runs the second argument with the value in the first, if available.

maybeH' :: Monad m => Maybe v -> (v -> Hamlet url m ()) -> Maybe (Hamlet url m ()) -> Hamlet url m ()Source

Runs the second argument with the value in the first, if available. Otherwise, runs the third argument, if available.

printHamlet :: (url -> String) -> Hamlet url IO () -> IO ()Source

Prints a Hamlet to standard out. Good for debugging.

hamletToText :: Monad m => (url -> String) -> Hamlet url m () -> m TextSource

Converts a Hamlet to lazy text, using strict I/O.

cdata :: HtmlContent -> HtmlContentSource

Wrap some HtmlContent for embedding in an XML file.