HStringTemplate-0.5.1.1: StringTemplate implementation in Haskell.

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

senv :: SEnv a
 
runSTMP :: SEnv a -> a
 

Instances

class Show a => StringTemplateShows a whereSource

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.

Methods

stringTemplateShow :: a -> StringSource

Defaults to show.

stringTemplateFormattedShow :: String -> a -> StringSource

Defaults to _ a -> stringTemplateShow a

class ToSElem a whereSource

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

Methods

toSElem :: Stringable b => a -> SElem bSource

toSElemList :: Stringable b => [a] -> SElem bSource

Instances

ToSElem Bool 
ToSElem Char 
ToSElem Double 
ToSElem Float 
ToSElem Int 
ToSElem Integer 
Data a => ToSElem a 
Data ToSElemD t => ToSElem t 
ToSElem ByteString 
ToSElem ByteString 
ToSElem CalendarTime 
ToSElem TimeDiff 
ToSElem LocalTime 
ToSElem ZonedTime 
ToSElem TimeOfDay 
ToSElem TimeZone 
ToSElem UTCTime 
ToSElem Day 
ToSElem a => ToSElem [a] 
Integral a => ToSElem (Ratio a) 
(ToSElem a, Foldable t) => ToSElem (t a) 
ToSElem a => ToSElem (Maybe a) 
(ToSElem a, ToSElem b) => ToSElem (a, b) 
(ToSElem a, Ix i) => ToSElem (Array i a) 
ToSElem a => ToSElem (Map String a) 
(ToSElem a, ToSElem b, ToSElem c) => ToSElem (a, b, c) 
(ToSElem a, ToSElem b, ToSElem c, ToSElem d) => ToSElem (a, b, c, d) 
(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e) => ToSElem (a, b, c, d, e) 
(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e, ToSElem f) => ToSElem (a, b, c, d, e, f) 
(ToSElem a, ToSElem b, ToSElem c, ToSElem d, ToSElem e, ToSElem f, ToSElem g) => ToSElem (a, b, c, d, e, f, g) 
(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) 
(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) 
(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) 

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 whereSource

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

Methods

stFromString :: String -> aSource

stFromByteString :: ByteString -> aSource

stToString :: a -> StringSource

mconcatMap :: [b] -> (b -> a) -> aSource

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

mintercalate :: a -> [a] -> aSource

Defaults to (mconcat .) . intersperse

mlabel :: a -> a -> aSource

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

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

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

toString :: StringTemplate String -> StringSource

Renders a StringTemplate to a String.

toPPDoc :: StringTemplate Doc -> DocSource

Renders a StringTemplate to a Text.PrettyPrint.HughesPJ.Doc.

render :: Stringable a => StringTemplate a -> aSource

Generic render function for a StringTemplate of any type.

newSTMP :: Stringable a => String -> StringTemplate aSource

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 aSource

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 bSource

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 bSource

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 bSource

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 bSource

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 bSource

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 aSource

Adds a set of global options to a single template

setEncoder :: Stringable a => (String -> String) -> StringTemplate a -> StringTemplate aSource

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

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

data SEnv a Source

Constructors

SEnv 

Fields

smp :: SMap a
 
sopts :: [(String, SEnv a -> SElem a)]
 
sgen :: STGroup a
 
senc :: String -> String
 

parseSTMP :: Stringable a => (Char, Char) -> String -> SEnv a -> aSource

dumpAttribs :: Stringable a => StringTemplate aSource

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)]