Maintainer | Bas van Dijk <v.dijk.bas@gmail.com> |
---|---|
Safe Haskell | Safe |
- (<>) :: Monoid m => m -> m -> m
- mid :: Monoid s => s -> s -> s -> s
- (<+>) :: (Monoid s, IsString s) => s -> s -> s
- ($$) :: (Monoid s, IsString s) => s -> s -> s
- intercalate :: Monoid s => (s -> s -> s) -> [s] -> s
- hcat :: Monoid s => [s] -> s
- unwords :: (Monoid s, IsString s) => [s] -> s
- unlines :: (Monoid s, IsString s) => [s] -> s
- punctuate :: Monoid s => s -> [s] -> [s]
- between :: Monoid s => s -> s -> s -> s
- parens :: (Monoid s, IsString s) => s -> s
- thenParens :: (Monoid s, IsString s) => Bool -> s -> s
- brackets :: (Monoid s, IsString s) => s -> s
- braces :: (Monoid s, IsString s) => s -> s
- angleBrackets :: (Monoid s, IsString s) => s -> s
- quotes :: (Monoid s, IsString s) => s -> s
- doubleQuotes :: (Monoid s, IsString s) => s -> s
- char :: IsString s => Char -> s
- semi :: IsString s => s
- colon :: IsString s => s
- comma :: IsString s => s
- space :: IsString s => s
- newline :: IsString s => s
- equals :: IsString s => s
- lparen :: IsString s => s
- rparen :: IsString s => s
- lbrack :: IsString s => s
- rbrack :: IsString s => s
- lbrace :: IsString s => s
- rbrace :: IsString s => s
- labrack :: IsString s => s
- rabrack :: IsString s => s
- fromShow :: (Show a, IsString s) => a -> s
- int :: IsString s => Int -> s
- integer :: IsString s => Integer -> s
- float :: IsString s => Float -> s
- double :: IsString s => Double -> s
- rational :: IsString s => Rational -> s
Combining
mid :: Monoid s => s -> s -> s -> sSource
mid m x y
Puts x
and y
around m
.
Note that: mid m x y =
.
between
x y m
(<+>) :: (Monoid s, IsString s) => s -> s -> sSource
Put two string-likes besides eachother separated by a space
.
($$) :: (Monoid s, IsString s) => s -> s -> sSource
Put two string-likes above eachother (separated by a newline
).
intercalate :: Monoid s => (s -> s -> s) -> [s] -> sSource
Combine the string-likes with a given function.
intercalate f [s1, ... sn] = s1 `f` (s2 `f` (... (sn-1 `f` sn)))
unwords :: (Monoid s, IsString s) => [s] -> sSource
List version of <+>
.
Note that: unwords =
.
intercalate
(<+>
)
Wrapping in delimiters
thenParens :: (Monoid s, IsString s) => Bool -> s -> sSource
Like showParen
conditionally wraps a string-like in (...)
This function is supposed to be used infix as in:
(precedence >= 10) `thenParens` ("fun" <+> "arg")
angleBrackets :: (Monoid s, IsString s) => s -> sSource
Wrap a string-like in <...>
.
doubleQuotes :: (Monoid s, IsString s) => s -> sSource
Wrap a string-like in "..."
.