{-# OPTIONS_GHC -Wall #-} {-# LANGUAGE FlexibleInstances #-} module Data.Stringz.Text where import Control.Lens import qualified Data.ByteString.Char8 as ByteStringChar8 import qualified Data.ByteString.Lazy.Char8 as ByteStringLazyChar8 import qualified Data.Text as Text import qualified Data.Text.Lazy as LazyText class HasText a where text :: Lens' a Text.Text instance HasText [Char] where text :: Lens' [Char] Text text = ([Char] -> Text) -> (Text -> [Char]) -> Iso [Char] [Char] Text Text forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso [Char] -> Text Text.pack Text -> [Char] Text.unpack instance HasText Text.Text where text :: Lens' Text Text text = (Text -> f Text) -> Text -> f Text forall a. a -> a id instance HasText LazyText.Text where text :: Lens' Text Text text = (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 instance HasText ByteStringChar8.ByteString where text :: Lens' ByteString Text text = (ByteString -> [Char]) -> ([Char] -> ByteString) -> Iso ByteString ByteString [Char] [Char] forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso ByteString -> [Char] ByteStringChar8.unpack [Char] -> ByteString ByteStringChar8.pack (([Char] -> f [Char]) -> ByteString -> f ByteString) -> ((Text -> f Text) -> [Char] -> f [Char]) -> (Text -> f Text) -> ByteString -> f ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> f Text) -> [Char] -> f [Char] forall a. HasText a => Lens' a Text Lens' [Char] Text text instance HasText ByteStringLazyChar8.ByteString where text :: Lens' ByteString Text text = (ByteString -> [Char]) -> ([Char] -> ByteString) -> Iso ByteString ByteString [Char] [Char] forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso ByteString -> [Char] ByteStringLazyChar8.unpack [Char] -> ByteString ByteStringLazyChar8.pack (([Char] -> f [Char]) -> ByteString -> f ByteString) -> ((Text -> f Text) -> [Char] -> f [Char]) -> (Text -> f Text) -> ByteString -> f ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> f Text) -> [Char] -> f [Char] forall a. HasText a => Lens' a Text Lens' [Char] Text text instance HasText a => HasText (Identity a) where text :: Lens' (Identity a) Text text = (Identity a -> a) -> (a -> Identity a) -> Iso (Identity a) (Identity a) a a forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Identity a -> a forall a. Identity a -> a runIdentity a -> Identity a forall a. a -> Identity a Identity ((a -> f a) -> Identity a -> f (Identity a)) -> ((Text -> f Text) -> a -> f a) -> (Text -> f Text) -> Identity a -> f (Identity a) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> f Text) -> a -> f a forall a. HasText a => Lens' a Text Lens' a Text text instance HasText a => HasText (Const a b) where text :: Lens' (Const a b) Text text = (Const a b -> a) -> (a -> Const a b) -> Iso (Const a b) (Const a b) a a forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Const a b -> a forall {k} a (b :: k). Const a b -> a getConst a -> Const a b forall {k} a (b :: k). a -> Const a b Const ((a -> f a) -> Const a b -> f (Const a b)) -> ((Text -> f Text) -> a -> f a) -> (Text -> f Text) -> Const a b -> f (Const a b) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> f Text) -> a -> f a forall a. HasText a => Lens' a Text Lens' a Text text class HasLazyText a where lazyText :: Lens' a LazyText.Text instance HasLazyText [Char] where lazyText :: Lens' [Char] Text lazyText = ([Char] -> Text) -> (Text -> [Char]) -> Iso [Char] [Char] Text Text forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso [Char] -> Text LazyText.pack Text -> [Char] LazyText.unpack instance HasLazyText Text.Text where lazyText :: Lens' Text Text lazyText = (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.fromStrict Text -> Text LazyText.toStrict instance HasLazyText LazyText.Text where lazyText :: Lens' Text Text lazyText = (Text -> f Text) -> Text -> f Text forall a. a -> a id instance HasLazyText ByteStringChar8.ByteString where lazyText :: Lens' ByteString Text lazyText = (ByteString -> [Char]) -> ([Char] -> ByteString) -> Iso ByteString ByteString [Char] [Char] forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso ByteString -> [Char] ByteStringChar8.unpack [Char] -> ByteString ByteStringChar8.pack (([Char] -> f [Char]) -> ByteString -> f ByteString) -> ((Text -> f Text) -> [Char] -> f [Char]) -> (Text -> f Text) -> ByteString -> f ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> f Text) -> [Char] -> f [Char] forall a. HasLazyText a => Lens' a Text Lens' [Char] Text lazyText instance HasLazyText ByteStringLazyChar8.ByteString where lazyText :: Lens' ByteString Text lazyText = (ByteString -> [Char]) -> ([Char] -> ByteString) -> Iso ByteString ByteString [Char] [Char] forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso ByteString -> [Char] ByteStringLazyChar8.unpack [Char] -> ByteString ByteStringLazyChar8.pack (([Char] -> f [Char]) -> ByteString -> f ByteString) -> ((Text -> f Text) -> [Char] -> f [Char]) -> (Text -> f Text) -> ByteString -> f ByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> f Text) -> [Char] -> f [Char] forall a. HasLazyText a => Lens' a Text Lens' [Char] Text lazyText instance HasLazyText a => HasLazyText (Identity a) where lazyText :: Lens' (Identity a) Text lazyText = (Identity a -> a) -> (a -> Identity a) -> Iso (Identity a) (Identity a) a a forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Identity a -> a forall a. Identity a -> a runIdentity a -> Identity a forall a. a -> Identity a Identity ((a -> f a) -> Identity a -> f (Identity a)) -> ((Text -> f Text) -> a -> f a) -> (Text -> f Text) -> Identity a -> f (Identity a) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> f Text) -> a -> f a forall a. HasLazyText a => Lens' a Text Lens' a Text lazyText instance HasLazyText a => HasLazyText (Const a b) where lazyText :: Lens' (Const a b) Text lazyText = (Const a b -> a) -> (a -> Const a b) -> Iso (Const a b) (Const a b) a a forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Const a b -> a forall {k} a (b :: k). Const a b -> a getConst a -> Const a b forall {k} a (b :: k). a -> Const a b Const ((a -> f a) -> Const a b -> f (Const a b)) -> ((Text -> f Text) -> a -> f a) -> (Text -> f Text) -> Const a b -> f (Const a b) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Text -> f Text) -> a -> f a forall a. HasLazyText a => Lens' a Text Lens' a Text lazyText class AsText a where _Text :: Prism' a Text.Text instance AsText [Char] where _Text :: Prism' [Char] Text _Text = ([Char] -> Text) -> (Text -> [Char]) -> Iso [Char] [Char] Text Text forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso [Char] -> Text Text.pack Text -> [Char] Text.unpack instance AsText Text.Text where _Text :: Prism' Text Text _Text = p Text (f Text) -> p Text (f Text) forall a. a -> a id instance AsText LazyText.Text where _Text :: Prism' Text Text _Text = (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 instance AsText ByteStringChar8.ByteString where _Text :: Prism' ByteString Text _Text = (ByteString -> [Char]) -> ([Char] -> ByteString) -> Iso ByteString ByteString [Char] [Char] forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso ByteString -> [Char] ByteStringChar8.unpack [Char] -> ByteString ByteStringChar8.pack (p [Char] (f [Char]) -> p ByteString (f ByteString)) -> (p Text (f Text) -> p [Char] (f [Char])) -> p Text (f Text) -> p ByteString (f ByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . p Text (f Text) -> p [Char] (f [Char]) forall a. AsText a => Prism' a Text Prism' [Char] Text _Text instance AsText ByteStringLazyChar8.ByteString where _Text :: Prism' ByteString Text _Text = (ByteString -> [Char]) -> ([Char] -> ByteString) -> Iso ByteString ByteString [Char] [Char] forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso ByteString -> [Char] ByteStringLazyChar8.unpack [Char] -> ByteString ByteStringLazyChar8.pack (p [Char] (f [Char]) -> p ByteString (f ByteString)) -> (p Text (f Text) -> p [Char] (f [Char])) -> p Text (f Text) -> p ByteString (f ByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . p Text (f Text) -> p [Char] (f [Char]) forall a. AsText a => Prism' a Text Prism' [Char] Text _Text instance AsText a => AsText (Identity a) where _Text :: Prism' (Identity a) Text _Text = (Identity a -> a) -> (a -> Identity a) -> Iso (Identity a) (Identity a) a a forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Identity a -> a forall a. Identity a -> a runIdentity a -> Identity a forall a. a -> Identity a Identity (p a (f a) -> p (Identity a) (f (Identity a))) -> (p Text (f Text) -> p a (f a)) -> p Text (f Text) -> p (Identity a) (f (Identity a)) forall b c a. (b -> c) -> (a -> b) -> a -> c . p Text (f Text) -> p a (f a) forall a. AsText a => Prism' a Text Prism' a Text _Text instance AsText a => AsText (Const a b) where _Text :: Prism' (Const a b) Text _Text = (Const a b -> a) -> (a -> Const a b) -> Iso (Const a b) (Const a b) a a forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Const a b -> a forall {k} a (b :: k). Const a b -> a getConst a -> Const a b forall {k} a (b :: k). a -> Const a b Const (p a (f a) -> p (Const a b) (f (Const a b))) -> (p Text (f Text) -> p a (f a)) -> p Text (f Text) -> p (Const a b) (f (Const a b)) forall b c a. (b -> c) -> (a -> b) -> a -> c . p Text (f Text) -> p a (f a) forall a. AsText a => Prism' a Text Prism' a Text _Text class AsLazyText a where _LazyText :: Prism' a LazyText.Text instance AsLazyText [Char] where _LazyText :: Prism' [Char] Text _LazyText = ([Char] -> Text) -> (Text -> [Char]) -> Iso [Char] [Char] Text Text forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso [Char] -> Text LazyText.pack Text -> [Char] LazyText.unpack instance AsLazyText Text.Text where _LazyText :: Prism' Text Text _LazyText = (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.fromStrict Text -> Text LazyText.toStrict instance AsLazyText LazyText.Text where _LazyText :: Prism' Text Text _LazyText = p Text (f Text) -> p Text (f Text) forall a. a -> a id instance AsLazyText ByteStringChar8.ByteString where _LazyText :: Prism' ByteString Text _LazyText = (ByteString -> [Char]) -> ([Char] -> ByteString) -> Iso ByteString ByteString [Char] [Char] forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso ByteString -> [Char] ByteStringChar8.unpack [Char] -> ByteString ByteStringChar8.pack (p [Char] (f [Char]) -> p ByteString (f ByteString)) -> (p Text (f Text) -> p [Char] (f [Char])) -> p Text (f Text) -> p ByteString (f ByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . p Text (f Text) -> p [Char] (f [Char]) forall a. AsLazyText a => Prism' a Text Prism' [Char] Text _LazyText instance AsLazyText ByteStringLazyChar8.ByteString where _LazyText :: Prism' ByteString Text _LazyText = (ByteString -> [Char]) -> ([Char] -> ByteString) -> Iso ByteString ByteString [Char] [Char] forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso ByteString -> [Char] ByteStringLazyChar8.unpack [Char] -> ByteString ByteStringLazyChar8.pack (p [Char] (f [Char]) -> p ByteString (f ByteString)) -> (p Text (f Text) -> p [Char] (f [Char])) -> p Text (f Text) -> p ByteString (f ByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . p Text (f Text) -> p [Char] (f [Char]) forall a. AsLazyText a => Prism' a Text Prism' [Char] Text _LazyText instance AsLazyText a => AsLazyText (Identity a) where _LazyText :: Prism' (Identity a) Text _LazyText = (Identity a -> a) -> (a -> Identity a) -> Iso (Identity a) (Identity a) a a forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Identity a -> a forall a. Identity a -> a runIdentity a -> Identity a forall a. a -> Identity a Identity (p a (f a) -> p (Identity a) (f (Identity a))) -> (p Text (f Text) -> p a (f a)) -> p Text (f Text) -> p (Identity a) (f (Identity a)) forall b c a. (b -> c) -> (a -> b) -> a -> c . p Text (f Text) -> p a (f a) forall a. AsLazyText a => Prism' a Text Prism' a Text _LazyText instance AsLazyText a => AsLazyText (Const a b) where _LazyText :: Prism' (Const a b) Text _LazyText = (Const a b -> a) -> (a -> Const a b) -> Iso (Const a b) (Const a b) a a forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b iso Const a b -> a forall {k} a (b :: k). Const a b -> a getConst a -> Const a b forall {k} a (b :: k). a -> Const a b Const (p a (f a) -> p (Const a b) (f (Const a b))) -> (p Text (f Text) -> p a (f a)) -> p Text (f Text) -> p (Const a b) (f (Const a b)) forall b c a. (b -> c) -> (a -> b) -> a -> c . p Text (f Text) -> p a (f a) forall a. AsLazyText a => Prism' a Text Prism' a Text _LazyText