{-# LANGUAGE CPP
            ,MultiParamTypeClasses
            ,TypeFamilies
            ,FlexibleInstances #-}

module Data.ListLike.Chars

where

#if !MIN_VERSION_base(4,8,0)
import           Control.Applicative
import           Data.Monoid
#endif
import           Control.DeepSeq
--import           Control.Monad
import           Data.String as String (IsString)
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup (Semigroup(..))
#endif
import qualified Data.Text.Lazy as T
--import qualified Data.Text.Lazy.IO as TI
import qualified Data.Text.Lazy.Builder as Builder
--import           Data.Text.Encoding (decodeUtf8)
import           Data.ListLike.Base as LL
import           Data.ListLike.FoldableLL as LL
import           Data.ListLike.IO
import           Data.ListLike.String as LL
import           Data.ListLike.Text ()
import           GHC.Exts (IsList(..))

data Chars
    = B Builder.Builder
    | T T.Text
    deriving (Int -> Chars -> ShowS
[Chars] -> ShowS
Chars -> String
(Int -> Chars -> ShowS)
-> (Chars -> String) -> ([Chars] -> ShowS) -> Show Chars
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Chars] -> ShowS
$cshowList :: [Chars] -> ShowS
show :: Chars -> String
$cshow :: Chars -> String
showsPrec :: Int -> Chars -> ShowS
$cshowsPrec :: Int -> Chars -> ShowS
Show, Chars -> Chars -> Bool
(Chars -> Chars -> Bool) -> (Chars -> Chars -> Bool) -> Eq Chars
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Chars -> Chars -> Bool
$c/= :: Chars -> Chars -> Bool
== :: Chars -> Chars -> Bool
$c== :: Chars -> Chars -> Bool
Eq, Eq Chars
Eq Chars
-> (Chars -> Chars -> Ordering)
-> (Chars -> Chars -> Bool)
-> (Chars -> Chars -> Bool)
-> (Chars -> Chars -> Bool)
-> (Chars -> Chars -> Bool)
-> (Chars -> Chars -> Chars)
-> (Chars -> Chars -> Chars)
-> Ord Chars
Chars -> Chars -> Bool
Chars -> Chars -> Ordering
Chars -> Chars -> Chars
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 :: Chars -> Chars -> Chars
$cmin :: Chars -> Chars -> Chars
max :: Chars -> Chars -> Chars
$cmax :: Chars -> Chars -> Chars
>= :: Chars -> Chars -> Bool
$c>= :: Chars -> Chars -> Bool
> :: Chars -> Chars -> Bool
$c> :: Chars -> Chars -> Bool
<= :: Chars -> Chars -> Bool
$c<= :: Chars -> Chars -> Bool
< :: Chars -> Chars -> Bool
$c< :: Chars -> Chars -> Bool
compare :: Chars -> Chars -> Ordering
$ccompare :: Chars -> Chars -> Ordering
Ord)

builder :: Chars -> Builder.Builder
builder :: Chars -> Builder
builder (B Builder
x) = Builder
x
builder (T Text
s) = Text -> Builder
Builder.fromLazyText Text
s
{-# INLINE builder #-}

instance Semigroup Chars where
  Chars
a <> :: Chars -> Chars -> Chars
<> Chars
b = Builder -> Chars
B (Builder -> Chars) -> Builder -> Chars
forall a b. (a -> b) -> a -> b
$ Chars -> Builder
builder Chars
a Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Chars -> Builder
builder Chars
b

instance Monoid Chars where
  mempty :: Chars
mempty  = Builder -> Chars
B Builder
forall a. Monoid a => a
mempty
  mappend :: Chars -> Chars -> Chars
mappend = Chars -> Chars -> Chars
forall a. Semigroup a => a -> a -> a
(<>)

instance String.IsString Chars where
  -- Builder already has an IsString instance, do we want to use it?
  -- fromString = B . String.fromString
  -- or do we want the implementation that used to be in the StringLike instance?
  fromString :: String -> Chars
fromString = Builder -> Chars
B (Builder -> Chars) -> (String -> Builder) -> String -> Chars
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Builder
Builder.fromLazyText (Text -> Builder) -> (String -> Text) -> String -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
LL.fromString

instance FoldableLL Chars Char where
    foldl :: forall a. (a -> Char -> a) -> a -> Chars -> a
foldl a -> Char -> a
f a
r0 (B Builder
b) = (a -> Char -> a) -> a -> Text -> a
forall full item a.
FoldableLL full item =>
(a -> item -> a) -> a -> full -> a
LL.foldl a -> Char -> a
f a
r0 (Text -> a) -> (Builder -> Text) -> Builder -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> a) -> Builder -> a
forall a b. (a -> b) -> a -> b
$ Builder
b
    foldl a -> Char -> a
