|
|
|
|
|
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 |
|
data StringTemplate a | | type STGroup a = String -> StFirst (StringTemplate a) | | class ToSElem a where | | | class Show a => StringTemplateShows a where | | | stShowsToSE :: (StringTemplateShows a, Stringable b) => a -> SElem b | | class Stringable a where | | | class Stringable b => SEType b a where | | | newSTMP :: Stringable a => String -> StringTemplate a | | newAngleSTMP :: Stringable a => String -> StringTemplate a | | getStringTemplate :: Stringable a => String -> STGroup a -> Maybe (StringTemplate a) | | getStringTemplate' :: Stringable a => String -> STGroup a -> Maybe (StringTemplate a) | | toString :: StringTemplate String -> String | | toPPDoc :: StringTemplate Doc -> Doc | | render :: Stringable a => StringTemplate a -> a | | dumpAttribs :: Stringable a => StringTemplate a | | checkTemplate :: Stringable a => StringTemplate a -> (Maybe String, Maybe [String], Maybe [String]) | | checkTemplateDeep :: (Stringable a, NFData a) => StringTemplate a -> ([(String, String)], [String], [String]) | | setAttribute :: (ToSElem a, Stringable b) => String -> a -> StringTemplate b -> StringTemplate b | | (|=) :: Monad m => a -> m a1 -> m (a, a1) | | setManyAttrib :: (ToSElem a, Stringable b) => [(String, a)] -> StringTemplate b -> StringTemplate b | | setNativeAttribute :: Stringable b => String -> b -> StringTemplate b -> StringTemplate b | | setManyNativeAttrib :: Stringable b => [(String, b)] -> StringTemplate b -> StringTemplate b | | withContext :: (ToSElem a, Stringable b) => StringTemplate b -> a -> StringTemplate b | | optInsertTmpl :: [(String, String)] -> StringTemplate a -> StringTemplate a | | optInsertGroup :: [(String, String)] -> STGroup a -> STGroup a | | setEncoder :: Stringable a => (a -> a) -> StringTemplate a -> StringTemplate a | | setEncoderGroup :: Stringable a => (a -> a) -> STGroup a -> STGroup a | | groupStringTemplates :: [(String, StringTemplate a)] -> STGroup a | | addSuperGroup :: STGroup a -> STGroup a -> STGroup a | | addSubGroup :: STGroup a -> STGroup a -> STGroup a | | mergeSTGroups :: STGroup a -> STGroup a -> STGroup a | | directoryGroup :: Stringable a => FilePath -> IO (STGroup a) | | unsafeVolatileDirectoryGroup :: Stringable a => FilePath -> Int -> IO (STGroup a) | | directoryGroupRecursive :: Stringable a => FilePath -> IO (STGroup a) | | directoryGroupRecursiveLazy :: Stringable a => FilePath -> IO (STGroup a) | | directoryGroupLazy :: Stringable a => FilePath -> IO (STGroup a) | | nullGroup :: Stringable a => STGroup a |
|
|
|
Types
|
|
|
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 | |
|
|
|
A function that generates StringTemplates.
This is conceptually a query function into a "group" of StringTemplates.
|
|
Classes
|
|
|
The ToSElem class should be instantiated for all types that can be
inserted as attributes into a StringTemplate.
| | Methods | | | 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 => 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) |
|
|
|
|
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 | | Defaults to show.
| | | Defaults to _ a -> stringTemplateShow a
|
| | Instances | |
|
|
|
This method should be used to create ToSElem instances for
types defining a custom formatted show function.
|
|
class Stringable a where | Source |
|
The Stringable class should be instantiated with care.
Generally, the provided instances should be enough for anything.
| | Methods | | | | | | | 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
| | | Defaults to mlabel x y = smconcat [x, stFromString [, y, stFromString ]]
| | | Just mempty. Here to avoid orphan instances
| | | Just mappend. Here to avoid orphan instances
| | | Just mconcat. Here to avoid orphan instances
|
| | Instances | |
|
|
|
| Methods | | | Instances | |
|
|
Creation
|
|
|
Parses a String to produce a StringTemplate, with '$'s as delimiters.
It is constructed with a stub group that cannot look up other templates.
|
|
|
Parses a String to produce a StringTemplate, delimited by angle brackets.
It is constructed with a stub group that cannot look up other templates.
|
|
|
Queries an String Template Group and returns Just the appropriate
StringTemplate if it exists, otherwise, Nothing.
|
|
|
As with getStringTemplate but never inlined, so appropriate for use
with volatile template groups.
|
|
Display
|
|
|
Renders a StringTemplate to a String.
|
|
|
Renders a StringTemplate to a Text.PrettyPrint.HughesPJ.Doc.
|
|
|
Generic render function for a StringTemplate of any type.
|
|
|
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)]
|
|
|
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.
|
|
|
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
|
|
|
Yields a StringTemplate with the appropriate attribute set.
If the attribute already exists, it is appended to a list.
|
|
|
|
|
Yields a StringTemplate with the appropriate attributes set.
If any attribute already exists, it is appended to a list.
|
|
|
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.
|
|
|
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.
|
|
|
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".
|
|
|
Adds a set of global options to a single template
|
|
|
Adds a set of global options to a group
|
|
|
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.
|
|
|
Sets an encoding function of a group that all values are
rendered with in each enclosed template
|
|
Groups
|
|
|
Given a list of named of StringTemplates, returns a group which generates
them such that they can call one another.
|
|
|
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.
|
|
|
Adds a "subgroup" to any StringTemplate group such that templates from
the original group now have template calls "shadowed" by the subgroup.
|
|
|
Merges two groups into a single group. This function is left-biased,
prefering bindings from the first group when there is a conflict.
|
|
|
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.
|
|
|
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.
|
|
|
As with directoryGroup, but traverses subdirectories as well. A template named
"foobar.st\" may be referenced by \"foobar" in the returned group.
|
|
|
See documentation for directoryGroupRecursive.
|
|
|
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.
|
|
|
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.
|
|
Produced by Haddock version 2.6.1 |