-- |
-- Module: Data.Text.Optics
-- Description: Optics for working with strict or lazy 'Text'.
--
-- This module provides 'Iso's for converting strict or lazy 'Text' to or from a
-- 'String' or 'Builder', and an 'IxTraversal' for traversing the individual
-- characters of a 'Text'.
--
-- The same combinators support both strict and lazy text using the 'IsText'
-- typeclass.  You can import "Data.Text.Strict.Optics" or
-- "Data.Text.Lazy.Optics" instead if you prefer monomorphic versions.
--
module Data.Text.Optics
  ( IsText(..)
  , unpacked
  , _Text
  , pattern Text
  ) where

import qualified Data.Text as Strict
import qualified Data.Text.Lazy as Lazy
import qualified Data.Text.Lazy.Builder as B

import Optics.Core
import qualified Data.Text.Lazy.Optics as Lazy
import qualified Data.Text.Strict.Optics as Strict

-- | Traversals for strict or lazy 'Text'
class IsText t where
  -- | This isomorphism can be used to 'pack' (or 'unpack') strict or lazy
  -- 'Text'.
  --
  -- @
  -- 'pack' x ≡ x 'Optics.Operators.^.' 'packed'
  -- 'unpack' x ≡ x 'Optics.Operators.^.' 're' 'packed'
  -- 'packed' ≡ 're' 'unpacked'
  -- @
  packed :: Iso' String t

  -- | Convert between strict or lazy 'Text' and a 'Builder'.
  --
  -- @
  -- 'fromText' x ≡ x 'Optics.Operators.^.' 'builder'
  -- @
  builder :: Iso' t B.Builder

  -- | Traverse the individual characters in strict or lazy 'Text'.
  --
  -- @
  -- 'text' = 'unpacked' . 'traversed'
  -- @
  text :: IxTraversal' Int t Char
  text = Iso' t String
forall t. IsText t => Iso' t String
unpacked Iso' t String
-> Optic A_Traversal (WithIx Int) String String Char Char
-> IxTraversal' Int t Char
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
       b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Traversal (WithIx Int) String String Char Char
forall i (f :: * -> *) a b.
TraversableWithIndex i f =>
IxTraversal i (f a) (f b) a b
itraversed
  {-# INLINE text #-}

instance IsText String where
  packed :: Iso' String String
packed  = (String -> String) -> (String -> String) -> Iso' String String
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso String -> String
forall a. a -> a
id String -> String
forall a. a -> a
id
  text :: Optic A_Traversal (WithIx Int) String String Char Char
text    = Optic A_Traversal (WithIx Int) String String Char Char
forall i (f :: * -> *) a b.
TraversableWithIndex i f =>
IxTraversal i (f a) (f b) a b
itraversed
  builder :: Iso' String Builder
builder = Iso' String Text
Lazy.packed Iso' String Text
-> Optic An_Iso NoIx Text Text Builder Builder
-> Iso' String Builder
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
       b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic An_Iso NoIx Text Text Builder Builder
forall t. IsText t => Iso' t Builder
builder
  {-# INLINE packed #-}
  {-# INLINE text #-}
  {-# INLINE builder #-}

-- | This isomorphism can be used to 'unpack' (or 'pack') both strict or lazy
-- 'Text'.
--
-- @
-- 'unpack' x ≡ x 'Optics.Operators.^.' 'unpacked'
-- 'pack' x ≡ x 'Optics.Operators.^.' 're' 'unpacked'
-- @
--
-- This 'Iso' is provided for notational convenience rather than out of great
-- need, since
--
-- @
-- 'unpacked' ≡ 're' 'packed'
-- @
--
unpacked :: IsText t => Iso' t String
unpacked :: Iso' t String
unpacked = Optic An_Iso NoIx String String t t
-> Optic (ReversedOptic An_Iso) NoIx t t String String
forall k (is :: IxList) s t a b.
(ReversibleOptic k, AcceptsEmptyIndices "re" is) =>
Optic k is s t a b -> Optic (ReversedOptic k) is b a t s
re Optic An_Iso NoIx String String t t
forall t. IsText t => Iso' String t
packed
{-# INLINE unpacked #-}

-- | This is an alias for 'unpacked' that makes it clearer how to use it with
-- @('Optics.Operators.#')@.
--
-- @
-- '_Text' = 're' 'packed'
-- @
--
-- >>> _Text # "hello" :: Strict.Text
-- "hello"
_Text :: IsText t => Iso' t String
_Text :: Iso' t String
_Text = Optic An_Iso NoIx String String t t
-> Optic (ReversedOptic An_Iso) NoIx t t String String
forall k (is :: IxList) s t a b.
(ReversibleOptic k, AcceptsEmptyIndices "re" is) =>
Optic k is s t a b -> Optic (ReversedOptic k) is b a t s
re Optic An_Iso NoIx String String t t
forall t. IsText t => Iso' String t
packed
{-# INLINE _Text #-}

pattern Text :: IsText t => String -> t
pattern $bText :: String -> t
$mText :: forall r t. IsText t => t -> (String -> r) -> (Void# -> r) -> r
Text a <- (view _Text -> a) where
  Text String
a = Optic' An_Iso NoIx t String -> String -> t
forall k (is :: IxList) t b.
Is k A_Review =>
Optic' k is t b -> b -> t
review Optic' An_Iso NoIx t String
forall t. IsText t => Iso' t String
_Text String
a

instance IsText Strict.Text where
  packed :: Iso' String Text
packed  = Iso' String Text
Strict.packed
  builder :: Iso' Text Builder
builder = Iso' Text Builder
Strict.builder
  text :: IxTraversal' Int Text Char
text    = IxTraversal' Int Text Char
Strict.text
  {-# INLINE packed #-}
  {-# INLINE builder #-}
  {-# INLINE text #-}

instance IsText Lazy.Text where
  packed :: Iso' String Text
packed  = Iso' String Text
Lazy.packed
  builder :: Optic An_Iso NoIx Text Text Builder Builder
builder = Optic An_Iso NoIx Text Text Builder Builder
Lazy.builder
  text :: IxTraversal' Int Text Char
text    = IxTraversal' Int Text Char
Lazy.text
  {-# INLINE packed #-}
  {-# INLINE builder #-}
  {-# INLINE text #-}