f a
r0 (T Text
s) = (a -> Char -> a) -> a -> Text -> a
forall full item a.
FoldableLL full item =>
(a -> item -> a) -> a -> full -> a
LL.foldl a -> Char -> a
f a
r0 (Text -> a) -> Text -> a
forall a b. (a -> b) -> a -> b
$ Text
s
    foldr :: forall b. (Char -> b -> b) -> b -> Chars -> b
foldr Char -> b -> b
f b
r0 (B Builder
b) = (Char -> b -> b) -> b -> Text -> b
forall full item b.
FoldableLL full item =>
(item -> b -> b) -> b -> full -> b
LL.foldr Char -> b -> b
f b
r0 (Text -> b) -> (Builder -> Text) -> Builder -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> b) -> Builder -> b
forall a b. (a -> b) -> a -> b
$ Builder
b
    foldr Char -> b -> b
f b
r0 (T Text
s) = (Char -> b -> b) -> b -> Text -> b
forall full item b.
FoldableLL full item =>
(item -> b -> b) -> b -> full -> b
LL.foldr Char -> b -> b
f b
r0 (Text -> b) -> Text -> b
forall a b. (a -> b) -> a -> b
$ Text
s
    --
    foldl' :: forall a. (a -> Char -> a) -> a -> Chars -> a
foldl' a -> Char -> a
f a
r0 (B Builder
b) = (a -> Char -> a) -> a -> Text -> a
forall full item a.
FoldableLL full item =>
(a -> item -> a) -> a -> full -> a
LL.foldl' a -> Char -> a
f a
r0 (Text -> a) -> (Builder -> Text) -> Builder -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> a) -> Builder -> a
forall a b. (a -> b) -> a -> b
$ Builder
b
    foldl' a -> Char -> a
f a
r0 (T Text
s) = (a -> Char -> a) -> a -> Text -> a
forall full item a.
FoldableLL full item =>
(a -> item -> a) -> a -> full -> a
LL.foldl' a -> Char -> a
f a
r0 (Text -> a) -> Text -> a
forall a b. (a -> b) -> a -> b
$ Text
s
    foldl1 :: (Char -> Char -> Char) -> Chars -> Char
foldl1 Char -> Char -> Char
f (B Builder
b) = (Char -> Char -> Char) -> Text -> Char
forall full item.
FoldableLL full item =>
(item -> item -> item) -> full -> item
LL.foldl1 Char -> Char -> Char
f (Text -> Char) -> (Builder -> Text) -> Builder -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> Char) -> Builder -> Char
forall a b. (a -> b) -> a -> b
$ Builder
b
    foldl1 Char -> Char -> Char
f (T Text
s) = (Char -> Char -> Char) -> Text -> Char
forall full item.
FoldableLL full item =>
(item -> item -> item) -> full -> item
LL.foldl1 Char -> Char -> Char
f (Text -> Char) -> Text -> Char
forall a b. (a -> b) -> a -> b
$ Text
s
    foldr' :: forall b. (Char -> b -> b) -> b -> Chars -> b
foldr' Char -> b -> b
f b
r0 (B Builder
b) = (Char -> b -> b) -> b -> Text -> b
forall full item b.
FoldableLL full item =>
(item -> b -> b) -> b -> full -> b
LL.foldr' Char -> b -> b
f b
r0 (Text -> b) -> (Builder -> Text) -> Builder -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> b) -> Builder -> b
forall a b. (a -> b) -> a -> b
$ Builder
b
    foldr' Char -> b -> b
f b
r0 (T Text
s) = (Char -> b -> b) -> b -> Text -> b
forall full item b.
FoldableLL full item =>
(item -> b -> b) -> b -> full -> b
LL.foldr' Char -> b -> b
f b
r0 (Text -> b) -> Text -> b
forall a b. (a -> b) -> a -> b
$ Text
s
    foldr1 :: (Char -> Char -> Char) -> Chars -> Char
foldr1 Char -> Char -> Char
f (B Builder
b) = (Char -> Char -> Char) -> Text -> Char
forall full item.
FoldableLL full item =>
(item -> item -> item) -> full -> item
LL.foldr1 Char -> Char -> Char
f (Text -> Char) -> (Builder -> Text) -> Builder -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> Char) -> Builder -> Char
forall a b. (a -> b) -> a -> b
$ Builder
b
    foldr1 Char -> Char -> Char
f (T Text
s) = (Char -> Char -> Char) -> Text -> Char
forall full item.
FoldableLL full item =>
(item -> item -> item) -> full -> item
LL.foldr1 Char -> Char -> Char
f (Text -> Char) -> Text -> Char
forall a b. (a -> b) -> a -> b
$ Text
s

instance IsList Chars where
    type Item Chars = Char
    toList :: Chars -> [Item Chars]
