string-class-0.1.6.5: String class library

Safe HaskellNone
LanguageHaskell2010

Data.String.Class

Synopsis

Documentation

class (StringCells s, StringRWIO s) => Stringy s Source

String super class

Instances

class (Eq s, Monoid s, IsString s, Typeable s, StringCell (StringCellChar s), StringCell (StringCellAltChar s), ConvGenString s, ConvString s, ConvStrictByteString s, ConvLazyByteString s, ConvText s, ConvLazyText s) => StringCells s where Source

Minimal complete definition: StringCellChar; StringCellAltChar; toStringCells; fromStringCells; toMainChar; toAltChar; cons; snoc; either all of head, tail, last, and init, or all of uncons and unsnoc; take, take64 or genericTake; drop, drop64, or genericDrop; and length, length64, or genericLength

Minimal complete definition

toStringCells, fromStringCells, cons, snoc, toMainChar, toAltChar

Associated Types

type StringCellChar s Source

type StringCellAltChar s Source

Methods

toStringCells :: StringCells s2 => s -> s2 Source

fromStringCells :: StringCells s2 => s2 -> s Source

cons :: StringCellChar s -> s -> s infixr 9 Source

uncons :: s -> (StringCellChar s, s) infixr 9 Source

snoc :: s -> StringCellChar s -> s Source

unsnoc :: s -> (s, StringCellChar s) Source

altCons :: StringCellAltChar s -> s -> s infixr 9 Source

altUncons :: s -> (StringCellAltChar s, s) infixr 9 Source

altSnoc :: s -> StringCellAltChar s -> s Source

altUnsnoc :: s -> (s, StringCellAltChar s) Source

toMainChar :: StringCell c => c -> Tagged s (StringCellChar s) Source

toAltChar :: StringCell c => c -> Tagged s (StringCellAltChar s) Source

append :: s -> s -> s infixr 9 Source

Append two strings

concat :: [s] -> s Source

empty :: s Source

null :: s -> Bool Source

head :: s -> StringCellChar s Source

tail :: s -> s Source

last :: s -> StringCellChar s Source

init :: s -> s Source

altHead :: s -> StringCellAltChar s Source

altLast :: s -> StringCellAltChar s Source

unfoldr :: (a -> Maybe (StringCellChar s, a)) -> a -> s Source

Construction of a string; implementations should behave safely with incorrect lengths

The default implementation of unfoldr is independent from that of altUnfoldr, as well as unfoldrN as and altUnfoldrN.

altUnfoldr :: (a -> Maybe (StringCellAltChar s, a)) -> a -> s Source

unfoldrN :: Int -> (a -> Maybe (StringCellChar s, a)) -> a -> s Source

altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s Source

unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar s, a)) -> a -> s Source

altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s Source

index :: s -> Int -> StringCellChar s Source

Get the character at the given position

Just like drop, drop64, and the variants of those functions, the default definitions of these three variants are independent of each other, and are defined in terms of head and tail, which can be inefficient.

index64 :: s -> Int64 -> StringCellChar s Source

genericIndex :: Integral i => s -> i -> StringCellChar s Source

Index a string at any location

Just like the other generic functions of this module, this function can be significantly slower than index, since the function must be able to support arbitrarily large indices. Consider using index or index64, even if you need to coerce the index to an Int.

take :: Int -> s -> s Source

take64 :: Int64 -> s -> s Source

genericTake :: Integral i => i -> s -> s Source

drop :: Int -> s -> s Source

drop64 :: Int64 -> s -> s Source

genericDrop :: Integral i => i -> s -> s Source

length :: s -> Int Source

length64 :: s -> Int64 Source

genericLength :: Integral i => s -> i Source

safeUncons :: s -> Maybe (StringCellChar s, s) Source

safeUnsnoc :: s -> Maybe (s, StringCellChar s) Source

safeAltUncons :: s -> Maybe (StringCellAltChar s, s) Source

safeAltUnsnoc :: s -> Maybe (s, StringCellAltChar s) Source

safeHead :: s -> Maybe (StringCellChar s) Source

safeTail :: s -> Maybe s Source

safeLast :: s -> Maybe (StringCellChar s) Source

safeInit :: s -> Maybe s Source

safeAltHead :: s -> Maybe (StringCellAltChar s) Source

