HStringTemplate-0.8.8: StringTemplate implementation in Haskell.
Safe HaskellNone
LanguageHaskell2010

Text.StringTemplate.Base

Synopsis

Documentation

data StringTemplate a Source #

A String with "holes" in it. StringTemplates may be composed of any Stringable type, which at the moment includes Strings, ByteStrings, PrettyPrinter Docs, and Endo Strings, which are actually of type ShowS. When a StringTemplate is composed of a type, its internals are as well, so it is, so to speak "turtles all the way down."

Constructors

STMP 

Fields

Instances

Instances details
Stringable a => SEType a (StringTemplate a) Source # 
Instance details

Defined in Text.StringTemplate.Renderf

class Show a => StringTemplateShows a where Source #

The StringTemplateShows class should be instantiated for all types that are directly displayed in a StringTemplate, but take an optional format string. Each such type must have an appropriate ToSElem method defined as well.

Minimal complete definition

Nothing

Methods

stringTemplateShow :: a -> String Source #

Defaults to show.

stringTemplateFormattedShow :: String -> a -> String Source #

Defaults to _ a -> stringTemplateShow a

Instances

Instances details
StringTemplateShows Double Source # 
Instance details

Defined in Text.StringTemplate.Instances

StringTemplateShows Float Source # 
Instance details

Defined in Text.StringTemplate.Instances

StringTemplateShows ZonedTime Source # 
Instance details

Defined in Text.StringTemplate.Instances

StringTemplateShows LocalTime Source # 
Instance details

Defined in Text.StringTemplate.Instances

StringTemplateShows TimeOfDay Source # 
Instance details

Defined in Text.StringTemplate.Instances

StringTemplateShows TimeZone Source # 
Instance details

Defined in Text.StringTemplate.Instances

StringTemplateShows UTCTime Source # 
Instance details

Defined in Text.StringTemplate.Instances

StringTemplateShows Day Source # 
Instance details

Defined in Text.StringTemplate.Instances

class ToSElem a where Source #

The ToSElem class should be instantiated for all types that can be inserted as attributes into a StringTemplate.

Minimal complete definition

toSElem

Methods

toSElem :: Stringable b => a -> SElem b Source #

toSElemList :: Stringable b => [a] -> SElem b Source #

Instances

Instances details
ToSElem Bool Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem Char Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem Double Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem Float Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem Int Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem Integer Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem () Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b => () -> SElem b Source #

toSElemList :: Stringable b => [()] -> SElem b Source #

Data a => ToSElem a Source # 
Instance details

Defined in Text.StringTemplate.GenericStandard

Methods

toSElem :: Stringable b => a -> SElem b Source #

toSElemList :: Stringable b => [a] -> SElem b Source #

ToSElem Void Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem ByteString Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem ByteString Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem Text Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem Text Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem ZonedTime Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem LocalTime Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem TimeOfDay Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem TimeZone Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem UTCTime Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem Day Source # 
Instance details

Defined in Text.StringTemplate.Instances

ToSElem a => ToSElem [a] Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b => [a] -> SElem b Source #

toSElemList :: Stringable b => [[a]] -> SElem b Source #

ToSElem a => ToSElem (Maybe a) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b => Maybe a -> SElem b Source #

toSElemList :: Stringable b => [Maybe a] -> SElem b Source #

(Integral a, Show a) => ToSElem (Ratio a) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b => Ratio a -> SElem b Source #

toSElemList :: Stringable b => [Ratio a] -> SElem b Source #

(ToSElem a, Foldable t) => ToSElem (t a) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b => t a -> SElem b Source #

toSElemList :: Stringable b => [t a] -> SElem b Source #

(ToSElem a, ToSElem b) => ToSElem (a, b) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b)] -> SElem b0 Source #

(ToSElem a, Ix i) => ToSElem (Array i a) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b => Array i a -> SElem b Source #

toSElemList :: Stringable b => [Array i a] -> SElem b Source #

