Copyright | (c) 2016 Stephen Diehl (c) 20016-2018 Serokell (c) 2018 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
Reexports functions to work with Text
and ByteString
types.
Synopsis
- class IsString a where
- fromString :: String -> a
- unwords :: [Text] -> Text
- unlines :: [Text] -> Text
- lines :: Text -> [Text]
- words :: Text -> [Text]
- data Text
- 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
- class Read a
- readMaybe :: Read a => String -> Maybe a
- reads :: Read a => ReadS a
- data ByteString
String
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
fromString :: String -> a #
Instances
IsString ShortByteString | |
Defined in Data.ByteString.Short.Internal fromString :: String -> ShortByteString # | |
IsString ByteString | |
Defined in Data.ByteString.Lazy.Internal fromString :: String -> ByteString # | |
IsString ByteString | |
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 # |
Text
A space efficient, packed, unboxed Unicode text type.
Instances
Hashable Text | |
Defined in Data.Hashable.Class | |
One Text Source # | |
ToString Text Source # | |
ToLText Text Source # | |
ToText Text Source # | |
LazyStrict LText Text 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 Text ByteString Source # | |
Defined in Relude.String.Conversion encodeUtf8 :: Text -> ByteString Source # decodeUtf8 :: ByteString -> Text Source # decodeUtf8Strict :: ByteString -> Either UnicodeException Text Source # | |
type Item Text | |
type OneItem Text Source # | |
Defined in Relude.Container.One |
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 -> () # |
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 Version | Since: base-2.1 |
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 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 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 IOMode | Since: base-4.2.0.0 |
Read Lexeme | Since: base-2.1 |
Read GeneralCategory | Since: base-2.1 |
Defined in GHC.Read | |
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 (Complex a) | Since: base-2.1 |
HasResolution a => Read (Fixed a) | Since: base-4.3.0.0 |
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) | 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 |
(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) | |
(Read1 m, Read a) => Read (MaybeT m a) | |
(Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) | |
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
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.