{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
#if MIN_VERSION_lens(5,0,0)
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif
-- |
-- Module       : Data.ByteString.Base64.Lens
-- Copyright 	: (c) 2019-2021 Emily Pillmore
-- License	: BSD-style
--
-- Maintainer	: Emily Pillmore <emilypi@cohomolo.gy>
-- Stability	: Experimental
-- Portability	: non-portable
--
-- This module contains 'Prism''s and 'Iso''s for Base64-encoding and
-- decoding 'ByteString' values.
--
module Data.ByteString.Base64.Lens
( -- * Prisms
  _Base64
, _Base64Url
, _Base64UrlUnpadded
, _Base64Lenient
, _Base64UrlLenient
  -- * Patterns
, pattern Base64
, pattern Base64Url
, pattern Base64UrlUnpadded
, pattern Base64Lenient
, pattern Base64UrlLenient
) where


import Control.Lens

import Data.ByteString (ByteString)
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Base64.URL as B64U


-- $setup
--
-- >>> import Control.Lens
-- >>> import Data.ByteString.Base64.Lens
--
-- >>> :set -XOverloadedStrings
-- >>> :set -XTypeApplications


-- -------------------------------------------------------------------------- --
-- Optics

-- | A 'Prism'' into the Base64 encoding of a 'ByteString' value
--
-- >>> _Base64 # "Sun"
-- "U3Vu"
--
-- >>> "U3Vu" ^? _Base64
-- Just "Sun"
--
_Base64 :: Prism' ByteString ByteString
_Base64 :: p ByteString (f ByteString) -> p ByteString (f ByteString)
_Base64 = (ByteString -> ByteString)
-> (ByteString -> Maybe ByteString)
-> Prism ByteString ByteString ByteString ByteString
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ByteString -> ByteString
B64.encodeBase64' ((ByteString -> Maybe ByteString)
 -> Prism ByteString ByteString ByteString ByteString)
-> (ByteString -> Maybe ByteString)
-> Prism ByteString ByteString ByteString ByteString
forall a b. (a -> b) -> a -> b
$ \ByteString
s -> case ByteString -> Either Text ByteString
B64.decodeBase64 ByteString
s of
    Left Text
_ -> Maybe ByteString
forall a. Maybe a
Nothing
    Right ByteString
a -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
a
{-# INLINE _Base64 #-}

-- | A 'Prism'' into the Base64url encoding of a 'ByteString' value
--
-- >>> _Base64Url # "Sun"
-- "U3Vu"
--
-- >>> "PDw_Pz8-Pg==" ^? _Base64Url
-- Just "<<???>>"
--
_Base64Url :: Prism' ByteString ByteString
_Base64Url :: p ByteString (f ByteString) -> p ByteString (f ByteString)
_Base64Url = (ByteString -> ByteString)
-> (ByteString -> Maybe ByteString)
-> Prism ByteString ByteString ByteString ByteString
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ByteString -> ByteString
B64U.encodeBase64' ((ByteString -> Maybe ByteString)
 -> Prism ByteString ByteString ByteString ByteString)
-> (ByteString -> Maybe ByteString)
-> Prism ByteString ByteString ByteString ByteString
forall a b. (a -> b) -> a -> b
$ \ByteString
s -> case ByteString -> Either Text ByteString
B64U.decodeBase64 ByteString
s of
    Left Text
_ -> Maybe ByteString
forall a. Maybe a
Nothing
    Right ByteString
a -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
a
{-# INLINE _Base64Url #-}

-- | A 'Prism'' into the Base64url encoding of a 'ByteString' value
--
-- Please note that unpadded variants should only be used
-- when assumptions about the data can be made. In particular, if the length of
-- the input is divisible by 3, then this is a safe function to call.
--
-- >>> _Base64UrlUnpadded # "<<??>>"
-- "PDw_Pz4-"
--
-- >>> "PDw_Pz4-" ^? _Base64UrlUnpadded
-- Just "<<??>>"
--
_Base64UrlUnpadded :: Prism' ByteString ByteString
_Base64UrlUnpadded :: p ByteString (f ByteString) -> p ByteString (f ByteString)
_Base64UrlUnpadded = (ByteString -> ByteString)
-> (ByteString -> Maybe ByteString)
-> Prism ByteString ByteString ByteString ByteString
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ByteString -> ByteString
B64U.encodeBase64Unpadded' ((ByteString -> Maybe ByteString)
 -> Prism ByteString ByteString ByteString ByteString)
-> (ByteString -> Maybe ByteString)
-> Prism ByteString ByteString ByteString ByteString
forall a b. (a -> b) -> a -> b
$ \ByteString
s -> case ByteString -> Either Text ByteString
B64U.decodeBase64Unpadded ByteString
s of
    Left Text
_ -> Maybe ByteString
forall a. Maybe a
Nothing
    Right ByteString
