Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Since: 0.2.2.0
Synopsis
- decodeUtf8 :: forall xs c t. (LLast xs ~ t, IsSuperset "r-UTF8" t ~ True) => Enc xs c ByteString -> Enc xs c Text
- encodeUtf8 :: forall xs c t. (LLast xs ~ t, IsSuperset "r-UTF8" t ~ True) => Enc xs c Text -> Enc xs c ByteString
Documentation
>>>
:set -XScopedTypeVariables -XOverloadedStrings -XDataKinds -XFlexibleContexts -XTypeApplications
>>>
import Test.QuickCheck
>>>
import Test.QuickCheck.Instances.Text()
>>>
import Test.QuickCheck.Instances.ByteString()
>>>
import qualified Data.ByteString.Char8 as B8
>>>
import Data.Char
>>>
import Data.Either
>>>
import Data.TypedEncoding
>>>
import Data.TypedEncoding.Conv.Text
>>>
let emptyUTF8B = unsafeSetPayload () "" :: Enc '["r-UTF8"] () B.ByteString
>>>
:{
instance Arbitrary (Enc '["r-UTF8"] () B.ByteString) where arbitrary = fmap (fromRight emptyUTF8B) . flip suchThat isRight . fmap (encodeFAll @'["r-UTF8"] @(Either EncodeEx) @(). toEncoding ()) $ arbitrary instance Arbitrary (Enc '["r-UTF8"] () T.Text) where arbitrary = fmap (unsafeSetPayload ()) arbitrary instance Arbitrary (Enc '["r-ASCII"] () B.ByteString) where arbitrary = fmap (unsafeSetPayload ()) . flip suchThat (B8.all isAscii) $ arbitrary instance Arbitrary (Enc '["r-ASCII"] () T.Text) where arbitrary = fmap (unsafeSetPayload ()) . flip suchThat (T.all isAscii) $ arbitrary :}
decodeUtf8 :: forall xs c t. (LLast xs ~ t, IsSuperset "r-UTF8" t ~ True) => Enc xs c ByteString -> Enc xs c Text Source #
With given constraints decodeUtf8
and encodeUtf8
can be used on subsets of "r-UTF8"
>>>
displ . decodeUtf8 $ (unsafeSetPayload () "Hello" :: Enc '["r-ASCII"] () B.ByteString)
"Enc '[r-ASCII] () (Text Hello)"
"r-UTF8" is redundant:
>>>
displ . utf8Demote . decodeUtf8 $ (unsafeSetPayload () "Hello" :: Enc '["r-UTF8"] () B.ByteString)
"Enc '[] () (Text Hello)"
decodeUtf8
and encodeUtf8
form isomorphism
\x -> getPayload x == (getPayload . encodeUtf8 . decodeUtf8 @ '["r-UTF8"] @() $ x)
\x -> getPayload x == (getPayload . decodeUtf8 . encodeUtf8 @ '["r-UTF8"] @() $ x)
These nicely work as iso's for "r-ASCII" subset
\x -> getPayload x == (getPayload . encodeUtf8 . decodeUtf8 @ '["r-ASCII"] @() $ x)
\x -> getPayload x == (getPayload . decodeUtf8 . encodeUtf8 @ '["r-ASCII"] @() $ x)
encodeUtf8 :: forall xs c t. (LLast xs ~ t, IsSuperset "r-UTF8" t ~ True) => Enc xs c Text -> Enc xs c ByteString Source #
>>>
displ $ encodeUtf8 $ utf8Promote $ toEncoding () ("text" :: T.Text)
"Enc '[r-UTF8] () (ByteString text)"