toList = Chars -> [Item Chars]
forall full item. ListLike full item => full -> [item]
LL.toList'
    fromList :: [Item Chars] -> Chars
fromList = [Item Chars] -> Chars
forall full item. ListLike full item => [item] -> full
LL.fromList'

instance ListLike Chars Char where
    singleton :: Char -> Chars
singleton = Builder -> Chars
B (Builder -> Chars) -> (Char -> Builder) -> Char -> Chars
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Builder
Builder.singleton
    uncons :: Chars -> Maybe (Char, Chars)
uncons (B Builder
b) =
        case Text -> Maybe (Char, Text)
forall full item. ListLike full item => full -> Maybe (item, full)
LL.uncons (Builder -> Text
Builder.toLazyText Builder
b) of
          Maybe (Char, Text)
Nothing -> Maybe (Char, Chars)
forall a. Maybe a
Nothing
          Just (Char
c, Text
s) -> (Char, Chars) -> Maybe (Char, Chars)
forall a. a -> Maybe a
Just (Char
c, Text -> Chars
T Text
s)
    uncons (T Text
s) =
        case Text -> Maybe (Char, Text)
forall full item. ListLike full item => full -> Maybe (item, full)
LL.uncons Text
s of
          Maybe (Char, Text)
Nothing -> Maybe (Char, Chars)
forall a. Maybe a
Nothing
          Just (Char
c, Text
s') -> (Char, Chars) -> Maybe (Char, Chars)
forall a. a -> Maybe a
Just (Char
c, Text -> Chars
T Text
s')
    null :: Chars -> Bool
null (B Builder
b) = Text -> Bool
forall full item. ListLike full item => full -> Bool
LL.null (Text -> Bool) -> (Builder -> Text) -> Builder -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> Bool) -> Builder -> Bool
forall a b. (a -> b) -> a -> b
$ Builder
b
    null (T Text
t) = Text -> Bool
forall full item. ListLike full item => full -> Bool
LL.null Text
t

instance ListLikeIO Chars Char where
    hGetLine :: Handle -> IO Chars
hGetLine Handle
h = Text -> Chars
T (Text -> Chars) -> IO Text -> IO Chars
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO Text
forall full item. ListLikeIO full item => Handle -> IO full
hGetLine Handle
h
    hGetContents :: Handle -> IO Chars
hGetContents Handle
h = Text -> Chars
T (Text -> Chars) -> IO Text -> IO Chars
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO Text
forall full item. ListLikeIO full item => Handle -> IO full
hGetContents Handle
h
    hGet :: Handle -> Int -> IO Chars
hGet Handle
h Int
n = Text -> Chars
T (Text -> Chars) -> IO Text -> IO Chars
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> Int -> IO Text
forall full item. ListLikeIO full item => Handle -> Int -> IO full
hGet Handle
h Int
n
    hGetNonBlocking :: Handle -> Int -> IO Chars
hGetNonBlocking Handle
h Int
n = Text -> Chars
T (Text -> Chars) -> IO Text -> IO Chars
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> Int -> IO Text
forall full item. ListLikeIO full item => Handle -> Int -> IO full
hGetNonBlocking Handle
h Int
n
    hPutStr :: Handle -> Chars -> IO ()
hPutStr Handle
h (B Builder
b) = Handle -> Text -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
h (Text -> IO ()) -> (Builder -> Text) -> Builder -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> IO ()) -> Builder -> IO ()
forall a b. (a -> b) -> a -> b
$ Builder
b
    hPutStr Handle
h (T Text
s) = Handle -> Text -> IO ()
forall full item. ListLikeIO full item => Handle -> full -> IO ()
hPutStr Handle
h (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
s

instance StringLike Chars where
    toString :: Chars -> String
toString (B Builder
b) = Text -> String
forall s. StringLike s => s -> String
toString (Text -> String) -> (Builder -> Text) -> Builder -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> String) -> Builder -> String
forall a b. (a -> b) -> a -> b
$ Builder
b
    toString (T Text
s) = Text -> String
forall s. StringLike s => s -> String
toString (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Text
s
    fromLazyText :: StringLike Text => Text -> Chars
fromLazyText = Builder -> Chars
B (Builder -> Chars) -> (Text -> Builder) -> Text -> Chars
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Builder
Builder.fromLazyText
    fromText :: StringLike Text => Text -> Chars
fromText = Builder -> Chars
B (Builder -> Chars) -> (Text -> Builder) -> Text -> Chars
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Builder
Builder.fromText

instance NFData Chars where
    rnf :: Chars -> ()
rnf (B Builder
b) = Text -> ()
forall a. NFData a => a -> ()
rnf (Text -> ()) -> (Builder -> Text) -> Builder -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
Builder.toLazyText (Builder -> ()) -> Builder -> ()
forall a b. (a -> b) -> a -> b
$ Builder
b
    rnf (T Text
s) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
s