a -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
a
{-# INLINE _Base64UrlUnpadded #-}

-- | An 'Iso'' into the Base64 encoding of a 'ByteString' value
-- using lenient decoding.
--
--
-- _Note:_ This is not a lawful 'Iso'. Please take care!
--
-- >>> _Base64Lenient # "Sun"
-- "U3Vu"
--
-- >>> "U3Vu" ^. _Base64Lenient
-- "Sun"
--
_Base64Lenient :: Iso' ByteString ByteString
_Base64Lenient :: p ByteString (f ByteString) -> p ByteString (f ByteString)
_Base64Lenient = (ByteString -> ByteString)
-> (ByteString -> ByteString)
-> Iso ByteString ByteString ByteString ByteString
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ByteString -> ByteString
B64.decodeBase64Lenient ByteString -> ByteString
B64.encodeBase64'

-- | An 'Iso'' into the Base64url encoding of a 'ByteString' value
-- using lenient decoding.
--
--
-- _Note:_ This is not a lawful 'Iso'. Please take care!
--
-- >>> _Base64UrlLenient # "<<??>>"
-- "PDw_Pz4-"
--
-- >>> "PDw_Pz4-" ^. _Base64UrlLenient
-- "<<??>>"
--
_Base64UrlLenient :: Iso' ByteString ByteString
_Base64UrlLenient :: p ByteString (f ByteString) -> p ByteString (f ByteString)
_Base64UrlLenient = (ByteString -> ByteString)
-> (ByteString -> ByteString)
-> Iso ByteString ByteString ByteString ByteString
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ByteString -> ByteString
B64U.decodeBase64Lenient ByteString -> ByteString
B64U.encodeBase64'

-- -------------------------------------------------------------------------- --
-- Patterns

-- | Bidirectional pattern synonym for base64-encoded 'ByteString' values.
--
pattern Base64 :: ByteString -> ByteString
pattern $bBase64 :: ByteString -> ByteString
$mBase64 :: forall r. ByteString -> (ByteString -> r) -> (Void# -> r) -> r
Base64 a <- (preview _Base64 -> Just a) where
    Base64 ByteString
a = Tagged ByteString (Identity ByteString)
-> Tagged ByteString (Identity ByteString)
Prism ByteString ByteString ByteString ByteString
_Base64 (Tagged ByteString (Identity ByteString)
 -> Tagged ByteString (Identity ByteString))
-> ByteString -> ByteString
forall t b. AReview t b -> b -> t
# ByteString
a

-- | Bidirectional pattern synonym for base64url-encoded 'ByteString' values.
--
pattern Base64Url :: ByteString -> ByteString
pattern $bBase64Url :: ByteString -> ByteString
$mBase64Url :: forall r. ByteString -> (ByteString -> r) -> (Void# -> r) -> r
Base64Url a <- (preview _Base64Url -> Just a) where
    Base64Url ByteString
a = Tagged ByteString (Identity ByteString)
-> Tagged ByteString (Identity ByteString)
Prism ByteString ByteString ByteString ByteString
_Base64Url (Tagged ByteString (Identity ByteString)
 -> Tagged ByteString (Identity ByteString))
-> ByteString -> ByteString
forall t b. AReview t b -> b -> t
# ByteString
a

-- | Bidirectional pattern synonym for unpadded base64url-encoded 'ByteString' values.
--
pattern Base64UrlUnpadded :: ByteString -> ByteString
pattern $bBase64UrlUnpadded :: ByteString -> ByteString
$mBase64UrlUnpadded :: forall r. ByteString -> (ByteString -> r) -> (Void# -> r) -> r
Base64UrlUnpadded a <- (preview _Base64UrlUnpadded -> Just a) where
    Base64UrlUnpadded ByteString
a = Tagged ByteString (Identity ByteString)
-> Tagged ByteString (Identity ByteString)
Prism ByteString ByteString ByteString ByteString
_Base64UrlUnpadded (Tagged ByteString (Identity ByteString)
 -> Tagged ByteString (Identity ByteString))
-> ByteString -> ByteString
forall t b. AReview t b -> b -> t
# ByteString
a

-- | Bidirectional pattern synonym for leniently Base64-encoded 'ByteString' values
--
pattern Base64Lenient :: ByteString -> ByteString
pattern $bBase64Lenient :: ByteString -> ByteString
$mBase64Lenient :: forall r. ByteString -> (ByteString -> r) -> (Void# -> r) -> r
Base64Lenient a <- (view (from _Base64Lenient) -> a) where
    Base64Lenient ByteString
a = Getting ByteString ByteString ByteString
-> ByteString -> ByteString
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ByteString ByteString ByteString
Iso ByteString ByteString ByteString ByteString
_Base64Lenient ByteString
a
{-# COMPLETE Base64Lenient #-}

-- | Bidirectional pattern synonym for leniently Base64-encoded 'ByteString' values
--
pattern Base64UrlLenient :: ByteString -> ByteString
pattern $bBase64UrlLenient :: ByteString -> ByteString
$mBase64UrlLenient :: forall r. ByteString -> (ByteString -> r) -> (Void# -> r) -> r
Base64UrlLenient a <- (view (from _Base64UrlLenient) -> a) where
    Base64UrlLenient ByteString
a = Getting ByteString ByteString ByteString
-> ByteString -> ByteString
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ByteString ByteString ByteString
Iso ByteString ByteString ByteString ByteString
_Base64UrlLenient ByteString
a
{-# COMPLETE Base64UrlLenient #-}