{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
#if MIN_VERSION_lens(5,0,0)
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Text.Short.Encoding.Base32.Lens
(
_Base32
, _Base32Unpadded
, _Base32Hex
, _Base32HexUnpadded
, pattern Base32
, pattern Base32Unpadded
, pattern Base32Hex
, pattern Base32HexUnpadded
) where
import Control.Lens
import Data.Text.Short (ShortText)
import qualified Data.Text.Short.Encoding.Base32 as B32TS
import qualified Data.Text.Short.Encoding.Base32.Hex as B32TSH
_Base32 :: Prism' ShortText ShortText
_Base32 :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base32 = (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
B32TS.encodeBase32 ((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
B32TS.decodeBase32 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 _Base32 #-}
_Base32Unpadded :: Prism' ShortText ShortText
_Base32Unpadded :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base32Unpadded = (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
B32TS.encodeBase32Unpadded ((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
B32TS.decodeBase32Unpadded 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 _Base32Unpadded #-}
_Base32Hex :: Prism' ShortText ShortText
_Base32Hex :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base32Hex = (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
B32TSH.encodeBase32 ((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
B32TSH.decodeBase32 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 _Base32Hex #-}
_Base32HexUnpadded :: Prism' ShortText ShortText
_Base32HexUnpadded :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base32HexUnpadded = (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
B32TSH.encodeBase32Unpadded ((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
B32TSH.decodeBase32Unpadded 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 _Base32HexUnpadded #-}
pattern Base32 :: ShortText -> ShortText
pattern $bBase32 :: ShortText -> ShortText
$mBase32 :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base32 a <- (preview _Base32 -> Just a) where
Base32 ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Base32 (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
pattern Base32Unpadded :: ShortText -> ShortText
pattern $bBase32Unpadded :: ShortText -> ShortText
$mBase32Unpadded :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base32Unpadded a <- (preview _Base32Unpadded -> Just a) where
Base32Unpadded ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Base32Unpadded (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
pattern Base32Hex :: ShortText -> ShortText
pattern $bBase32Hex :: ShortText -> ShortText
$mBase32Hex :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base32Hex a <- (preview _Base32Hex -> Just a) where
Base32Hex ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Base32Hex (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
pattern Base32HexUnpadded :: ShortText -> ShortText
pattern $bBase32HexUnpadded :: ShortText -> ShortText
$mBase32HexUnpadded :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base32HexUnpadded a <- (preview _Base32HexUnpadded -> Just a) where
Base32HexUnpadded ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Base32HexUnpadded (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a