{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Text.Strict.Lens
( packed, unpacked
, builder
, text
, utf8
, _Text
, pattern Text
) where
import Control.Lens.Type
import Control.Lens.Getter
import Control.Lens.Fold
import Control.Lens.Iso
import Control.Lens.Prism
import Control.Lens.Review
import Control.Lens.Setter
import Control.Lens.Traversal
import Data.ByteString (ByteString)
import Data.Monoid
import qualified Data.Text as Strict
import Data.Text (Text)
import Data.Text.Encoding
import Data.Text.Lazy (toStrict)
import qualified Data.Text.Lazy.Builder as Builder
import Data.Text.Lazy.Builder (Builder)
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 = (Text -> String) -> (String -> Text) -> Iso' Text String
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Text -> String
Strict.unpack String -> Text
Strict.pack
{-# INLINE unpacked #-}
_Text :: Iso' Text String
_Text :: Iso' Text String
_Text = p String (f String) -> p Text (f Text)
Iso' Text String
unpacked
{-# INLINE _Text #-}
builder :: Iso' Text 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
Builder.fromText (LazyText -> Text
toStrict (LazyText -> Text) -> (Builder -> LazyText) -> Builder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> LazyText
Builder.toLazyText)
{-# INLINE builder #-}
text :: IndexedTraversal' Int Text Char
text :: IndexedTraversal' Int Text Char
text = (String -> f String) -> Text -> f Text
Iso' Text String
unpacked ((String -> f String) -> Text -> f Text)
-> (p Char (f Char) -> String -> f String)
-> p Char (f Char)
-> Text
-> f Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. p Char (f Char) -> String -> f String
forall (f :: * -> *) a b.
Traversable f =>
IndexedTraversal Int (f a) (f b) a b
IndexedTraversal Int String String Char Char
traversed
{-# INLINE [0] text #-}
{-# RULES
"strict text -> map" text = sets Strict.map :: ASetter' Text Char;
"strict text -> imap" text = isets imapStrict :: AnIndexedSetter' Int Text Char;
"strict text -> foldr" text = foldring Strict.foldr :: Getting (Endo r) Text Char;
"strict text -> ifoldr" text = ifoldring ifoldrStrict :: IndexedGetting Int (Endo r) Text Char;
#-}
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)
forall a b. a -> b -> b
`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 #-}
ifoldrStrict :: (Int -> Char -> a -> a) -> a -> Text -> a
ifoldrStrict :: forall a. (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
forall a b. a -> b -> b
`seq` Int -> Char -> a -> a
f Int
i Char
x (Int -> a
g (Int
iInt -> 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 #-}
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
encodeUtf8 (Getting (First Text) (Either UnicodeException Text) Text
-> Either UnicodeException Text -> Maybe Text
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First Text) (Either UnicodeException Text) Text
forall c a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Either c a) (f (Either c b))
_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
decodeUtf8')
{-# INLINE utf8 #-}
pattern Text :: String -> Text
pattern $mText :: forall {r}. Text -> (String -> r) -> ((# #) -> r) -> r
$bText :: String -> Text
Text a <- (view _Text -> a) where
Text String
a = AReview Text String -> String -> Text
forall b (m :: * -> *) t. MonadReader b m => AReview t b -> m t
review AReview Text String
Iso' Text String
_Text String
a