{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Text.Strict.Lens
-- Copyright   :  (C) 2012-2016 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  experimental
-- Portability :  non-portable
--
----------------------------------------------------------------------------
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)

-- $setup
-- >>> :set -XOverloadedStrings
-- >>> import Control.Lens

-- | This isomorphism can be used to 'pack' (or 'unpack') strict 'Text'.
--
--
-- >>> "hello"^.packed -- :: Text
-- "hello"
--
-- @
-- 'pack' x ≡ x '^.' 'packed'
-- 'unpack' x ≡ x '^.' 'from' 'packed'
-- 'packed' ≡ 'from' 'unpacked'
-- 'packed' ≡ 'iso' 'pack' 'unpack'
-- @
packed :: Iso' String Text
packed :: p Text (f Text) -> p String (f String)
packed = (String -> Text) -> (Text -> String) -> Iso String String Text 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 #-}

-- | This isomorphism can be used to 'unpack' (or 'pack') lazy 'Text'.
--
-- >>> "hello"^.unpacked -- :: String
-- "hello"
--
-- This 'Iso' is provided for notational convenience rather than out of great need, since
--
-- @
-- 'unpacked' ≡ 'from' 'packed'
-- @
--
-- @
-- 'pack' x ≡ x '^.' 'from' 'unpacked'
-- 'unpack' x ≡ x '^.' 'packed'
-- 'unpacked' ≡ 'iso' 'unpack' 'pack'
-- @
unpacked :: Iso' Text String
unpacked :: p String (f String) -> p Text (f Text)
unpacked = (Text -> String) -> (String -> Text) -> Iso Text Text String 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 #-}

-- | This is an alias for 'unpacked' that makes it more obvious how to use it with '#'
--
-- >> _Text # "hello" -- :: Text
-- "hello"
_Text :: Iso' Text String
_Text :: p String (f String) -> p Text (f Text)
_Text = p String (f String) -> p Text (f Text)
Iso Text Text String String
unpacked
{-# INLINE _Text #-}

-- | Convert between strict 'Text' and 'Builder' .
--
-- @
-- 'fromText' x ≡ x '^.' 'builder'
-- 'toStrict' ('toLazyText' x) ≡ x '^.' 'from' 'builder'
-- @
builder :: Iso' Text Builder
builder :: p Builder (f Builder) -> p Text (f Text)
builder = (Text -> Builder)
-> (Builder -> Text) -> Iso Text Text Builder Builder
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Text -> Builder
Builder.fromText (Text -> Text
toStrict (Text -> Text) -> (Builder -> Text) -> Builder -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText)
{-# INLINE builder #-}

-- | Traverse the individual characters in strict 'Text'.
--
-- >>> anyOf text (=='o') "hello"
-- True
--
-- When the type is unambiguous, you can also use the more general 'each'.
--
-- @
-- 'text' ≡ 'unpacked' . 'traversed'
-- 'text' ≡ 'each'
-- @
--
-- Note that when just using this as a 'Setter', @'setting' 'Data.Text.map'@ can
-- be more efficient.
text :: IndexedTraversal' Int Text Char
text :: p Char (f Char) -> Text -> f Text
text = (String -> f String) -> Text -> f Text
Iso Text Text String 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
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)
`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 :: (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
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 #-}

-- | Encode\/Decode a strict 'Text' to\/from strict 'ByteString', via UTF-8.
--
-- >>> utf8 # "☃"
-- "\226\152\131"
utf8 :: Prism' ByteString Text
utf8 :: p Text (f Text) -> p ByteString (f ByteString)
utf8 = (Text -> ByteString)
-> (ByteString -> Maybe Text)
-> Prism ByteString ByteString Text 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. Prism (Either c a) (Either c b) a 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 $bText :: String -> Text
$mText :: forall r. Text -> (String -> r) -> (Void# -> r) -> r
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 Text String String
_Text String
a