mirror of
https://github.com/tfausak/witch.git
synced 2024-11-22 14:58:13 +03:00
Add aliases for encodings (#104)
* Add aliases for encodings * Use shorter aliases for encodings
This commit is contained in:
parent
309ae27db4
commit
7e7cd448cf
@ -26,11 +26,42 @@ module Witch
|
||||
Witch.TryFromException.TryFromException (..),
|
||||
|
||||
-- ** Encodings
|
||||
|
||||
-- | Witch supports decoding text and encoding byte strings using various
|
||||
-- character encodings. For example to convert from a 'String' into a
|
||||
-- strict 'Data.ByteString.ByteString', you can use the
|
||||
-- 'Witch.Encoding.Utf8S' alias:
|
||||
--
|
||||
-- @
|
||||
-- 'Witch.Utility.into' @'Data.ByteString.ByteString' ('Witch.Utility.into' @'Witch.Encoding.Utf8S' ("..." :: 'String'))
|
||||
-- -- "..."
|
||||
-- @
|
||||
--
|
||||
-- And to convert from a strict 'Data.ByteString.ByteString' into a
|
||||
-- 'String', you can use the 'Witch.Encoding.Utf8S' alias in the other
|
||||
-- direction:
|
||||
--
|
||||
-- @
|
||||
-- 'Witch.Utility.tryInto' @'String' ('Witch.Utility.into' @'Witch.Encoding.Utf8S' ("..." :: 'Data.ByteString.ByteString'))
|
||||
-- -- Right "..."
|
||||
-- @
|
||||
Witch.Encoding.Latin1S,
|
||||
Witch.Encoding.Latin1L,
|
||||
Witch.Encoding.ISO_8859_1,
|
||||
Witch.Encoding.Utf8S,
|
||||
Witch.Encoding.Utf8L,
|
||||
Witch.Encoding.UTF_8,
|
||||
Witch.Encoding.Utf16LS,
|
||||
Witch.Encoding.Utf16LL,
|
||||
Witch.Encoding.UTF_16LE,
|
||||
Witch.Encoding.Utf16BS,
|
||||
Witch.Encoding.Utf16BL,
|
||||
Witch.Encoding.UTF_16BE,
|
||||
Witch.Encoding.Utf32LS,
|
||||
Witch.Encoding.Utf32LL,
|
||||
Witch.Encoding.UTF_32LE,
|
||||
Witch.Encoding.Utf32BS,
|
||||
Witch.Encoding.Utf32BL,
|
||||
Witch.Encoding.UTF_32BE,
|
||||
|
||||
-- * Utilities
|
||||
|
@ -2,22 +2,60 @@
|
||||
|
||||
module Witch.Encoding where
|
||||
|
||||
import qualified Data.ByteString as ByteString
|
||||
import qualified Data.ByteString.Lazy as LazyByteString
|
||||
import qualified Data.Tagged as Tagged
|
||||
|
||||
-- | <https://en.wikipedia.org/wiki/ISO/IEC_8859-1>
|
||||
type ISO_8859_1 = Tagged.Tagged "ISO-8859-1"
|
||||
|
||||
-- | The 'ISO_8859_1' encoding for strict 'ByteString.ByteString's.
|
||||
type Latin1S = ISO_8859_1 ByteString.ByteString
|
||||
|
||||
-- | The 'ISO_8859_1' encoding for lazy 'LazyByteString.ByteString's.
|
||||
type Latin1L = ISO_8859_1 LazyByteString.ByteString
|
||||
|
||||
-- | <https://en.wikipedia.org/wiki/UTF-8>
|
||||
type UTF_8 = Tagged.Tagged "UTF-8"
|
||||
|
||||
-- | The 'UTF_8' encoding for strict 'ByteString.ByteString's.
|
||||
type Utf8S = UTF_8 ByteString.ByteString
|
||||
|
||||
-- | The 'UTF_8' encoding for lazy 'LazyByteString.ByteString's.
|
||||
type Utf8L = UTF_8 LazyByteString.ByteString
|
||||
|
||||
-- | <https://en.wikipedia.org/wiki/UTF-16>
|
||||
type UTF_16LE = Tagged.Tagged "UTF-16LE"
|
||||
|
||||
-- | The 'UTF_16LE' encoding for strict 'ByteString.ByteString's.
|
||||
type Utf16LS = UTF_16LE ByteString.ByteString
|
||||
|
||||
-- | The 'UTF_16LE' encoding for lazy 'LazyByteString.ByteString's.
|
||||
type Utf16LL = UTF_16LE LazyByteString.ByteString
|
||||
|
||||
-- | <https://en.wikipedia.org/wiki/UTF-16>
|
||||
type UTF_16BE = Tagged.Tagged "UTF-16BE"
|
||||
|
||||
-- | The 'UTF_16BE' encoding for strict 'ByteString.ByteString's.
|
||||
type Utf16BS = UTF_16BE ByteString.ByteString
|
||||
|
||||
-- | The 'UTF_16BE' encoding for lazy 'LazyByteString.ByteString's.
|
||||
type Utf16BL = UTF_16BE LazyByteString.ByteString
|
||||
|
||||
-- | <https://en.wikipedia.org/wiki/UTF-32>
|
||||
type UTF_32LE = Tagged.Tagged "UTF-32LE"
|
||||
|
||||
-- | The 'UTF_32LE' encoding for strict 'ByteString.ByteString's.
|
||||
type Utf32LS = UTF_32LE ByteString.ByteString
|
||||
|
||||
-- | The 'UTF_32LE' encoding for lazy 'LazyByteString.ByteString's.
|
||||
type Utf32LL = UTF_32LE LazyByteString.ByteString
|
||||
|
||||
-- | <https://en.wikipedia.org/wiki/UTF-32>
|
||||
type UTF_32BE = Tagged.Tagged "UTF-32BE"
|
||||
|
||||
-- | The 'UTF_32BE' encoding for strict 'ByteString.ByteString's.
|
||||
type Utf32BS = UTF_32BE ByteString.ByteString
|
||||
|
||||
-- | The 'UTF_32BE' encoding for lazy 'LazyByteString.ByteString's.
|
||||
type Utf32BL = UTF_32BE LazyByteString.ByteString
|
||||
|
@ -1235,53 +1235,53 @@ instance From.From (Tagged.Tagged t a) (Tagged.Tagged u a)
|
||||
-- ISO-8859-1
|
||||
|
||||
-- | Uses 'Text.decodeLatin1'.
|
||||
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) Text.Text where
|
||||
instance From.From Encoding.Latin1S Text.Text where
|
||||
from = Text.decodeLatin1 . From.from
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) LazyText.Text where
|
||||
instance From.From Encoding.Latin1S LazyText.Text where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From (Encoding.ISO_8859_1 ByteString.ByteString) String where
|
||||
instance From.From Encoding.Latin1S String where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Uses 'LazyText.decodeLatin1'.
|
||||
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) LazyText.Text where
|
||||
instance From.From Encoding.Latin1L LazyText.Text where
|
||||
from = LazyText.decodeLatin1 . From.from
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) Text.Text where
|
||||
instance From.From Encoding.Latin1L Text.Text where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From (Encoding.ISO_8859_1 LazyByteString.ByteString) String where
|
||||
instance From.From Encoding.Latin1L String where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- | Converts via 'String'.
|
||||
instance TryFrom.TryFrom Text.Text (Encoding.ISO_8859_1 ByteString.ByteString) where
|
||||
instance TryFrom.TryFrom Text.Text Encoding.Latin1S where
|
||||
tryFrom = Utility.eitherTryFrom $ TryFrom.tryFrom . Utility.into @String
|
||||
|
||||
-- | Converts via 'String'.
|
||||
instance TryFrom.TryFrom Text.Text (Encoding.ISO_8859_1 LazyByteString.ByteString) where
|
||||
instance TryFrom.TryFrom Text.Text Encoding.Latin1L where
|
||||
tryFrom = Utility.eitherTryFrom $ TryFrom.tryFrom . Utility.into @String
|
||||
|
||||
-- | Converts via 'String'.
|
||||
instance TryFrom.TryFrom LazyText.Text (Encoding.ISO_8859_1 LazyByteString.ByteString) where
|
||||
instance TryFrom.TryFrom LazyText.Text Encoding.Latin1L where
|
||||
tryFrom = Utility.eitherTryFrom $ TryFrom.tryFrom . Utility.into @String
|
||||
|
||||
-- | Converts via 'String'.
|
||||
instance TryFrom.TryFrom LazyText.Text (Encoding.ISO_8859_1 ByteString.ByteString) where
|
||||
instance TryFrom.TryFrom LazyText.Text Encoding.Latin1S where
|
||||
tryFrom = Utility.eitherTryFrom $ TryFrom.tryFrom . Utility.into @String
|
||||
|
||||
-- | Uses 'Char8.pack' when each character 'Char.isLatin1'.
|
||||
instance TryFrom.TryFrom String (Encoding.ISO_8859_1 ByteString.ByteString) where
|
||||
instance TryFrom.TryFrom String Encoding.Latin1S where
|
||||
tryFrom = Utility.maybeTryFrom $ \string -> do
|
||||
Monad.guard $ all Char.isLatin1 string
|
||||
pure . From.from $ Char8.pack string
|
||||
|
||||
-- | Uses 'LazyChar8.pack' when each character 'Char.isLatin1'.
|
||||
instance TryFrom.TryFrom String (Encoding.ISO_8859_1 LazyByteString.ByteString) where
|
||||
instance TryFrom.TryFrom String Encoding.Latin1L where
|
||||
tryFrom = Utility.maybeTryFrom $ \string -> do
|
||||
Monad.guard $ all Char.isLatin1 string
|
||||
pure . From.from $ LazyChar8.pack string
|
||||
@ -1289,251 +1289,251 @@ instance TryFrom.TryFrom String (Encoding.ISO_8859_1 LazyByteString.ByteString)
|
||||
-- UTF-8
|
||||
|
||||
-- | Uses 'Text.decodeUtf8''.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_8 ByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf8S Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ Text.decodeUtf8' . From.from
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_8 ByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf8S LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @LazyText.Text) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_8 ByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf8S String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Uses 'LazyText.decodeUtf8''.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_8 LazyByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf8L LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ LazyText.decodeUtf8' . From.from
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_8 LazyByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf8L Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @Text.Text) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_8 LazyByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf8L String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Uses 'Text.encodeUtf8'.
|
||||
instance From.From Text.Text (Encoding.UTF_8 ByteString.ByteString) where
|
||||
instance From.From Text.Text Encoding.Utf8S where
|
||||
from = From.from . Text.encodeUtf8
|
||||
|
||||
-- | Converts via 'ByteString.ByteString'.
|
||||
instance From.From Text.Text (Encoding.UTF_8 LazyByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_8 ByteString.ByteString)
|
||||
instance From.From Text.Text Encoding.Utf8L where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf8S
|
||||
|
||||
-- | Uses 'LazyText.encodeUtf8'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_8 LazyByteString.ByteString) where
|
||||
instance From.From LazyText.Text Encoding.Utf8L where
|
||||
from = From.from . LazyText.encodeUtf8
|
||||
|
||||
-- | Converts via 'LazyByteString.ByteString'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_8 ByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_8 LazyByteString.ByteString)
|
||||
instance From.From LazyText.Text Encoding.Utf8S where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf8L
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From String (Encoding.UTF_8 ByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf8S where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From String (Encoding.UTF_8 LazyByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf8L where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- UTF-16LE
|
||||
|
||||
-- | Uses 'Text.decodeUtf16LE'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16LE ByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf16LS Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ tryEvaluate @Text.UnicodeException . Text.decodeUtf16LE . From.from
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16LE ByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf16LS LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @LazyText.Text) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16LE ByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf16LS String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Uses 'LazyText.decodeUtf16LE'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16LE LazyByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf16LL LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ tryEvaluate @Text.UnicodeException . LazyText.decodeUtf16LE . From.from
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16LE LazyByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf16LL Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @Text.Text) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16LE LazyByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf16LL String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Uses 'Text.encodeUtf16LE'.
|
||||
instance From.From Text.Text (Encoding.UTF_16LE ByteString.ByteString) where
|
||||
instance From.From Text.Text Encoding.Utf16LS where
|
||||
from = From.from . Text.encodeUtf16LE
|
||||
|
||||
-- | Converts via 'ByteString.ByteString'.
|
||||
instance From.From Text.Text (Encoding.UTF_16LE LazyByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_16LE ByteString.ByteString)
|
||||
instance From.From Text.Text Encoding.Utf16LL where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf16LS
|
||||
|
||||
-- | Uses 'LazyText.encodeUtf16LE'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_16LE LazyByteString.ByteString) where
|
||||
instance From.From LazyText.Text Encoding.Utf16LL where
|
||||
from = From.from . LazyText.encodeUtf16LE
|
||||
|
||||
-- | Converts via 'LazyByteString.ByteString'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_16LE ByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_16LE LazyByteString.ByteString)
|
||||
instance From.From LazyText.Text Encoding.Utf16LS where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf16LL
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From String (Encoding.UTF_16LE ByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf16LS where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From String (Encoding.UTF_16LE LazyByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf16LL where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- UTF-16BE
|
||||
|
||||
-- | Uses 'Text.decodeUtf16BE'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16BE ByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf16BS Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ tryEvaluate @Text.UnicodeException . Text.decodeUtf16BE . From.from
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16BE ByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf16BS LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @LazyText.Text) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16BE ByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf16BS String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Uses 'LazyText.decodeUtf16BE'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16BE LazyByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf16BL LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ tryEvaluate @Text.UnicodeException . LazyText.decodeUtf16BE . From.from
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16BE LazyByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf16BL Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @Text.Text) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_16BE LazyByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf16BL String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Uses 'Text.encodeUtf16BE'.
|
||||
instance From.From Text.Text (Encoding.UTF_16BE ByteString.ByteString) where
|
||||
instance From.From Text.Text Encoding.Utf16BS where
|
||||
from = From.from . Text.encodeUtf16BE
|
||||
|
||||
-- | Converts via 'ByteString.ByteString'.
|
||||
instance From.From Text.Text (Encoding.UTF_16BE LazyByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_16BE ByteString.ByteString)
|
||||
instance From.From Text.Text Encoding.Utf16BL where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf16BS
|
||||
|
||||
-- | Uses 'LazyText.encodeUtf16BE'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_16BE LazyByteString.ByteString) where
|
||||
instance From.From LazyText.Text Encoding.Utf16BL where
|
||||
from = From.from . LazyText.encodeUtf16BE
|
||||
|
||||
-- | Converts via 'LazyByteString.ByteString'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_16BE ByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_16BE LazyByteString.ByteString)
|
||||
instance From.From LazyText.Text Encoding.Utf16BS where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf16BL
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From String (Encoding.UTF_16BE ByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf16BS where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From String (Encoding.UTF_16BE LazyByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf16BL where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- UTF-32LE
|
||||
|
||||
-- | Uses 'Text.decodeUtf32LE'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32LE ByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf32LS Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ tryEvaluate @Text.UnicodeException . Text.decodeUtf32LE . From.from
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32LE ByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf32LS LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @LazyText.Text) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32LE ByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf32LS String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Uses 'LazyText.decodeUtf32LE'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32LE LazyByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf32LL LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ tryEvaluate @Text.UnicodeException . LazyText.decodeUtf32LE . From.from
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32LE LazyByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf32LL Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @Text.Text) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32LE LazyByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf32LL String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Uses 'Text.encodeUtf32LE'.
|
||||
instance From.From Text.Text (Encoding.UTF_32LE ByteString.ByteString) where
|
||||
instance From.From Text.Text Encoding.Utf32LS where
|
||||
from = From.from . Text.encodeUtf32LE
|
||||
|
||||
-- | Converts via 'ByteString.ByteString'.
|
||||
instance From.From Text.Text (Encoding.UTF_32LE LazyByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_32LE ByteString.ByteString)
|
||||
instance From.From Text.Text Encoding.Utf32LL where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf32LS
|
||||
|
||||
-- | Uses 'LazyText.encodeUtf32LE'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_32LE LazyByteString.ByteString) where
|
||||
instance From.From LazyText.Text Encoding.Utf32LL where
|
||||
from = From.from . LazyText.encodeUtf32LE
|
||||
|
||||
-- | Converts via 'LazyByteString.ByteString'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_32LE ByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_32LE LazyByteString.ByteString)
|
||||
instance From.From LazyText.Text Encoding.Utf32LS where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf32LL
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From String (Encoding.UTF_32LE ByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf32LS where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From String (Encoding.UTF_32LE LazyByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf32LL where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
-- UTF-32BE
|
||||
|
||||
-- | Uses 'Text.decodeUtf32BE'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32BE ByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf32BS Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ tryEvaluate @Text.UnicodeException . Text.decodeUtf32BE . From.from
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32BE ByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf32BS LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @LazyText.Text) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32BE ByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf32BS String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @Text.Text
|
||||
|
||||
-- | Uses 'LazyText.decodeUtf32BE'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32BE LazyByteString.ByteString) LazyText.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf32BL LazyText.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ tryEvaluate @Text.UnicodeException . LazyText.decodeUtf32BE . From.from
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32BE LazyByteString.ByteString) Text.Text where
|
||||
instance TryFrom.TryFrom Encoding.Utf32BL Text.Text where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @Text.Text) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance TryFrom.TryFrom (Encoding.UTF_32BE LazyByteString.ByteString) String where
|
||||
instance TryFrom.TryFrom Encoding.Utf32BL String where
|
||||
tryFrom = Utility.eitherTryFrom $ fmap (Utility.into @String) . Utility.tryInto @LazyText.Text
|
||||
|
||||
-- | Uses 'Text.encodeUtf32BE'.
|
||||
instance From.From Text.Text (Encoding.UTF_32BE ByteString.ByteString) where
|
||||
instance From.From Text.Text Encoding.Utf32BS where
|
||||
from = From.from . Text.encodeUtf32BE
|
||||
|
||||
-- | Converts via 'ByteString.ByteString'.
|
||||
instance From.From Text.Text (Encoding.UTF_32BE LazyByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_32BE ByteString.ByteString)
|
||||
instance From.From Text.Text Encoding.Utf32BL where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf32BS
|
||||
|
||||
-- | Uses 'LazyText.encodeUtf32BE'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_32BE LazyByteString.ByteString) where
|
||||
instance From.From LazyText.Text Encoding.Utf32BL where
|
||||
from = From.from . LazyText.encodeUtf32BE
|
||||
|
||||
-- | Converts via 'LazyByteString.ByteString'.
|
||||
instance From.From LazyText.Text (Encoding.UTF_32BE ByteString.ByteString) where
|
||||
from = fmap From.from . Utility.into @(Encoding.UTF_32BE LazyByteString.ByteString)
|
||||
instance From.From LazyText.Text Encoding.Utf32BS where
|
||||
from = fmap From.from . Utility.into @Encoding.Utf32BL
|
||||
|
||||
-- | Converts via 'Text.Text'.
|
||||
instance From.From String (Encoding.UTF_32BE ByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf32BS where
|
||||
from = Utility.via @Text.Text
|
||||
|
||||
-- | Converts via 'LazyText.Text'.
|
||||
instance From.From String (Encoding.UTF_32BE LazyByteString.ByteString) where
|
||||
instance From.From String Encoding.Utf32BL where
|
||||
from = Utility.via @LazyText.Text
|
||||
|
||||
--
|
||||
|
@ -2011,74 +2011,74 @@ spec = describe "Witch" $ do
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged False) `shouldBe` Tagged.Tagged False
|
||||
|
||||
describe "From (ISO_8859_1 ByteString) Text" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 ByteString.ByteString) @Text.Text
|
||||
describe "From Latin1S Text" $ do
|
||||
let f = Witch.from @Encoding.Latin1S @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` Text.pack "a"
|
||||
|
||||
describe "From (ISO_8859_1 ByteString) LazyText" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 ByteString.ByteString) @LazyText.Text
|
||||
describe "From Latin1S LazyText" $ do
|
||||
let f = Witch.from @Encoding.Latin1S @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` LazyText.pack "a"
|
||||
|
||||
describe "From (ISO_8859_1 ByteString) String" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 ByteString.ByteString) @String
|
||||
describe "From Latin1S String" $ do
|
||||
let f = Witch.from @Encoding.Latin1S @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` "a"
|
||||
|
||||
describe "From (ISO_8859_1 LazyByteString) LazyText" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 LazyByteString.ByteString) @LazyText.Text
|
||||
describe "From Latin1L LazyText" $ do
|
||||
let f = Witch.from @Encoding.Latin1L @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` LazyText.pack "a"
|
||||
|
||||
describe "From (ISO_8859_1 LazyByteString) Text" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 LazyByteString.ByteString) @Text.Text
|
||||
describe "From Latin1L Text" $ do
|
||||
let f = Witch.from @Encoding.Latin1L @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` Text.pack "a"
|
||||
|
||||
describe "From (ISO_8859_1 LazyByteString) String" $ do
|
||||
let f = Witch.from @(Encoding.ISO_8859_1 LazyByteString.ByteString) @String
|
||||
describe "From Latin1L String" $ do
|
||||
let f = Witch.from @Encoding.Latin1L @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` "a"
|
||||
|
||||
describe "TryFrom Text (ISO_8859_1 ByteString)" $ do
|
||||
let f = hush . Witch.tryFrom @Text.Text @(Encoding.ISO_8859_1 ByteString.ByteString)
|
||||
describe "TryFrom Text Latin1S" $ do
|
||||
let f = hush . Witch.tryFrom @Text.Text @Encoding.Latin1S
|
||||
it "works" $ do
|
||||
f (Text.pack "a") `shouldBe` Just (Tagged.Tagged $ ByteString.pack [0x61])
|
||||
f (Text.pack "\x100") `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom Text (ISO_8859_1 LazyByteString)" $ do
|
||||
let f = hush . Witch.tryFrom @Text.Text @(Encoding.ISO_8859_1 LazyByteString.ByteString)
|
||||
describe "TryFrom Text Latin1L" $ do
|
||||
let f = hush . Witch.tryFrom @Text.Text @Encoding.Latin1L
|
||||
it "works" $ do
|
||||
f (Text.pack "a") `shouldBe` Just (Tagged.Tagged $ LazyByteString.pack [0x61])
|
||||
f (Text.pack "\x100") `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom LazyText (ISO_8859_1 LazyByteString)" $ do
|
||||
let f = hush . Witch.tryFrom @LazyText.Text @(Encoding.ISO_8859_1 LazyByteString.ByteString)
|
||||
describe "TryFrom LazyText Latin1L" $ do
|
||||
let f = hush . Witch.tryFrom @LazyText.Text @Encoding.Latin1L
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Just (Tagged.Tagged $ LazyByteString.pack [0x61])
|
||||
f (LazyText.pack "\x100") `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom LazyText (ISO_8859_1 ByteString)" $ do
|
||||
let f = hush . Witch.tryFrom @LazyText.Text @(Encoding.ISO_8859_1 ByteString.ByteString)
|
||||
describe "TryFrom LazyText Latin1S" $ do
|
||||
let f = hush . Witch.tryFrom @LazyText.Text @Encoding.Latin1S
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Just (Tagged.Tagged $ ByteString.pack [0x61])
|
||||
f (LazyText.pack "\x100") `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom String (ISO_8859_1 ByteString)" $ do
|
||||
let f = hush . Witch.tryFrom @String @(Encoding.ISO_8859_1 ByteString.ByteString)
|
||||
describe "TryFrom String Latin1S" $ do
|
||||
let f = hush . Witch.tryFrom @String @Encoding.Latin1S
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Just (Tagged.Tagged $ ByteString.pack [0x61])
|
||||
f "\x100" `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom String (ISO_8859_1 LazyByteString)" $ do
|
||||
let f = hush . Witch.tryFrom @String @(Encoding.ISO_8859_1 LazyByteString.ByteString)
|
||||
describe "TryFrom String Latin1L" $ do
|
||||
let f = hush . Witch.tryFrom @String @Encoding.Latin1L
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Just (Tagged.Tagged $ LazyByteString.pack [0x61])
|
||||
f "\x100" `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_8 ByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_8 ByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf8S Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf8S @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [])) `shouldBe` Just (Text.pack "")
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` Just (Text.pack "a")
|
||||
@ -2088,43 +2088,43 @@ spec = describe "Witch" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0xe2, 0x82, 0xac])) `shouldBe` Just (Text.pack "\x20ac")
|
||||
f (Tagged.Tagged (ByteString.pack [0xf0, 0x90, 0x8d, 0x88])) `shouldBe` Just (Text.pack "\x10348")
|
||||
|
||||
describe "TryFrom (UTF_8 ByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_8 ByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf8S LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf8S @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [])) `shouldBe` Just (LazyText.pack "")
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` Just (LazyText.pack "a")
|
||||
f (Tagged.Tagged (ByteString.pack [0xff])) `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_8 ByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_8 ByteString.ByteString) @String
|
||||
describe "TryFrom Utf8S String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf8S @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [])) `shouldBe` Just ""
|
||||
f (Tagged.Tagged (ByteString.pack [0x61])) `shouldBe` Just "a"
|
||||
f (Tagged.Tagged (ByteString.pack [0xff])) `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_8 LazyByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_8 LazyByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf8L LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf8L @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [])) `shouldBe` Just (LazyText.pack "")
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` Just (LazyText.pack "a")
|
||||
f (Tagged.Tagged (LazyByteString.pack [0xff])) `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_8 LazyByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_8 LazyByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf8L Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf8L @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [])) `shouldBe` Just (Text.pack "")
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` Just (Text.pack "a")
|
||||
f (Tagged.Tagged (LazyByteString.pack [0xff])) `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_8 LazyByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_8 LazyByteString.ByteString) @String
|
||||
describe "TryFrom Utf8L String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf8L @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [])) `shouldBe` Just ""
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61])) `shouldBe` Just "a"
|
||||
f (Tagged.Tagged (LazyByteString.pack [0xff])) `shouldBe` Nothing
|
||||
|
||||
describe "From Text (UTF_8 ByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_8 ByteString.ByteString)
|
||||
describe "From Text Utf8S" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf8S
|
||||
it "works" $ do
|
||||
f (Text.pack "") `shouldBe` Tagged.Tagged (ByteString.pack [])
|
||||
f (Text.pack "a") `shouldBe` Tagged.Tagged (ByteString.pack [0x61])
|
||||
@ -2133,38 +2133,38 @@ spec = describe "Witch" $ do
|
||||
f (Text.pack "\x20ac") `shouldBe` Tagged.Tagged (ByteString.pack [0xe2, 0x82, 0xac])
|
||||
f (Text.pack "\x10348") `shouldBe` Tagged.Tagged (ByteString.pack [0xf0, 0x90, 0x8d, 0x88])
|
||||
|
||||
describe "From Text (UTF_8 LazyByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_8 LazyByteString.ByteString)
|
||||
describe "From Text Utf8L" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf8L
|
||||
it "works" $ do
|
||||
f (Text.pack "") `shouldBe` Tagged.Tagged (LazyByteString.pack [])
|
||||
f (Text.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61])
|
||||
|
||||
describe "From LazyText (UTF_8 LazyByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_8 LazyByteString.ByteString)
|
||||
describe "From LazyText Utf8L" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf8L
|
||||
it "works" $ do
|
||||
f (LazyText.pack "") `shouldBe` Tagged.Tagged (LazyByteString.pack [])
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61])
|
||||
|
||||
describe "From LazyText (UTF_8 ByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_8 ByteString.ByteString)
|
||||
describe "From LazyText Utf8S" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf8S
|
||||
it "works" $ do
|
||||
f (LazyText.pack "") `shouldBe` Tagged.Tagged (ByteString.pack [])
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (ByteString.pack [0x61])
|
||||
|
||||
describe "From String (UTF_8 ByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_8 ByteString.ByteString)
|
||||
describe "From String Utf8S" $ do
|
||||
let f = Witch.from @String @Encoding.Utf8S
|
||||
it "works" $ do
|
||||
f "" `shouldBe` Tagged.Tagged (ByteString.pack [])
|
||||
f "a" `shouldBe` Tagged.Tagged (ByteString.pack [0x61])
|
||||
|
||||
describe "From String (UTF_8 LazyByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_8 LazyByteString.ByteString)
|
||||
describe "From String Utf8L" $ do
|
||||
let f = Witch.from @String @Encoding.Utf8L
|
||||
it "works" $ do
|
||||
f "" `shouldBe` Tagged.Tagged (LazyByteString.pack [])
|
||||
f "a" `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61])
|
||||
|
||||
describe "TryFrom (UTF_16LE ByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16LE ByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf16LS Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16LS @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [])) `shouldBe` Just (Text.pack "")
|
||||
f (Tagged.Tagged (ByteString.pack [0x24, 0x00])) `shouldBe` Just (Text.pack "\x24")
|
||||
@ -2173,33 +2173,33 @@ spec = describe "Witch" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x00, 0xd8, 0x48, 0xdf])) `shouldBe` Just (Text.pack "\x10348")
|
||||
f (Tagged.Tagged (ByteString.pack [0x00])) `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_16LE ByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16LE ByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf16LS LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16LS @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61, 0x00])) `shouldBe` Just (LazyText.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_16LE ByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16LE ByteString.ByteString) @String
|
||||
describe "TryFrom Utf16LS String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16LS @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61, 0x00])) `shouldBe` Just "a"
|
||||
|
||||
describe "TryFrom (UTF_16LE LazyByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16LE LazyByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf16LL LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16LL @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61, 0x00])) `shouldBe` Just (LazyText.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_16LE LazyByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16LE LazyByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf16LL Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16LL @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61, 0x00])) `shouldBe` Just (Text.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_16LE LazyByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16LE LazyByteString.ByteString) @String
|
||||
describe "TryFrom Utf16LL String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16LL @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61, 0x00])) `shouldBe` Just "a"
|
||||
|
||||
describe "From Text (UTF_16LE ByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_16LE ByteString.ByteString)
|
||||
describe "From Text Utf16LS" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf16LS
|
||||
it "works" $ do
|
||||
f (Text.pack "") `shouldBe` Tagged.Tagged (ByteString.pack [])
|
||||
f (Text.pack "\x24") `shouldBe` Tagged.Tagged (ByteString.pack [0x24, 0x00])
|
||||
@ -2207,33 +2207,33 @@ spec = describe "Witch" $ do
|
||||
f (Text.pack "\x20ac") `shouldBe` Tagged.Tagged (ByteString.pack [0xac, 0x20])
|
||||
f (Text.pack "\x10348") `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0xd8, 0x48, 0xdf])
|
||||
|
||||
describe "From Text (UTF_16LE LazyByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_16LE LazyByteString.ByteString)
|
||||
describe "From Text Utf16LL" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf16LL
|
||||
it "works" $ do
|
||||
f (Text.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61, 0x00])
|
||||
|
||||
describe "From LazyText (UTF_16LE LazyByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_16LE LazyByteString.ByteString)
|
||||
describe "From LazyText Utf16LL" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf16LL
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61, 0x00])
|
||||
|
||||
describe "From LazyText (UTF_16LE ByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_16LE ByteString.ByteString)
|
||||
describe "From LazyText Utf16LS" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf16LS
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (ByteString.pack [0x61, 0x00])
|
||||
|
||||
describe "From String (UTF_16LE ByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_16LE ByteString.ByteString)
|
||||
describe "From String Utf16LS" $ do
|
||||
let f = Witch.from @String @Encoding.Utf16LS
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (ByteString.pack [0x61, 0x00])
|
||||
|
||||
describe "From String (UTF_16LE LazyByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_16LE LazyByteString.ByteString)
|
||||
describe "From String Utf16LL" $ do
|
||||
let f = Witch.from @String @Encoding.Utf16LL
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61, 0x00])
|
||||
|
||||
describe "TryFrom (UTF_16BE ByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16BE ByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf16BS Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16BS @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [])) `shouldBe` Just (Text.pack "")
|
||||
f (Tagged.Tagged (ByteString.pack [0x00, 0x24])) `shouldBe` Just (Text.pack "\x24")
|
||||
@ -2242,33 +2242,33 @@ spec = describe "Witch" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0xd8, 0x00, 0xdf, 0x48])) `shouldBe` Just (Text.pack "\x10348")
|
||||
f (Tagged.Tagged (ByteString.pack [0x00])) `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_16BE ByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16BE ByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf16BS LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16BS @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x00, 0x61])) `shouldBe` Just (LazyText.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_16BE ByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16BE ByteString.ByteString) @String
|
||||
describe "TryFrom Utf16BS String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16BS @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x00, 0x61])) `shouldBe` Just "a"
|
||||
|
||||
describe "TryFrom (UTF_16BE LazyByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16BE LazyByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf16BL LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16BL @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x00, 0x61])) `shouldBe` Just (LazyText.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_16BE LazyByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16BE LazyByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf16BL Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16BL @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x00, 0x61])) `shouldBe` Just (Text.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_16BE LazyByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_16BE LazyByteString.ByteString) @String
|
||||
describe "TryFrom Utf16BL String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf16BL @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x00, 0x61])) `shouldBe` Just "a"
|
||||
|
||||
describe "From Text (UTF_16BE ByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_16BE ByteString.ByteString)
|
||||
describe "From Text Utf16BS" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf16BS
|
||||
it "works" $ do
|
||||
f (Text.pack "") `shouldBe` Tagged.Tagged (ByteString.pack [])
|
||||
f (Text.pack "\x24") `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0x24])
|
||||
@ -2276,33 +2276,33 @@ spec = describe "Witch" $ do
|
||||
f (Text.pack "\x20ac") `shouldBe` Tagged.Tagged (ByteString.pack [0x20, 0xac])
|
||||
f (Text.pack "\x10348") `shouldBe` Tagged.Tagged (ByteString.pack [0xd8, 0x00, 0xdf, 0x48])
|
||||
|
||||
describe "From Text (UTF_16BE LazyByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_16BE LazyByteString.ByteString)
|
||||
describe "From Text Utf16BL" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf16BL
|
||||
it "works" $ do
|
||||
f (Text.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x00, 0x61])
|
||||
|
||||
describe "From LazyText (UTF_16BE LazyByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_16BE LazyByteString.ByteString)
|
||||
describe "From LazyText Utf16BL" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf16BL
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x00, 0x61])
|
||||
|
||||
describe "From LazyText (UTF_16BE ByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_16BE ByteString.ByteString)
|
||||
describe "From LazyText Utf16BS" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf16BS
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0x61])
|
||||
|
||||
describe "From String (UTF_16BE ByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_16BE ByteString.ByteString)
|
||||
describe "From String Utf16BS" $ do
|
||||
let f = Witch.from @String @Encoding.Utf16BS
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0x61])
|
||||
|
||||
describe "From String (UTF_16BE LazyByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_16BE LazyByteString.ByteString)
|
||||
describe "From String Utf16BL" $ do
|
||||
let f = Witch.from @String @Encoding.Utf16BL
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (LazyByteString.pack [0x00, 0x61])
|
||||
|
||||
describe "TryFrom (UTF_32LE ByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32LE ByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf32LS Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32LS @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [])) `shouldBe` Just (Text.pack "")
|
||||
f (Tagged.Tagged (ByteString.pack [0x24, 0x00, 0x00, 0x00])) `shouldBe` Just (Text.pack "\x24")
|
||||
@ -2311,33 +2311,33 @@ spec = describe "Witch" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x48, 0x03, 0x01, 0x00])) `shouldBe` Just (Text.pack "\x10348")
|
||||
f (Tagged.Tagged (ByteString.pack [0x00])) `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_32LE ByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32LE ByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf32LS LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32LS @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61, 0x00, 0x00, 0x00])) `shouldBe` Just (LazyText.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_32LE ByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32LE ByteString.ByteString) @String
|
||||
describe "TryFrom Utf32LS String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32LS @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x61, 0x00, 0x00, 0x00])) `shouldBe` Just "a"
|
||||
|
||||
describe "TryFrom (UTF_32LE LazyByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32LE LazyByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf32LL LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32LL @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61, 0x00, 0x00, 0x00])) `shouldBe` Just (LazyText.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_32LE LazyByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32LE LazyByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf32LL Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32LL @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61, 0x00, 0x00, 0x00])) `shouldBe` Just (Text.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_32LE LazyByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32LE LazyByteString.ByteString) @String
|
||||
describe "TryFrom Utf32LL String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32LL @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x61, 0x00, 0x00, 0x00])) `shouldBe` Just "a"
|
||||
|
||||
describe "From Text (UTF_32LE ByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_32LE ByteString.ByteString)
|
||||
describe "From Text Utf32LS" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf32LS
|
||||
it "works" $ do
|
||||
f (Text.pack "") `shouldBe` Tagged.Tagged (ByteString.pack [])
|
||||
f (Text.pack "\x24") `shouldBe` Tagged.Tagged (ByteString.pack [0x24, 0x00, 0x00, 0x00])
|
||||
@ -2345,33 +2345,33 @@ spec = describe "Witch" $ do
|
||||
f (Text.pack "\x20ac") `shouldBe` Tagged.Tagged (ByteString.pack [0xac, 0x20, 0x00, 0x00])
|
||||
f (Text.pack "\x10348") `shouldBe` Tagged.Tagged (ByteString.pack [0x48, 0x03, 0x01, 0x00])
|
||||
|
||||
describe "From Text (UTF_32LE LazyByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_32LE LazyByteString.ByteString)
|
||||
describe "From Text Utf32LL" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf32LL
|
||||
it "works" $ do
|
||||
f (Text.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61, 0x00, 0x00, 0x00])
|
||||
|
||||
describe "From LazyText (UTF_32LE LazyByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_32LE LazyByteString.ByteString)
|
||||
describe "From LazyText Utf32LL" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf32LL
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61, 0x00, 0x00, 0x00])
|
||||
|
||||
describe "From LazyText (UTF_32LE ByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_32LE ByteString.ByteString)
|
||||
describe "From LazyText Utf32LS" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf32LS
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (ByteString.pack [0x61, 0x00, 0x00, 0x00])
|
||||
|
||||
describe "From String (UTF_32LE ByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_32LE ByteString.ByteString)
|
||||
describe "From String Utf32LS" $ do
|
||||
let f = Witch.from @String @Encoding.Utf32LS
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (ByteString.pack [0x61, 0x00, 0x00, 0x00])
|
||||
|
||||
describe "From String (UTF_32LE LazyByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_32LE LazyByteString.ByteString)
|
||||
describe "From String Utf32LL" $ do
|
||||
let f = Witch.from @String @Encoding.Utf32LL
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (LazyByteString.pack [0x61, 0x00, 0x00, 0x00])
|
||||
|
||||
describe "TryFrom (UTF_32BE ByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32BE ByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf32BS Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32BS @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [])) `shouldBe` Just (Text.pack "")
|
||||
f (Tagged.Tagged (ByteString.pack [0x00, 0x00, 0x00, 0x24])) `shouldBe` Just (Text.pack "\x24")
|
||||
@ -2380,33 +2380,33 @@ spec = describe "Witch" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x00, 0x01, 0x03, 0x48])) `shouldBe` Just (Text.pack "\x10348")
|
||||
f (Tagged.Tagged (ByteString.pack [0x00])) `shouldBe` Nothing
|
||||
|
||||
describe "TryFrom (UTF_32BE ByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32BE ByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf32BS LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32BS @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x00, 0x00, 0x00, 0x61])) `shouldBe` Just (LazyText.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_32BE ByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32BE ByteString.ByteString) @String
|
||||
describe "TryFrom Utf32BS String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32BS @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (ByteString.pack [0x00, 0x00, 0x00, 0x61])) `shouldBe` Just "a"
|
||||
|
||||
describe "TryFrom (UTF_32BE LazyByteString) LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32BE LazyByteString.ByteString) @LazyText.Text
|
||||
describe "TryFrom Utf32BL LazyText" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32BL @LazyText.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x00, 0x00, 0x00, 0x61])) `shouldBe` Just (LazyText.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_32BE LazyByteString) Text" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32BE LazyByteString.ByteString) @Text.Text
|
||||
describe "TryFrom Utf32BL Text" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32BL @Text.Text
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x00, 0x00, 0x00, 0x61])) `shouldBe` Just (Text.pack "a")
|
||||
|
||||
describe "TryFrom (UTF_32BE LazyByteString) String" $ do
|
||||
let f = hush . Witch.tryFrom @(Encoding.UTF_32BE LazyByteString.ByteString) @String
|
||||
describe "TryFrom Utf32BL String" $ do
|
||||
let f = hush . Witch.tryFrom @Encoding.Utf32BL @String
|
||||
it "works" $ do
|
||||
f (Tagged.Tagged (LazyByteString.pack [0x00, 0x00, 0x00, 0x61])) `shouldBe` Just "a"
|
||||
|
||||
describe "From Text (UTF_32BE ByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_32BE ByteString.ByteString)
|
||||
describe "From Text Utf32BS" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf32BS
|
||||
it "works" $ do
|
||||
f (Text.pack "") `shouldBe` Tagged.Tagged (ByteString.pack [])
|
||||
f (Text.pack "\x24") `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0x00, 0x00, 0x24])
|
||||
@ -2414,28 +2414,28 @@ spec = describe "Witch" $ do
|
||||
f (Text.pack "\x20ac") `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0x00, 0x20, 0xac])
|
||||
f (Text.pack "\x10348") `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0x01, 0x03, 0x48])
|
||||
|
||||
describe "From Text (UTF_32BE LazyByteString)" $ do
|
||||
let f = Witch.from @Text.Text @(Encoding.UTF_32BE LazyByteString.ByteString)
|
||||
describe "From Text Utf32BL" $ do
|
||||
let f = Witch.from @Text.Text @Encoding.Utf32BL
|
||||
it "works" $ do
|
||||
f (Text.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x00, 0x00, 0x00, 0x61])
|
||||
|
||||
describe "From LazyText (UTF_32BE LazyByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_32BE LazyByteString.ByteString)
|
||||
describe "From LazyText Utf32BL" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf32BL
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (LazyByteString.pack [0x00, 0x00, 0x00, 0x61])
|
||||
|
||||
describe "From LazyText (UTF_32BE ByteString)" $ do
|
||||
let f = Witch.from @LazyText.Text @(Encoding.UTF_32BE ByteString.ByteString)
|
||||
describe "From LazyText Utf32BS" $ do
|
||||
let f = Witch.from @LazyText.Text @Encoding.Utf32BS
|
||||
it "works" $ do
|
||||
f (LazyText.pack "a") `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0x00, 0x00, 0x61])
|
||||
|
||||
describe "From String (UTF_32BE ByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_32BE ByteString.ByteString)
|
||||
describe "From String Utf32BS" $ do
|
||||
let f = Witch.from @String @Encoding.Utf32BS
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (ByteString.pack [0x00, 0x00, 0x00, 0x61])
|
||||
|
||||
describe "From String (UTF_32BE LazyByteString)" $ do
|
||||
let f = Witch.from @String @(Encoding.UTF_32BE LazyByteString.ByteString)
|
||||
describe "From String Utf32BL" $ do
|
||||
let f = Witch.from @String @Encoding.Utf32BL
|
||||
it "works" $ do
|
||||
f "a" `shouldBe` Tagged.Tagged (LazyByteString.pack [0x00, 0x00, 0x00, 0x61])
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user