Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2023 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Relude.String.Reexport
Description
Reexports functions to work with Text
, ByteString
and
ShortByteString
types.
Synopsis
- class IsString a where
- fromString :: String -> a
- type String = [Char]
- class Read a
- reads :: Read a => ReadS a
- readMaybe :: Read a => String -> Maybe 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
- decodeUtf8With :: OnDecodeError -> ByteString -> Text
- decodeUtf8' :: ByteString -> Either UnicodeException Text
- data UnicodeException
- type OnDecodeError = OnError Word8 Char
- type OnError a b = String -> Maybe a -> Maybe b
- strictDecode :: OnDecodeError
- lenientDecode :: OnDecodeError
- data ByteString
- data ShortByteString
- toShort :: ByteString -> ShortByteString
- fromShort :: ShortByteString -> ByteString
String
IsString
is used in combination with the -XOverloadedStrings
language extension to convert the literals to different string types.
For example, if you use the text package, you can say
{-# LANGUAGE OverloadedStrings #-} myText = "hello world" :: Text
Internally, the extension will convert this to the equivalent of
myText = fromString @Text ("hello world" :: String)
Note: You can use fromString
in normal code as well,
but the usual performance/memory efficiency problems with String
apply.
Methods
fromString :: String -> a #
Instances
IsString ByteString | Beware: |
Defined in Data.ByteString.Internal.Type Methods fromString :: String -> ByteString # | |
IsString ByteString | Beware: |
Defined in Data.ByteString.Lazy.Internal Methods fromString :: String -> ByteString # | |
IsString ShortByteString | Beware: |
Defined in Data.ByteString.Short.Internal Methods fromString :: String -> ShortByteString # | |
IsString Doc | |
Defined in Text.PrettyPrint.HughesPJ Methods fromString :: String -> Doc # | |
IsString Builder | Performs replacement on invalid scalar values:
|
Defined in Data.Text.Internal.Builder Methods fromString :: String -> Builder # | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a # | |
IsString a => IsString (Identity a) | @since base-4.9.0.0 |
Defined in GHC.Internal.Data.String Methods fromString :: String -> Identity a # | |
(IsString a, Hashable a) => IsString (Hashed a) | |
Defined in Data.Hashable.Class Methods fromString :: String -> Hashed a # | |
IsString (Doc a) | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Methods fromString :: String -> Doc a # | |
a ~ Char => IsString [a] |
@since base-2.01 |
Defined in GHC.Internal.Data.String Methods fromString :: String -> [a] # | |
IsString a => IsString (Const a b) | @since base-4.9.0.0 |
Defined in GHC.Internal.Data.String Methods fromString :: String -> Const a b # |
String
is an alias for a list of characters.
String constants in Haskell are values of type String
.
That means if you write a string literal like "hello world"
,
it will have the type [Char]
, which is the same as String
.
Note: You can ask the compiler to automatically infer different types
with the -XOverloadedStrings
language extension, for example
"hello world" :: Text
. See IsString
for more information.
Because String
is just a list of characters, you can use normal list functions
to do basic string manipulation. See Data.List for operations on lists.
Performance considerations
[Char]
is a relatively memory-inefficient type.
It is a linked list of boxed word-size characters, internally it looks something like:
╭─────┬───┬──╮ ╭─────┬───┬──╮ ╭─────┬───┬──╮ ╭────╮ │ (:) │ │ ─┼─>│ (:) │ │ ─┼─>│ (:) │ │ ─┼─>│ [] │ ╰─────┴─┼─┴──╯ ╰─────┴─┼─┴──╯ ╰─────┴─┼─┴──╯ ╰────╯ v v v 'a' 'b' 'c'
The String
"abc" will use 5*3+1 = 16
(in general 5n+1
)
words of space in memory.
Furthermore, operations like (++)
(string concatenation) are O(n)
(in the left argument).
For historical reasons, the base
library uses String
in a lot of places
for the conceptual simplicity, but library code dealing with user-data
should use the text
package for Unicode text, or the the
bytestring package
for binary data.
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 ByteString | |
Defined in Data.ByteString.Internal.Type Methods readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |
Read ByteString | |
Defined in Data.ByteString.Lazy.Internal Methods readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |
Read ShortByteString | |
Defined in Data.ByteString.Short.Internal Methods readsPrec :: Int -> ReadS ShortByteString # readList :: ReadS [ShortByteString] # | |
Read IntSet | |
Read Void | Reading a @since base-4.8.0.0 |
Read All | @since base-2.01 |
Read Any | @since base-2.01 |
Read Version | @since base-2.01 |
Read Associativity | @since base-4.6.0.0 |
Defined in GHC.Internal.Generics Methods readsPrec :: Int -> ReadS Associativity # readList :: ReadS [Associativity] # | |
Read DecidedStrictness | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics Methods readsPrec :: Int -> ReadS DecidedStrictness # readList :: ReadS [DecidedStrictness] # | |
Read Fixity | @since base-4.6.0.0 |
Read SourceStrictness | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics Methods readsPrec :: Int -> ReadS SourceStrictness # readList :: ReadS [SourceStrictness] # | |
Read SourceUnpackedness | @since base-4.9.0.0 |
Defined in GHC.Internal.Generics Methods readsPrec :: Int -> ReadS SourceUnpackedness # readList :: ReadS [SourceUnpackedness] # | |
Read ExitCode | |
Read BufferMode | @since base-4.2.0.0 |
Defined in GHC.Internal.IO.Handle.Types Methods 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.Internal.IO.Handle.Types Methods readsPrec :: Int -> ReadS NewlineMode # readList :: ReadS [NewlineMode] # readPrec :: ReadPrec NewlineMode # readListPrec :: ReadPrec [NewlineMode] # | |
Read IOMode | @since base-4.2.0.0 |
Read Int16 | @since base-2.01 |
Read Int32 | @since base-2.01 |
Read Int64 | @since base-2.01 |
Read Int8 | @since base-2.01 |
Read Lexeme | @since base-2.01 |
Read SomeNat | @since base-4.7.0.0 |
Read GeneralCategory | @since base-2.01 |
Defined in GHC.Internal.Read Methods readsPrec :: Int -> ReadS GeneralCategory # readList :: ReadS [GeneralCategory] # | |
Read Word16 | @since base-2.01 |
Read Word32 | @since base-2.01 |
Read Word64 | @since base-2.01 |
Read Word8 | @since base-2.01 |
Read Ordering | @since base-2.01 |
Read Undefined Source # | |
Read I8 | |
Read FPFormat | |
Read Integer | @since base-2.01 |
Read Natural | @since base-4.8.0.0 |
Read () | @since base-2.01 |
Read Bool | @since base-2.01 |
Read Char | @since base-2.01 |
Read Double | @since base-2.01 |
Read Float | @since base-2.01 |
Read Int | @since base-2.01 |
Read Word | @since base-4.5.0.0 |
Read a => Read (Complex a) | Since: base-2.1 |
Read a => Read (First a) | Since: base-4.9.0.0 |
Read a => Read (Last a) | Since: base-4.9.0.0 |
Read a => Read (Max a) | Since: base-4.9.0.0 |
Read a => Read (Min a) | Since: base-4.9.0.0 |
Read m => Read (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup Methods readsPrec :: Int -> ReadS (WrappedMonoid m) # readList :: ReadS [WrappedMonoid m] # readPrec :: ReadPrec (WrappedMonoid m) # readListPrec :: ReadPrec [WrappedMonoid m] # | |
Read vertex => Read (SCC vertex) | Since: containers-0.5.9 |
Read e => Read (IntMap e) | |
Read a => Read (Seq a) | |
Read a => Read (ViewL a) | |
Read a => Read (ViewR a) | |
(Read a, Ord a) => Read (Set a) | |
Read a => Read (Tree a) | |
Read a => Read (NonEmpty a) | @since base-4.11.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.01 |
Read a => Read (Last a) | @since base-2.01 |
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 (Dual a) | @since base-2.01 |
Read a => Read (Product a) | @since base-2.01 |
Read a => Read (Sum a) | @since base-2.01 |
Read a => Read (ZipList a) | @since base-4.7.0.0 |
Read p => Read (Par1 p) | @since base-4.7.0.0 |
(Integral a, Read a) => Read (Ratio a) | @since base-2.01 |
(Eq a, Hashable a, Read a) => Read (HashSet a) | |
Read a => Read (Maybe a) | @since base-2.01 |
Read a => Read (Solo a) | @since base-4.15 |
Read a => Read [a] | @since base-2.01 |
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 |
(Ord k, Read k, Read e) => Read (Map k e) | |
(Ix a, Read a, Read b) => Read (Array a b) | @since base-2.01 |
(Read a, Read b) => Read (Either a b) | @since base-3.0 |
Read (Proxy t) | @since base-4.7.0.0 |
Read (U1 p) | @since base-4.9.0.0 |
Read (V1 p) | @since base-4.9.0.0 |
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) | |
(Read1 f, Read a) => Read (Lift f a) | |
(Read1 m, Read a) => Read (MaybeT m a) | |
(Read a, Read b) => Read (a, b) | @since base-2.01 |
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 |
Read (f p) => Read (Rec1 f p) | @since base-4.7.0.0 |
(Read1 f, Read a) => Read (Backwards f a) | |
(Read e, Read1 m, Read a) => Read (ExceptT e m a) | |
(Read1 f, Read a) => Read (IdentityT f a) | |
(Read w, Read1 m, Read a) => Read (WriterT w m a) | |
(Read w, Read1 m, Read a) => Read (WriterT w m a) | |
Read a => Read (Constant a b) | |
(Read1 f, Read a) => Read (Reverse f a) | |
(Read a, Read b, Read c) => Read (a, b, c) | @since base-2.01 |
(Read (f a), Read (g a)) => Read (Product f g a) | Since: base-4.18.0.0 |
(Read (f a), Read (g a)) => Read (Sum f g a) | Since: base-4.18.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 c => Read (K1 i c p) | @since base-4.7.0.0 |
(Read a, Read b, Read c, Read d) => Read (a, b, c, d) | @since base-2.01 |
Read (f (g a)) => Read (Compose f g a) | Since: base-4.18.0.0 |
Read (f (g p)) => Read ((f :.: g) p) | @since base-4.7.0.0 |
Read (f p) => Read (M1 i c f 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.01 |
(Read a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) | @since base-2.01 |
(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.01 |
(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.01 |
(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.01 |
(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.01 |
(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.01 |
(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.01 |
(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.01 |
(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.01 |
Defined in GHC.Internal.Read | |
(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.01 |
Defined in GHC.Internal.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
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' ...
decodeUtf8With :: OnDecodeError -> ByteString -> Text #
Decode a ByteString
containing UTF-8 encoded text.
Surrogate code points in replacement character returned by OnDecodeError
will be automatically remapped to the replacement char U+FFFD
.
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.
data UnicodeException #
An exception type for representing Unicode encoding errors.
Instances
NFData UnicodeException | |
Defined in Data.Text.Encoding.Error Methods rnf :: UnicodeException -> () # | |
Exception UnicodeException | |
Defined in Data.Text.Encoding.Error Methods toException :: UnicodeException -> SomeException # fromException :: SomeException -> Maybe UnicodeException # | |
Show UnicodeException | |
Defined in Data.Text.Encoding.Error Methods showsPrec :: Int -> UnicodeException -> ShowS # show :: UnicodeException -> String # showList :: [UnicodeException] -> ShowS # | |
Eq UnicodeException | |
Defined in Data.Text.Encoding.Error Methods (==) :: UnicodeException -> UnicodeException -> Bool # (/=) :: UnicodeException -> UnicodeException -> Bool # |
type OnDecodeError = OnError Word8 Char #
A handler for a decoding error.
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.
strictDecode :: OnDecodeError #
Throw a UnicodeException
if decoding fails.
lenientDecode :: OnDecodeError #
Replace an invalid input byte with the Unicode replacement character U+FFFD.
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
NFData ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods rnf :: ByteString -> () # | |||||
Monoid ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |||||
Semigroup ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |||||
Data ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods 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 # | |||||
IsString ByteString | Beware: | ||||
Defined in Data.ByteString.Internal.Type Methods fromString :: String -> ByteString # | |||||
IsList ByteString | Since: bytestring-0.10.12.0 | ||||
Defined in Data.ByteString.Internal.Type Associated Types
Methods fromList :: [Item ByteString] -> ByteString # fromListN :: Int -> [Item ByteString] -> ByteString # toList :: ByteString -> [Item ByteString] # | |||||
Read ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods readsPrec :: Int -> ReadS ByteString # readList :: ReadS [ByteString] # readPrec :: ReadPrec ByteString # readListPrec :: ReadPrec [ByteString] # | |||||
Show ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods showsPrec :: Int -> ByteString -> ShowS # show :: ByteString -> String # showList :: [ByteString] -> ShowS # | |||||
Eq ByteString | |||||
Defined in Data.ByteString.Internal.Type | |||||
Ord ByteString | |||||
Defined in Data.ByteString.Internal.Type Methods compare :: ByteString -> ByteString -> Ordering # (<) :: ByteString -> ByteString -> Bool # (<=) :: ByteString -> ByteString -> Bool # (>) :: ByteString -> ByteString -> Bool # (>=) :: ByteString -> ByteString -> Bool # max :: ByteString -> ByteString -> ByteString # min :: ByteString -> ByteString -> ByteString # | |||||
Hashable ByteString | |||||
Defined in Data.Hashable.Class | |||||
One ByteString Source # | Create singleton strict
law> | ||||
Defined in Relude.Container.One Associated Types
Methods one :: OneItem ByteString -> ByteString 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 Methods toLText :: ByteString -> LText Source # | |||||
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 Methods toString :: ByteString -> String 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 Methods toText :: ByteString -> Text Source # | |||||
ConvertUtf8 LText ByteString Source # | |||||
Defined in Relude.String.Conversion Methods encodeUtf8 :: LText -> ByteString Source # decodeUtf8 :: ByteString -> LText Source # decodeUtf8Strict :: ByteString -> Either UnicodeException LText Source # | |||||
ConvertUtf8 Text ByteString Source # | |||||
Defined in Relude.String.Conversion Methods encodeUtf8 :: Text -> ByteString Source # decodeUtf8 :: ByteString -> Text Source # decodeUtf8Strict :: ByteString -> Either UnicodeException Text Source # | |||||
ConvertUtf8 String ByteString Source # | |||||
Defined in Relude.String.Conversion Methods encodeUtf8 :: String -> ByteString Source # decodeUtf8 :: ByteString -> String Source # decodeUtf8Strict :: ByteString -> Either UnicodeException String Source # | |||||
LazyStrict LByteString ByteString Source # | |||||
Defined in Relude.String.Conversion | |||||
Lift ByteString | Since: bytestring-0.11.2.0 | ||||
Defined in Data.ByteString.Internal.Type Methods lift :: Quote m => ByteString -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => ByteString -> Code m ByteString # | |||||
type Item ByteString | |||||
Defined in Data.ByteString.Internal.Type | |||||
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.
Instances
NFData ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Methods rnf :: ShortByteString -> () # | |||||
Monoid ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Methods mappend :: ShortByteString -> ShortByteString -> ShortByteString # mconcat :: [ShortByteString] -> ShortByteString # | |||||
Semigroup ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Methods (<>) :: ShortByteString -> ShortByteString -> ShortByteString # sconcat :: NonEmpty ShortByteString -> ShortByteString # stimes :: Integral b => b -> ShortByteString -> ShortByteString # | |||||
Data ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Methods 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 # | |||||
IsString ShortByteString | Beware: | ||||
Defined in Data.ByteString.Short.Internal Methods fromString :: String -> ShortByteString # | |||||
Generic ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Associated Types
Methods from :: ShortByteString -> Rep ShortByteString x # to :: Rep ShortByteString x -> ShortByteString # | |||||
IsList ShortByteString | Since: bytestring-0.10.12.0 | ||||
Defined in Data.ByteString.Short.Internal Associated Types
Methods fromList :: [Item ShortByteString] -> ShortByteString # fromListN :: Int -> [Item ShortByteString] -> ShortByteString # toList :: ShortByteString -> [Item ShortByteString] # | |||||
Read ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Methods readsPrec :: Int -> ReadS ShortByteString # readList :: ReadS [ShortByteString] # | |||||
Show ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Methods showsPrec :: Int -> ShortByteString -> ShowS # show :: ShortByteString -> String # showList :: [ShortByteString] -> ShowS # | |||||
Eq ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Methods (==) :: ShortByteString -> ShortByteString -> Bool # (/=) :: ShortByteString -> ShortByteString -> Bool # | |||||
Ord ShortByteString | Lexicographic order. | ||||
Defined in Data.ByteString.Short.Internal Methods compare :: ShortByteString -> ShortByteString -> Ordering # (<) :: ShortByteString -> ShortByteString -> Bool # (<=) :: ShortByteString -> ShortByteString -> Bool # (>) :: ShortByteString -> ShortByteString -> Bool # (>=) :: ShortByteString -> ShortByteString -> Bool # max :: ShortByteString -> ShortByteString -> ShortByteString # min :: ShortByteString -> ShortByteString -> ShortByteString # | |||||
Hashable ShortByteString | |||||
Defined in Data.Hashable.Class | |||||
One ShortByteString Source # | Create singleton
law> | ||||
Defined in Relude.Container.One Associated Types
Methods | |||||
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 Methods toLText :: ShortByteString -> LText Source # | |||||
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 Methods toString :: ShortByteString -> String 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 Methods toText :: ShortByteString -> Text Source # | |||||
ConvertUtf8 LText ShortByteString Source # | Since: 0.6.0.0 | ||||
Defined in Relude.String.Conversion Methods encodeUtf8 :: LText -> ShortByteString Source # decodeUtf8 :: ShortByteString -> LText Source # decodeUtf8Strict :: ShortByteString -> Either UnicodeException LText Source # | |||||
ConvertUtf8 Text ShortByteString Source # | Since: 0.6.0.0 | ||||
Defined in Relude.String.Conversion Methods encodeUtf8 :: Text -> ShortByteString Source # decodeUtf8 :: ShortByteString -> Text Source # decodeUtf8Strict :: ShortByteString -> Either UnicodeException Text Source # | |||||
ConvertUtf8 String ShortByteString Source # | Since: 0.6.0.0 | ||||
Defined in Relude.String.Conversion Methods encodeUtf8 :: String -> ShortByteString Source # decodeUtf8 :: ShortByteString -> String Source # decodeUtf8Strict :: ShortByteString -> Either UnicodeException String Source # | |||||
Lift ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Methods lift :: Quote m => ShortByteString -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => ShortByteString -> Code m ShortByteString # | |||||
type Rep ShortByteString | |||||
Defined in Data.ByteString.Short.Internal type Rep ShortByteString = D1 ('MetaData "ShortByteString" "Data.ByteString.Short.Internal" "bytestring-0.12.1.0-d0da" 'True) (C1 ('MetaCons "ShortByteString" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShortByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteArray))) | |||||
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
.