Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class (StringCells s, StringRWIO s) => Stringy s
- 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
- 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
- unfoldrN64 :: Int64 -> (a -> Maybe (StringCellChar s, a)) -> a -> s
- altUnfoldrN64 :: Int64 -> (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 StringRWIO s where
- hGetContents :: Handle -> IO s
- hGetLine :: Handle -> IO s
- hPutStr :: Handle -> s -> IO ()
- hPutStrLn :: Handle -> s -> IO ()
- interact :: (s -> s) -> IO ()
- getContents :: IO s
- getLine :: IO s
- putStr :: s -> IO ()
- putStrLn :: s -> IO ()
- readFile :: FilePath -> IO s
- writeFile :: FilePath -> s -> IO ()
- appendFile :: FilePath -> s -> IO ()
- 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.Stringy s => GenString {
- gen_string :: s
- type GenStringDefault = ByteString
Documentation
class (StringCells s, StringRWIO s) => Stringy s Source #
String super class
Instances
(StringCells s, StringRWIO s) => Stringy s Source # | |
Defined in Data.String.Class |
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
type StringCellChar s Source #
type StringCellAltChar s Source #
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
head :: s -> StringCellChar s Source #
last :: s -> StringCellChar 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 #
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 #
Instances
class StringCell c where Source #
toWord8 :: c -> Word8 Source #
toWord16 :: c -> Word16 Source #
toWord32 :: c -> Word32 Source #
toWord64 :: c -> Word64 Source #
fromChar :: Char -> c Source #
fromWord8 :: Word8 -> c Source #
fromWord16 :: Word16 -> c Source #
fromWord32 :: Word32 -> c Source #
fromWord64 :: Word64 -> c Source #
Instances
class StringRWIO s where Source #
Minimal complete definition: hGetContents
, hGetLine
, hPutStr
, and hPutStrLn
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
Read a single line of user input from stdin
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
class ConvGenString s where Source #
toGenString :: s -> GenString Source #
fromGenString :: GenString -> s Source #
Instances
ConvGenString ByteString Source # | |
Defined in Data.String.Class toGenString :: ByteString -> GenString Source # fromGenString :: GenString -> ByteString Source # | |
ConvGenString ByteString Source # | |
Defined in Data.String.Class toGenString :: ByteString -> GenString Source # fromGenString :: GenString -> ByteString Source # | |
ConvGenString GenString Source # | |
Defined in Data.String.Class toGenString :: GenString -> GenString Source # fromGenString :: GenString -> GenString Source # | |
ConvGenString Text Source # | |
Defined in Data.String.Class toGenString :: Text -> GenString Source # fromGenString :: GenString -> Text Source # | |
ConvGenString Text Source # | |
Defined in Data.String.Class toGenString :: Text -> GenString Source # fromGenString :: GenString -> Text Source # | |
ConvGenString String Source # | |
Defined in Data.String.Class toGenString :: String -> GenString Source # fromGenString :: GenString -> String Source # |
class ConvString s where Source #
Instances
ConvString ByteString Source # | |
Defined in Data.String.Class toString :: ByteString -> String Source # fromString :: String -> ByteString Source # | |
ConvString ByteString Source # | |
Defined in Data.String.Class toString :: ByteString -> String Source # fromString :: String -> ByteString Source # | |
ConvString GenString Source # | |
ConvString Text Source # | |
ConvString Text Source # | |
ConvString String Source # | |
class ConvStrictByteString s where Source #
toStrictByteString :: s -> ByteString Source #
fromStrictByteString :: ByteString -> s Source #
Instances
ConvStrictByteString ByteString Source # | |
Defined in Data.String.Class | |
ConvStrictByteString ByteString Source # | |
Defined in Data.String.Class | |
ConvStrictByteString GenString Source # | |
Defined in Data.String.Class | |
ConvStrictByteString Text Source # | |
Defined in Data.String.Class toStrictByteString :: Text -> ByteString Source # | |
ConvStrictByteString Text Source # | |
Defined in Data.String.Class toStrictByteString :: Text -> ByteString Source # | |
ConvStrictByteString String Source # | |
Defined in Data.String.Class |
class ConvLazyByteString s where Source #
toLazyByteString :: s -> ByteString Source #
fromLazyByteString :: ByteString -> s Source #
Instances
ConvLazyByteString ByteString Source # | |
Defined in Data.String.Class | |
ConvLazyByteString ByteString Source # | |
Defined in Data.String.Class | |
ConvLazyByteString GenString Source # | |
Defined in Data.String.Class | |
ConvLazyByteString Text Source # | |
Defined in Data.String.Class toLazyByteString :: Text -> ByteString Source # fromLazyByteString :: ByteString -> Text Source # | |
ConvLazyByteString Text Source # | |
Defined in Data.String.Class toLazyByteString :: Text -> ByteString Source # fromLazyByteString :: ByteString -> Text Source # | |
ConvLazyByteString String Source # | |
Defined in Data.String.Class toLazyByteString :: String -> ByteString Source # |
class ConvText s where Source #
Instances
ConvText ByteString Source # | |
Defined in Data.String.Class toText :: ByteString -> Text Source # fromText :: Text -> ByteString Source # | |
ConvText ByteString Source # | |
Defined in Data.String.Class toText :: ByteString -> Text Source # fromText :: Text -> ByteString Source # | |
ConvText GenString Source # | |
ConvText Text Source # | |
ConvText Text Source # | |
ConvText String Source # | |
Polymorphic container of a string
When operations take place on multiple GenString
s, 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.
forall s.Stringy s => GenString | |
|
Instances
type GenStringDefault = ByteString Source #
This type is used by GenString
when a concrete string type is needed