{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DeriveDataTypeable #-} module Data.Text1.Text1( Text1(..) , AsText1(..) , HasText1(..) , cons1 , snoc1 , length1 , compareLength1 , _head1 , _tail1 , _last1 , _init1 , maybeText , maybeLazyText , each1 ) where import Control.Applicative(Applicative((<*>), pure), (*>)) import Control.Category(Category(id, (.))) import Control.Lens ( uncons, cons, from, iso, seconding, prism', (#), over, Index, IxValue, Ixed(..), Cons(..), Snoc(..), Each(..), Reversing(..), Plated(..), Field1(_1), Field2(_2), _Just, Iso', Lens', Prism', Traversal1' ) import Data.Binary(Binary(put, get)) import Data.Char(Char) import Data.Data(Data) import Data.Eq(Eq((==))) import Data.Functor(Functor(fmap), (<$>)) import Data.Functor.Apply ( Apply((<.>)) ) import Data.Int(Int) import Data.List.NonEmpty(NonEmpty((:|))) import Data.Maybe(Maybe(Just, Nothing)) import Data.Ord(Ord, Ordering) import Data.Semigroup(Semigroup((<>))) import Data.String(String) import Data.Text(Text) import qualified Data.Text as Text(cons, snoc, uncons, unsnoc, null, empty, length, compareLength, append, unpack, pack) import qualified Data.Text.Lazy as LazyText(Text, toStrict, fromStrict) import Data.Text.Lens ( IsText(builder), text ) import Data.Text1.AsSingle ( AsSingle(..) ) import Data.Text1.IsText1 ( IsText1(packed1, builder1) ) import Data.Tuple(uncurry) import Data.Typeable(Typeable) import GHC.Show(Show(show)) import Prelude((-), (+)) data Text1 = Text1 !Char !Text deriving (Text1 -> Text1 -> Bool (Text1 -> Text1 -> Bool) -> (Text1 -> Text1 -> Bool) -> Eq Text1 forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Text1 -> Text1 -> Bool $c/= :: Text1 -> Text1 -> Bool == :: Text1 -> Text1 -> Bool $c== :: Text1 -> Text1 -> Bool Eq, Eq Text1 Eq Text1 -> (Text1 -> Text1 -> Ordering) -> (Text1 -> Text1 -> Bool) -> (Text1 -> Text1 -> Bool) -> (Text1 -> Text1 -> Bool) -> (Text1 -> Text1 -> Bool) -> (Text1 -> Text1 -> Text1) -> (Text1 -> Text1 -> Text1) -> Ord Text1 Text1 -> Text1 -> Bool Text1 -> Text1 -> Ordering Text1 -> Text1 -> Text1 forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Text1 -> Text1 -> Text1 $cmin :: Text1 -> Text1 -> Text1 max :: Text1 -> Text1 -> Text1 $cmax :: Text1 -> Text1 -> Text1 >= :: Text1 -> Text1 -> Bool $c>= :: Text1 -> Text1 -> Bool > :: Text1 -> Text1 -> Bool $c> :: Text1 -> Text1 -> Bool <= :: Text1 -> Text1 -> Bool $c<= :: Text1 -> Text1 -> Bool < :: Text1 -> Text1 -> Bool $c< :: Text1 -> Text1 -> Bool compare :: Text1 -> Text1 -> Ordering $ccompare :: Text1 -> Text1 -> Ordering $cp1Ord :: Eq Text1 Ord, Typeable Text1 DataType Constr Typeable Text1 -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Text1 -> c Text1) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Text1) -> (Text1 -> Constr) -> (Text1 -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Text1)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Text1)) -> ((forall b. Data b => b -> b) -> Text1 -> Text1) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r) -> (forall u. (forall d. Data d => d -> u) -> Text1 -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> Text1 -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Text1 -> m Text1) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Text1 -> m Text1) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Text1 -> m Text1) -> Data Text1 Text1 -> DataType Text1 -> Constr (forall b. Data b => b -> b) -> Text1 -> Text1 (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Text1 -> c Text1 (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Text1 forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Text1 -> u forall u. (forall d. Data d => d -> u) -> Text1 -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Text1 -> m Text1 forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Text1 -> m Text1 forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Text1 forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Text1 -> c Text1 forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Text1) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Text1) $cText1 :: Constr $tText1 :: DataType gmapMo :: (forall d. Data d => d -> m d) -> Text1 -> m Text1 $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Text1 -> m Text1 gmapMp :: (forall d. Data d => d -> m d) -> Text1 -> m Text1 $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Text1 -> m Text1 gmapM :: (forall d. Data d => d -> m d) -> Text1 -> m Text1 $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Text1 -> m Text1 gmapQi :: Int -> (forall d. Data d => d -> u) -> Text1 -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Text1 -> u gmapQ :: (forall d. Data d => d -> u) -> Text1 -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Text1 -> [u] gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Text1 -> r gmapT :: (forall b. Data b => b -> b) -> Text1 -> Text1 $cgmapT :: (forall b. Data b => b -> b) -> Text1 -> Text1 dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Text1) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Text1) dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Text1) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Text1) dataTypeOf :: Text1 -> DataType $cdataTypeOf :: Text1 -> DataType toConstr :: Text1 -> Constr $ctoConstr :: Text1 -> Constr gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Text1 $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Text1 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Text1 -> c Text1 $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Text1 -> c Text1 $cp1Data :: Typeable Text1 Data, Typeable) class AsText1 a where _Text1 :: Prism' a Text1 instance AsText1 Text1 where _Text1 :: p Text1 (f Text1) -> p Text1 (f Text1) _Text1 = p Text1 (f Text1) -> p Text1 (f Text1) forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a id instance AsText1 (NonEmpty Char) where _Text1 :: p Text1 (f Text1) -> p (NonEmpty Char) (f (NonEmpty Char)) _Text1 = p Text1 (f Text1) -> p (NonEmpty Char) (f (NonEmpty Char)) forall t. IsText1 t => Iso' (NonEmpty Char) t packed1 instance AsText1 String where _Text1 :: p Text1 (f Text1) -> p String (f String) _Text1 = (Text1 -> String) -> (String -> Maybe Text1) -> Prism' String Text1 forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b prism' (\(Text1 Char h Text t) -> Char h Char -> String -> String forall a. a -> [a] -> [a] : Text -> String Text.unpack Text t) (((Char, String) -> Text1) -> Maybe (Char, String) -> Maybe Text1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\(Char h, String t) -> Char -> Text -> Text1 Text1 Char h (String -> Text Text.pack String t)) (Maybe (Char, String) -> Maybe Text1) -> (String -> Maybe (Char, String)) -> String -> Maybe Text1 forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . String -> Maybe (Char, String) forall s a. Cons s s a a => s -> Maybe (a, s) uncons) instance AsText1 Text where _Text1 :: p Text1 (f Text1) -> p Text (f Text) _Text1 = p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text) Iso' Text (Maybe Text1) maybeText (p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text)) -> (p Text1 (f Text1) -> p (Maybe Text1) (f (Maybe Text1))) -> p Text1 (f Text1) -> p Text (f Text) forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . p Text1 (f Text1) -> p (Maybe Text1) (f (Maybe Text1)) forall a b. Prism (Maybe a) (Maybe b) a b _Just instance AsText1 LazyText.Text where _Text1 :: p Text1 (f Text1) -> p Text (f Text) _Text1 = p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text) Iso' Text (Maybe Text1) maybeLazyText (p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text)) -> (p Text1 (f Text1) -> p (Maybe Text1) (f (Maybe Text1))) -> p Text1 (f Text1) -> p Text (f Text) forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . p Text1 (f Text1) -> p (Maybe Text1) (f (Maybe Text1)) forall a b. Prism (Maybe a) (Maybe b) a b _Just class HasText1 a where text1 :: Lens' a Text1 instance HasText1 Text1 where text1 :: (Text1 -> f Text1) -> Text1 -> f Text1 text1 = (Text1 -> f Text1) -> Text1 -> f Text1 forall k (cat :: k -> k -> *) (a :: k). Category cat => cat a a id instance IsText1 Text1 where packed1 :: p Text1 (f Text1) -> p (NonEmpty Char) (f (NonEmpty Char)) packed1 = (NonEmpty Char -> Text1) -> (Text1 -> NonEmpty Char) -> Iso' (NonEmpty Char) Text1 forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso (\(Char h:|String t) -> Char -> Text -> Text1 Text1 Char h (String -> Text Text.pack String t)) (\(Text1 Char h Text t) -> Char h Char -> String -> NonEmpty Char forall a. a -> [a] -> NonEmpty a :| Text -> String Text.unpack Text t) builder1 :: p Text1 (f Text1) -> p (Char, Builder) (f (Char, Builder)) builder1 = AnIso Text1 Text1 (Char, Builder) (Char, Builder) -> Iso' (Char, Builder) Text1 forall s t a b. AnIso s t a b -> Iso b a t s from (Exchange (Char, Builder) (Char, Builder) (Char, Text) (Identity (Char, Text)) -> Exchange (Char, Builder) (Char, Builder) Text1 (Identity Text1) Iso' Text1 (Char, Text) cons1 (Exchange (Char, Builder) (Char, Builder) (Char, Text) (Identity (Char, Text)) -> Exchange (Char, Builder) (Char, Builder) Text1 (Identity Text1)) -> (Exchange (Char, Builder) (Char, Builder) (Char, Builder) (Identity (Char, Builder)) -> Exchange (Char, Builder) (Char, Builder) (Char, Text) (Identity (Char, Text))) -> AnIso Text1 Text1 (Char, Builder) (Char, Builder) forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . AnIso Text Text Builder Builder -> Iso (Char, Text) (Char, Text) (Char, Builder) (Char, Builder) forall (f :: * -> * -> *) (g :: * -> * -> *) s t a b x y. (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f x s) (g y t) (f x a) (g y b) seconding AnIso Text Text Builder Builder forall t. IsText t => Iso' t Builder builder) instance AsSingle Text1 Char where _Single :: p Char (f Char) -> p Text1 (f Text1) _Single = (Char -> Text1) -> (Text1 -> Maybe Char) -> Prism' Text1 Char forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b prism' (Char -> Text -> Text1 `Text1` Text Text.empty) (\(Text1 Char h Text t) -> if Text -> Bool Text.null Text t then Char -> Maybe Char forall a. a -> Maybe a Just Char h else Maybe Char forall a. Maybe a Nothing) instance Show Text1 where show :: Text1 -> String show (Text1 Char h Text t) = Text -> String forall a. Show a => a -> String show (Char -> Text -> Text Text.cons Char h Text t) instance Semigroup Text1 where Text1 Char h1 Text t1 <> :: Text1 -> Text1 -> Text1 <> Text1 t = Char -> Text -> Text1 Text1 Char h1 (Text -> Text -> Text Text.append Text t1 (Tagged Text1 (Identity Text1) -> Tagged Text (Identity Text) forall a. AsText1 a => Prism' a Text1 _Text1 (Tagged Text1 (Identity Text1) -> Tagged Text (Identity Text)) -> Text1 -> Text forall t b. AReview t b -> b -> t # Text1 t)) instance Binary Text1 where put :: Text1 -> Put put (Text1 Char h Text t) = Char -> Put forall t. Binary t => t -> Put put Char h Put -> Put -> Put forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Text -> Put forall t. Binary t => t -> Put put Text t get :: Get Text1 get = Char -> Text -> Text1 Text1 (Char -> Text -> Text1) -> Get Char -> Get (Text -> Text1) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Get Char forall t. Binary t => Get t get Get (Text -> Text1) -> Get Text -> Get Text1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Get Text forall t. Binary t => Get t get instance Each Text1 Text1 Char Char where each :: (Char -> f Char) -> Text1 -> f Text1 each Char -> f Char f (Text1 Char h Text t) = Char -> Text -> Text1 Text1 (Char -> Text -> Text1) -> f Char -> f (Text -> Text1) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Char -> f Char f Char h f (Text -> Text1) -> f Text -> f Text1 forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Char -> f Char) -> Text -> f Text forall t. IsText t => IndexedTraversal' Int t Char text Char -> f Char f Text t instance Reversing Text1 where reversing :: Text1 -> Text1 reversing (Text1 Char h Text t) = case Text -> Maybe (Char, Text) forall s a. Cons s s a a => s -> Maybe (a, s) uncons (Text -> Text forall t. Reversing t => t -> t reversing Text t) of Maybe (Char, Text) Nothing -> Char -> Text -> Text1 Text1 Char h Text Text.empty Just (Char h', Text t') -> Char -> Text -> Text1 Text1 Char h' (Text -> Char -> Text Text.snoc Text t' Char h) instance Cons Text1 Text1 Char Char where _Cons :: p (Char, Text1) (f (Char, Text1)) -> p Text1 (f Text1) _Cons = ((Char, Text1) -> Text1) -> (Text1 -> Maybe (Char, Text1)) -> Prism Text1 Text1 (Char, Text1) (Char, Text1) forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b prism' (\(Char h, Text1 Char h' Text t) -> Char -> Text -> Text1 Text1 Char h (Char -> Text -> Text Text.cons Char h' Text t)) (\(Text1 Char h Text t) -> ((Char, Text) -> (Char, Text1)) -> Maybe (Char, Text) -> Maybe (Char, Text1) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\(Char, Text) r' -> (Char h, (Char -> Text -> Text1) -> (Char, Text) -> Text1 forall a b c. (a -> b -> c) -> (a, b) -> c uncurry Char -> Text -> Text1 Text1 (Char, Text) r')) (Text -> Maybe (Char, Text) Text.uncons Text t)) instance Snoc Text1 Text1 Char Char where _Snoc :: p (Text1, Char) (f (Text1, Char)) -> p Text1 (f Text1) _Snoc = ((Text1, Char) -> Text1) -> (Text1 -> Maybe (Text1, Char)) -> Prism Text1 Text1 (Text1, Char) (Text1, Char) forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b prism' (\(Text1 Char h Text t, Char l) -> Char -> Text -> Text1 Text1 Char h (Text -> Char -> Text Text.snoc Text t Char l)) (\(Text1 Char h Text t) -> ((Text, Char) -> (Text1, Char)) -> Maybe (Text, Char) -> Maybe (Text1, Char) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (ASetter (Text, Char) (Text1, Char) Text Text1 -> (Text -> Text1) -> (Text, Char) -> (Text1, Char) forall s t a b. ASetter s t a b -> (a -> b) -> s -> t over ASetter (Text, Char) (Text1, Char) Text Text1 forall s t a b. Field1 s t a b => Lens s t a b _1 (Char -> Text -> Text1 Text1 Char h)) (Text -> Maybe (Text, Char) Text.unsnoc Text t)) type instance Index Text1 = Int type instance IxValue Text1 = Char instance Ixed Text1 where ix :: Index Text1 -> Traversal' Text1 (IxValue Text1) ix Index Text1 n IxValue Text1 -> f (IxValue Text1) f (Text1 Char h Text t) = if Int Index Text1 n Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == Int 0 then (Char -> Text1) -> f Char -> f Text1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Char -> Text -> Text1 `Text1` Text t) (IxValue Text1 -> f (IxValue Text1) f Char IxValue Text1 h) else (Text -> Text1) -> f Text -> f Text1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Char -> Text -> Text1 Text1 Char h) (Index Text -> (IxValue Text -> f (IxValue Text)) -> Text -> f Text forall m. Ixed m => Index m -> Traversal' m (IxValue m) ix (Int Index Text1 n Int -> Int -> Int forall a. Num a => a -> a -> a - Int 1) IxValue Text -> f (IxValue Text) IxValue Text1 -> f (IxValue Text1) f Text t) instance Plated Text1 where plate :: (Text1 -> f Text1) -> Text1 -> f Text1 plate Text1 -> f Text1 f (Text1 Char h Text t) = case Text -> Maybe (Char, Text) Text.uncons Text t of Maybe (Char, Text) Nothing -> Text1 -> f Text1 forall (f :: * -> *) a. Applicative f => a -> f a pure (Char -> Text -> Text1 Text1 Char h Text Text.empty) Just (Char h', Text t') -> Char -> Text1 -> Text1 forall s a. Cons s s a a => a -> s -> s cons Char h (Text1 -> Text1) -> f Text1 -> f Text1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Text1 -> f Text1 f (Char -> Text -> Text1 Text1 Char h' Text t') cons1 :: Iso' Text1 (Char, Text) cons1 :: p (Char, Text) (f (Char, Text)) -> p Text1 (f Text1) cons1 = (Text1 -> (Char, Text)) -> ((Char, Text) -> Text1) -> Iso' Text1 (Char, Text) forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso (\(Text1 Char h Text t) -> (Char h, Text t)) ((Char -> Text -> Text1) -> (Char, Text) -> Text1 forall a b c. (a -> b -> c) -> (a, b) -> c uncurry Char -> Text -> Text1 Text1) snoc1 :: Iso' Text1 (Text, Char) snoc1 :: p (Text, Char) (f (Text, Char)) -> p Text1 (f Text1) snoc1 = (Text1 -> (Text, Char)) -> ((Text, Char) -> Text1) -> Iso Text1 Text1 (Text, Char) (Text, Char) forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso (\(Text1 Char h Text t) -> case Text -> Maybe (Text, Char) Text.unsnoc Text t of Maybe (Text, Char) Nothing -> (Text Text.empty, Char h) Just (Text i, Char l) -> (Char -> Text -> Text Text.cons Char h Text i, Char l)) (\(Text i, Char l) -> case Text -> Maybe (Char, Text) Text.uncons Text i of Maybe (Char, Text) Nothing -> Char -> Text -> Text1 Text1 Char l Text Text.empty Just (Char h, Text t) -> Char -> Text -> Text1 Text1 Char h (Text -> Char -> Text Text.snoc Text t Char l) ) length1 :: Text1 -> Int length1 :: Text1 -> Int length1 (Text1 Char _ Text t) = Int 1 Int -> Int -> Int forall a. Num a => a -> a -> a + Text -> Int Text.length Text t compareLength1 :: Text1 -> Int -> Ordering compareLength1 :: Text1 -> Int -> Ordering compareLength1 (Text1 Char _ Text t) Int n = Text -> Int -> Ordering Text.compareLength Text t (Int n Int -> Int -> Int forall a. Num a => a -> a -> a - Int 1) _head1 :: Lens' Text1 Char _head1 :: (Char -> f Char) -> Text1 -> f Text1 _head1 = ((Char, Text) -> f (Char, Text)) -> Text1 -> f Text1 Iso' Text1 (Char, Text) cons1 (((Char, Text) -> f (Char, Text)) -> Text1 -> f Text1) -> ((Char -> f Char) -> (Char, Text) -> f (Char, Text)) -> (Char -> f Char) -> Text1 -> f Text1 forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (Char -> f Char) -> (Char, Text) -> f (Char, Text) forall s t a b. Field1 s t a b => Lens s t a b _1 _tail1 :: Lens' Text1 Text _tail1 :: (Text -> f Text) -> Text1 -> f Text1 _tail1 = ((Char, Text) -> f (Char, Text)) -> Text1 -> f Text1 Iso' Text1 (Char, Text) cons1 (((Char, Text) -> f (Char, Text)) -> Text1 -> f Text1) -> ((Text -> f Text) -> (Char, Text) -> f (Char, Text)) -> (Text -> f Text) -> Text1 -> f Text1 forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (Text -> f Text) -> (Char, Text) -> f (Char, Text) forall s t a b. Field2 s t a b => Lens s t a b _2 _last1 :: Lens' Text1 Char _last1 :: (Char -> f Char) -> Text1 -> f Text1 _last1 = ((Text, Char) -> f (Text, Char)) -> Text1 -> f Text1 Iso Text1 Text1 (Text, Char) (Text, Char) snoc1 (((Text, Char) -> f (Text, Char)) -> Text1 -> f Text1) -> ((Char -> f Char) -> (Text, Char) -> f (Text, Char)) -> (Char -> f Char) -> Text1 -> f Text1 forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (Char -> f Char) -> (Text, Char) -> f (Text, Char) forall s t a b. Field2 s t a b => Lens s t a b _2 _init1 :: Lens' Text1 Text _init1 :: (Text -> f Text) -> Text1 -> f Text1 _init1 = ((Text, Char) -> f (Text, Char)) -> Text1 -> f Text1 Iso Text1 Text1 (Text, Char) (Text, Char) snoc1 (((Text, Char) -> f (Text, Char)) -> Text1 -> f Text1) -> ((Text -> f Text) -> (Text, Char) -> f (Text, Char)) -> (Text -> f Text) -> Text1 -> f Text1 forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (Text -> f Text) -> (Text, Char) -> f (Text, Char) forall s t a b. Field1 s t a b => Lens s t a b _1 maybeText :: Iso' Text (Maybe Text1) maybeText :: p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text) maybeText = (Text -> Maybe Text1) -> (Maybe Text1 -> Text) -> Iso' Text (Maybe Text1) forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso (((Char, Text) -> Text1) -> Maybe (Char, Text) -> Maybe Text1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Char -> Text -> Text1) -> (Char, Text) -> Text1 forall a b c. (a -> b -> c) -> (a, b) -> c uncurry Char -> Text -> Text1 Text1) (Maybe (Char, Text) -> Maybe Text1) -> (Text -> Maybe (Char, Text)) -> Text -> Maybe Text1 forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Text -> Maybe (Char, Text) Text.uncons) (\case Maybe Text1 Nothing -> Text Text.empty Just (Text1 Char h Text t) -> Char -> Text -> Text Text.cons Char h Text t) maybeLazyText :: Iso' LazyText.Text (Maybe Text1) maybeLazyText :: p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text) maybeLazyText = (Text -> Text) -> (Text -> Text) -> Iso Text Text Text Text forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Text -> Text LazyText.toStrict Text -> Text LazyText.fromStrict (p Text (f Text) -> p Text (f Text)) -> (p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text)) -> p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text) forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . p (Maybe Text1) (f (Maybe Text1)) -> p Text (f Text) Iso' Text (Maybe Text1) maybeText each1 :: Traversal1' Text1 Char each1 :: (Char -> f Char) -> Text1 -> f Text1 each1 Char -> f Char f (Text1 Char h Text t) = case Text -> Maybe (Char, Text) Text.uncons Text t of Maybe (Char, Text) Nothing -> (Char -> Text -> Text1 `Text1` Text Text.empty) (Char -> Text1) -> f Char -> f Text1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Char -> f Char f Char h Just (Char h', Text t') -> Char -> Text1 -> Text1 forall s a. Cons s s a a => a -> s -> s cons (Char -> Text1 -> Text1) -> f Char -> f (Text1 -> Text1) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Char -> f Char f Char h f (Text1 -> Text1) -> f Text1 -> f Text1 forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b <.> (Char -> f Char) -> Text1 -> f Text1 Traversal1' Text1 Char each1 Char -> f Char f (Char -> Text -> Text1 Text1 Char h' Text t')