typed-encoding-0.2.0.0: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Instances.Enc.Base64

Contents

Description

Defines Base64 encoding

Synopsis

Documentation

>>> :set -XScopedTypeVariables -XKindSignatures -XMultiParamTypeClasses -XDataKinds -XPolyKinds -XPartialTypeSignatures -XFlexibleInstances
>>> import Test.QuickCheck
>>> import Test.QuickCheck.Instances.Text()
>>> import Test.QuickCheck.Instances.ByteString()

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

Type-safer version of Byte-string to text conversion that prevent invalid UTF8 bytestrings to be conversted to B64 encoded Text.

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

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

Converts encoded text to ByteString adding "r-UTF8" annotation. The question is why "r-UTF8", not for example, "r-UTF16"? No reason, there maybe a diffrent combinator for that in the future or one that accepts a proxy.

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

byteString2TextS' :: Enc ("enc-B64" ': ys) c ByteString -> Enc ("enc-B64-nontext" ': ys) c Text Source #

B64 encoded bytestring can be converted to Text as "enc-B64-nontext" preventing it from being B64-decoded directly to Text

byteString2TextL' :: Enc ("enc-B64" ': ys) c ByteString -> Enc ("enc-B64-nontext" ': ys) c Text Source #

text2ByteStringS' :: Enc ("enc-B64-nontext" ': ys) c Text -> Enc ("enc-B64" ': ys) c ByteString Source #

text2ByteStringL' :: Enc ("enc-B64-nontext" ': ys) c Text -> Enc ("enc-B64" ': ys) c ByteString Source #

acceptLenientS :: Enc ("enc-B64-len" ': ys) c ByteString -> Enc ("enc-B64" ': ys) c ByteString Source #

acceptLenientL :: Enc ("enc-B64-len" ': ys) c ByteString -> Enc ("enc-B64" ': ys) c ByteString Source #

Orphan instances

FlattenAs "r-ASCII" "enc-B64" Source # 
Instance details

Methods

flattenAs :: Enc ("enc-B64" ': xs) c str -> Enc ("r-ASCII" ': []) c str Source #

FlattenAs "r-ASCII" "enc-B64-nontext" Source #

allow to treat B64 encodings as ASCII forgetting about B64 encoding

>>> let tstB64 = encodeAll . toEncoding () $ "Hello World" :: Enc '["enc-B64"] () B.ByteString
>>> displ (flattenAs tstB64 :: Enc '["r-ASCII"] () B.ByteString)
"MkEnc '[r-ASCII] () (ByteString SGVsbG8gV29ybGQ=)"
Instance details

Methods

flattenAs :: Enc ("enc-B64-nontext" ': xs) c str -> Enc ("r-ASCII" ': []) c str Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("enc-B64" ': xs) c Text) Source # 
Instance details

Methods

checkPrevF :: Enc ("enc-B64" ': xs) c Text -> f (Enc xs c Text) Source #

(RecreateErr f, Applicative f) => RecreateF (f :: Type -> Type) (Enc xs c Text :: Type) (Enc ("enc-B64" ': xs) c Text) Source # 
Instance details

Methods

checkPrevF :: Enc ("enc-B64" ': xs) c Text -> f (Enc xs c Text) Source #

Applicative f => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("enc-B64-len" ': xs) c ByteString) Source # 
Instance details

Methods

checkPrevF :: Enc ("enc-B64-len" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

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

Methods

checkPrevF :: Enc ("enc-B64" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => RecreateF (f :: Type -> Type) (Enc xs c ByteString :: Type) (Enc ("enc-B64-len" ': xs) c ByteString) Source # 
Instance details

Methods

checkPrevF :: Enc ("enc-B64-len" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

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

Methods

checkPrevF :: Enc ("enc-B64" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("enc-B64" ': xs) c Text :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c Text -> f (Enc ("enc-B64" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c Text) (Enc ("enc-B64" ': xs) c Text :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c Text -> f (Enc ("enc-B64" ': xs) c Text) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c ByteString) (Enc ("enc-B64" ': xs) c ByteString :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c ByteString -> f (Enc ("enc-B64" ': xs) c ByteString) Source #

Applicative f => EncodeF (f :: Type -> Type) (Enc xs c ByteString) (Enc ("enc-B64" ': xs) c ByteString :: Type) Source # 
Instance details

Methods

encodeF :: Enc xs c ByteString -> f (Enc ("enc-B64" ': xs) c ByteString) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c Text) (Enc xs c Text :: Type) Source # 
Instance details

Methods

decodeF :: Enc ("enc-B64" ': xs) c Text -> f (Enc xs c Text) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c Text) (Enc xs c Text :: Type) Source # 
Instance details

Methods

decodeF :: Enc ("enc-B64" ': xs) c Text -> f (Enc xs c Text) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source # 
Instance details

Methods

decodeF :: Enc ("enc-B64" ': xs) c ByteString -> f (Enc xs c ByteString) Source #

(UnexpectedDecodeErr f, Applicative f) => DecodeF (f :: Type -> Type) (Enc ("enc-B64" ': xs) c ByteString) (Enc xs c ByteString :: Type) Source #

Effectful instance for corruption detection. This protocol is used, for example, in emails. It is a well known encoding and hackers will have no problem making undetectable changes, but error handling at this stage could verify that email was corrupted.

Instance details

Methods

decodeF :: Enc ("enc-B64" ': xs) c ByteString -> f (Enc xs c ByteString) Source #