{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
module Data.TypedEncoding.Instances.Enc.Base64 where
import Data.TypedEncoding
import Data.TypedEncoding.Instances.Support
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Lazy.Encoding as TEL
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Base64.Lazy as BL64
byteString2TextS :: Enc ("enc-B64" ': "r-UTF8" ': ys) c B.ByteString -> Enc ("enc-B64" ': ys) c T.Text
byteString2TextS = withUnsafeCoerce TE.decodeUtf8
byteString2TextL :: Enc ("enc-B64" ': "r-UTF8" ': ys) c BL.ByteString -> Enc ("enc-B64" ': ys) c TL.Text
byteString2TextL = withUnsafeCoerce TEL.decodeUtf8
text2ByteStringS :: Enc ("enc-B64" ': ys) c T.Text -> Enc ("enc-B64" ': "r-UTF8" ': ys) c B.ByteString
text2ByteStringS = withUnsafeCoerce TE.encodeUtf8
text2ByteStringL :: Enc ("enc-B64" ': ys) c TL.Text -> Enc ("enc-B64" ': "r-UTF8" ': ys) c BL.ByteString
text2ByteStringL = withUnsafeCoerce TEL.encodeUtf8
byteString2TextS' :: Enc ("enc-B64" ': ys) c B.ByteString -> Enc ("enc-B64-nontext" ': ys) c T.Text
byteString2TextS' = withUnsafeCoerce TE.decodeUtf8
byteString2TextL' :: Enc ("enc-B64" ': ys) c BL.ByteString -> Enc ("enc-B64-nontext" ': ys) c TL.Text
byteString2TextL' = withUnsafeCoerce TEL.decodeUtf8
text2ByteStringS' :: Enc ("enc-B64-nontext" ': ys) c T.Text -> Enc ("enc-B64" ': ys) c B.ByteString
text2ByteStringS' = withUnsafeCoerce TE.encodeUtf8
text2ByteStringL' :: Enc ("enc-B64-nontext" ': ys) c TL.Text -> Enc ("enc-B64" ': ys) c BL.ByteString
text2ByteStringL' = withUnsafeCoerce TEL.encodeUtf8
acceptLenientS :: Enc ("enc-B64-len" ': ys) c B.ByteString -> Enc ("enc-B64" ': ys) c B.ByteString
acceptLenientS = withUnsafeCoerce (B64.encode . B64.decodeLenient)
acceptLenientL :: Enc ("enc-B64-len" ': ys) c BL.ByteString -> Enc ("enc-B64" ': ys) c BL.ByteString
acceptLenientL = withUnsafeCoerce (BL64.encode . BL64.decodeLenient)
instance FlattenAs "r-ASCII" "enc-B64-nontext" where
instance FlattenAs "r-ASCII" "enc-B64" where
instance Superset "r-ASCII" "enc-B64-nontext" where
instance Superset "r-ASCII" "enc-B64" where
instance Encodings (Either EncodeEx) xs grps c B.ByteString => Encodings (Either EncodeEx) ("enc-B64" ': xs) ("enc-B64" ': grps) c B.ByteString where
encodings = encodeFEncoder @(Either EncodeEx) @"enc-B64" @"enc-B64"
instance Applicative f => EncodeF f (Enc xs c B.ByteString) (Enc ("enc-B64" ': xs) c B.ByteString) where
encodeF = implEncodeP B64.encode
instance (UnexpectedDecodeErr f, Applicative f) => DecodeF f (Enc ("enc-B64" ': xs) c B.ByteString) (Enc xs c B.ByteString) where
decodeF = implDecodeF (asUnexpected @"enc-B64" . B64.decode)
instance (RecreateErr f, Applicative f) => RecreateF f (Enc xs c B.ByteString) (Enc ("enc-B64" ': xs) c B.ByteString) where
checkPrevF = implCheckPrevF (asRecreateErr @"enc-B64" . B64.decode)
instance Applicative f => RecreateF f (Enc xs c B.ByteString) (Enc ("enc-B64-len" ': xs) c B.ByteString) where
checkPrevF = implTranP id
instance Applicative f => EncodeF f (Enc xs c BL.ByteString) (Enc ("enc-B64" ': xs) c BL.ByteString) where
encodeF = implEncodeP BL64.encode
instance (UnexpectedDecodeErr f, Applicative f) => DecodeF f (Enc ("enc-B64" ': xs) c BL.ByteString) (Enc xs c BL.ByteString) where
decodeF = implDecodeF (asUnexpected @"enc-B64" . BL64.decode)
instance (RecreateErr f, Applicative f) => RecreateF f (Enc xs c BL.ByteString) (Enc ("enc-B64" ': xs) c BL.ByteString) where
checkPrevF = implCheckPrevF (asRecreateErr @"enc-B64" . BL64.decode)
instance Applicative f => RecreateF f (Enc xs c BL.ByteString) (Enc ("enc-B64-len" ': xs) c BL.ByteString) where
checkPrevF = implTranP id
instance Applicative f => EncodeF f (Enc xs c T.Text) (Enc ("enc-B64" ': xs) c T.Text) where
encodeF = implEncodeP (TE.decodeUtf8 . B64.encode . TE.encodeUtf8)
instance (UnexpectedDecodeErr f, Applicative f) => DecodeF f (Enc ("enc-B64" ': xs) c T.Text) (Enc xs c T.Text) where
decodeF = implDecodeF (asUnexpected @"enc-B64" . fmap TE.decodeUtf8 . B64.decode . TE.encodeUtf8)
instance (RecreateErr f, Applicative f) => RecreateF f (Enc xs c T.Text) (Enc ("enc-B64" ': xs) c T.Text) where
checkPrevF = implCheckPrevF (asRecreateErr @"enc-B64" . fmap TE.decodeUtf8 . B64.decode . TE.encodeUtf8)
instance Applicative f => EncodeF f (Enc xs c TL.Text) (Enc ("enc-B64" ': xs) c TL.Text) where
encodeF = implEncodeP (TEL.decodeUtf8 . BL64.encode . TEL.encodeUtf8)
instance (UnexpectedDecodeErr f, Applicative f) => DecodeF f (Enc ("enc-B64" ': xs) c TL.Text) (Enc xs c TL.Text) where
decodeF = implDecodeF (asUnexpected @"enc-B64" . fmap TEL.decodeUtf8 . BL64.decode . TEL.encodeUtf8)
instance (RecreateErr f, Applicative f) => RecreateF f (Enc xs c TL.Text) (Enc ("enc-B64" ': xs) c TL.Text) where
checkPrevF = implCheckPrevF (asRecreateErr @"enc-B64" . fmap TEL.decodeUtf8 . BL64.decode . TEL.encodeUtf8)