typed-encoding-0.2.2.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Instances.Restriction.UTF8

Contents

Description

'UTF-8' encoding

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.Internal.Util (proxiedId)
>>> :{
>>> instance Arbitrary (Enc '["r-UTF8"] () B.ByteString) where
     arbitrary =  fmap (fromRight (emptyUTF8B ())) 
                  . flip suchThat isRight 
                  . fmap (encodeFAll @(Either EncodeEx) @'["r-UTF8"] @(). toEncoding ()) $ arbitrary 
:}

emptyUTF8B :: c -> Enc '["r-UTF8"] c ByteString Source #

DEPRECATED will be removed in 0.3 empty string is valid utf8

text2ByteStringS :: Enc ys c Text -> Enc ("r-UTF8" ': ys) c ByteString Source #

| DEPRECATED will be removed in 0.3

use encodeUtf8 and utf8Promote

byteString2TextS :: Enc ("r-UTF8" ': ys) c ByteString -> Enc ys c Text Source #

DEPRECATED

| DEPRECATED will be removed in 0.3

use decodeUtf8 and utf8Demote

See warning in byteString2TextS

Type-safer version of Data.Text.Encoding.decodeUtf8

txtBsSIdProp :: Proxy (ys :: [Symbol]) -> Enc ys c Text -> Enc ys c Text Source #

To be removed

bsTxtIdProp :: Proxy (ys :: [Symbol]) -> Enc ("r-UTF8" ': ys) c ByteString -> Enc ("r-UTF8" ': ys) c ByteString Source #

text2ByteStringL :: Enc ys c Text -> Enc ("r-UTF8" ': ys) c ByteString Source #

byteString2TextL :: Enc ("r-UTF8" ': ys) c ByteString -> Enc ys c Text Source #

prxyUtf8 :: Proxy "r-UTF8" Source #

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) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-UTF8" ': xs) c ByteString) Source # 
Instance details

Methods

checkPrevF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("r-UTF8" ': xs) c ByteString) Source # 
Instance details

Methods

checkPrevF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-UTF8" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Methods

decodeF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => DecodeF (f :: Type -> Type) (Enc ("r-UTF8" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Methods

decodeF :: Enc ("r-UTF8" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source #

EncodeF (Either EncodeEx) (Enc xs c ByteString) (Enc ("r-UTF8" ': xs) c ByteString :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c ByteString -> Either EncodeEx (Enc ("r-UTF8" ': xs) c ByteString) Source #

Encodings (Either EncodeEx) xs grps c ByteString => Encodings (Either EncodeEx) ("r-UTF8" ': xs) ("r-UTF8" ': grps) c ByteString Source # 
Instance details

Methods

encodings :: Encoder (Either EncodeEx) ("r-UTF8" ': xs) ("r-UTF8" ': grps) c ByteString Source #

Encodings (Either EncodeEx) xs grps c ByteString => Encodings (Either EncodeEx) ("r-UTF8" ': xs) ("r-UTF8" ': grps) 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 (MkEnc 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

\(b :: B.ByteString) -> verEncoding b (fmap (fromEncoding . decodeAll . proxiedId (Proxy :: Proxy (Enc '["r-UTF8"] _ _))) . (encodeFAll :: _ -> Either EncodeEx _). toEncoding () $ b)
Instance details

Methods

encodings :: Encoder (Either EncodeEx) ("r-UTF8" ': xs) ("r-UTF8" ': grps) c ByteString Source #