module Data.Text.Strict.Optics
( packed
, unpacked
, builder
, text
, utf8
, _Text
, pattern Text
) where
import Data.ByteString (ByteString)
import Data.Text (Text)
import qualified Data.Text as Strict
import qualified Data.Text.Encoding as TE
import Data.Text.Lazy (toStrict)
import qualified Data.Text.Lazy.Builder as B
import Data.Profunctor.Indexed
import Optics.Core
import Optics.Internal.Fold
import Optics.Internal.IxFold
import Optics.Internal.IxTraversal
import Optics.Internal.Optic
packed :: Iso' String Text
packed :: Iso' String Text
packed = (String -> Text) -> (Text -> String) -> Iso' String Text
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso String -> Text
Strict.pack Text -> String
Strict.unpack
{-# INLINE packed #-}
unpacked :: Iso' Text String
unpacked :: Iso' Text String
unpacked = (forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ An_Iso p i (Curry NoIx i) Text Text String String)
-> Iso' Text String
forall k (is :: IxList) s t a b.
(forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ k p i (Curry is i) s t a b)
-> Optic k is s t a b
Optic forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic__ p i i Text Text String String
forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ An_Iso p i (Curry NoIx i) Text Text String String
unpacked__
{-# INLINE unpacked #-}
_Text :: Iso' Text String
_Text :: Iso' Text String
_Text = Iso' Text String
unpacked
{-# INLINE _Text #-}
builder :: Iso' Text B.Builder
builder :: Iso' Text Builder
builder = (Text -> Builder) -> (Builder -> Text) -> Iso' Text Builder
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Text -> Builder
B.fromText (Text -> Text
toStrict (Text -> Text) -> (Builder -> Text) -> Builder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
B.toLazyText)
{-# INLINE builder #-}
text :: IxTraversal' Int Text Char
text :: IxTraversal' Int Text Char
text = (forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ A_Traversal p i (Curry (WithIx Int) i) Text Text Char Char)
-> IxTraversal' Int Text Char
forall k (is :: IxList) s t a b.
(forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ k p i (Curry is i) s t a b)
-> Optic k is s t a b
Optic forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ A_Traversal p i (Curry (WithIx Int) i) Text Text Char Char
forall (p :: * -> * -> * -> *) j.
Traversing p =>
Optic__ p j (Int -> j) Text Text Char Char
text__
{-# INLINE text #-}
utf8 :: Prism' ByteString Text
utf8 :: Prism' ByteString Text
utf8 = (Text -> ByteString)
-> (ByteString -> Maybe Text) -> Prism' ByteString Text
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
prism' Text -> ByteString
TE.encodeUtf8 (Optic' A_Prism NoIx (Either UnicodeException Text) Text
-> Either UnicodeException Text -> Maybe Text
forall k (is :: IxList) s a.
Is k An_AffineFold =>
Optic' k is s a -> s -> Maybe a
preview Optic' A_Prism NoIx (Either UnicodeException Text) Text
forall a b c. Prism (Either a b) (Either a c) b c
_Right (Either UnicodeException Text -> Maybe Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
TE.decodeUtf8')
{-# INLINE utf8 #-}
pattern Text :: String -> Text
pattern $bText :: String -> Text
$mText :: forall r. Text -> (String -> r) -> (Void# -> r) -> r
Text a <- (view _Text -> a) where
Text String
a = Iso' Text String -> String -> Text
forall k (is :: IxList) t b.
Is k A_Review =>
Optic' k is t b -> b -> t
review Iso' Text String
_Text String
a
unpacked__ :: Profunctor p => Optic__ p i i Text Text String String
unpacked__ :: Optic__ p i i Text Text String String
unpacked__ = (Text -> String)
-> (String -> Text) -> Optic__ p i i Text Text String String
forall (p :: * -> * -> * -> *) a b c d i.
Profunctor p =>
(a -> b) -> (c -> d) -> p i b c -> p i a d
dimap Text -> String
Strict.unpack String -> Text
Strict.pack
{-# INLINE unpacked__ #-}
text__ :: Traversing p => Optic__ p j (Int -> j) Text Text Char Char
text__ :: Optic__ p j (Int -> j) Text Text Char Char
text__ = Optic__ p (Int -> j) (Int -> j) Text Text String String
forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic__ p i i Text Text String String
unpacked__ Optic__ p (Int -> j) (Int -> j) Text Text String String
-> (p j Char Char -> p (Int -> j) String String)
-> Optic__ p j (Int -> j) Text Text Char Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p j Char Char -> p (Int -> j) String String
forall (p :: * -> * -> * -> *) i (f :: * -> *) j a b.
(Traversing p, TraversableWithIndex i f) =>
Optic__ p j (i -> j) (f a) (f b) a b
itraversed__
{-# INLINE [0] text__ #-}
{-# RULES
"strict text__ -> foldr"
forall (o :: Forget r j Char Char). text__ o = foldring__ Strict.foldr (reForget o)
:: Forget r (Int -> j) Text Text
"strict text__ -> ifoldr"
forall (o :: IxForget r j Char Char). text__ o = ifoldring__ ifoldrStrict o
:: IxForget r (Int -> j) Text Text
"strict text__ -> map"
forall (o :: FunArrow j Char Char). text__ o = roam Strict.map (reFunArrow o)
:: FunArrow (Int -> j) Text Text
"strict text__ -> imap"
forall (o :: IxFunArrow j Char Char). text__ o = iroam imapStrict o
:: IxFunArrow (Int -> j) Text Text
#-}
ifoldrStrict :: (Int -> Char -> a -> a) -> a -> Text -> a
ifoldrStrict :: (Int -> Char -> a -> a) -> a -> Text -> a
ifoldrStrict Int -> Char -> a -> a
f a
z Text
xs =
(Char -> (Int -> a) -> Int -> a) -> (Int -> a) -> Text -> Int -> a
forall a. (Char -> a -> a) -> a -> Text -> a
Strict.foldr (\Char
x Int -> a
g Int
i -> Int
i Int -> a -> a
`seq` Int -> Char -> a -> a
f Int
i Char
x (Int -> a
g (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1))) (a -> Int -> a
forall a b. a -> b -> a
const a
z) Text
xs Int
0
{-# INLINE ifoldrStrict #-}
imapStrict :: (Int -> Char -> Char) -> Text -> Text
imapStrict :: (Int -> Char -> Char) -> Text -> Text
imapStrict Int -> Char -> Char
f = (Int, Text) -> Text
forall a b. (a, b) -> b
snd ((Int, Text) -> Text) -> (Text -> (Int, Text)) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Char -> (Int, Char)) -> Int -> Text -> (Int, Text)
forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
Strict.mapAccumL (\Int
i Char
a -> Int
i Int -> (Int, Char) -> (Int, Char)
`seq` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1, Int -> Char -> Char
f Int
i Char
a)) Int
0
{-# INLINE imapStrict #-}