typed-encoding-0.5.2.1: Type safe string transformations

Safe HaskellSafe
LanguageHaskell2010

Data.TypedEncoding.Instances.Enc.Base64

Contents

Description

Defines Base64 encoding

Since: 0.1.0.0

Synopsis

Documentation

>>> :set -XOverloadedStrings -XScopedTypeVariables -XKindSignatures -XMultiParamTypeClasses -XDataKinds -XPolyKinds -XPartialTypeSignatures -XFlexibleInstances -XTypeApplications
>>> import Test.QuickCheck
>>> import Test.QuickCheck.Instances.ByteString()
>>> :{
instance Arbitrary (UncheckedEnc () B.ByteString) where 
     arbitrary = do
         payload <- frequency [ (5, fmap (getPayload . encodeAll @'["enc-B64"] @(). toEncoding ()) $ arbitrary) 
                            , (1, arbitrary)]
         pure $ toUncheckedEnc ["enc-B64"] () payload
:}

Conversions

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

Since: 0.1.0.0

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

Since: 0.1.0.0

asEncodingB :: Enc '["r-B64"] c ByteString -> Enc '["enc-B64"] c ByteString Source #

Validated "r-B64" is guaranteed to decode.

Use flattenAs in the other direction.

This would not be safe for Text

asEncodingBL :: Enc '["r-B64"] c ByteString -> Enc '["enc-B64"] c ByteString Source #

Validated "r-B64" is guaranteed to decode. This would not be safe for Text

Encoders

encB64B :: Applicative f => Encoding f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

encB64BL :: Applicative f => Encoding f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Decoders

decB64B :: (UnexpectedDecodeErr f, Applicative f) => Decoding f "enc-B64" "enc-B64" c ByteString Source #

Effectful decoding 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.

_propSafeDecoding @"enc-B64" @() @B.ByteString encB64B decB64B ()
_propSafeValidatedDecoding @"enc-B64" @() @B.ByteString validation decB64B () . getUncheckedPayload @() @B.ByteString

Since: 0.3.0.0

decB64BL :: (UnexpectedDecodeErr f, Applicative f) => Decoding f "enc-B64" "enc-B64" c ByteString Source #

_propSafeDecoding @"enc-B64" @() @BL.ByteString encB64BL decB64BL

Since: 0.3.0.0

Validation

Orphan instances

EncodingSuperset "enc-B64" Source #

This is not precise, actually Base 64 uses a subset of ASCII and that would require a new definition "r-B64".

This instance likely to be changed / corrected in the future if "r-B64" is defined.

>>> let tstB64 = encodeAll . toEncoding () $ "Hello World" :: Enc '["enc-B64"] () B.ByteString
>>> displ (_encodesInto @"r-ASCII" $ tstB64)
"Enc '[r-ASCII,enc-B64] () (ByteString SGVsbG8gV29ybGQ=)"
>>> displ (_encodesInto @"r-UTF8" $ tstB64)
"Enc '[r-UTF8,enc-B64] () (ByteString SGVsbG8gV29ybGQ=)"

Since: 0.3.0.0

Instance details

Associated Types

type EncSuperset "enc-B64" :: Symbol Source #

Methods

implEncInto :: Enc ("enc-B64" ': xs) c str -> Enc (EncSuperset "enc-B64" ': ("enc-B64" ': xs)) c str Source #

EncodingSuperset "enc-B64-len" Source #
>>> tstChar8Encodable @ '["enc-B64-len", "enc-B64"]
"I am CHAR8 encodable"
Instance details

Associated Types

type EncSuperset "enc-B64-len" :: Symbol Source #

Methods

implEncInto :: Enc ("enc-B64-len" ': xs) c str -> Enc (EncSuperset "enc-B64-len" ': ("enc-B64-len" ': xs)) c str Source #

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

allow to treat B64 encodings as ASCII forgetting about B64 encoding.

Converting to "r-B64" is also an option now.

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

Since: 0.1.0.0

Instance details

Methods

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

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

Methods

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

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

Since: 0.5.1.0

Instance details

Methods

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

Applicative f => Encode f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Instance details

Methods

encoding :: Encoding f "enc-B64" "enc-B64" c ByteString Source #

Applicative f => Encode f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Instance details

Methods

encoding :: Encoding f "enc-B64" "enc-B64" c ByteString Source #

Applicative f => Validate f "enc-B64-len" "enc-B64-len" c ByteString Source #

Lenient decoding does not fail

Since: 0.3.0.0

Instance details

Methods

validation :: Validation f "enc-B64-len" "enc-B64-len" c ByteString Source #

Applicative f => Validate f "enc-B64-len" "enc-B64-len" c ByteString Source #

Lenient decoding does not fail

Since: 0.3.0.0

Instance details

Methods

validation :: Validation f "enc-B64-len" "enc-B64-len" c ByteString Source #

(RecreateErr f, Applicative f) => Validate f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Instance details

Methods

validation :: Validation f "enc-B64" "enc-B64" c ByteString Source #

(RecreateErr f, Applicative f) => Validate f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Instance details

Methods

validation :: Validation f "enc-B64" "enc-B64" c ByteString Source #

(UnexpectedDecodeErr f, Applicative f) => Decode f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Instance details

Methods

decoding :: Decoding f "enc-B64" "enc-B64" c ByteString Source #

(UnexpectedDecodeErr f, Applicative f) => Decode f "enc-B64" "enc-B64" c ByteString Source #

Since: 0.3.0.0

Instance details

Methods

decoding :: Decoding f "enc-B64" "enc-B64" c ByteString Source #