safeAltLast :: s -> Maybe (StringCellAltChar s) Source

safeIndex :: s -> Int -> Maybe (StringCellChar s) Source

safeIndex64 :: s -> Int64 -> Maybe (StringCellChar s) Source

safeGenericIndex :: Integral i => s -> i -> Maybe (StringCellChar s) Source

safeTake :: Int -> s -> Maybe s Source

safeTake64 :: Int64 -> s -> Maybe s Source

safeGenericTake :: Integral i => i -> s -> Maybe s Source

safeDrop :: Int -> s -> Maybe s Source

safeDrop64 :: Int64 -> s -> Maybe s Source

safeGenericDrop :: Integral i => i -> s -> Maybe s Source

safeUncons2 :: s -> Maybe (StringCellChar s, StringCellChar s, s) Source

safeUncons3 :: s -> Maybe (StringCellChar s, StringCellChar s, StringCellChar s, s) Source

safeUncons4 :: s -> Maybe (StringCellChar s, StringCellChar s, StringCellChar s, StringCellChar s, s) Source

cons2 :: StringCellChar s -> StringCellChar s -> s -> s infixr 9 Source

cons3 :: StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s infixr 9 Source

cons4 :: StringCellChar s -> StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s infixr 9 Source

uncons2 :: s -> (StringCellChar s, StringCellChar s, s) infixr 9 Source

uncons3 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, s) infixr 9 Source

uncons4 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, StringCellChar s, s) infixr 9 Source

class StringRWIO s where Source

Minimal complete definition: hGetContents, hGetLine, hPutStr, and hPutStrLn

Minimal complete definition

hGetContents, hGetLine, hPutStr, hPutStrLn

Methods

hGetContents :: Handle -> IO s Source

Read n bytes *or* characters, depending on the implementation into a ByteString, directly from the specified Handle

Whether or not this function is lazy depends on the instance; laziness is preferred.

hGetLine :: Handle -> IO s Source

Read a single line from a handle

hPutStr :: Handle -> s -> IO () Source

Write a string to a handle

hPutStrLn :: Handle -> s -> IO () Source

Write a string to a handle, followed by a newline

N.B.: implementations might not define this atomically. If the state of being atomic is necessary, one possible solution is to convert a string to an efficient type for which hPutStrLn is atomic.

interact :: (s -> s) -> IO () Source

Take a function of type Text -> Text as its argument

The entire input from the standard input device is passed to this function as its argument, and the resulting string is output on the standard output device.

getContents :: IO s Source

Read all user input on stdin as a single string

getLine :: IO s Source

Read a single line of user input from stdin

putStr :: s -> IO () Source

Write a string to stdout

putStrLn :: s -> IO () Source

Write a string to stdout, followed by a newline

readFile :: FilePath -> IO s Source

Read a file and returns the contents of the file as a string

Depending on the instance, this function might expect the file to be non-binary. The default definition uses openFile to open the file.

writeFile :: FilePath -> s -> IO () Source

Write a string to a file

The file is truncated to zero length before writing begins. The default definition uses withFile to open the file.

appendFile :: FilePath -> s -> IO () Source

Write a string to the end of a file

The default definition uses withFile to open the file.

Instances

StringRWIO String

See 'System.IO for documentation of behaviour.

StringRWIO ByteString

See ByteString for documentation of behaviour.

StringRWIO ByteString

See Lazy for documentation of behaviour.

hGetLine and getLine are defined in terms of toStringCells and the equivalent methods of ByteString. hPutStrLn is defined non-atomically: it is defined as an action that puts the string and then separately puts a newline character string.

StringRWIO Text

See IO for documentation of behaviour.

StringRWIO Text

See IO for documentation of behaviour.

StringRWIO GenString

This is minimally defined with GenStringDefault.

data GenString Source

Polymorphic container of a string

When operations take place on multiple GenStrings, they are first converted to the type GenStringDefault, which are lazy bytestrings, whenever absolutely necessary (which includes testing for equality, appending strings, concatenating lists of strings, empty strings with empty, and unfolding), making them the most efficient type for this polymorphic container.

Constructors

forall s . Stringy s => GenString 

Fields

gen_string :: s
 

type GenStringDefault = ByteString Source

This type is used by GenString when a concrete string type is needed