{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
#if MIN_VERSION_lens(5,0,0)
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Text.Short.Encoding.Base64.Lens
(
_Base64
, _Base64Url
, _Base64UrlUnpadded
, _Base64Lenient
, _Base64UrlLenient
, pattern Base64
, pattern Base64Url
, pattern Base64UrlUnpadded
, pattern Base64Lenient
, pattern Base64UrlLenient
) where
import Control.Lens
import Data.Text.Short (ShortText)
import qualified Data.Text.Short.Encoding.Base64 as TS64
import qualified Data.Text.Short.Encoding.Base64.URL as TS64U
_Base64 :: Prism' ShortText ShortText
_Base64 :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base64 = (ShortText -> ShortText)
-> (ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ShortText -> ShortText
TS64.encodeBase64 ((ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText)
-> (ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText
forall a b. (a -> b) -> a -> b
$ \ShortText
s -> case ShortText -> Either Text ShortText
TS64.decodeBase64 ShortText
s of
Left Text
_ -> Maybe ShortText
forall a. Maybe a
Nothing
Right ShortText
a -> ShortText -> Maybe ShortText
forall a. a -> Maybe a
Just ShortText
a
{-# INLINE _Base64 #-}
_Base64Url :: Prism' ShortText ShortText
_Base64Url :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base64Url = (ShortText -> ShortText)
-> (ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ShortText -> ShortText
TS64U.encodeBase64 ((ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText)
-> (ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText
forall a b. (a -> b) -> a -> b
$ \ShortText
s -> case ShortText -> Either Text ShortText
TS64U.decodeBase64 ShortText
s of
Left Text
_ -> Maybe ShortText
forall a. Maybe a
Nothing
Right ShortText
a -> ShortText -> Maybe ShortText
forall a. a -> Maybe a
Just ShortText
a
{-# INLINE _Base64Url #-}
_Base64UrlUnpadded :: Prism' ShortText ShortText
_Base64UrlUnpadded :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base64UrlUnpadded = (ShortText -> ShortText)
-> (ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' ShortText -> ShortText
TS64U.encodeBase64Unpadded ((ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText)
-> (ShortText -> Maybe ShortText)
-> Prism ShortText ShortText ShortText ShortText
forall a b. (a -> b) -> a -> b
$ \ShortText
s -> case ShortText -> Either Text ShortText
TS64U.decodeBase64Unpadded ShortText
s of
Left Text
_ -> Maybe ShortText
forall a. Maybe a
Nothing
Right ShortText
a -> ShortText -> Maybe ShortText
forall a. a -> Maybe a
Just ShortText
a
{-# INLINE _Base64UrlUnpadded #-}
_Base64Lenient :: Iso' ShortText ShortText
_Base64Lenient :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base64Lenient = (ShortText -> ShortText)
-> (ShortText -> ShortText)
-> Iso ShortText ShortText ShortText ShortText
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ShortText -> ShortText
TS64.decodeBase64Lenient ShortText -> ShortText
TS64.encodeBase64
_Base64UrlLenient :: Iso' ShortText ShortText
_Base64UrlLenient :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base64UrlLenient = (ShortText -> ShortText)
-> (ShortText -> ShortText)
-> Iso ShortText ShortText ShortText ShortText
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso ShortText -> ShortText
TS64U.decodeBase64Lenient ShortText -> ShortText
TS64U.encodeBase64
pattern Base64 :: ShortText -> ShortText
pattern $bBase64 :: ShortText -> ShortText
$mBase64 :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base64 a <- (preview _Base64 -> Just a) where
Base64 ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Base64 (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
pattern Base64Url :: ShortText -> ShortText
pattern $bBase64Url :: ShortText -> ShortText
$mBase64Url :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base64Url a <- (preview _Base64Url -> Just a) where
Base64Url ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Base64Url (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
pattern Base64UrlUnpadded :: ShortText -> ShortText
pattern $bBase64UrlUnpadded :: ShortText -> ShortText
$mBase64UrlUnpadded :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base64UrlUnpadded a <- (preview _Base64UrlUnpadded -> Just a) where
Base64UrlUnpadded ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Base64UrlUnpadded (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
pattern Base64Lenient :: ShortText -> ShortText
pattern $bBase64Lenient :: ShortText -> ShortText
$mBase64Lenient :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base64Lenient a <- (view (from _Base64Lenient) -> a) where
Base64Lenient ShortText
a = Getting ShortText ShortText ShortText -> ShortText -> ShortText
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ShortText ShortText ShortText
Iso ShortText ShortText ShortText ShortText
_Base64Lenient ShortText
a
{-# COMPLETE Base64Lenient #-}
pattern Base64UrlLenient :: ShortText -> ShortText
pattern $bBase64UrlLenient :: ShortText -> ShortText
$mBase64UrlLenient :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base64UrlLenient a <- (view (from _Base64UrlLenient) -> a) where
Base64UrlLenient ShortText
a = Getting ShortText ShortText ShortText -> ShortText -> ShortText
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting ShortText ShortText ShortText
Iso ShortText ShortText ShortText ShortText
_Base64UrlLenient ShortText
a
{-# COMPLETE Base64UrlLenient #-}