Safe Haskell | None |
---|
Text.StringTemplate.Base
- data StringTemplate a = STMP {}
- class Show a => StringTemplateShows a where
- stringTemplateShow :: a -> String
- stringTemplateFormattedShow :: String -> a -> String
- class ToSElem a where
- toSElem :: Stringable b => a -> SElem b
- toSElemList :: Stringable b => [a] -> SElem b
- type STGroup a = String -> StFirst (StringTemplate a)
- class Monoid a => Stringable a where
- stFromString :: String -> a
- stFromByteString :: ByteString -> a
- stFromText :: Text -> a
- stToString :: a -> String
- mconcatMap :: [b] -> (b -> a) -> a
- mintercalate :: a -> [a] -> a
- mlabel :: a -> a -> a
- stShowsToSE :: (StringTemplateShows a, Stringable b) => a -> SElem b
- inSGen :: (STGroup a -> STGroup a) -> StringTemplate a -> StringTemplate a
- toString :: StringTemplate String -> String
- toPPDoc :: StringTemplate Doc -> Doc
- render :: Stringable a => StringTemplate a -> a
- 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)
- setAttribute :: (ToSElem a, Stringable b) => String -> a -> StringTemplate b -> StringTemplate b
- 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
- setEncoder :: Stringable a => (a -> a) -> StringTemplate a -> StringTemplate a
- paddedTrans :: a -> [[a]] -> [[a]]
- data SEnv a = SEnv {}
- parseSTMP :: Stringable a => (Char, Char) -> String -> Either String (SEnv 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])
- parseSTMPNames :: (Char, Char) -> String -> Either ParseError ([String], [String], [String])
Documentation
data StringTemplate a Source
A String with "holes" in it. StringTemplates may be composed of any
Stringable
type, which at the moment includes String
s, ByteString
s,
PrettyPrinter Doc
s, and Endo
String
s, 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 | |
Instances
Stringable a => SEType a (StringTemplate a) |
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
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
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
stFromText :: Text -> 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
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.
inSGen :: (STGroup a -> STGroup a) -> StringTemplate a -> StringTemplate aSource
toString :: StringTemplate String -> StringSource
Renders a StringTemplate to a String.
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 => (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 stringToHtmlString
. All attributes will be encoded once and only once.
paddedTrans :: a -> [[a]] -> [[a]]Source
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.
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.