str-0.1.0.0: A type class to abstract between many different string types.

Safe HaskellNone
LanguageHaskell2010

Text.Str

Synopsis

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 newtyped 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 Strs.

Methods

toString :: s -> String Source

toByteString :: s -> ByteString Source

toText :: s -> Text Source

toOctets :: s -> [Octet] Source

toHex :: s -> s Source

fromText :: Text -> s 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

singleton :: Char -> s Source

cons :: Char -> s -> s Source

snoc :: s -> Char -> s Source

lower :: s -> s Source

upper :: s -> s Source

capitalize :: s -> s Source

reverse :: s -> s Source

length :: s -> Int Source

dropWhile :: (Char -> Bool) -> s -> s Source

isPrefixOf :: s -> s -> Bool Source

isSuffixOf :: s -> s -> Bool Source

trim :: s -> s Source

class IsString a where

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

Methods

fromString :: String -> a

show :: (Show a, Str s) => a -> s Source

Generalizes show to return any string type.

error :: Str s => s -> a Source

Generalizes error to accept any string type.

joinLines :: Str s => [s] -> s Source

Joins strings with newlines.

joinCommas :: Str s => [s] -> s Source

Joins strings with commas.

joinSemis :: Str s => [s] -> s Source

Joins strings with semicolons.

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 Strings to one that operates on any Str.

asByteString :: Str s => (ByteString -> ByteString) -> s -> s Source

Converts a function that operates on ByteStrings 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.

unlines :: Str s => [s] -> s Source

Joins strings with newline separation, and adds a trailing newline.

putStrLn :: Str s => s -> IO () Source

Generalizes putStrLn.