HStringTemplate-0.6.8: StringTemplate implementation in Haskell.

Portabilityportable
Stabilityexperimental
Maintainers.clover@gmail.com

Text.StringTemplate

Contents

Description

A StringTemplate is a String with "holes" in it. This is a port of the Java StringTemplate library written by Terrence Parr. (http://www.stringtemplate.org). User-contributed documentation available at http://www.haskell.org/haskellwiki/HStringTemplate.

This library implements the basic 3.1 grammar, lacking group files (though not groups themselves), Regions, and Interfaces. The goal is not to blindly copy the StringTemplate API, but rather to take its central ideas and implement them in a Haskellish manner. Indentation and wrapping, for example, are implemented through the HughesPJ Pretty Printing library. Calling toPPDoc on a StringTemplate yields a Doc with appropriate paragraph-fill wrapping that can be rendered in the usual fashion.

Basic instances are provided of the StringTemplateShows and ToSElem class. Any type deriving ToSElem can be passed automatically as a StringTemplate attribute. This package can be installed with syb-with-class bindings that provide a ToSElem instance for anything deriving Data.Generics.SYB.WithClass.Basics.Data. When defining an instance of ToSElem that can take a format parameter, you should first define an instance of StringTemplateShows, and then define an instance of ToSElem where toSElem = stShowsToSE.

Synopsis

Types

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."

Instances

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

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

Classes

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 Text 
ToSElem Text 
ToSElem LocalTime 
ToSElem ZonedTime 
ToSElem TimeOfDay 
ToSElem TimeZone 
ToSElem UTCTime 
ToSElem Day 
ToSElem a => ToSElem [a] 
(Integral a, Show 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) 

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

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.

class 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 = smconcat [x, stFromString [, y, stFromString ]]

smempty :: aSource

Just mempty. Here to avoid orphan instances

smappend :: a -> a -> aSource

Just mappend. Here to avoid orphan instances

smconcat :: [a] -> aSource

Just mconcat. Here to avoid orphan instances

class Stringable b => SEType b a whereSource

Methods

renderf :: StringTemplate b -> aSource

Instances

Stringable a => SEType a a 
Stringable a => SEType a (StringTemplate a) 
(ToSElem a, SEType b r) => SEType b ((String, a) -> r) 

Creation

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.

Display

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.

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

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 erros. The next is of missing attributes, and the last is of missing templates. If there are no errors, then all lists will be empty.

Modification

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.

(|=) :: Monad m => a -> m a1 -> m (a, a1)Source

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

optInsertGroup :: [(String, String)] -> STGroup a -> STGroup aSource

Adds a set of global options to a group

setEncoder :: Stringable a => (a -> a) -> 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.

setEncoderGroup :: Stringable a => (a -> a) -> STGroup a -> STGroup aSource

Sets an encoding function of a group that all values are rendered with in each enclosed template

Groups

groupStringTemplates :: [(String, StringTemplate a)] -> STGroup aSource

Given a list of named of StringTemplates, returns a group which generates them such that they can call one another.

addSuperGroup :: STGroup a -> STGroup a -> STGroup aSource

Adds a supergroup to any StringTemplate group such that templates from the original group are now able to call ones from the supergroup as well.

addSubGroup :: STGroup a -> STGroup a -> STGroup aSource

Adds a "subgroup" to any StringTemplate group such that templates from the original group now have template calls "shadowed" by the subgroup.

mergeSTGroups :: STGroup a -> STGroup a -> STGroup aSource

Merges two groups into a single group. This function is left-biased, prefering bindings from the first group when there is a conflict.

directoryGroup :: Stringable a => FilePath -> IO (STGroup a)Source

Given a path, returns a group which generates all files in said directory which have the proper "st" extension. This function is strict, with all files read once. As it performs file IO, expect it to throw the usual exceptions.

unsafeVolatileDirectoryGroup :: Stringable a => FilePath -> Int -> IO (STGroup a)Source

Given an integral amount of seconds and a path, returns a group generating all files in said directory and subdirectories with the proper "st" extension, cached for that amount of seconds. IO errors are "swallowed" by this so that exceptions don't arise in unexpected places. This violates referential transparency, but can be very useful in developing templates for any sort of server application. It should be swapped out for production purposes. The dumpAttribs template is added to the returned group by default, as it should prove useful for debugging and developing templates.

directoryGroupRecursive :: Stringable a => FilePath -> IO (STGroup a)Source

As with directoryGroup, but traverses subdirectories as well. A template named "foobar.st\" may be referenced by \"foobar" in the returned group.

directoryGroupLazy :: Stringable a => FilePath -> IO (STGroup a)Source

Given a path, returns a group which generates all files in said directory which have the proper "st" extension. This function is lazy in the same way that readFile is lazy, with all files read on demand, but no more than once. The list of files, however, is generated at the time the function is called. As this performs file IO, expect it to throw the usual exceptions. And, as it is lazy, expect these exceptions in unexpected places.

nullGroup :: Stringable a => STGroup aSource

For any requested template, returns a message that the template was unable to be found. Useful to add as a super group for a set of templates under development, to aid in debugging.