typed-encoding-0.4.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Instances.Restriction.UTF8

Contents

Description

'UTF-8' encoding

Since: 0.1.0.0

Synopsis

Documentation

>>> :set -XScopedTypeVariables -XKindSignatures -XMultiParamTypeClasses -XDataKinds -XPolyKinds -XPartialTypeSignatures -XFlexibleInstances -XTypeApplications
>>> import Test.QuickCheck
>>> import Test.QuickCheck.Instances.Text()
>>> import Test.QuickCheck.Instances.ByteString()
>>> import Data.TypedEncoding
>>> import Data.TypedEncoding.Internal.Util (proxiedId)
>>> 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 
:}

prxyUtf8 :: Proxy "r-UTF8" Source #

encUTF8B :: Encoding (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source #

Warning: This method was not optimized for performance.

encUTF8BL :: Encoding (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source #

Warning: This method was not optimized for performance.

Decoding

verEncoding :: ByteString -> Either err ByteString -> Bool Source #

helper function checks that given ByteString, if is encoded as Left is must be not Utf8 decodable is is encoded as Right is must be Utf8 encodable

Orphan instances

(RecreateErr f, Applicative f) => Validate f "r-UTF8" "r-UTF8" c ByteString Source # 
Instance details

Methods

validation :: Validation f "r-UTF8" "r-UTF8" c ByteString Source #

(RecreateErr f, Applicative f) => Validate f "r-UTF8" "r-UTF8" c ByteString Source # 
Instance details

Methods

validation :: Validation f "r-UTF8" "r-UTF8" c ByteString Source #

Applicative f => Decode f "r-UTF8" "r-UTF8" c str Source # 
Instance details

Methods

decoding :: Decoding f "r-UTF8" "r-UTF8" c str Source #

Encode (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source # 
Instance details

Methods

encoding :: Encoding (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source #

Encode (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source #

UTF8 encodings are defined for ByteString only as that would not make much sense for Text

>>> encodeFAll . toEncoding () $ "\xc3\xb1" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Right (UnsafeMkEnc Proxy () "\195\177")
>>> encodeFAll . toEncoding () $ "\xc3\x28" :: Either EncodeEx (Enc '["r-UTF8"] () B.ByteString)
Left (EncodeEx "r-UTF8" (Cannot decode byte '\xc3': Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream))

Following test uses verEncoding helper that checks that bytes are encoded as Right iff they are valid UTF8 bytes

>>> :{
quickCheck $ \(b :: B.ByteString) -> verEncoding b $ fmap (
         fromEncoding 
         . decodeAll @'["r-UTF8"]
         ) . encodeFAll @'["r-UTF8"] @(Either EncodeEx)
         . toEncoding () $ b
:}
+++ OK, passed 100 tests.
Instance details

Methods

encoding :: Encoding (Either EncodeEx) "r-UTF8" "r-UTF8" c ByteString Source #