{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
#if MIN_VERSION_lens(5,0,0)
{-# LANGUAGE Safe #-}
#else
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Text.Short.Encoding.Base16.Lens
(
_Hex
, _Base16
, _Base16Lenient
, pattern Hex
, pattern Base16
, pattern Base16Lenient
) where
import Control.Lens
import Data.Text.Short (ShortText)
import qualified Data.Text.Short.Encoding.Base16 as B16TS
_Base16 :: Prism' ShortText ShortText
_Base16 :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base16 = (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
B16TS.encodeBase16 ((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
B16TS.decodeBase16 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 _Base16 #-}
_Hex :: Prism' ShortText ShortText
_Hex :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Hex = (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
B16TS.encodeBase16 ((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
B16TS.decodeBase16 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 _Hex #-}
_Base16Lenient :: Iso' ShortText ShortText
_Base16Lenient :: p ShortText (f ShortText) -> p ShortText (f ShortText)
_Base16Lenient = (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
B16TS.decodeBase16Lenient ShortText -> ShortText
B16TS.encodeBase16
{-# INLINE _Base16Lenient #-}
pattern Hex :: ShortText -> ShortText
pattern $bHex :: ShortText -> ShortText
$mHex :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Hex a <- (preview _Hex -> Just a) where
Hex ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Hex (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
pattern Base16 :: ShortText -> ShortText
pattern $bBase16 :: ShortText -> ShortText
$mBase16 :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base16 a <- (preview _Base16 -> Just a) where
Base16 ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Prism ShortText ShortText ShortText ShortText
_Base16 (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
pattern Base16Lenient :: ShortText -> ShortText
pattern $bBase16Lenient :: ShortText -> ShortText
$mBase16Lenient :: forall r. ShortText -> (ShortText -> r) -> (Void# -> r) -> r
Base16Lenient a <- (view _Base16Lenient -> a) where
Base16Lenient ShortText
a = Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText)
Iso ShortText ShortText ShortText ShortText
_Base16Lenient (Tagged ShortText (Identity ShortText)
-> Tagged ShortText (Identity ShortText))
-> ShortText -> ShortText
forall t b. AReview t b -> b -> t
# ShortText
a
{-# COMPLETE Base16Lenient #-}