HStringTemplate-0.6.3: StringTemplate implementation in Haskell.Source codeContentsIndex
Text.StringTemplate.Classes
Synopsis
data SElem a
= STR String
| BS ByteString
| STSH STShow
| SM (SMap a)
| LI [SElem a]
| SBLE a
| SNAT a
| SNull
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 SMap a = Map String (SElem a)
data STShow = forall a . StringTemplateShows a => STShow a
newtype StFirst a = StFirst {
stGetFirst :: Maybe a
}
class Stringable a where
stFromString :: String -> a
stFromByteString :: ByteString -> a
stToString :: a -> String
mconcatMap :: [b] -> (b -> a) -> a
mintercalate :: a -> [a] -> a
mlabel :: a -> a -> a
smempty :: a
smappend :: a -> a -> a
smconcat :: [a] -> a
stShowsToSE :: (StringTemplateShows a, Stringable b) => a -> SElem b
Documentation
data SElem a Source
Constructors
STR String
BS ByteString
STSH STShow
SM (SMap a)
LI [SElem a]
SBLE a
SNAT a
SNull
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
show/hide Instances
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
show/hide Instances
type SMap a = Map String (SElem a)Source
data STShow Source
Constructors
forall a . StringTemplateShows a => STShow a
newtype StFirst a Source
Constructors
StFirst
stGetFirst :: Maybe a
show/hide Instances
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
show/hide Instances
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.
Produced by Haddock version 2.6.1