Data.String.Class
- class (StringCell (StringCellChar s), StringCell (StringCellAltChar s), ConvGenString s, ConvString s, ConvStrictByteString s, ConvLazyByteString s, ConvText s, Eq s, Typeable s) => StringCells s where
- type StringCellChar s
- type StringCellAltChar s
- toStringCells :: StringCells s2 => s -> s2
- fromStringCells :: StringCells s2 => s2 -> s
- cons :: StringCellChar s -> s -> s
- uncons :: s -> (StringCellChar s, s)
- snoc :: s -> StringCellChar s -> s
- unsnoc :: s -> (s, StringCellChar s)
- altCons :: StringCellAltChar s -> s -> s
- altUncons :: s -> (StringCellAltChar s, s)
- altSnoc :: s -> StringCellAltChar s -> s
- altUnsnoc :: s -> (s, StringCellAltChar s)
- toMainChar :: StringCell c => c -> Tagged s (StringCellChar s)
- toAltChar :: StringCell c => c -> Tagged s (StringCellAltChar s)
- append :: s -> s -> s
- concat :: [s] -> s
- empty :: s
- null :: s -> Bool
- head :: s -> StringCellChar s
- tail :: s -> s
- last :: s -> StringCellChar s
- init :: s -> s
- altHead :: s -> StringCellAltChar s
- altLast :: s -> StringCellAltChar s
- unfoldr :: (a -> Maybe (StringCellChar s, a)) -> a -> s
- altUnfoldr :: (a -> Maybe (StringCellAltChar s, a)) -> a -> s
- unfoldrN :: Int -> (a -> Maybe (StringCellChar s, a)) -> a -> s
- altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s
- index :: s -> Int -> StringCellChar s
- index64 :: s -> Int64 -> StringCellChar s
- genericIndex :: Integral i => s -> i -> StringCellChar s
- take :: Int -> s -> s
- take64 :: Int64 -> s -> s
- genericTake :: Integral i => i -> s -> s
- drop :: Int -> s -> s
- drop64 :: Int64 -> s -> s
- genericDrop :: Integral i => i -> s -> s
- length :: s -> Int
- length64 :: s -> Int64
- genericLength :: Integral i => s -> i
- safeUncons :: s -> Maybe (StringCellChar s, s)
- safeUnsnoc :: s -> Maybe (s, StringCellChar s)
- safeAltUncons :: s -> Maybe (StringCellAltChar s, s)
- safeAltUnsnoc :: s -> Maybe (s, StringCellAltChar s)
- safeHead :: s -> Maybe (StringCellChar s)
- safeTail :: s -> Maybe s
- safeLast :: s -> Maybe (StringCellChar s)
- safeInit :: s -> Maybe s
- safeAltHead :: s -> Maybe (StringCellAltChar s)
- safeAltLast :: s -> Maybe (StringCellAltChar s)
- safeIndex :: s -> Int -> Maybe (StringCellChar s)
- safeIndex64 :: s -> Int64 -> Maybe (StringCellChar s)
- safeGenericIndex :: Integral i => s -> i -> Maybe (StringCellChar s)
- safeTake :: Int -> s -> Maybe s
- safeTake64 :: Int64 -> s -> Maybe s
- safeGenericTake :: Integral i => i -> s -> Maybe s
- safeDrop :: Int -> s -> Maybe s
- safeDrop64 :: Int64 -> s -> Maybe s
- safeGenericDrop :: Integral i => i -> s -> Maybe s
- safeUncons2 :: s -> Maybe (StringCellChar s, StringCellChar s, s)
- safeUncons3 :: s -> Maybe (StringCellChar s, StringCellChar s, StringCellChar s, s)
- safeUncons4 :: s -> Maybe (StringCellChar s, StringCellChar s, StringCellChar s, StringCellChar s, s)
- cons2 :: StringCellChar s -> StringCellChar s -> s -> s
- cons3 :: StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s
- cons4 :: StringCellChar s -> StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s
- uncons2 :: s -> (StringCellChar s, StringCellChar s, s)
- uncons3 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, s)
- uncons4 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, StringCellChar s, s)
- class StringCell c where
- class ConvGenString s where
- toGenString :: s -> GenString
- fromGenString :: GenString -> s
- class ConvString s where
- toString :: s -> String
- fromString :: String -> s
- class ConvStrictByteString s where
- toStrictByteString :: s -> ByteString
- fromStrictByteString :: ByteString -> s
- class ConvLazyByteString s where
- toLazyByteString :: s -> ByteString
- fromLazyByteString :: ByteString -> s
- class ConvText s where
- data GenString = forall s . StringCells s => GenString {
- gen_string :: s
- type GenStringDefault = ByteString
Documentation
class (StringCell (StringCellChar s), StringCell (StringCellAltChar s), ConvGenString s, ConvString s, ConvStrictByteString s, ConvLazyByteString s, ConvText s, Eq s, Typeable s) => StringCells s whereSource
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; length, length64, or genericLength; empty; null; and concat
Methods
toStringCells :: StringCells s2 => s -> s2Source
fromStringCells :: StringCells s2 => s2 -> sSource
cons :: StringCellChar s -> s -> sSource
uncons :: s -> (StringCellChar s, s)Source
snoc :: s -> StringCellChar s -> sSource
unsnoc :: s -> (s, StringCellChar s)Source
altCons :: StringCellAltChar s -> s -> sSource
altUncons :: s -> (StringCellAltChar s, s)Source
altSnoc :: s -> StringCellAltChar s -> sSource
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 two strings
head :: s -> StringCellChar sSource
last :: s -> StringCellChar sSource
altHead :: s -> StringCellAltChar sSource
altLast :: s -> StringCellAltChar sSource
unfoldr :: (a -> Maybe (StringCellChar s, a)) -> a -> sSource
Construction of a string; implementations should behave safely with incorrect lengths
The default implementation of undfoldr is independent from that of altUnfoldr,
as well as unfoldrN as and altUnfoldrN.
altUnfoldr :: (a -> Maybe (StringCellAltChar s, a)) -> a -> sSource
unfoldrN :: Int -> (a -> Maybe (StringCellChar s, a)) -> a -> sSource
altUnfoldrN :: Int -> (a -> Maybe (StringCellAltChar s, a)) -> a -> sSource
index :: s -> Int -> StringCellChar sSource
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 sSource
genericIndex :: Integral i => s -> i -> StringCellChar sSource
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.
take64 :: Int64 -> s -> sSource
genericTake :: Integral i => i -> s -> sSource
drop64 :: Int64 -> s -> sSource
genericDrop :: Integral i => i -> s -> sSource
genericLength :: Integral i => s -> iSource
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 sSource
safeLast :: s -> Maybe (StringCellChar s)Source
safeInit :: s -> Maybe sSource
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 sSource
safeTake64 :: Int64 -> s -> Maybe sSource
safeGenericTake :: Integral i => i -> s -> Maybe sSource
safeDrop :: Int -> s -> Maybe sSource
safeDrop64 :: Int64 -> s -> Maybe sSource
safeGenericDrop :: Integral i => i -> s -> Maybe sSource
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 -> sSource
cons3 :: StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> sSource
cons4 :: StringCellChar s -> StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> sSource
uncons2 :: s -> (StringCellChar s, StringCellChar s, s)Source
uncons3 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, s)Source
uncons4 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, StringCellChar s, s)Source
class StringCell c whereSource
Methods
fromWord16 :: Word16 -> cSource
fromWord32 :: Word32 -> cSource
fromWord64 :: Word64 -> cSource
class ConvGenString s whereSource
class ConvString s whereSource
class ConvStrictByteString s whereSource
class ConvLazyByteString s whereSource
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 . StringCells s => GenString | |
Fields
| |
type GenStringDefault = ByteStringSource
This type is used by GenString when a concrete string type is needed