| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Text.StringTemplate.Classes
Synopsis
- data SElem a
 - 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
 - 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
 
Documentation
class Show a => StringTemplateShows a where Source #
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.
Minimal complete definition
Nothing
Methods
stringTemplateShow :: a -> String Source #
Defaults to show.
stringTemplateFormattedShow :: String -> a -> String Source #
Defaults to    _ a -> stringTemplateShow a 
Instances
| StringTemplateShows Double Source # | |
Defined in Text.StringTemplate.Instances  | |
| StringTemplateShows Float Source # | |
Defined in Text.StringTemplate.Instances  | |
| StringTemplateShows ZonedTime Source # | |
Defined in Text.StringTemplate.Instances  | |
| StringTemplateShows LocalTime Source # | |
Defined in Text.StringTemplate.Instances  | |
| StringTemplateShows TimeOfDay Source # | |
Defined in Text.StringTemplate.Instances  | |
| StringTemplateShows TimeZone Source # | |
Defined in Text.StringTemplate.Instances  | |
| StringTemplateShows UTCTime Source # | |
Defined in Text.StringTemplate.Instances  | |
| StringTemplateShows Day Source # | |
Defined in Text.StringTemplate.Instances  | |
class ToSElem a where Source #
The ToSElem class should be instantiated for all types that can be inserted as attributes into a StringTemplate.
Minimal complete definition
Methods
toSElem :: Stringable b => a -> SElem b Source #
toSElemList :: Stringable b => [a] -> SElem b Source #
Instances
Constructors
| forall a.StringTemplateShows a => STShow a | 
Constructors
| StFirst | |
Fields 
  | |
Instances
| Functor StFirst Source # | |
| Eq a => Eq (StFirst a) Source # | |
| Ord a => Ord (StFirst a) Source # | |
| Read a => Read (StFirst a) Source # | |
| Show a => Show (StFirst a) Source # | |
| Semigroup (StFirst a) Source # | |
| Monoid (StFirst a) Source # | |
class Monoid a => Stringable a where Source #
The Stringable class should be instantiated with care. Generally, the provided instances should be enough for anything.
Minimal complete definition
Methods
stFromString :: String -> a Source #
stFromByteString :: ByteString -> a Source #
stFromText :: Text -> a Source #
stToString :: a -> String Source #
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 
mlabel :: a -> a -> a Source #
Defaults to    mlabel x y = mconcat [x, stFromString "[", y, stFromString "]"] 
Instances
stShowsToSE :: (StringTemplateShows a, Stringable b) => a -> SElem b Source #
This method should be used to create ToSElem instances for types defining a custom formatted show function.