ToSElem a => ToSElem (Map String a) Source # 
Instance details

Defined in Text.StringTemplate.Instances

(ToSElem a, ToSElem b, ToSElem c) => ToSElem (a, b, c) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b, c) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b, c)] -> SElem b0 Source #

(ToSElem a, ToSElem b, ToSElem c, ToSElem d) => ToSElem (a, b, c, d) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b, c, d) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b, c, d)] -> SElem b0 Source #

(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e) => ToSElem (a, b, c, d, e) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b, c, d, e) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b, c, d, e)] -> SElem b0 Source #

(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e, ToSElem f) => ToSElem (a, b, c, d, e, f) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b, c, d, e, f) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b, c, d, e, f)] -> SElem b0 Source #

(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e, ToSElem f, ToSElem g) => ToSElem (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b, c, d, e, f, g) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b, c, d, e, f, g)] -> SElem b0 Source #

(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e, ToSElem f, ToSElem g, ToSElem h) => ToSElem (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b, c, d, e, f, g, h) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b, c, d, e, f, g, h)] -> SElem b0 Source #

(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e, ToSElem f, ToSElem g, ToSElem h, ToSElem i) => ToSElem (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b, c, d, e, f, g, h, i) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b, c, d, e, f, g, h, i)] -> SElem b0 Source #

