Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.Str
- class (IsString s, Show s, Ord s, Hashable s, Monoid s) => Str s where
- toString :: s -> String
- toByteString :: s -> ByteString
- toText :: s -> Text
- toOctets :: s -> [Octet]
- toHex :: s -> s
- fromText :: Text -> s
- fromByteString :: ByteString -> s
- fromOctets :: [Octet] -> s
- joinBy :: s -> [s] -> s
- splitOn :: s -> s -> [s]
- smap :: (Char -> Char) -> s -> s
- singleton :: Char -> s
- cons :: Char -> s -> s
- snoc :: s -> Char -> s
- lower :: s -> s
- upper :: s -> s
- capitalize :: s -> s
- reverse :: s -> s
- length :: s -> Int
- dropWhile :: (Char -> Bool) -> s -> s
- isPrefixOf :: s -> s -> Bool
- isSuffixOf :: s -> s -> Bool
- trim :: s -> s
- class IsString a where
- fromString :: String -> a
- show :: (Show a, Str s) => a -> s
- error :: Str s => s -> a
- joinLines :: Str s => [s] -> s
- joinCommas :: Str s => [s] -> s
- joinSemis :: Str s => [s] -> s
- joinSlashes :: Str s => [s] -> s
- asString :: Str s => (String -> String) -> s -> s
- asByteString :: Str s => (ByteString -> ByteString) -> s -> s
- asText :: Str s => (Text -> Text) -> s -> s
- asString2 :: Str s => (String -> String -> String) -> s -> s -> s
- asByteString2 :: Str s => (ByteString -> ByteString -> ByteString) -> s -> s -> s
- wrapText :: Str s => (Text -> a) -> s -> a
- wrapString :: Str s => (String -> a) -> s -> a
- wrapByteString :: Str s => (ByteString -> a) -> s -> a
- wrapByteString2 :: Str s => (ByteString -> ByteString -> a) -> s -> s -> a
- unlines :: Str s => [s] -> s
- putStrLn :: Str s => s -> IO ()
Documentation
class (IsString s, Show s, Ord s, Hashable s, Monoid s) => Str s where Source
Str
types are any type which can be thought as abstract strings; that
is, ordered lists of Char. There are at least 3 commonly-used string types
in Haskell (String, ByteString and Text), as well as newtype
d strings.
The interop with these types can be tedious or even bug-prone. Using
Str
allows functions to be written agnostically towards any particular
type. It provides a set of commonly-needed string manipulation functions,
and the ability to convert to and from a variety of string types, which
lets us "borrow" existing functions which only operate on one of the types
(see the various as-
functions). Str
extends several useful classes,
perhaps most importantly IsString
, which lets us use string literals to
represent Str
s.
Minimal complete definition
toString, toByteString, toText, toOctets, fromText, fromByteString, fromOctets, joinBy, splitOn, smap, singleton, cons, snoc, reverse, length, dropWhile, isPrefixOf, isSuffixOf
Methods
toString :: s -> String Source
toByteString :: s -> ByteString Source
toOctets :: s -> [Octet] Source
fromByteString :: ByteString -> s Source
fromOctets :: [Octet] -> s Source
joinBy :: s -> [s] -> s Source
splitOn :: s -> s -> [s] Source
smap :: (Char -> Char) -> s -> s Source
capitalize :: s -> s Source
dropWhile :: (Char -> Bool) -> s -> s Source
isPrefixOf :: s -> s -> Bool Source
isSuffixOf :: s -> s -> Bool Source
class IsString a where
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
Methods
fromString :: String -> a
joinCommas :: Str s => [s] -> s Source
Joins strings with commas.
joinSlashes :: Str s => [s] -> s Source
Joins strings with forward slashes.
asString :: Str s => (String -> String) -> s -> s Source
Converts a function that operates on String
s to one that operates
on any Str
.
asByteString :: Str s => (ByteString -> ByteString) -> s -> s Source
Converts a function that operates on ByteString
s to one that operates
on any Str
.
asText :: Str s => (Text -> Text) -> s -> s Source
Converts a function that operates on Text
to one that operates on any
Str
.
asString2 :: Str s => (String -> String -> String) -> s -> s -> s Source
Same as asString
but for functions with arity 2.
asByteString2 :: Str s => (ByteString -> ByteString -> ByteString) -> s -> s -> s Source
Same as asByteString
but for functions with arity 2.
wrapText :: Str s => (Text -> a) -> s -> a Source
Converts a function that takes a Text
into one that takes any Str
.
wrapString :: Str s => (String -> a) -> s -> a Source
Generalizes functions that take a String
.
wrapByteString :: Str s => (ByteString -> a) -> s -> a Source
Generalizes functions that take a ByteString
.
wrapByteString2 :: Str s => (ByteString -> ByteString -> a) -> s -> s -> a Source
Generalizes functions that take two ByteStrings
.