Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2021 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Reexports functions to work with Text
, ByteString
and
ShortByteString
types.
Synopsis
- class IsString a where
- fromString :: String -> a
- type String = [Char]
- class Read a
- readMaybe :: Read a => String -> Maybe a
- reads :: Read a => ReadS a
- data Text
- lines :: IsText t "lines" => t -> [t]
- unlines :: IsText t "unlines" => [t] -> t
- words :: IsText t "words" => t -> [t]
- unwords :: IsText t "unwords" => [t] -> t
- decodeUtf8' :: ByteString -> Either UnicodeException Text
- decodeUtf8With :: OnDecodeError -> ByteString -> Text
- lenientDecode :: OnDecodeError
- strictDecode :: OnDecodeError
- type OnError a b = String -> Maybe a -> Maybe b
- type OnDecodeError = OnError Word8 Char
- data UnicodeException
- data ByteString
- data ShortByteString
- toShort :: ByteString -> ShortByteString
- fromShort :: ShortByteString -> ByteString
String
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
fromString :: String -> a #
Instances
IsString ShortByteString | Beware: |
Defined in Data.ByteString.Short.Internal fromString :: String -> ShortByteString # | |
IsString ByteString | Beware: |
Defined in Data.ByteString.Lazy.Internal fromString :: String -> ByteString # | |
IsString ByteString | Beware: |
Defined in Data.ByteString.Internal fromString :: String -> ByteString # | |
a ~ Char => IsString [a] |
Since: base-2.1 |
Defined in Data.String fromString :: String -> [a] # | |
IsString a => IsString (Identity a) | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Identity a # | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal fromString :: String -> Seq a # | |
(IsString a, Hashable a) => IsString (Hashed a) | |
Defined in Data.Hashable.Class fromString :: String -> Hashed a # | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b # |
Parsing of String
s, producing values.
Derived instances of Read
make the following assumptions, which
derived instances of Show
obey:
- If the constructor is defined to be an infix operator, then the
derived
Read
instance will parse only infix applications of the constructor (not the prefix form). - Associativity is not used to reduce the occurrence of parentheses, although precedence may be.
- If the constructor is defined using record syntax, the derived
Read
will parse only the record-syntax form, and furthermore, the fields must be given in the same order as the original declaration. - The derived
Read
instance allows arbitrary Haskell whitespace between tokens of the input string. Extra parentheses are also allowed.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Read
in Haskell 2010 is equivalent to
instance (Read a) => Read (Tree a) where readsPrec d r = readParen (d > app_prec) (\r -> [(Leaf m,t) | ("Leaf",s) <- lex r, (m,t) <- readsPrec (app_prec+1) s]) r ++ readParen (d > up_prec) (\r -> [(u:^:v,w) | (u,s) <- readsPrec (up_prec+1) r, (":^:",t) <- lex s, (v,w) <- readsPrec (up_prec+1) t]) r where app_prec = 10 up_prec = 5
Note that right-associativity of :^:
is unused.
The derived instance in GHC is equivalent to
instance (Read a) => Read (Tree a) where readPrec = parens $ (prec app_prec $ do Ident "Leaf" <- lexP m <- step readPrec return (Leaf m)) +++ (prec up_prec $ do u <- step readPrec Symbol ":^:" <- lexP v <- step readPrec return (u :^: v)) where app_prec = 10 up_prec = 5 readListPrec = readListPrecDefault
Why do both readsPrec
and readPrec
exist, and why does GHC opt to
implement readPrec
in derived Read
instances instead of readsPrec
?
The reason is that readsPrec
is based on the ReadS
type, and although
ReadS
is mentioned in the Haskell 2010 Report, it is not a very efficient
parser data structure.
readPrec
, on the other hand, is based on a much more efficient ReadPrec
datatype (a.k.a "new-style parsers"), but its definition relies on the use
of the RankNTypes
language extension. Therefore, readPrec
(and its
cousin, readListPrec
) are marked as GHC-only. Nevertheless, it is
recommended to use readPrec
instead of readsPrec
whenever possible
for the efficiency improvements it brings.
As mentioned above, derived Read
instances in GHC will implement
readPrec
instead of readsPrec
. The default implementations of
readsPrec
(and its cousin, readList
) will simply use readPrec
under
the hood. If you are writing a Read
instance by hand, it is recommended
to write it like so:
instanceRead
T wherereadPrec
= ...readListPrec
=readListPrecDefault
Instances
Read Bool | Since: base-2.1 |
Read Char | Since: base-2.1 |
Read Double | Since: base-2.1 |
Read Float | Since: base-2.1 |
Read Int | Since: base-2.1 |
Read Int8 | Since: base-2.1 |
Read Int16 | Since: base-2.1 |
Read Int32 | Since: base-2.1 |
Read Int64 | Since: base-2.1 |
Read Integer | Since: base-2.1 |
Read Natural | Since: base-4.8.0.0 |
Read Ordering | Since: base-2.1 |
Read Word | Since: base-4.5.0.0 |
Read Word8 | Since: base-2.1 |
Read Word16 | Since: base-2.1 |
Read Word32 | Since: base-2.1 |
Read Word64 | Since: base-2.1 |
Read () | Since: base-2.1 |
Read Void | Reading a Since: base-4.8.0.0 |
Read ExitCode | |
Read BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types readsPrec :: Int -> ReadS BufferMode # readList :: ReadS [BufferMode] # readPrec :: ReadPrec BufferMode # readListPrec :: ReadPrec [BufferMode] # | |
Read Newline | Since: base-4.3.0.0 |
Read NewlineMode | Since: base-4.3.0.0 |
Defined in GHC.IO.Handle.Types readsPrec :: Int -> ReadS NewlineMode # readList :: ReadS [NewlineMode] # readPrec :: ReadPrec NewlineMode # readListPrec :: ReadPrec [NewlineMode] # | |
Read All | Since: base-2.1 |
Read Any | Since: base-2.1 |
Read Fixity | Since: base-4.6.0.0 |
Read Associativity | Since: base-4.6.0.0 |
Defined in GHC.Generics readsPrec :: Int -> ReadS Associativity # readList :: ReadS [Associativity] # | |
Read SourceUnpackedness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Read SourceStrictness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Read DecidedStrictness | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Read CChar | |
Read CSChar | |
Read CUChar | |
Read CShort | |
Read CUShort | |
Read CInt | |
Read CUInt | |
Read CLong | |
Read CULong | |
Read CLLong | |
Read CULLong | |
Read CBool | |
Read CFloat | |
Read CDouble | |
Read CPtrdiff | |
Read CSize | |
Read CWchar | |
Read CSigAtomic | |
Defined in Foreign.C.Types readsPrec :: Int -> ReadS CSigAtomic # readList :: ReadS [CSigAtomic] # readPrec :: ReadPrec CSigAtomic # readListPrec :: ReadPrec [CSigAtomic] # | |
Read CClock | |
Read CTime | |
Read CUSeconds | |
Read CSUSeconds | |
Defined in Foreign.C.Types readsPrec :: Int -> ReadS CSUSeconds # readList :: ReadS [CSUSeconds] # readPrec :: ReadPrec CSUSeconds # readListPrec :: ReadPrec [CSUSeconds] # | |
Read CIntPtr | |
Read CUIntPtr | |
Read CIntMax | |
Read CUIntMax | |
Read WordPtr | |
Read IntPtr | |
Read SomeSymbol | Since: base-4.7.0.0 |
Defined in GHC.TypeLits readsPrec :: Int -> ReadS SomeSymbol # readList :: ReadS [SomeSymbol] # readPrec :: ReadPrec SomeSymbol # readListPrec :: ReadPrec [SomeSymbol] # | |
Read SomeNat | Since: base-4.7.0.0 |
Read IOMode | Since: base-4.2.0.0 |
Read Lexeme | Since: base-2.1 |
Read GeneralCategory | Since: base-2.1 |
Defined in GHC.Read | |
Read Version | Since: base-2.1 |
Read ShortByteString | |
Defined in Data.ByteString.Short.Internal | |
Read ByteString | |
Defined in Data.ByteString.Lazy.Internal readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |
Read ByteString | |
Defined in Data.ByteString.Internal readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |
Read IntSet | |
Read Undefined Source # | |
Read a => Read [a] | Since: base-2.1 |
Read a => Read (Maybe a) | Since: base-2.1 |
(Integral a, Read a) => Read (Ratio a) | Since: base-2.1 |
Read p => Read (Par1 p) | Since: base-4.7.0.0 |
Read a => Read (a) | Since: base-4.15 |
Read a => Read (Complex a) | Since: base-2.1 |
Read a => Read (Min a) | Since: base-4.9.0.0 |
Read a => Read (Max a) | Since: base-4.9.0.0 |
Read a => Read (First a) | Since: base-4.9.0.0 |
Read a => Read (Last a) | Since: base-4.9.0.0 |
Read m => Read (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup readsPrec :: Int -> ReadS (WrappedMonoid m) # readList :: ReadS [WrappedMonoid m] # readPrec :: ReadPrec (WrappedMonoid m) # readListPrec :: ReadPrec [WrappedMonoid m] # | |
Read a => Read (Option a) | Since: base-4.9.0.0 |
Read a => Read (ZipList a) | Since: base-4.7.0.0 |
Read a => Read (Identity a) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Read a => Read (First a) | Since: base-2.1 |
Read a => Read (Last a) | Since: base-2.1 |
Read a => Read (Dual a) | Since: base-2.1 |
Read a => Read (Sum a) | Since: base-2.1 |
Read a => Read (Product a) | Since: base-2.1 |
Read a => Read (Down a) | This instance would be equivalent to the derived instances of the
Since: base-4.7.0.0 |
Read a => Read (NonEmpty a) | Since: base-4.11.0.0 |
Read e => Read (IntMap e) | |
Read a => Read (Tree a) | |
Read a => Read (Seq a) | |
Read a => Read (ViewL a) | |
Read a => Read (ViewR a) | |
(Read a, Ord a) => Read (Set a) | |
(Eq a, Hashable a, Read a) => Read (HashSet a) | |
(Read a, Read b) => Read (Either a b) | Since: base-3.0 |
Read (V1 p) | Since: base-4.9.0.0 |
Read (U1 p) | Since: base-4.9.0.0 |
(Read a, Read b) => Read (a, b) | Since: base-2.1 |
(Ix a, Read a, Read b) => Read (Array a b) | Since: base-2.1 |
HasResolution a => Read (Fixed a) | Since: base-4.3.0.0 |
(Read a, Read b) => Read (Arg a b) | Since: base-4.9.0.0 |
Read (Proxy t) | Since: base-4.7.0.0 |
(Ord k, Read k, Read e) => Read (Map k e) | |
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) | |
(Read1 m, Read a) => Read (MaybeT m a) | |
Read (f p) => Read (Rec1 f p) | Since: base-4.7.0.0 |
(Read a, Read b, Read c) => Read (a, b, c) | Since: base-2.1 |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Read (f a) => Read (Ap f a) | Since: base-4.12.0.0 |
Read (f a) => Read (Alt f a) | Since: base-4.8.0.0 |
a ~ b => Read (a :~: b) | Since: base-4.7.0.0 |
(Read1 f, Read a) => Read (IdentityT f a) | |
(Read e, Read1 m, Read a) => Read (ErrorT e m a) | |
(Read e, Read1 m, Read a) => Read (ExceptT e m a) | |
Read c => Read (K1 i c p) | Since: base-4.7.0.0 |
(Read (f p), Read (g p)) => Read ((f :+: g) p) | Since: base-4.7.0.0 |
(Read (f p), Read (g p)) => Read ((f :*: g) p) | Since: base-4.7.0.0 |
(Read a, Read b, Read c, Read d) => Read (a, b, c, d) | Since: base-2.1 |
(Read1 f, Read1 g, Read a) => Read (Product f g a) | Since: base-4.9.0.0 |
(Read1 f, Read1 g, Read a) => Read (Sum f g a) | Since: base-4.9.0.0 |
a ~~ b => Read (a :~~: b) | Since: base-4.10.0.0 |
Read (f p) => Read (M1 i c f p) | Since: base-4.7.0.0 |
Read (f (g p)) => Read ((f :.: g) p) | Since: base-4.7.0.0 |
(Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) | Since: base-2.1 |
(Read1 f, Read1 g, Read a) => Read (Compose f g a) | Since: base-4.9.0.0 |
(Read a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (a, b, c, d, e, f, g) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) => Read (a, b, c, d, e, f, g, h) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i) => Read (a, b, c, d, e, f, g, h, i) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j) => Read (a, b, c, d, e, f, g, h, i, j) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k) => Read (a, b, c, d, e, f, g, h, i, j, k) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l) => Read (a, b, c, d, e, f, g, h, i, j, k, l) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n, Read o) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | Since: base-2.1 |
Defined in GHC.Read |
readMaybe :: Read a => String -> Maybe a #
Parse a string using the Read
instance.
Succeeds if there is exactly one valid result.
>>>
readMaybe "123" :: Maybe Int
Just 123
>>>
readMaybe "hello" :: Maybe Int
Nothing
Since: base-4.6.0.0
Text
A space efficient, packed, unboxed Unicode text type.
Instances
Hashable Text | |
Defined in Data.Hashable.Class | |
ToString Text Source # | |
ToLText Text Source # | |
ToText Text Source # | |
One Text Source # | Create singleton strict
law> |
LazyStrict LText Text Source # | |
ConvertUtf8 Text ShortByteString Source # | Since: 0.6.0.0 |
Defined in Relude.String.Conversion | |
ConvertUtf8 Text ByteString Source # | |
Defined in Relude.String.Conversion encodeUtf8 :: Text -> ByteString Source # decodeUtf8 :: ByteString -> Text Source # decodeUtf8Strict :: ByteString -> Either UnicodeException Text Source # | |
ConvertUtf8 Text LByteString Source # | |
Defined in Relude.String.Conversion encodeUtf8 :: Text -> LByteString Source # decodeUtf8 :: LByteString -> Text Source # decodeUtf8Strict :: LByteString -> Either UnicodeException Text Source # | |
type Item Text | |
type OneItem Text Source # | |
Defined in Relude.Container.One |
lines :: IsText t "lines" => t -> [t] Source #
lines
takes Text
and splits it into the list by lines.
Actual type of this function is the following:
lines ::Text
-> [Text
]
but it was given a more complex type to provide friendlier compile time errors.
>>>
lines ""
[]>>>
lines "one line"
["one line"]>>>
lines "line 1\nline 2"
["line 1","line 2"]>>>
lines ("string line" :: String)
... ... 'lines' works with 'Text', not 'String'. Possible fixes: 1. Make sure OverloadedStrings extension is enabled. 2. Apply 'toText' to a single value. 3. Apply 'map toText' to the list value. ...>>>
lines True
... ... 'lines' works with 'Text' But given: 'Bool' ...
unlines :: IsText t "unlines" => [t] -> t Source #
unlines
takes list of Text
values and joins them with line separator.
Actual type of this function is the following:
unlines :: [Text
] ->Text
but it was given a more complex type to provide friendlier compile time errors.
>>>
unlines []
"">>>
unlines ["line 1"]
"line 1\n">>>
unlines ["first line", "second line"]
"first line\nsecond line\n">>>
unlines (["line 1", "line 2"] :: [String])
... ... 'unlines' works with 'Text', not 'String'. Possible fixes: 1. Make sure OverloadedStrings extension is enabled. 2. Apply 'toText' to a single value. 3. Apply 'map toText' to the list value. ...>>>
unlines [True, False]
... ... 'unlines' works with 'Text' But given: 'Bool' ...
words :: IsText t "words" => t -> [t] Source #
words
takes Text
and splits it into the list by words.
Actual type of this function is the following:
words ::Text
-> [Text
]
but it was given a more complex type to provide friendlier compile time errors.
>>>
words ""
[]>>>
words "one line"
["one","line"]>>>
words " >_< "
[">_<"]>>>
words ("string words" :: String)
... ... 'words' works with 'Text', not 'String'. Possible fixes: 1. Make sure OverloadedStrings extension is enabled. 2. Apply 'toText' to a single value. 3. Apply 'map toText' to the list value. ...>>>
words True
... ... 'words' works with 'Text' But given: 'Bool' ...
unwords :: IsText t "unwords" => [t] -> t Source #
unwords
takes list of Text
values and joins them with space character.
Actual type of this function is the following:
unwords :: [Text
] ->Text
but it was given a more complex type to provide friendlier compile time errors.
>>>
unwords []
"">>>
unwords ["singleWord"]
"singleWord">>>
unwords ["word", "another"]
"word another">>>
unwords (["word", "another"] :: [String])
... ... 'unwords' works with 'Text', not 'String'. Possible fixes: 1. Make sure OverloadedStrings extension is enabled. 2. Apply 'toText' to a single value. 3. Apply 'map toText' to the list value. ...>>>
unwords [True, False]
... ... 'unwords' works with 'Text' But given: 'Bool' ...
decodeUtf8' :: ByteString -> Either UnicodeException Text #
Decode a ByteString
containing UTF-8 encoded text.
If the input contains any invalid UTF-8 data, the relevant exception will be returned, otherwise the decoded text.
decodeUtf8With :: OnDecodeError -> ByteString -> Text #
Decode a ByteString
containing UTF-8 encoded text.
NOTE: The replacement character returned by OnDecodeError
MUST be within the BMP plane; surrogate code points will
automatically be remapped to the replacement char U+FFFD
(since 0.11.3.0), whereas code points beyond the BMP will throw an
error
(since 1.2.3.1); For earlier versions of text
using
those unsupported code points would result in undefined behavior.
lenientDecode :: OnDecodeError #
Replace an invalid input byte with the Unicode replacement character U+FFFD.
strictDecode :: OnDecodeError #
Throw a UnicodeException
if decoding fails.
type OnError a b = String -> Maybe a -> Maybe b #
Function type for handling a coding error. It is supplied with two inputs:
- A
String
that describes the error. - The input value that caused the error. If the error arose
because the end of input was reached or could not be identified
precisely, this value will be
Nothing
.
If the handler returns a value wrapped with Just
, that value will
be used in the output as the replacement for the invalid input. If
it returns Nothing
, no value will be used in the output.
Should the handler need to abort processing, it should use error
or throw
an exception (preferably a UnicodeException
). It may
use the description provided to construct a more helpful error
report.
type OnDecodeError = OnError Word8 Char #
A handler for a decoding error.
data UnicodeException #
An exception type for representing Unicode encoding errors.
Instances
Eq UnicodeException | |
Defined in Data.Text.Encoding.Error (==) :: UnicodeException -> UnicodeException -> Bool # (/=) :: UnicodeException -> UnicodeException -> Bool # | |
Show UnicodeException | |
Defined in Data.Text.Encoding.Error showsPrec :: Int -> UnicodeException -> ShowS # show :: UnicodeException -> String # showList :: [UnicodeException] -> ShowS # | |
Exception UnicodeException | |
Defined in Data.Text.Encoding.Error | |
NFData UnicodeException | |
Defined in Data.Text.Encoding.Error rnf :: UnicodeException -> () # |
ByteString
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
IsList ByteString | Since: bytestring-0.10.12.0 |
Defined in Data.ByteString.Internal type Item ByteString # fromList :: [Item ByteString] -> ByteString # fromListN :: Int -> [Item ByteString] -> ByteString # toList :: ByteString -> [Item ByteString] # | |
Eq ByteString | |
Defined in Data.ByteString.Internal (==) :: ByteString -> ByteString -> Bool # (/=) :: ByteString -> ByteString -> Bool # | |
Data ByteString | |
Defined in Data.ByteString.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString # toConstr :: ByteString -> Constr # dataTypeOf :: ByteString -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) # gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r # gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString # | |
Ord ByteString | |
Defined in Data.ByteString.Internal compare :: ByteString -> ByteString -> Ordering # (<) :: ByteString -> ByteString -> Bool # (<=) :: ByteString -> ByteString -> Bool # (>) :: ByteString -> ByteString -> Bool # (>=) :: ByteString -> ByteString -> Bool # max :: ByteString -> ByteString -> ByteString # min :: ByteString -> ByteString -> ByteString # | |
Read ByteString | |
Defined in Data.ByteString.Internal readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |
Show ByteString | |
Defined in Data.ByteString.Internal showsPrec :: Int -> ByteString -> ShowS # show :: ByteString -> String # showList :: [ByteString] -> ShowS # | |
IsString ByteString | Beware: |
Defined in Data.ByteString.Internal fromString :: String -> ByteString # | |
Semigroup ByteString | |
Defined in Data.ByteString.Internal (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |
Monoid ByteString | |
Defined in Data.ByteString.Internal mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
NFData ByteString | |
Defined in Data.ByteString.Internal rnf :: ByteString -> () # | |
Hashable ByteString | |
Defined in Data.Hashable.Class hashWithSalt :: Int -> ByteString -> Int # hash :: ByteString -> Int # | |
EncodingError ToString "ByteString" "String" => ToString ByteString Source # | ⚠️CAUTION⚠️ This instance is for custom error display only. You should always specify encoding of bytes explicitly. In case it is used by mistake, the user will see the following:
Since: 0.6.0.0 |
Defined in Relude.String.Conversion toString :: ByteString -> String Source # | |
EncodingError ToLText "ByteString" "LText" => ToLText ByteString Source # | ⚠️CAUTION⚠️ This instance is for custom error display only. You should always specify encoding of bytes explicitly. In case it is used by mistake, the user will see the following:
Since: 0.6.0.0 |
Defined in Relude.String.Conversion toLText :: ByteString -> LText Source # | |
EncodingError ToText "ByteString" "Text" => ToText ByteString Source # | ⚠️CAUTION⚠️ This instance is for custom error display only. You should always specify encoding of bytes explicitly. In case it is used by mistake, the user will see the following:
Since: 0.6.0.0 |
Defined in Relude.String.Conversion toText :: ByteString -> Text Source # | |
One ByteString Source # | Create singleton strict
law> |
Defined in Relude.Container.One type OneItem ByteString Source # one :: OneItem ByteString -> ByteString Source # | |
LazyStrict LByteString ByteString Source # | |
Defined in Relude.String.Conversion toLazy :: ByteString -> LByteString Source # toStrict :: LByteString -> ByteString Source # | |
ConvertUtf8 String ByteString Source # | |
Defined in Relude.String.Conversion encodeUtf8 :: String -> ByteString Source # decodeUtf8 :: ByteString -> String Source # decodeUtf8Strict :: ByteString -> Either UnicodeException String Source # | |
ConvertUtf8 Text ByteString Source # | |
Defined in Relude.String.Conversion encodeUtf8 :: Text -> ByteString Source # decodeUtf8 :: ByteString -> Text Source # decodeUtf8Strict :: ByteString -> Either UnicodeException Text Source # | |
ConvertUtf8 LText ByteString Source # | |
Defined in Relude.String.Conversion encodeUtf8 :: LText -> ByteString Source # decodeUtf8 :: ByteString -> LText Source # decodeUtf8Strict :: ByteString -> Either UnicodeException LText Source # | |
type Item ByteString | |
Defined in Data.ByteString.Internal | |
type OneItem ByteString Source # | |
Defined in Relude.Container.One |
ShortByteString
data ShortByteString #
A compact representation of a Word8
vector.
It has a lower memory overhead than a ByteString
and does not
contribute to heap fragmentation. It can be converted to or from a
ByteString
(at the cost of copying the string data). It supports very few
other operations.
It is suitable for use as an internal representation for code that needs
to keep many short strings in memory, but it should not be used as an
interchange type. That is, it should not generally be used in public APIs.
The ByteString
type is usually more suitable for use in interfaces; it is
more flexible and it supports a wide range of operations.
Instances
IsList ShortByteString | Since: bytestring-0.10.12.0 |
Defined in Data.ByteString.Short.Internal type Item ShortByteString # fromList :: [Item ShortByteString] -> ShortByteString # fromListN :: Int -> [Item ShortByteString] -> ShortByteString # toList :: ShortByteString -> [Item ShortByteString] # | |
Eq ShortByteString | |
Defined in Data.ByteString.Short.Internal (==) :: ShortByteString -> ShortByteString -> Bool # (/=) :: ShortByteString -> ShortByteString -> Bool # | |
Data ShortByteString | |
Defined in Data.ByteString.Short.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShortByteString -> c ShortByteString # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShortByteString # toConstr :: ShortByteString -> Constr # dataTypeOf :: ShortByteString -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShortByteString) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortByteString) # gmapT :: (forall b. Data b => b -> b) -> ShortByteString -> ShortByteString # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShortByteString -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShortByteString -> r # gmapQ :: (forall d. Data d => d -> u) -> ShortByteString -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ShortByteString -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString # | |
Ord ShortByteString | |
Defined in Data.ByteString.Short.Internal compare :: ShortByteString -> ShortByteString -> Ordering # (<) :: ShortByteString -> ShortByteString -> Bool # (<=) :: ShortByteString -> ShortByteString -> Bool # (>) :: ShortByteString -> ShortByteString -> Bool # (>=) :: ShortByteString -> ShortByteString -> Bool # max :: ShortByteString -> ShortByteString -> ShortByteString # min :: ShortByteString -> ShortByteString -> ShortByteString # | |
Read ShortByteString | |
Defined in Data.ByteString.Short.Internal | |
Show ShortByteString | |
Defined in Data.ByteString.Short.Internal showsPrec :: Int -> ShortByteString -> ShowS # show :: ShortByteString -> String # showList :: [ShortByteString] -> ShowS # | |
IsString ShortByteString | Beware: |
Defined in Data.ByteString.Short.Internal fromString :: String -> ShortByteString # | |
Semigroup ShortByteString | |
Defined in Data.ByteString.Short.Internal (<>) :: ShortByteString -> ShortByteString -> ShortByteString # sconcat :: NonEmpty ShortByteString -> ShortByteString # stimes :: Integral b => b -> ShortByteString -> ShortByteString # | |
Monoid ShortByteString | |
Defined in Data.ByteString.Short.Internal mappend :: ShortByteString -> ShortByteString -> ShortByteString # mconcat :: [ShortByteString] -> ShortByteString # | |
NFData ShortByteString | |
Defined in Data.ByteString.Short.Internal rnf :: ShortByteString -> () # | |
Hashable ShortByteString | |
Defined in Data.Hashable.Class hashWithSalt :: Int -> ShortByteString -> Int # hash :: ShortByteString -> Int # | |
EncodingError ToString "ShortByteString" "String" => ToString ShortByteString Source # | ⚠️CAUTION⚠️ This instance is for custom error display only. You should always specify encoding of bytes explicitly. In case it is used by mistake, the user will see the following:
Since: 0.6.0.0 |
Defined in Relude.String.Conversion toString :: ShortByteString -> String Source # | |
EncodingError ToLText "ShortByteString" "LText" => ToLText ShortByteString Source # | ⚠️CAUTION⚠️ This instance is for custom error display only. You should always specify encoding of bytes explicitly. In case it is used by mistake, the user will see the following:
Since: 0.6.0.0 |
Defined in Relude.String.Conversion toLText :: ShortByteString -> LText Source # | |
EncodingError ToText "ShortByteString" "Text" => ToText ShortByteString Source # | ⚠️CAUTION⚠️ This instance is for custom error display only. You should always specify encoding of bytes explicitly. In case it is used by mistake, the user will see the following:
Since: 0.6.0.0 |
Defined in Relude.String.Conversion toText :: ShortByteString -> Text Source # | |
One ShortByteString Source # | Create singleton
law> |
Defined in Relude.Container.One type OneItem ShortByteString Source # | |
ConvertUtf8 String ShortByteString Source # | Since: 0.6.0.0 |
Defined in Relude.String.Conversion | |
ConvertUtf8 Text ShortByteString Source # | Since: 0.6.0.0 |
Defined in Relude.String.Conversion | |
ConvertUtf8 LText ShortByteString Source # | Since: 0.6.0.0 |
Defined in Relude.String.Conversion | |
type Item ShortByteString | |
Defined in Data.ByteString.Short.Internal | |
type OneItem ShortByteString Source # | |
Defined in Relude.Container.One |
toShort :: ByteString -> ShortByteString #
O(n). Convert a ByteString
into a ShortByteString
.
This makes a copy, so does not retain the input string.
fromShort :: ShortByteString -> ByteString #
O(n). Convert a ShortByteString
into a ByteString
.