(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e, ToSElem f, ToSElem g, ToSElem h, ToSElem i, ToSElem j) => ToSElem (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Text.StringTemplate.Instances

Methods

toSElem :: Stringable b0 => (a, b, c, d, e, f, g, h, i, j) -> SElem b0 Source #

toSElemList :: Stringable b0 => [(a, b, c, d, e, f, g, h, i, j)] -> SElem b0 Source #

type STGroup a = String -> StFirst (StringTemplate a) Source #

A function that generates StringTemplates. This is conceptually a query function into a "group" of StringTemplates.

class Monoid a => Stringable a where Source #

The Stringable class should be instantiated with care. Generally, the provided instances should be enough for anything.

Minimal complete definition

stFromString, stToString

Methods

stFromString :: String -> a Source #

stFromByteString :: ByteString -> a Source #

stFromText :: Text -> a Source #

stToString :: a -> String Source #

mconcatMap :: [b] -> (b -> a) -> a Source #

Defaults to mconcatMap m k = foldr (mappend . k) mempty m

mintercalate :: a -> [a] -> a Source #

Defaults to (mconcat .) . intersperse

mlabel :: a -> a -> a Source #

Defaults to mlabel x y = mconcat [x, stFromString "[", y, stFromString "]"]

Instances

Instances details
Stringable String Source # 
Instance details

Defined in Text.StringTemplate.Classes

Stringable ByteString Source # 
Instance details

Defined in Text.StringTemplate.Classes

Stringable ByteString Source # 
Instance details

Defined in Text.StringTemplate.Classes

Stringable Builder Source # 
Instance details

Defined in Text.StringTemplate.Classes

Stringable Text Source # 
Instance details

Defined in Text.StringTemplate.Classes

Stringable Text Source # 
Instance details

Defined in Text.StringTemplate.Classes

Stringable Doc Source # 
Instance details

Defined in Text.StringTemplate.Classes

Stringable Builder Source # 
Instance details

Defined in Text.StringTemplate.Classes

Stringable (Endo String) Source # 
Instance details

Defined in Text.StringTemplate.Classes

stShowsToSE :: (StringTemplateShows a, Stringable b) => a -> SElem b Source #

This method should be used to create ToSElem instances for types defining a custom formatted show function.

toString :: StringTemplate String -> String Source #

Renders a StringTemplate to a String.

toPPDoc :: StringTemplate Doc -> Doc Source #

Renders a StringTemplate to a Doc.

render :: Stringable a => StringTemplate a -> a Source #

Generic render function for a StringTemplate of any type.

newSTMP :: Stringable a => String -> StringTemplate a Source #

Parses a String to produce a StringTemplate, with '$'s as delimiters. It is constructed with a stub group that cannot look up other templates.

newAngleSTMP :: Stringable a => String -> StringTemplate a Source #

Parses a String to produce a StringTemplate, delimited by angle brackets. It is constructed with a stub group that cannot look up other templates.

getStringTemplate :: Stringable a => String -> STGroup a -> Maybe (StringTemplate a) Source #

Queries an String Template Group and returns Just the appropriate StringTemplate if it exists, otherwise, Nothing.

getStringTemplate' :: Stringable a => String -> STGroup a -> Maybe (StringTemplate a) Source #

As with getStringTemplate but never inlined, so appropriate for use with volatile template groups.

setAttribute :: (ToSElem a, Stringable b) => String -> a -> StringTemplate b -> StringTemplate b Source #

Yields a StringTemplate with the appropriate attribute set. If the attribute already exists, it is appended to a list.

setManyAttrib :: (ToSElem a, Stringable b) => [(String, a)] -> StringTemplate b -> StringTemplate b Source #

Yields a StringTemplate with the appropriate attributes set. If any attribute already exists, it is appended to a list.

setNativeAttribute :: Stringable b => String -> b -> StringTemplate b -> StringTemplate b Source #

Yields a StringTemplate with the appropriate attribute set. If the attribute already exists, it is appended to a list. This will not translate the attribute through any intermediate representation, so is more efficient when, e.g. setting attributes that are large bytestrings in a bytestring template.

setManyNativeAttrib :: Stringable b => [(String, b)] -> StringTemplate b -> StringTemplate b Source #

Yields a StringTemplate with the appropriate attributes set. If any attribute already exists, it is appended to a list. Attributes are added natively, which may provide efficiency gains.

withContext :: (ToSElem a, Stringable b) => StringTemplate b -> a -> StringTemplate b Source #

Replaces the attributes of a StringTemplate with those described in the second argument. If the argument does not yield a set of named attributes but only a single one, that attribute is named, as a default, "it".

optInsertTmpl :: [(String, String)] -> StringTemplate a -> StringTemplate a Source #

Adds a set of global options to a single template

setEncoder :: Stringable a => (a -> a) -> StringTemplate a -> StringTemplate a Source #

Sets an encoding function of a template that all values are rendered with. For example one useful encoder would be stringToHtmlString. All attributes will be encoded once and only once.

paddedTrans :: a -> [[a]] -> [[a]] Source #

data SEnv a Source #

Constructors

SEnv 

Fields

dumpAttribs :: Stringable a => StringTemplate a Source #

A special template that simply dumps the values of all the attributes set in it. This may be made available to any template as a function by adding it to its group. I.e. myNewGroup = addSuperGroup myGroup $ groupStringTemplates [("dumpAttribs", dumpAttribs)]

checkTemplate :: Stringable a => StringTemplate a -> (Maybe String, Maybe [String], Maybe [String]) Source #

Returns a tuple of three Maybes. The first is set if there is a parse error in the template. The next is set to a list of attributes that have not been set, or Nothing if all attributes are set. The last is set to a list of invoked templates that cannot be looked up, or Nothing if all invoked templates can be found. Note that this check is shallow -- i.e. missing attributes and templates are only caught in the top level template, not any invoked subtemplate.

checkTemplateDeep :: (Stringable a, NFData a) => StringTemplate a -> ([(String, String)], [String], [String]) Source #

Returns a tuple of three lists. The first is of templates with parse errors, and their errors. The next is of missing attributes, and the last is of missing templates. If there are no errors, then all lists will be empty. This check is performed recursively.

parseSTMPNames :: (Char, Char) -> String -> Either ParseError ([String], [String], [String]) Source #

Gets all quasiquoted names, normal names & templates used in a given template. Must be passed a pair of chars denoting the delimeters to be used.