{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module Data.ByteString.Base16.Lens
(
_Hex
, _Base16
, _Base16Lenient
, pattern Hex
, pattern Base16
, pattern Base16Lenient
) where
import Control.Lens
import Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as B16
_Base16 :: Prism' ByteString ByteString
_Base16 :: p ByteString (f ByteString) -> p ByteString (f ByteString)
_Base16 = (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
B16.encodeBase16' ((ByteString -> Maybe ByteString)
-> p ByteString (f ByteString) -> p ByteString (f ByteString))
-> (ByteString -> Maybe ByteString)
-> p ByteString (f ByteString)
-> p ByteString (f ByteString)
forall a b. (a -> b) -> a -> b
$ \s :: ByteString
s -> case ByteString -> Either Text ByteString
B16.decodeBase16 ByteString
s of
Left _ -> Maybe ByteString
forall a. Maybe a
Nothing
Right a :: ByteString
a -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
a
{-# INLINE _Base16 #-}
_Hex :: Prism' ByteString ByteString
_Hex :: p ByteString (f ByteString) -> p ByteString (f ByteString)
_Hex = (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
B16.encodeBase16' ((ByteString -> Maybe ByteString)
-> p ByteString (f ByteString) -> p ByteString (f ByteString))
-> (ByteString -> Maybe ByteString)
-> p ByteString (f ByteString)
-> p ByteString (f ByteString)
forall a b. (a -> b) -> a -> b
$ \s :: ByteString
s -> case ByteString -> Either Text ByteString
B16.decodeBase16 ByteString
s of
Left _ -> Maybe ByteString
forall a. Maybe a
Nothing
Right a :: ByteString
a -> ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
a
{-# INLINE _Hex #-}
_Base16Lenient :: Iso' ByteString ByteString
_Base16Lenient :: p ByteString (f ByteString) -> p ByteString (f ByteString)
_Base16Lenient = (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
B16.decodeBase16Lenient ByteString -> ByteString
B16.encodeBase16'
{-# INLINE _Base16Lenient #-}
pattern Hex :: ByteString -> ByteString
pattern $bHex :: ByteString -> ByteString
$mHex :: forall r. ByteString -> (ByteString -> r) -> (Void# -> r) -> r
Hex a <- (preview _Hex -> Just a) where
Hex a :: ByteString
a = Tagged ByteString (Identity ByteString)
-> Tagged ByteString (Identity ByteString)
Prism ByteString ByteString ByteString ByteString
_Hex (Tagged ByteString (Identity ByteString)
-> Tagged ByteString (Identity ByteString))
-> ByteString -> ByteString
forall t b. AReview t b -> b -> t
# ByteString
a
pattern Base16 :: ByteString -> ByteString
pattern $bBase16 :: ByteString -> ByteString
$mBase16 :: forall r. ByteString -> (ByteString -> r) -> (Void# -> r) -> r
Base16 a <- (preview _Base16 -> Just a) where
Base16 a :: ByteString
a = Tagged ByteString (Identity ByteString)
-> Tagged ByteString (Identity ByteString)
Prism ByteString ByteString ByteString ByteString
_Base16 (Tagged ByteString (Identity ByteString)
-> Tagged ByteString (Identity ByteString))
-> ByteString -> ByteString
forall t b. AReview t b -> b -> t
# ByteString
a
pattern Base16Lenient :: ByteString -> ByteString
pattern $bBase16Lenient :: ByteString -> ByteString
$mBase16Lenient :: forall r. ByteString -> (ByteString -> r) -> (Void# -> r) -> r
Base16Lenient a <- (view (from _Base16Lenient) -> a) where
Base16Lenient a :: 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
Prism ByteString ByteString ByteString ByteString
_Base16 ByteString
a