string-combinators-0.2: Polymorphic functions to build and combine stringlike valuesSource codeContentsIndex
Data.String.Combinators
PortabilityRequires OverloadedStrings
StabilityStable
MaintainerBas van Dijk <v.dijk.bas@gmail.com>
Contents
Combining
Wrapping in delimiters
From characters
From showable values
Description
Note that I am thinking about putting some of the combinators ((<>), (<+>), ($$) and maybe more) in a type class. This allows the 'pretty' package to use this package.
Synopsis
(<>) :: Monoid s => s -> s -> s
mid :: Monoid s => s -> s -> s -> s
(<+>) :: (Monoid s, IsString s) => s -> s -> s
($$) :: (Monoid s, IsString s) => s -> s -> s
hcat :: Monoid s => [s] -> s
hsep :: (Monoid s, IsString s) => [s] -> s
vcat :: (Monoid s, IsString s) => [s] -> s
punctuate :: Monoid s => s -> [s] -> [s]
between :: Monoid s => s -> s -> s -> s
paren :: (Monoid s, IsString s) => 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
(<>) :: Monoid s => s -> s -> sSource
Put two strings besides eachother. Note that <> is just a synonym for mappend.
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 strings besides eachother separated by a space.
($$) :: (Monoid s, IsString s) => s -> s -> sSource
Put two strings above eachother.
hcat :: Monoid s => [s] -> sSource
List version of <>
hsep :: (Monoid s, IsString s) => [s] -> sSource
List version of <+>
vcat :: (Monoid s, IsString s) => [s] -> sSource
List version of $$
punctuate :: Monoid s => s -> [s] -> [s]Source
punctuate p [d1, ... dn] = [d1 <> p, d2 <> p, ... dn-1 <> p, dn]
Wrapping in delimiters
between :: Monoid s => s -> s -> s -> sSource
between b c s wraps the string s between b and c
paren :: (Monoid s, IsString s) => s -> sSource
wrap a string in (...)
brackets :: (Monoid s, IsString s) => s -> sSource
wrap a string in [...]
braces :: (Monoid s, IsString s) => s -> sSource
wrap a string in {...}
angleBrackets :: (Monoid s, IsString s) => s -> sSource
wrap a string in <...>
quotes :: (Monoid s, IsString s) => s -> sSource
wrap a string in '...'
doubleQuotes :: (Monoid s, IsString s) => s -> sSource
wrap a string in "..."
From characters
char :: IsString s => Char -> sSource
convert a character to a string
semi :: IsString s => sSource
A ';' character
colon :: IsString s => sSource
A ':' character
comma :: IsString s => sSource
A ',' character
space :: IsString s => sSource
A ' ' character
newline :: IsString s => sSource
A '\n' character
equals :: IsString s => sSource
A '=' character
lparen :: IsString s => sSource
A '(' character
rparen :: IsString s => sSource
A ')' character
lbrack :: IsString s => sSource
A '[' character
rbrack :: IsString s => sSource
A ']' character
lbrace :: IsString s => sSource
A '{' character
rbrace :: IsString s => sSource
A '}' character
labrack :: IsString s => sSource
A '<' character
rabrack :: IsString s => sSource
A '>' character
From showable values
fromShow :: (Show a, IsString s) => a -> sSource
Convert a Show-able value to a string. fromShow = fromString . show
int :: IsString s => Int -> sSource
integer :: IsString s => Integer -> sSource
float :: IsString s => Float -> sSource
double :: IsString s => Double -> sSource
rational :: IsString s => Rational -> sSource
Produced by Haddock version 2.4.2