HStringTemplate-0.4.2: StringTemplate implementation in Haskell.Source codeContentsIndex
Text.StringTemplate.Classes
Synopsis
data SElem a
= STR String
| STSH STShow
| SM (SMap a)
| LI [SElem a]
| SBLE 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 Monoid a => Stringable a where
stFromString :: String -> 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
Documentation
data SElem a Source
Constructors
STR String
STSH STShow
SM (SMap a)
LI [SElem a]
SBLE 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
ToSElem Bool
ToSElem Char
ToSElem Double
ToSElem Float
ToSElem Int
ToSElem Integer
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 => 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 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 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
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 ]]
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.4.1