{-# LANGUAGE TypeFamilies, FlexibleContexts, TypeSynonymInstances, ExistentialQuantification, DeriveDataTypeable, FlexibleInstances, UndecidableInstances #-}

module Data.String.Class
    ( Stringy
    , StringCells(..)
    , StringCell(..)
    , StringRWIO(..)
    , ConvGenString(..)
    , ConvString(..)
    , ConvStrictByteString(..)
    , ConvLazyByteString(..)
    , ConvText(..)
    , GenString(..)
    , GenStringDefault
    ) where

import Prelude hiding (head, tail, last, init, take, drop, length, null, concat, putStr, getContents)
import Control.Applicative hiding (empty)
import qualified Data.ByteString as S
import qualified Data.ByteString.Char8 as SC
import qualified Data.ByteString.Internal as BI
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Char8 as LC
import Data.Int
import qualified Data.List as List
import Data.Semigroup
import Data.Monoid hiding ((<>))
import Data.String (IsString)
import qualified Data.String
import Data.Tagged
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Encoding.Error as TEE
import qualified Data.Text.IO as T
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Encoding as LTE
import qualified Data.Text.Lazy.IO as LT
import Data.Typeable
import Data.Word
import qualified System.IO as IO

-- | String super class
class    (StringCells s, StringRWIO s) => Stringy s
instance (StringCells s, StringRWIO s) => Stringy s

-- | Minimal complete definition: StringCellChar; StringCellAltChar; toStringCells; fromStringCells; toMainChar; toAltChar; cons; snoc; either all of head, tail, last, and init, or all of uncons and unsnoc; take, take64 or genericTake; drop, drop64, or genericDrop; and length, length64, or genericLength
class (Eq s, Monoid s, IsString s, Typeable s, StringCell (StringCellChar s), StringCell (StringCellAltChar s), ConvGenString s, ConvString s, ConvStrictByteString s, ConvLazyByteString s, ConvText s, ConvLazyText s) => StringCells s where
    type StringCellChar s
    type StringCellAltChar s

    toStringCells   :: (StringCells s2) => s  -> s2
    fromStringCells :: (StringCells s2) => s2 -> s

    infixr 9 `cons`
    infixr 9 `uncons`
    infixr 9 `altCons`
    infixr 9 `altUncons`
    cons      :: StringCellChar s -> s -> s
    uncons    :: s -> (StringCellChar s, s)
    snoc      :: s -> StringCellChar s -> s
    unsnoc    :: s -> (s, StringCellChar s)
    altCons   :: StringCellAltChar s -> s -> s
    altUncons :: s -> (StringCellAltChar s, s)
    altSnoc   :: s -> StringCellAltChar s -> s
    altUnsnoc :: s -> (s, StringCellAltChar s)

    toMainChar :: (StringCell c) => c -> Tagged s (StringCellChar s)
    toAltChar  :: (StringCell c) => c -> Tagged s (StringCellAltChar s)

    -- | Append two strings
    infixr 9 `append`
    append :: s -> s -> s
    concat :: [s] -> s

    empty :: s
    null :: s -> Bool

    head :: s -> StringCellChar s
    tail :: s -> s
    last :: s -> StringCellChar s
    init :: s -> s
    altHead :: s -> StringCellAltChar s
    altLast :: s -> StringCellAltChar s

    -- | Construction of a string; implementations should behave safely with incorrect lengths
    --
    -- The default implementation of 'unfoldr' is independent from that of 'altUnfoldr',
    -- as well as 'unfoldrN' as and 'altUnfoldrN'.
    unfoldr       ::          (a -> Maybe (StringCellChar    s, a)) -> a -> s
    altUnfoldr    ::          (a -> Maybe (StringCellAltChar s, a)) -> a -> s
    unfoldrN      :: Int   -> (a -> Maybe (StringCellChar    s, a)) -> a -> s
    altUnfoldrN   :: Int   -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s
    unfoldrN64    :: Int64 -> (a -> Maybe (StringCellChar    s, a)) -> a -> s
    altUnfoldrN64 :: Int64 -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s

    unfoldr a -> Maybe (StringCellChar s, a)
f a
b =
        case a -> Maybe (StringCellChar s, a)
f a
b of
            (Just (StringCellChar s
a, a
new_b)) -> StringCellChar s
a forall s. StringCells s => StringCellChar s -> s -> s
`cons` forall s a.
StringCells s =>
(a -> Maybe (StringCellChar s, a)) -> a -> s
unfoldr a -> Maybe (StringCellChar s, a)
f a
new_b
            (Maybe (StringCellChar s, a)
Nothing)         -> forall s. StringCells s => s
empty

    altUnfoldr a -> Maybe (StringCellAltChar s, a)
f a
b =
        case a -> Maybe (StringCellAltChar s, a)
f a
b of
            (Just (StringCellAltChar s
a, a
new_b)) -> StringCellAltChar s
a forall s. StringCells s => StringCellAltChar s -> s -> s
`altCons` forall s a.
StringCells s =>
(a -> Maybe (StringCellAltChar s, a)) -> a -> s
altUnfoldr a -> Maybe (StringCellAltChar s, a)
f a
new_b
            (Maybe (StringCellAltChar s, a)
Nothing)         -> forall s. StringCells s => s
empty
    unfoldrN    = forall a b. a -> b -> a
const forall s a.
StringCells s =>
(a -> Maybe (StringCellChar s, a)) -> a -> s
unfoldr
    altUnfoldrN = forall a b. a -> b -> a
const forall s a.
StringCells s =>
(a -> Maybe (StringCellAltChar s, a)) -> a -> s
altUnfoldr

    unfoldrN64 Int64
l a -> Maybe (StringCellChar s, a)
f a
z = forall s a.
StringCells s =>
Int -> (a -> Maybe (StringCellChar s, a)) -> a -> s
unfoldrN (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
l) a -> Maybe (StringCellChar s, a)
f a
z

    altUnfoldrN64 Int64
l a -> Maybe (StringCellAltChar s, a)
f a
z = forall s a.
StringCells s =>
Int -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s
altUnfoldrN (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
l) a -> Maybe (StringCellAltChar s, a)
f a
z

    -- | Get the character at the given position
    --
    -- Just like 'drop', 'drop64', and the variants of those functions, the
    -- default definitions of these three variants are independent of each
    -- other, and are defined in terms of 'head' and 'tail', which can be
    -- inefficient.
    index   :: s -> Int   -> StringCellChar s
    index64 :: s -> Int64 -> StringCellChar s
    -- | Index a string at any location
    --
    -- Just like the other 'generic' functions of this module, this function
    -- can be significantly slower than 'index', since the function must be
    -- able to support arbitrarily large indices.  Consider using 'index' or
    -- 'index64', even if you need to coerce the index to an 'Int'.
    genericIndex :: (Integral i) => s -> i -> StringCellChar s

    take        :: Int -> s -> s
    take64      :: Int64 -> s -> s
    genericTake :: (Integral i) => i -> s -> s
    drop        :: Int -> s -> s
    drop64      :: Int64 -> s -> s
    genericDrop :: (Integral i) => i -> s -> s

    length        :: s -> Int
    length64      :: s -> Int64
    genericLength :: (Integral i) => s -> i

    safeUncons        :: s -> Maybe ((StringCellChar s), s)
    safeUnsnoc        :: s -> Maybe (s, (StringCellChar s))
    safeAltUncons     :: s -> Maybe ((StringCellAltChar s), s)
    safeAltUnsnoc     :: s -> Maybe (s, (StringCellAltChar s))
    safeHead          :: s -> Maybe (StringCellChar s)
    safeTail          :: s -> Maybe s
    safeLast          :: s -> Maybe (StringCellChar s)
    safeInit          :: s -> Maybe s
    safeAltHead       :: s -> Maybe (StringCellAltChar s)
    safeAltLast       :: s -> Maybe (StringCellAltChar s)
    safeIndex         :: s -> Int   -> Maybe (StringCellChar s)
    safeIndex64       :: s -> Int64 -> Maybe (StringCellChar s)
    safeGenericIndex  :: (Integral i) => s -> i -> Maybe (StringCellChar s)
    safeTake          :: Int -> s -> Maybe s
    safeTake64        :: Int64 -> s -> Maybe s
    safeGenericTake   :: (Integral i) => i -> s -> Maybe s
    safeDrop          :: Int -> s -> Maybe s
    safeDrop64        :: Int64 -> s -> Maybe s
    safeGenericDrop   :: (Integral i) => i -> s -> Maybe s
    safeUncons2       :: s -> Maybe ((StringCellChar s), (StringCellChar s), s)
    safeUncons3       :: s -> Maybe ((StringCellChar s), (StringCellChar s), (StringCellChar s), s)
    safeUncons4       :: s -> Maybe ((StringCellChar s), (StringCellChar s), (StringCellChar s), (StringCellChar s), s)

    infixr 9 `cons2`
    infixr 9 `cons3`
    infixr 9 `cons4`
    infixr 9 `uncons2`
    infixr 9 `uncons3`
    infixr 9 `uncons4`
    cons2   :: StringCellChar s -> StringCellChar s -> s -> s
    cons3   :: StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s
    cons4   :: StringCellChar s -> StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s
    uncons2 :: s -> (StringCellChar s, StringCellChar s, s)
    uncons3 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, s)
    uncons4 :: s -> (StringCellChar s, StringCellChar s, StringCellChar s, StringCellChar s, s)

    altCons StringCellAltChar s
c s
s = forall s. StringCells s => StringCellChar s -> s -> s
cons (s
s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellAltChar s
c) s
s
    altSnoc s
s StringCellAltChar s
c = forall s. StringCells s => s -> StringCellChar s -> s
snoc s
s (s
s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellAltChar s
c)
    altUncons s
s = (\ ~(StringCellChar s
a, s
s') -> (s
s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar StringCellChar s
a, s
s')) forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s
    altUnsnoc s
s = (\ ~(s
s', StringCellChar s
a) -> (s
s', s
s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar StringCellChar s
a)) forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> (s, StringCellChar s)
unsnoc s
s

    append = forall a. Monoid a => a -> a -> a
mappend
    concat = forall a. Monoid a => [a] -> a
mconcat
    empty  = forall a. Monoid a => a
mempty
    null   = (forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty)

    head = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> (StringCellChar s, s)
uncons
    tail = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> (StringCellChar s, s)
uncons
    last = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> (s, StringCellChar s)
unsnoc
    init = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> (s, StringCellChar s)
unsnoc
    altHead s
s = (s
s forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> StringCellChar s
head forall a b. (a -> b) -> a -> b
$ s
s
    altLast s
s = (s
s forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> StringCellChar s
last forall a b. (a -> b) -> a -> b
$ s
s

    index        s
s Int
0 = forall s. StringCells s => s -> StringCellChar s
head s
s
    index        s
s Int
n = (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall s. StringCells s => s -> Int -> StringCellChar s
index forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> a
pred Int
n) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> s
tail forall a b. (a -> b) -> a -> b
$ s
s
    index64      s
s Int64
0 = forall s. StringCells s => s -> StringCellChar s
head s
s
    index64      s
s Int64
n = (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall s. StringCells s => s -> Int64 -> StringCellChar s
index64 forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> a
pred Int64
n) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> s
tail forall a b. (a -> b) -> a -> b
$ s
s
    genericIndex s
s i
0 = forall s. StringCells s => s -> StringCellChar s
head s
s
    genericIndex s
s i
n = (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall s i.
(StringCells s, Integral i) =>
s -> i -> StringCellChar s
genericIndex forall a b. (a -> b) -> a -> b
$ forall a. Enum a => a -> a
pred i
n) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> s
tail forall a b. (a -> b) -> a -> b
$ s
s

    take        Int
n s
s = forall s. StringCells s => Int64 -> s -> s
take64      (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) s
s
    take64      Int64
n s
s = forall s i. (StringCells s, Integral i) => i -> s -> s
genericTake (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
n  :: Integer) s
s
    genericTake i
n s
s = forall s. StringCells s => Int -> s -> s
take        (forall a b. (Integral a, Num b) => a -> b
fromIntegral i
n) s
s
    drop        Int
n s
s = forall s. StringCells s => Int64 -> s -> s
drop64      (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) s
s
    drop64      Int64
n s
s = forall s i. (StringCells s, Integral i) => i -> s -> s
genericDrop (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
n  :: Integer) s
s
    genericDrop i
n s
s = forall s. StringCells s => Int -> s -> s
drop        (forall a b. (Integral a, Num b) => a -> b
fromIntegral i
n) s
s

    length        = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> Int64
length64
    length64      = (forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Integer -> Int64) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s i. (StringCells s, Integral i) => s -> i
genericLength
    genericLength = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> Int
length

    {-
    -- More efficient default implementation provided above
    append a b = case safeUncons a of
        (Just (c, cs)) -> c `cons` append cs b
        (Nothing)      -> a

    concat = foldr append empty
    -}

    uncons s
s = (forall s. StringCells s => s -> StringCellChar s
head s
s, forall s. StringCells s => s -> s
tail s
s)
    unsnoc s
s = (forall s. StringCells s => s -> s
init s
s, forall s. StringCells s => s -> StringCellChar s
last s
s)

    cons2 StringCellChar s
a StringCellChar s
b s
s = StringCellChar s
a forall s. StringCells s => StringCellChar s -> s -> s
`cons` StringCellChar s
b forall s. StringCells s => StringCellChar s -> s -> s
`cons` s
s
    cons3 StringCellChar s
a StringCellChar s
b StringCellChar s
c s
s = StringCellChar s
a forall s. StringCells s => StringCellChar s -> s -> s
`cons` StringCellChar s
b forall s. StringCells s => StringCellChar s -> s -> s
`cons` StringCellChar s
c forall s. StringCells s => StringCellChar s -> s -> s
`cons` s
s
    cons4 StringCellChar s
a StringCellChar s
b StringCellChar s
c StringCellChar s
d s
s = StringCellChar s
a forall s. StringCells s => StringCellChar s -> s -> s
`cons` StringCellChar s
b forall s. StringCells s => StringCellChar s -> s -> s
`cons` StringCellChar s
c forall s. StringCells s => StringCellChar s -> s -> s
`cons` StringCellChar s
d forall s. StringCells s => StringCellChar s -> s -> s
`cons` s
s
    uncons2 s
s       =
        let (StringCellChar s
a, s
s')   = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s
            (StringCellChar s
b, s
s'')  = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s'
        in  (StringCellChar s
a, StringCellChar s
b, s
s'')
    uncons3 s
s       =
        let (StringCellChar s
a, s
s')   = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s
            (StringCellChar s
b, s
s'')  = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s'
            (StringCellChar s
c, s
s''') = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s''
        in  (StringCellChar s
a, StringCellChar s
b, StringCellChar s
c, s
s''')
    uncons4 s
s       =
        let (StringCellChar s
a, s
s')    = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s
            (StringCellChar s
b, s
s'')   = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s'
            (StringCellChar s
c, s
s''')  = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s''
            (StringCellChar s
d, s
s'''') = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s'''
        in  (StringCellChar s
a, StringCellChar s
b, StringCellChar s
c, StringCellChar s
d, s
s'''')

    safeUncons s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
s
    safeUnsnoc s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> (s, StringCellChar s)
unsnoc s
s
    safeAltUncons s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> (StringCellAltChar s, s)
altUncons s
s
    safeAltUnsnoc s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> (s, StringCellAltChar s)
altUnsnoc s
s
    safeHead s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> StringCellChar s
head s
s
    safeTail s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> s
tail s
s
    safeLast s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> StringCellChar s
last s
s
    safeInit s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> s
init s
s
    safeAltHead s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> StringCellAltChar s
altHead s
s
    safeAltLast s
s
        | forall s. StringCells s => s -> Bool
null s
s    = forall a. Maybe a
Nothing
        | Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> StringCellAltChar s
altLast s
s
    safeIndex s
s Int
n
        | forall s. StringCells s => s -> Int
length s
s forall a. Ord a => a -> a -> Bool
<= Int
n = forall a. Maybe a
Nothing
        | Bool
otherwise     = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ s
s forall s. StringCells s => s -> Int -> StringCellChar s
`index` Int
n
    safeIndex64 s
s Int64
n
        | forall s. StringCells s => s -> Int64
length64 s
s forall a. Ord a => a -> a -> Bool
<= Int64
n = forall a. Maybe a
Nothing
        | Bool
otherwise     = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ s
s forall s. StringCells s => s -> Int64 -> StringCellChar s
`index64` Int64
n
    safeGenericIndex s
s i
n
        | forall s i. (StringCells s, Integral i) => s -> i
genericLength s
s forall a. Ord a => a -> a -> Bool
<= i
n = forall a. Maybe a
Nothing
        | Bool
otherwise            = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ s
s forall s i.
(StringCells s, Integral i) =>
s -> i -> StringCellChar s
`genericIndex` i
n
    safeTake Int
n s
s
        | Int
n forall a. Ord a => a -> a -> Bool
> forall s. StringCells s => s -> Int
length s
s = forall a. Maybe a
Nothing
        | Bool
otherwise    = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => Int -> s -> s
take Int
n s
s
    safeTake64 Int64
n s
s
        | Int64
n forall a. Ord a => a -> a -> Bool
> forall s. StringCells s => s -> Int64
length64 s
s = forall a. Maybe a
Nothing
        | Bool
otherwise      = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => Int64 -> s -> s
take64 Int64
n s
s
    safeGenericTake i
n s
s
        | i
n forall a. Ord a => a -> a -> Bool
> forall s i. (StringCells s, Integral i) => s -> i
genericLength s
s = forall a. Maybe a
Nothing
        | Bool
otherwise           = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s i. (StringCells s, Integral i) => i -> s -> s
genericTake i
n s
s
    safeDrop Int
n s
s
        | Int
n forall a. Ord a => a -> a -> Bool
> forall s. StringCells s => s -> Int
length s
s = forall a. Maybe a
Nothing
        | Bool
otherwise    = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => Int -> s -> s
drop Int
n s
s
    safeDrop64 Int64
n s
s
        | Int64
n forall a. Ord a => a -> a -> Bool
> forall s. StringCells s => s -> Int64
length64 s
s = forall a. Maybe a
Nothing
        | Bool
otherwise      = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => Int64 -> s -> s
drop64 Int64
n s
s
    safeGenericDrop i
n s
s
        | i
n forall a. Ord a => a -> a -> Bool
> forall s i. (StringCells s, Integral i) => s -> i
genericLength s
s = forall a. Maybe a
Nothing
        | Bool
otherwise           = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall s i. (StringCells s, Integral i) => i -> s -> s
genericDrop i
n s
s
    safeUncons2 s
s = do
        (StringCellChar s
a, s
s')    <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s
        (StringCellChar s
b, s
s'')   <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s'
        forall (m :: * -> *) a. Monad m => a -> m a
return (StringCellChar s
a, StringCellChar s
b, s
s'')
    safeUncons3 s
s = do
        (StringCellChar s
a, s
s')    <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s
        (StringCellChar s
b, s
s'')   <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s'
        (StringCellChar s
c, s
s''')  <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s''
        forall (m :: * -> *) a. Monad m => a -> m a
return (StringCellChar s
a, StringCellChar s
b, StringCellChar s
c, s
s''')
    safeUncons4 s
s = do
        (StringCellChar s
a, s
s')    <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s
        (StringCellChar s
b, s
s'')   <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s'
        (StringCellChar s
c, s
s''')  <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s''
        (StringCellChar s
d, s
s'''') <- forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
s'''
        forall (m :: * -> *) a. Monad m => a -> m a
return (StringCellChar s
a, StringCellChar s
b, StringCellChar s
c, StringCellChar s
d, s
s'''')

class StringCell c where
    toChar     :: c      -> Char
    toWord8    :: c      -> Word8
    toWord16   :: c      -> Word16
    toWord32   :: c      -> Word32
    toWord64   :: c      -> Word64
    fromChar   :: Char   -> c
    fromWord8  :: Word8  -> c
    fromWord16 :: Word16 -> c
    fromWord32 :: Word32 -> c
    fromWord64 :: Word64 -> c

class ConvGenString s where
    toGenString   :: s -> GenString
    fromGenString :: GenString -> s

class ConvString s where
    toString   :: s -> String
    fromString :: String -> s

class ConvStrictByteString s where
    toStrictByteString :: s -> S.ByteString
    fromStrictByteString :: S.ByteString -> s

class ConvLazyByteString s where
    toLazyByteString :: s -> L.ByteString
    fromLazyByteString :: L.ByteString -> s

class ConvText s where
    toText :: s -> T.Text
    fromText :: T.Text -> s

class ConvLazyText s where
    toLazyText :: s -> LT.Text
    fromLazyText :: LT.Text -> s

-- | Minimal complete definition: 'hGetContents', 'hGetLine', 'hPutStr', and 'hPutStrLn'
class StringRWIO s where
    --- Handles

    -- | Read n bytes *or* characters, depending on the implementation into a
    -- ByteString, directly from the specified Handle
    --
    -- Whether or not this function is lazy depends on the instance; laziness
    -- is preferred.
    hGetContents :: IO.Handle -> IO s

    -- | Read a single line from a handle
    hGetLine :: IO.Handle -> IO s

    -- | Write a string to a handle
    hPutStr :: IO.Handle -> s -> IO ()

    -- | Write a string to a handle, followed by a newline
    --
    -- N.B.: implementations might not define this atomically.  If the state
    -- of being atomic is necessary, one possible solution is to convert a
    -- string to an efficient type for which 'hPutStrLn' is atomic.
    hPutStrLn :: IO.Handle -> s -> IO ()

    --- Special cases for standard input and output

    -- | Take a function of type Text -> Text as its argument
    --
    -- The entire input from the standard input device is passed to this
    -- function as its argument, and the resulting string is output on the
    -- standard output device.
    interact :: (s -> s) -> IO ()
    interact s -> s
f = forall s. StringRWIO s => s -> IO ()
putStr forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> s
f forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall s. StringRWIO s => IO s
getContents

    -- | Read all user input on 'stdin' as a single string
    getContents :: IO s
    getContents = forall s. StringRWIO s => Handle -> IO s
hGetContents Handle
IO.stdin

    -- | Read a single line of user input from 'stdin'
    getLine :: IO s
    getLine = forall s. StringRWIO s => Handle -> IO s
hGetLine Handle
IO.stdin

    -- | Write a string to 'stdout'
    putStr :: s -> IO ()
    putStr = forall s. StringRWIO s => Handle -> s -> IO ()
hPutStr Handle
IO.stdout

    -- | Write a string to 'stdout', followed by a newline
    putStrLn :: s -> IO ()
    putStrLn = forall s. StringRWIO s => Handle -> s -> IO ()
hPutStrLn Handle
IO.stdout

    ---

    -- | Read a file and returns the contents of the file as a string
    --
    -- Depending on the instance, this function might expect the file to be
    -- non-binary.  The default definition uses 'openFile' to open the file.
    readFile :: FilePath -> IO s
    readFile String
fn = forall s. StringRWIO s => Handle -> IO s
hGetContents forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> IOMode -> IO Handle
IO.openFile String
fn IOMode
IO.ReadMode

    -- | Write a string to a file
    --
    -- The file is truncated to zero length before writing begins.
    -- The default definition uses 'withFile' to open the file.
    writeFile :: FilePath -> s -> IO ()
    writeFile String
fn s
s = forall r. String -> IOMode -> (Handle -> IO r) -> IO r
IO.withFile String
fn IOMode
IO.WriteMode forall a b. (a -> b) -> a -> b
$ \Handle
hdl -> forall s. StringRWIO s => Handle -> s -> IO ()
hPutStr Handle
hdl s
s

    -- | Write a string to the end of a file
    --
    -- The default definition uses 'withFile' to open the file.
    appendFile :: FilePath -> s -> IO ()
    appendFile String
fn s
s = forall r. String -> IOMode -> (Handle -> IO r) -> IO r
IO.withFile String
fn IOMode
IO.AppendMode forall a b. (a -> b) -> a -> b
$ \Handle
hdl -> forall s. StringRWIO s => Handle -> s -> IO ()
hPutStr Handle
hdl s
s



instance StringCells String where
    type StringCellChar    String = Char
    type StringCellAltChar String = Char

    toStringCells :: forall s2. StringCells s2 => String -> s2
toStringCells   = forall s. ConvString s => String -> s
fromString
    fromStringCells :: forall s2. StringCells s2 => s2 -> String
fromStringCells = forall s. ConvString s => s -> String
toString

    length :: String -> Int
length = forall i a. Num i => [a] -> i
List.genericLength
    empty :: String
empty  = []
    null :: String -> Bool
null   = forall (t :: * -> *) a. Foldable t => t a -> Bool
List.null
    cons :: StringCellChar String -> String -> String
cons          = (:)
    snoc :: String -> StringCellChar String -> String
snoc String
s StringCellChar String
c      = String
s forall a. [a] -> [a] -> [a]
++ [StringCellChar String
c]
    safeUncons :: String -> Maybe (StringCellChar String, String)
safeUncons (Char
x:String
xs) = forall a. a -> Maybe a
Just (Char
x, String
xs)
    safeUncons String
_      = forall a. Maybe a
Nothing
    uncons :: String -> (StringCellChar String, String)
uncons (Char
x:String
xs) = (Char
x, String
xs)
    uncons String
_      = forall a. HasCallStack => String -> a
error String
"String.uncons: null string"
    toMainChar :: forall c.
StringCell c =>
c -> Tagged String (StringCellChar String)
toMainChar    = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    toAltChar :: forall c.
StringCell c =>
c -> Tagged String (StringCellAltChar String)
toAltChar     = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    head :: String -> StringCellChar String
head          = forall a. [a] -> a
List.head
    tail :: String -> String
tail          = forall a. [a] -> [a]
List.tail
    init :: String -> String
init          = forall a. [a] -> [a]
List.init
    last :: String -> StringCellChar String
last          = forall a. [a] -> a
List.last
    unfoldr :: forall a. (a -> Maybe (StringCellChar String, a)) -> a -> String
unfoldr       = forall b a. (b -> Maybe (a, b)) -> b -> [a]
List.unfoldr
    index :: String -> Int -> StringCellChar String
index         = forall a. [a] -> Int -> a
(List.!!)
    index64 :: String -> Int64 -> StringCellChar String
index64 String
s     = forall s. StringCells s => s -> Int -> StringCellChar s
index String
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    genericIndex :: forall i. Integral i => String -> i -> StringCellChar String
genericIndex  = forall i a. Integral i => [a] -> i -> a
List.genericIndex
    take :: Int -> String -> String
take          = forall a. Int -> [a] -> [a]
List.take
    genericTake :: forall i. Integral i => i -> String -> String
genericTake   = forall i a. Integral i => i -> [a] -> [a]
List.genericTake
    drop :: Int -> String -> String
drop          = forall a. Int -> [a] -> [a]
List.drop
    genericDrop :: forall i. Integral i => i -> String -> String
genericDrop   = forall i a. Integral i => i -> [a] -> [a]
List.genericDrop
    append :: String -> String -> String
append        = forall a. [a] -> [a] -> [a]
(List.++)
    concat :: [String] -> String
concat        = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
List.concat

instance StringCells S.ByteString where
    type StringCellChar    S.ByteString = Word8
    type StringCellAltChar S.ByteString = Char

    toStringCells :: forall s2. StringCells s2 => ByteString -> s2
toStringCells   = forall s. ConvStrictByteString s => ByteString -> s
fromStrictByteString
    fromStringCells :: forall s2. StringCells s2 => s2 -> ByteString
fromStringCells = forall s. ConvStrictByteString s => s -> ByteString
toStrictByteString

    length :: ByteString -> Int
length          = ByteString -> Int
S.length
    empty :: ByteString
empty           = ByteString
S.empty
    null :: ByteString -> Bool
null            = ByteString -> Bool
S.null
    cons :: StringCellChar ByteString -> ByteString -> ByteString
cons            = Word8 -> ByteString -> ByteString
S.cons
    snoc :: ByteString -> StringCellChar ByteString -> ByteString
snoc            = ByteString -> Word8 -> ByteString
S.snoc
    safeUncons :: ByteString -> Maybe (StringCellChar ByteString, ByteString)
safeUncons      = ByteString -> Maybe (Word8, ByteString)
S.uncons
    uncons :: ByteString -> (StringCellChar ByteString, ByteString)
uncons          = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => String -> a
error String
"StringCells.Data.ByteString.ByteString.uncons: string is null") forall a. a -> a
id forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons
    toMainChar :: forall c.
StringCell c =>
c -> Tagged ByteString (StringCellChar ByteString)
toMainChar      = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Word8
toWord8
    toAltChar :: forall c.
StringCell c =>
c -> Tagged ByteString (StringCellAltChar ByteString)
toAltChar       = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    head :: ByteString -> StringCellChar ByteString
head            = HasCallStack => ByteString -> Word8
S.head
    tail :: ByteString -> ByteString
tail            = HasCallStack => ByteString -> ByteString
S.tail
    init :: ByteString -> ByteString
init            = HasCallStack => ByteString -> ByteString
S.init
    last :: ByteString -> StringCellChar ByteString
last            = HasCallStack => ByteString -> Word8
S.last
    unfoldr :: forall a.
(a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString
unfoldr         = forall a. (a -> Maybe (Word8, a)) -> a -> ByteString
S.unfoldr
    altUnfoldr :: forall a.
(a -> Maybe (StringCellAltChar ByteString, a)) -> a -> ByteString
altUnfoldr      = forall a. (a -> Maybe (Char, a)) -> a -> ByteString
SC.unfoldr
    unfoldrN :: forall a.
Int
-> (a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString
unfoldrN        = ((forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)
S.unfoldrN
    altUnfoldrN :: forall a.
Int
-> (a -> Maybe (StringCellAltChar ByteString, a))
-> a
-> ByteString
altUnfoldrN     = ((forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
.) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Int -> (a -> Maybe (Char, a)) -> a -> (ByteString, Maybe a)
SC.unfoldrN
    index :: ByteString -> Int -> StringCellChar ByteString
index           = HasCallStack => ByteString -> Int -> Word8
S.index
    index64 :: ByteString -> Int64 -> StringCellChar ByteString
index64 ByteString
s       = forall s. StringCells s => s -> Int -> StringCellChar s
index ByteString
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    take :: Int -> ByteString -> ByteString
take            = Int -> ByteString -> ByteString
S.take
    drop :: Int -> ByteString -> ByteString
drop            = Int -> ByteString -> ByteString
S.drop
    append :: ByteString -> ByteString -> ByteString
append          = ByteString -> ByteString -> ByteString
S.append
    concat :: [ByteString] -> ByteString
concat          = [ByteString] -> ByteString
S.concat

instance StringCells L.ByteString where
    type StringCellChar    L.ByteString = Word8
    type StringCellAltChar L.ByteString = Char

    toStringCells :: forall s2. StringCells s2 => ByteString -> s2
toStringCells   = forall s. ConvLazyByteString s => ByteString -> s
fromLazyByteString
    fromStringCells :: forall s2. StringCells s2 => s2 -> ByteString
fromStringCells = forall s. ConvLazyByteString s => s -> ByteString
toLazyByteString

    length64 :: ByteString -> Int64
length64        = ByteString -> Int64
L.length
    length :: ByteString -> Int
length          = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> Int64
length64
    empty :: ByteString
empty           = ByteString
L.empty
    null :: ByteString -> Bool
null            = ByteString -> Bool
L.null
    cons :: StringCellChar ByteString -> ByteString -> ByteString
cons            = Word8 -> ByteString -> ByteString
L.cons
    snoc :: ByteString -> StringCellChar ByteString -> ByteString
snoc            = ByteString -> Word8 -> ByteString
L.snoc
    safeUncons :: ByteString -> Maybe (StringCellChar ByteString, ByteString)
safeUncons      = ByteString -> Maybe (Word8, ByteString)
L.uncons
    uncons :: ByteString -> (StringCellChar ByteString, ByteString)
uncons          = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => String -> a
error String
"StringCells.Data.ByteString.Lazy.ByteString.uncons: string is null") forall a. a -> a
id forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons
    toMainChar :: forall c.
StringCell c =>
c -> Tagged ByteString (StringCellChar ByteString)
toMainChar      = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Word8
toWord8
    toAltChar :: forall c.
StringCell c =>
c -> Tagged ByteString (StringCellAltChar ByteString)
toAltChar       = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    head :: ByteString -> StringCellChar ByteString
head            = HasCallStack => ByteString -> Word8
L.head
    tail :: ByteString -> ByteString
tail            = HasCallStack => ByteString -> ByteString
L.tail
    init :: ByteString -> ByteString
init            = HasCallStack => ByteString -> ByteString
L.init
    last :: ByteString -> StringCellChar ByteString
last            = HasCallStack => ByteString -> Word8
L.last
    unfoldr :: forall a.
(a -> Maybe (StringCellChar ByteString, a)) -> a -> ByteString
unfoldr         = forall a. (a -> Maybe (Word8, a)) -> a -> ByteString
L.unfoldr
    altUnfoldr :: forall a.
(a -> Maybe (StringCellAltChar ByteString, a)) -> a -> ByteString
altUnfoldr      = forall a. (a -> Maybe (Char, a)) -> a -> ByteString
LC.unfoldr
    index :: ByteString -> Int -> StringCellChar ByteString
index ByteString
s         = forall s. StringCells s => s -> Int64 -> StringCellChar s
index64 ByteString
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    index64 :: ByteString -> Int64 -> StringCellChar ByteString
index64         = HasCallStack => ByteString -> Int64 -> Word8
L.index
    take64 :: Int64 -> ByteString -> ByteString
take64          = Int64 -> ByteString -> ByteString
L.take
    drop64 :: Int64 -> ByteString -> ByteString
drop64          = Int64 -> ByteString -> ByteString
L.drop
    append :: ByteString -> ByteString -> ByteString
append          = ByteString -> ByteString -> ByteString
L.append
    concat :: [ByteString] -> ByteString
concat          = [ByteString] -> ByteString
L.concat

instance StringCells T.Text where
    type StringCellChar    T.Text = Char
    type StringCellAltChar T.Text = Char

    toStringCells :: forall s2. StringCells s2 => Text -> s2
toStringCells   = forall s. ConvText s => Text -> s
fromText
    fromStringCells :: forall s2. StringCells s2 => s2 -> Text
fromStringCells = forall s. ConvText s => s -> Text
toText

    length :: Text -> Int
length          = Text -> Int
T.length
    empty :: Text
empty           = Text
T.empty
    null :: Text -> Bool
null            = Text -> Bool
T.null
    cons :: StringCellChar Text -> Text -> Text
cons            = Char -> Text -> Text
T.cons
    safeUncons :: Text -> Maybe (StringCellChar Text, Text)
safeUncons      = Text -> Maybe (Char, Text)
T.uncons
    uncons :: Text -> (StringCellChar Text, Text)
uncons          = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => String -> a
error String
"StringCells.Data.Text.Text.uncons: string is null") forall a. a -> a
id forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons
    snoc :: Text -> StringCellChar Text -> Text
snoc            = Text -> Char -> Text
T.snoc
    altSnoc :: Text -> StringCellAltChar Text -> Text
altSnoc         = Text -> Char -> Text
T.snoc
    toMainChar :: forall c. StringCell c => c -> Tagged Text (StringCellChar Text)
toMainChar      = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    toAltChar :: forall c. StringCell c => c -> Tagged Text (StringCellAltChar Text)
toAltChar       = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    head :: Text -> StringCellChar Text
head            = Text -> Char
T.head
    tail :: Text -> Text
tail            = Text -> Text
T.tail
    init :: Text -> Text
init            = Text -> Text
T.init
    last :: Text -> StringCellChar Text
last            = Text -> Char
T.last
    unfoldr :: forall a. (a -> Maybe (StringCellChar Text, a)) -> a -> Text
unfoldr         = forall a. (a -> Maybe (Char, a)) -> a -> Text
T.unfoldr
    altUnfoldr :: forall a. (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text
altUnfoldr      = forall a. (a -> Maybe (Char, a)) -> a -> Text
T.unfoldr
    unfoldrN :: forall a. Int -> (a -> Maybe (StringCellChar Text, a)) -> a -> Text
unfoldrN        = forall a. Int -> (a -> Maybe (Char, a)) -> a -> Text
T.unfoldrN
    altUnfoldrN :: forall a.
Int -> (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text
altUnfoldrN     = forall a. Int -> (a -> Maybe (Char, a)) -> a -> Text
T.unfoldrN
    index :: Text -> Int -> StringCellChar Text
index           = Text -> Int -> Char
T.index
    index64 :: Text -> Int64 -> StringCellChar Text
index64 Text
s       = forall s. StringCells s => s -> Int -> StringCellChar s
index Text
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    append :: Text -> Text -> Text
append          = Text -> Text -> Text
T.append
    concat :: [Text] -> Text
concat          = [Text] -> Text
T.concat

instance StringCells LT.Text where
    type StringCellChar    LT.Text = Char
    type StringCellAltChar LT.Text = Char

    toStringCells :: forall s2. StringCells s2 => Text -> s2
toStringCells   = forall s. ConvLazyText s => Text -> s
fromLazyText
    fromStringCells :: forall s2. StringCells s2 => s2 -> Text
fromStringCells = forall s. ConvLazyText s => s -> Text
toLazyText

    length64 :: Text -> Int64
length64        = Text -> Int64
LT.length
    empty :: Text
empty           = Text
LT.empty
    null :: Text -> Bool
null            = Text -> Bool
LT.null
    cons :: StringCellChar Text -> Text -> Text
cons            = Char -> Text -> Text
LT.cons
    safeUncons :: Text -> Maybe (StringCellChar Text, Text)
safeUncons      = Text -> Maybe (Char, Text)
LT.uncons
    uncons :: Text -> (StringCellChar Text, Text)
uncons          = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => String -> a
error String
"StringCells.Data.Text.Lazy.Text.uncons: string is null") forall a. a -> a
id forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons
    snoc :: Text -> StringCellChar Text -> Text
snoc            = Text -> Char -> Text
LT.snoc
    altSnoc :: Text -> StringCellAltChar Text -> Text
altSnoc         = Text -> Char -> Text
LT.snoc
    toMainChar :: forall c. StringCell c => c -> Tagged Text (StringCellChar Text)
toMainChar      = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    toAltChar :: forall c. StringCell c => c -> Tagged Text (StringCellAltChar Text)
toAltChar       = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    head :: Text -> StringCellChar Text
head            = Text -> Char
LT.head
    tail :: Text -> Text
tail            = Text -> Text
LT.tail
    init :: Text -> Text
init            = Text -> Text
LT.init
    last :: Text -> StringCellChar Text
last            = Text -> Char
LT.last
    unfoldr :: forall a. (a -> Maybe (StringCellChar Text, a)) -> a -> Text
unfoldr         = forall a. (a -> Maybe (Char, a)) -> a -> Text
LT.unfoldr
    altUnfoldr :: forall a. (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text
altUnfoldr      = forall a. (a -> Maybe (Char, a)) -> a -> Text
LT.unfoldr
    unfoldrN64 :: forall a.
Int64 -> (a -> Maybe (StringCellChar Text, a)) -> a -> Text
unfoldrN64      = forall a. Int64 -> (a -> Maybe (Char, a)) -> a -> Text
LT.unfoldrN
    altUnfoldrN64 :: forall a.
Int64 -> (a -> Maybe (StringCellAltChar Text, a)) -> a -> Text
altUnfoldrN64   = forall a. Int64 -> (a -> Maybe (Char, a)) -> a -> Text
LT.unfoldrN
    index :: Text -> Int -> StringCellChar Text
index Text
s         = forall s. StringCells s => s -> Int64 -> StringCellChar s
index64 Text
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    index64 :: Text -> Int64 -> StringCellChar Text
index64         = Text -> Int64 -> Char
LT.index
    append :: Text -> Text -> Text
append          = Text -> Text -> Text
LT.append
    concat :: [Text] -> Text
concat          = [Text] -> Text
LT.concat

instance StringCell Char where
    toChar :: Char -> Char
toChar     = forall a. a -> a
id
    toWord8 :: Char -> Word8
toWord8    = Char -> Word8
BI.c2w
    toWord16 :: Char -> Word16
toWord16   = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Word8
toWord8
    toWord32 :: Char -> Word32
toWord32   = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Word8
toWord8
    toWord64 :: Char -> Word64
toWord64   = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Word8
toWord8
    fromChar :: Char -> Char
fromChar   = forall a. a -> a
id
    fromWord8 :: Word8 -> Char
fromWord8  = Word8 -> Char
BI.w2c
    fromWord16 :: Word16 -> Char
fromWord16 = Word8 -> Char
BI.w2c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord32 :: Word32 -> Char
fromWord32 = Word8 -> Char
BI.w2c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord64 :: Word64 -> Char
fromWord64 = Word8 -> Char
BI.w2c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance StringCell Word8 where
    toChar :: Word8 -> Char
toChar     = Word8 -> Char
BI.w2c
    toWord8 :: Word8 -> Word8
toWord8    = forall a. a -> a
id
    toWord16 :: Word8 -> Word16
toWord16   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord32 :: Word8 -> Word32
toWord32   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord64 :: Word8 -> Word64
toWord64   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromChar :: Char -> Word8
fromChar   = Char -> Word8
BI.c2w
    fromWord8 :: Word8 -> Word8
fromWord8  = forall a. a -> a
id
    fromWord16 :: Word16 -> Word8
fromWord16 = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord32 :: Word32 -> Word8
fromWord32 = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord64 :: Word64 -> Word8
fromWord64 = forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance StringCell Word16 where
    toChar :: Word16 -> Char
toChar     = Word8 -> Char
BI.w2c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord8 :: Word16 -> Word8
toWord8    = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord16 :: Word16 -> Word16
toWord16   = forall a. a -> a
id
    toWord32 :: Word16 -> Word32
toWord32   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord64 :: Word16 -> Word64
toWord64   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromChar :: Char -> Word16
fromChar   = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Word8
BI.c2w
    fromWord8 :: Word8 -> Word16
fromWord8  = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord16 :: Word16 -> Word16
fromWord16 = forall a. a -> a
id
    fromWord32 :: Word32 -> Word16
fromWord32 = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord64 :: Word64 -> Word16
fromWord64 = forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance StringCell Word32 where
    toChar :: Word32 -> Char
toChar     = Word8 -> Char
BI.w2c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord8 :: Word32 -> Word8
toWord8    = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord16 :: Word32 -> Word16
toWord16   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord32 :: Word32 -> Word32
toWord32   = forall a. a -> a
id
    toWord64 :: Word32 -> Word64
toWord64   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromChar :: Char -> Word32
fromChar   = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Word8
BI.c2w
    fromWord8 :: Word8 -> Word32
fromWord8  = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord16 :: Word16 -> Word32
fromWord16 = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord32 :: Word32 -> Word32
fromWord32 = forall a. a -> a
id
    fromWord64 :: Word64 -> Word32
fromWord64 = forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance StringCell Word64 where
    toChar :: Word64 -> Char
toChar     = Word8 -> Char
BI.w2c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord8 :: Word64 -> Word8
toWord8    = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord16 :: Word64 -> Word16
toWord16   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord32 :: Word64 -> Word32
toWord32   = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    toWord64 :: Word64 -> Word64
toWord64   = forall a. a -> a
id
    fromChar :: Char -> Word64
fromChar   = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Word8
BI.c2w
    fromWord8 :: Word8 -> Word64
fromWord8  = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord16 :: Word16 -> Word64
fromWord16 = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord32 :: Word32 -> Word64
fromWord32 = forall a b. (Integral a, Num b) => a -> b
fromIntegral
    fromWord64 :: Word64 -> Word64
fromWord64 = forall a. a -> a
id

instance ConvGenString GenString where
    toGenString :: GenString -> GenString
toGenString   = forall a. a -> a
id
    fromGenString :: GenString -> GenString
fromGenString = forall a. a -> a
id

instance ConvGenString String where
    toGenString :: String -> GenString
toGenString      = forall s. Stringy s => s -> GenString
GenString
    fromGenString :: GenString -> String
fromGenString GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells s
_s

instance ConvGenString SC.ByteString where
    toGenString :: ByteString -> GenString
toGenString      = forall s. Stringy s => s -> GenString
GenString
    fromGenString :: GenString -> ByteString
fromGenString GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells s
_s

instance ConvGenString LC.ByteString where
    toGenString :: ByteString -> GenString
toGenString      = forall s. Stringy s => s -> GenString
GenString
    fromGenString :: GenString -> ByteString
fromGenString GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells s
_s

instance ConvGenString T.Text where
    toGenString :: Text -> GenString
toGenString      = forall s. Stringy s => s -> GenString
GenString
    fromGenString :: GenString -> Text
fromGenString GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells s
_s

instance ConvGenString LT.Text where
    toGenString :: Text -> GenString
toGenString      = forall s. Stringy s => s -> GenString
GenString
    fromGenString :: GenString -> Text
fromGenString GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells s
_s

instance ConvString GenString where
    toString :: GenString -> String
toString   = forall s. ConvGenString s => GenString -> s
fromGenString
    fromString :: String -> GenString
fromString = forall s. ConvGenString s => s -> GenString
toGenString

instance ConvString String where
    toString :: String -> String
toString   = forall a. a -> a
id
    fromString :: String -> String
fromString = forall a. a -> a
id

instance ConvString SC.ByteString where
    toString :: ByteString -> String
toString   = ByteString -> String
SC.unpack
    fromString :: String -> ByteString
fromString = String -> ByteString
SC.pack

instance ConvString LC.ByteString where
    toString :: ByteString -> String
toString   = ByteString -> String
LC.unpack
    fromString :: String -> ByteString
fromString = String -> ByteString
LC.pack

instance ConvString T.Text where
    toString :: Text -> String
toString   = Text -> String
T.unpack
    fromString :: String -> Text
fromString = String -> Text
T.pack

instance ConvString LT.Text where
    toString :: Text -> String
toString   = Text -> String
LT.unpack
    fromString :: String -> Text
fromString = String -> Text
LT.pack

instance ConvStrictByteString GenString where
    toStrictByteString :: GenString -> ByteString
toStrictByteString   = forall s. ConvGenString s => GenString -> s
fromGenString
    fromStrictByteString :: ByteString -> GenString
fromStrictByteString = forall s. ConvGenString s => s -> GenString
toGenString

instance ConvStrictByteString String where
    toStrictByteString :: String -> ByteString
toStrictByteString   = String -> ByteString
SC.pack
    fromStrictByteString :: ByteString -> String
fromStrictByteString = ByteString -> String
SC.unpack

instance ConvStrictByteString S.ByteString where
    toStrictByteString :: ByteString -> ByteString
toStrictByteString   = forall a. a -> a
id
    fromStrictByteString :: ByteString -> ByteString
fromStrictByteString = forall a. a -> a
id

instance ConvStrictByteString L.ByteString where
    toStrictByteString :: ByteString -> ByteString
toStrictByteString   = ByteString -> ByteString
L.toStrict
    fromStrictByteString :: ByteString -> ByteString
fromStrictByteString = forall s. ConvLazyByteString s => s -> ByteString
toLazyByteString

instance ConvStrictByteString T.Text where
    toStrictByteString :: Text -> ByteString
toStrictByteString   = Text -> ByteString
TE.encodeUtf8
    fromStrictByteString :: ByteString -> Text
fromStrictByteString = forall s. ConvText s => s -> Text
toText

instance ConvStrictByteString LT.Text where
    toStrictByteString :: Text -> ByteString
toStrictByteString   = forall s. ConvStrictByteString s => s -> ByteString
toStrictByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
LTE.encodeUtf8
    fromStrictByteString :: ByteString -> Text
fromStrictByteString = forall s. ConvLazyText s => s -> Text
toLazyText

instance ConvLazyByteString GenString where
    toLazyByteString :: GenString -> ByteString
toLazyByteString   = forall s. ConvGenString s => GenString -> s
fromGenString
    fromLazyByteString :: ByteString -> GenString
fromLazyByteString = forall s. ConvGenString s => s -> GenString
toGenString

instance ConvLazyByteString String where
    toLazyByteString :: String -> ByteString
toLazyByteString   = String -> ByteString
LC.pack
    fromLazyByteString :: ByteString -> String
fromLazyByteString = ByteString -> String
LC.unpack

instance ConvLazyByteString S.ByteString where
    toLazyByteString :: ByteString -> ByteString
toLazyByteString   = ByteString -> ByteString
L.fromStrict
    fromLazyByteString :: ByteString -> ByteString
fromLazyByteString = forall s. ConvStrictByteString s => s -> ByteString
toStrictByteString

instance ConvLazyByteString L.ByteString where
    toLazyByteString :: ByteString -> ByteString
toLazyByteString   = forall a. a -> a
id
    fromLazyByteString :: ByteString -> ByteString
fromLazyByteString = forall a. a -> a
id

instance ConvLazyByteString T.Text where
    toLazyByteString :: Text -> ByteString
toLazyByteString   = forall s. ConvLazyByteString s => s -> ByteString
toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. ConvStrictByteString s => s -> ByteString
toStrictByteString
    fromLazyByteString :: ByteString -> Text
fromLazyByteString = forall s. ConvText s => s -> Text
toText

instance ConvLazyByteString LT.Text where
    toLazyByteString :: Text -> ByteString
toLazyByteString   = forall s. ConvLazyByteString s => s -> ByteString
toLazyByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. ConvStrictByteString s => s -> ByteString
toStrictByteString
    fromLazyByteString :: ByteString -> Text
fromLazyByteString = forall s. ConvLazyText s => s -> Text
toLazyText

instance ConvText GenString where
    toText :: GenString -> Text
toText   = forall s. ConvGenString s => GenString -> s
fromGenString
    fromText :: Text -> GenString
fromText = forall s. ConvGenString s => s -> GenString
toGenString

instance ConvText String where
    toText :: String -> Text
toText   = String -> Text
T.pack
    fromText :: Text -> String
fromText = Text -> String
T.unpack

instance ConvText S.ByteString where
    toText :: ByteString -> Text
toText   = OnDecodeError -> ByteString -> Text
TE.decodeUtf8With OnDecodeError
TEE.lenientDecode
    fromText :: Text -> ByteString
fromText = forall s. ConvStrictByteString s => s -> ByteString
toStrictByteString

instance ConvText L.ByteString where
    toText :: ByteString -> Text
toText   = forall s. ConvText s => s -> Text
toText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. ConvStrictByteString s => s -> ByteString
toStrictByteString
    fromText :: Text -> ByteString
fromText = forall s. ConvLazyByteString s => s -> ByteString
toLazyByteString

instance ConvText T.Text where
    toText :: Text -> Text
toText   = forall a. a -> a
id
    fromText :: Text -> Text
fromText = forall a. a -> a
id

instance ConvText LT.Text where
    toText :: Text -> Text
toText   = Text -> Text
LT.toStrict
    fromText :: Text -> Text
fromText = forall s. ConvLazyText s => s -> Text
toLazyText

instance ConvLazyText GenString where
    toLazyText :: GenString -> Text
toLazyText   = forall s. ConvGenString s => GenString -> s
fromGenString
    fromLazyText :: Text -> GenString
fromLazyText = forall s. ConvGenString s => s -> GenString
toGenString

instance ConvLazyText String where
    toLazyText :: String -> Text
toLazyText   = String -> Text
LT.pack
    fromLazyText :: Text -> String
fromLazyText = Text -> String
LT.unpack

instance ConvLazyText S.ByteString where
    toLazyText :: ByteString -> Text
toLazyText   = OnDecodeError -> ByteString -> Text
LTE.decodeUtf8With OnDecodeError
TEE.lenientDecode forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. ConvLazyByteString s => s -> ByteString
toLazyByteString
    fromLazyText :: Text -> ByteString
fromLazyText = forall s. ConvStrictByteString s => s -> ByteString
toStrictByteString

instance ConvLazyText L.ByteString where
    toLazyText :: ByteString -> Text
toLazyText   = OnDecodeError -> ByteString -> Text
LTE.decodeUtf8With OnDecodeError
TEE.lenientDecode
    fromLazyText :: Text -> ByteString
fromLazyText = forall s. ConvLazyByteString s => s -> ByteString
toLazyByteString

instance ConvLazyText T.Text where
    toLazyText :: Text -> Text
toLazyText   = Text -> Text
LT.fromStrict
    fromLazyText :: Text -> Text
fromLazyText = forall s. ConvLazyText s => Text -> s
fromLazyText

instance ConvLazyText LT.Text where
    toLazyText :: Text -> Text
toLazyText   = forall a. a -> a
id
    fromLazyText :: Text -> Text
fromLazyText = forall a. a -> a
id

-- |
--
-- This is minimally defined with 'GenStringDefault'.
instance StringRWIO GenString where
    hGetContents :: Handle -> IO GenString
hGetContents Handle
h = ByteString -> GenString
genStringFromConConv forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringRWIO s => Handle -> IO s
hGetContents Handle
h

    hGetLine :: Handle -> IO GenString
hGetLine Handle
h = ByteString -> GenString
genStringFromConConv forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringRWIO s => Handle -> IO s
hGetLine Handle
h

    hPutStr :: Handle -> GenString -> IO ()
hPutStr Handle
h GenString
s = forall s. StringRWIO s => Handle -> s -> IO ()
hPutStr Handle
h (GenString -> ByteString
genStringConConv GenString
s)

    hPutStrLn :: Handle -> GenString -> IO ()
hPutStrLn Handle
h GenString
s = forall s. StringRWIO s => Handle -> s -> IO ()
hPutStrLn Handle
h (GenString -> ByteString
genStringConConv GenString
s)

-- | Type-restricted string conversion used by 'GenString's instance definition for 'StringRWIO'
genStringConConv :: GenString -> GenStringDefault
genStringConConv :: GenString -> ByteString
genStringConConv = forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells

-- | Type-restricted string conversion used by 'GenString's instance definition for 'StringRWIO'
genStringFromConConv :: GenStringDefault -> GenString
genStringFromConConv :: ByteString -> GenString
genStringFromConConv = forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells

-- |
--
-- See 'System.IO for documentation of behaviour.
instance StringRWIO String where
    hGetContents :: Handle -> IO String
hGetContents = Handle -> IO String
IO.hGetContents

    hGetLine :: Handle -> IO String
hGetLine     = Handle -> IO String
IO.hGetLine

    hPutStr :: Handle -> String -> IO ()
hPutStr      = Handle -> String -> IO ()
IO.hPutStr

    hPutStrLn :: Handle -> String -> IO ()
hPutStrLn    = Handle -> String -> IO ()
IO.hPutStrLn

    interact :: (String -> String) -> IO ()
interact     = (String -> String) -> IO ()
IO.interact

    getContents :: IO String
getContents  = IO String
IO.getContents

    getLine :: IO String
getLine      = IO String
IO.getLine

    putStr :: String -> IO ()
putStr       = String -> IO ()
IO.putStr

    putStrLn :: String -> IO ()
putStrLn     = String -> IO ()
IO.putStrLn

    readFile :: String -> IO String
readFile     = String -> IO String
IO.readFile

    writeFile :: String -> String -> IO ()
writeFile    = String -> String -> IO ()
IO.writeFile

    appendFile :: String -> String -> IO ()
appendFile   = String -> String -> IO ()
IO.appendFile

-- |
--
-- See 'Data.ByteString' for documentation of behaviour.
instance StringRWIO S.ByteString where
    hGetContents :: Handle -> IO ByteString
hGetContents = Handle -> IO ByteString
S.hGetContents

    hGetLine :: Handle -> IO ByteString
hGetLine     = Handle -> IO ByteString
S.hGetLine

    hPutStr :: Handle -> ByteString -> IO ()
hPutStr      = Handle -> ByteString -> IO ()
S.hPutStr

    hPutStrLn :: Handle -> ByteString -> IO ()
hPutStrLn    = Handle -> ByteString -> IO ()
SC.hPutStrLn

    interact :: (ByteString -> ByteString) -> IO ()
interact     = (ByteString -> ByteString) -> IO ()
S.interact

    getContents :: IO ByteString
getContents  = IO ByteString
S.getContents

    getLine :: IO ByteString
getLine      = IO ByteString
S.getLine

    putStr :: ByteString -> IO ()
putStr       = ByteString -> IO ()
S.putStr

    putStrLn :: ByteString -> IO ()
putStrLn     = ByteString -> IO ()
SC.putStrLn

    readFile :: String -> IO ByteString
readFile     = String -> IO ByteString
S.readFile

    writeFile :: String -> ByteString -> IO ()
writeFile    = String -> ByteString -> IO ()
S.writeFile

    appendFile :: String -> ByteString -> IO ()
appendFile   = String -> ByteString -> IO ()
S.appendFile

-- |
--
-- See 'Data.ByteString.Lazy' for documentation of behaviour.
--
-- 'hGetLine' and 'getLine' are defined in terms of 'toStringCells' and the equivalent methods of 'Data.ByteString'.
-- 'hPutStrLn' is defined non-atomically: it is defined as an action that puts the string and then separately puts a newline character string.
instance StringRWIO L.ByteString where
    hGetContents :: Handle -> IO ByteString
hGetContents = Handle -> IO ByteString
L.hGetContents

    hGetLine :: Handle -> IO ByteString
hGetLine     = (forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Handle -> IO ByteString
S.hGetLine

    hPutStr :: Handle -> ByteString -> IO ()
hPutStr      = Handle -> ByteString -> IO ()
L.hPutStr

    hPutStrLn :: Handle -> ByteString -> IO ()
hPutStrLn Handle
h  = (forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s. StringRWIO s => Handle -> s -> IO ()
hPutStr Handle
h ((forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells :: String -> L.ByteString) [Char
'\n'])) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringRWIO s => Handle -> s -> IO ()
hPutStr Handle
h

    interact :: (ByteString -> ByteString) -> IO ()
interact     = (ByteString -> ByteString) -> IO ()
L.interact

    getContents :: IO ByteString
getContents  = IO ByteString
L.getContents

    getLine :: IO ByteString
getLine      = forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO ByteString
S.getLine

    putStr :: ByteString -> IO ()
putStr       = ByteString -> IO ()
L.putStr

    putStrLn :: ByteString -> IO ()
putStrLn     = ByteString -> IO ()
LC.putStrLn

    readFile :: String -> IO ByteString
readFile     = String -> IO ByteString
L.readFile

    writeFile :: String -> ByteString -> IO ()
writeFile    = String -> ByteString -> IO ()
L.writeFile

    appendFile :: String -> ByteString -> IO ()
appendFile   = String -> ByteString -> IO ()
L.appendFile

-- |
--
-- See 'Data.Text.IO' for documentation of behaviour.
instance StringRWIO T.Text where
    hGetContents :: Handle -> IO Text
hGetContents = Handle -> IO Text
T.hGetContents

    hGetLine :: Handle -> IO Text
hGetLine     = Handle -> IO Text
T.hGetLine

    hPutStr :: Handle -> Text -> IO ()
hPutStr      = Handle -> Text -> IO ()
T.hPutStr

    hPutStrLn :: Handle -> Text -> IO ()
hPutStrLn    = Handle -> Text -> IO ()
T.hPutStrLn

    interact :: (Text -> Text) -> IO ()
interact     = (Text -> Text) -> IO ()
T.interact

    getContents :: IO Text
getContents  = IO Text
T.getContents

    getLine :: IO Text
getLine      = IO Text
T.getLine

    putStr :: Text -> IO ()
putStr       = Text -> IO ()
T.putStr

    putStrLn :: Text -> IO ()
putStrLn     = Text -> IO ()
T.putStrLn

    readFile :: String -> IO Text
readFile     = String -> IO Text
T.readFile

    writeFile :: String -> Text -> IO ()
writeFile    = String -> Text -> IO ()
T.writeFile

    appendFile :: String -> Text -> IO ()
appendFile   = String -> Text -> IO ()
T.appendFile

-- |
--
-- See 'Data.Text.Lazy.IO' for documentation of behaviour.
instance StringRWIO LT.Text where
    hGetContents :: Handle -> IO Text
hGetContents = Handle -> IO Text
LT.hGetContents

    hGetLine :: Handle -> IO Text
hGetLine     = Handle -> IO Text
LT.hGetLine

    hPutStr :: Handle -> Text -> IO ()
hPutStr      = Handle -> Text -> IO ()
LT.hPutStr

    hPutStrLn :: Handle -> Text -> IO ()
hPutStrLn    = Handle -> Text -> IO ()
LT.hPutStrLn

    interact :: (Text -> Text) -> IO ()
interact     = (Text -> Text) -> IO ()
LT.interact

    getContents :: IO Text
getContents  = IO Text
LT.getContents

    getLine :: IO Text
getLine      = IO Text
LT.getLine

    putStr :: Text -> IO ()
putStr       = Text -> IO ()
LT.putStr

    putStrLn :: Text -> IO ()
putStrLn     = Text -> IO ()
LT.putStrLn

    readFile :: String -> IO Text
readFile     = String -> IO Text
LT.readFile

    writeFile :: String -> Text -> IO ()
writeFile    = String -> Text -> IO ()
LT.writeFile

    appendFile :: String -> Text -> IO ()
appendFile   = String -> Text -> IO ()
LT.appendFile

-- | Polymorphic container of a string
--
-- When operations take place on multiple 'GenString's, they are first
-- converted to the type 'GenStringDefault', which are lazy bytestrings,
-- whenever absolutely necessary (which includes testing for equality,
-- appending strings, concatenating lists of strings, empty strings with
-- 'empty', and unfolding), making them the most efficient type for this
-- polymorphic container.
data GenString = forall s. (Stringy s) => GenString {()
gen_string :: s}
    deriving (Typeable)

toGenDefaultString :: (Stringy s) => s -> GenStringDefault
toGenDefaultString :: forall s. Stringy s => s -> ByteString
toGenDefaultString = forall s s2. (StringCells s, StringCells s2) => s -> s2
toStringCells

instance Eq GenString where
    GenString
_a == :: GenString -> GenString -> Bool
== GenString
_b = case (GenString
_a, GenString
_b) of
        ((GenString s
_a), (GenString s
_b)) -> forall s. Stringy s => s -> ByteString
toGenDefaultString s
_a forall a. Eq a => a -> a -> Bool
== forall s. Stringy s => s -> ByteString
toGenDefaultString s
_b
    GenString
_a /= :: GenString -> GenString -> Bool
/= GenString
_b = case (GenString
_a, GenString
_b) of
        ((GenString s
_a), (GenString s
_b)) -> forall s. Stringy s => s -> ByteString
toGenDefaultString s
_a forall a. Eq a => a -> a -> Bool
/= forall s. Stringy s => s -> ByteString
toGenDefaultString s
_b

instance IsString GenString where
    fromString :: String -> GenString
fromString = forall s. Stringy s => s -> GenString
GenString

instance Semigroup GenString where
    <> :: GenString -> GenString -> GenString
(<>) GenString
a GenString
b = case (GenString
a, GenString
b) of
        (GenString s
_a, GenString s
_b) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> s -> s
append (forall s. Stringy s => s -> ByteString
toGenDefaultString s
_a) (forall s. Stringy s => s -> ByteString
toGenDefaultString s
_b)

instance Monoid GenString where
    mempty :: GenString
mempty  = forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ (forall s. StringCells s => s
empty :: GenStringDefault)
    mappend :: GenString -> GenString -> GenString
mappend = forall a. Semigroup a => a -> a -> a
(<>)
    mconcat :: [GenString] -> GenString
mconcat [GenString]
ss = forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => [s] -> s
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall s. Stringy s => s -> ByteString
toGenDefaultString forall a b. (a -> b) -> a -> b
$ [GenString]
ss

instance StringCells GenString where
    -- These associated types were rather arbitrarily chosen
    type StringCellChar GenString = Char
    type StringCellAltChar GenString = Word8

    toStringCells :: forall s2. StringCells s2 => GenString -> s2
toStringCells   = forall s. ConvGenString s => GenString -> s
fromGenString
    fromStringCells :: forall s2. StringCells s2 => s2 -> GenString
fromStringCells = forall s. ConvGenString s => s -> GenString
toGenString

    cons :: StringCellChar GenString -> GenString -> GenString
cons StringCellChar GenString
c GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => StringCellChar s -> s -> s
cons (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
c) s
_s
    uncons :: GenString -> (StringCellChar GenString, GenString)
uncons GenString
_s = case GenString
_s of
        (GenString s
_s) -> let (StringCellChar s
c, s
s') = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
_s
                          in  (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
c, forall s. Stringy s => s -> GenString
GenString s
s')
    snoc :: GenString -> StringCellChar GenString -> GenString
snoc GenString
_s StringCellChar GenString
c = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> StringCellChar s -> s
snoc s
_s (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
c)
    unsnoc :: GenString -> (GenString, StringCellChar GenString)
unsnoc GenString
_s = case GenString
_s of
        (GenString s
_s) -> let (s
s', StringCellChar s
c) = forall s. StringCells s => s -> (s, StringCellChar s)
unsnoc s
_s
                          in  (forall s. Stringy s => s -> GenString
GenString s
s', GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
c)

    altCons :: StringCellAltChar GenString -> GenString -> GenString
altCons StringCellAltChar GenString
c GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => StringCellChar s -> s -> s
cons (forall c. StringCell c => Word8 -> c
fromWord8 StringCellAltChar GenString
c) s
_s
    altUncons :: GenString -> (StringCellAltChar GenString, GenString)
altUncons GenString
_s = case GenString
_s of
        (GenString s
_s) -> let (StringCellChar s
c, s
s') = forall s. StringCells s => s -> (StringCellChar s, s)
uncons s
_s
                          in  (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar StringCellChar s
c, forall s. Stringy s => s -> GenString
GenString s
s')
    altSnoc :: GenString -> StringCellAltChar GenString -> GenString
altSnoc GenString
_s StringCellAltChar GenString
c = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> StringCellChar s -> s
snoc s
_s (forall c. StringCell c => Word8 -> c
fromWord8 StringCellAltChar GenString
c)
    altUnsnoc :: GenString -> (GenString, StringCellAltChar GenString)
altUnsnoc GenString
_s = case GenString
_s of
        (GenString s
_s) -> let (s
s', StringCellChar s
c) = forall s. StringCells s => s -> (s, StringCellChar s)
unsnoc s
_s
                          in  (forall s. Stringy s => s -> GenString
GenString s
s', GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar StringCellChar s
c)

    toMainChar :: forall c.
StringCell c =>
c -> Tagged GenString (StringCellChar GenString)
toMainChar = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Char
toChar
    toAltChar :: forall c.
StringCell c =>
c -> Tagged GenString (StringCellAltChar GenString)
toAltChar  = forall {k} (s :: k) b. b -> Tagged s b
Tagged forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. StringCell c => c -> Word8
toWord8

    null :: GenString -> Bool
null GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. StringCells s => s -> Bool
null s
_s

    head :: GenString -> StringCellChar GenString
head GenString
_s = case GenString
_s of
        (GenString s
_s) -> GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar (forall s. StringCells s => s -> StringCellChar s
head s
_s)
    tail :: GenString -> GenString
tail GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> s
tail s
_s
    last :: GenString -> StringCellChar GenString
last GenString
_s = case GenString
_s of
        (GenString s
_s) -> GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar (forall s. StringCells s => s -> StringCellChar s
last s
_s)
    init :: GenString -> GenString
init GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => s -> s
init s
_s
    altHead :: GenString -> StringCellAltChar GenString
altHead GenString
_s = case GenString
_s of
        (GenString s
_s) -> GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar (forall s. StringCells s => s -> StringCellChar s
head s
_s)
    altLast :: GenString -> StringCellAltChar GenString
altLast GenString
_s = case GenString
_s of
        (GenString s
_s) -> GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar (forall s. StringCells s => s -> StringCellChar s
last s
_s)

    unfoldr :: forall a.
(a -> Maybe (StringCellChar GenString, a)) -> a -> GenString
unfoldr       a -> Maybe (StringCellChar GenString, a)
f a
z = forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ (forall s a.
StringCells s =>
(a -> Maybe (StringCellAltChar s, a)) -> a -> s
altUnfoldr    a -> Maybe (StringCellChar GenString, a)
f a
z  :: GenStringDefault)
    altUnfoldr :: forall a.
(a -> Maybe (StringCellAltChar GenString, a)) -> a -> GenString
altUnfoldr    a -> Maybe (StringCellAltChar GenString, a)
f a
z = forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ (forall s a.
StringCells s =>
(a -> Maybe (StringCellChar s, a)) -> a -> s
unfoldr       a -> Maybe (StringCellAltChar GenString, a)
f a
z  :: GenStringDefault)
    unfoldrN :: forall a.
Int -> (a -> Maybe (StringCellChar GenString, a)) -> a -> GenString
unfoldrN    Int
n a -> Maybe (StringCellChar GenString, a)
f a
z = forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ (forall s a.
StringCells s =>
Int -> (a -> Maybe (StringCellAltChar s, a)) -> a -> s
altUnfoldrN Int
n a -> Maybe (StringCellChar GenString, a)
f a
z  :: GenStringDefault)
    altUnfoldrN :: forall a.
Int
-> (a -> Maybe (StringCellAltChar GenString, a)) -> a -> GenString
altUnfoldrN Int
n a -> Maybe (StringCellAltChar GenString, a)
f a
z = forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ (forall s a.
StringCells s =>
Int -> (a -> Maybe (StringCellChar s, a)) -> a -> s
unfoldrN    Int
n a -> Maybe (StringCellAltChar GenString, a)
f a
z  :: GenStringDefault)

    index :: GenString -> Int -> StringCellChar GenString
index GenString
_s Int
i = case GenString
_s of
        (GenString s
_s) -> GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar (forall s. StringCells s => s -> Int -> StringCellChar s
index s
_s Int
i)
    index64 :: GenString -> Int64 -> StringCellChar GenString
index64 GenString
_s Int64
i = case GenString
_s of
        (GenString s
_s) -> GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar (forall s. StringCells s => s -> Int64 -> StringCellChar s
index64 s
_s Int64
i)
    genericIndex :: forall i. Integral i => GenString -> i -> StringCellChar GenString
genericIndex GenString
_s i
i = case GenString
_s of
        (GenString s
_s) -> GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar (forall s i.
(StringCells s, Integral i) =>
s -> i -> StringCellChar s
genericIndex s
_s i
i)

    take :: Int -> GenString -> GenString
take Int
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => Int -> s -> s
take Int
n s
_s
    take64 :: Int64 -> GenString -> GenString
take64 Int64
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => Int64 -> s -> s
take64 Int64
n s
_s
    genericTake :: forall b. Integral b => b -> GenString -> GenString
genericTake i
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s i. (StringCells s, Integral i) => i -> s -> s
genericTake i
n s
_s
    drop :: Int -> GenString -> GenString
drop Int
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => Int -> s -> s
drop Int
n s
_s
    drop64 :: Int64 -> GenString -> GenString
drop64 Int64
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s. StringCells s => Int64 -> s -> s
drop64 Int64
n s
_s
    genericDrop :: forall b. Integral b => b -> GenString -> GenString
genericDrop i
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s i. (StringCells s, Integral i) => i -> s -> s
genericDrop i
n s
_s

    length :: GenString -> Int
length GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. StringCells s => s -> Int
length s
_s
    length64 :: GenString -> Int64
length64 GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. StringCells s => s -> Int64
length64 s
_s
    genericLength :: forall i. Integral i => GenString -> i
genericLength GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s i. (StringCells s, Integral i) => s -> i
genericLength s
_s

    safeUncons :: GenString -> Maybe (StringCellChar GenString, GenString)
safeUncons GenString
_s = case GenString
_s of
        (GenString s
_s) -> (\(StringCellChar s
c, s
s') -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
c, forall s. Stringy s => s -> GenString
GenString s
s')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe (StringCellChar s, s)
safeUncons s
_s
    safeUnsnoc :: GenString -> Maybe (GenString, StringCellChar GenString)
safeUnsnoc GenString
_s = case GenString
_s of
        (GenString s
_s) -> (\(s
s', StringCellChar s
c) -> (forall s. Stringy s => s -> GenString
GenString s
s', GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
c)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe (s, StringCellChar s)
safeUnsnoc s
_s
    safeAltUncons :: GenString -> Maybe (StringCellAltChar GenString, GenString)
safeAltUncons GenString
_s = case GenString
_s of
        (GenString s
_s) -> (\(StringCellAltChar s
c, s
s') -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar StringCellAltChar s
c, forall s. Stringy s => s -> GenString
GenString s
s')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe (StringCellAltChar s, s)
safeAltUncons s
_s
    safeAltUnsnoc :: GenString -> Maybe (GenString, StringCellAltChar GenString)
safeAltUnsnoc GenString
_s = case GenString
_s of
        (GenString s
_s) -> (\(s
s', StringCellAltChar s
c) -> (forall s. Stringy s => s -> GenString
GenString s
s', GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar StringCellAltChar s
c)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe (s, StringCellAltChar s)
safeAltUnsnoc s
_s
    safeHead :: GenString -> Maybe (StringCellChar GenString)
safeHead GenString
_s = case GenString
_s of
        (GenString s
_s) -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe (StringCellChar s)
safeHead s
_s
    safeTail :: GenString -> Maybe GenString
safeTail GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe s
safeTail s
_s
    safeLast :: GenString -> Maybe (StringCellChar GenString)
safeLast GenString
_s = case GenString
_s of
        (GenString s
_s) -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe (StringCellChar s)
safeLast s
_s
    safeInit :: GenString -> Maybe GenString
safeInit GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe s
safeInit s
_s
    safeAltHead :: GenString -> Maybe (StringCellAltChar GenString)
safeAltHead GenString
_s = case GenString
_s of
        (GenString s
_s) -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe (StringCellAltChar s)
safeAltHead s
_s
    safeAltLast :: GenString -> Maybe (StringCellAltChar GenString)
safeAltLast GenString
_s = case GenString
_s of
        (GenString s
_s) -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellAltChar s)
toAltChar  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Maybe (StringCellAltChar s)
safeAltLast s
_s
    safeIndex :: GenString -> Int -> Maybe (StringCellChar GenString)
safeIndex GenString
_s Int
i = case GenString
_s of
        (GenString s
_s) -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Int -> Maybe (StringCellChar s)
safeIndex s
_s Int
i
    safeIndex64 :: GenString -> Int64 -> Maybe (StringCellChar GenString)
safeIndex64 GenString
_s Int64
i = case GenString
_s of
        (GenString s
_s) -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => s -> Int64 -> Maybe (StringCellChar s)
safeIndex64 s
_s Int64
i
    safeGenericIndex :: forall i.
Integral i =>
GenString -> i -> Maybe (StringCellChar GenString)
safeGenericIndex GenString
_s i
i = case GenString
_s of
        (GenString s
_s) -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf`) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s i.
(StringCells s, Integral i) =>
s -> i -> Maybe (StringCellChar s)
safeGenericIndex s
_s i
i
    safeTake :: Int -> GenString -> Maybe GenString
safeTake Int
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => Int -> s -> Maybe s
safeTake Int
n s
_s
    safeTake64 :: Int64 -> GenString -> Maybe GenString
safeTake64 Int64
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => Int64 -> s -> Maybe s
safeTake64 Int64
n s
_s
    safeGenericTake :: forall i. Integral i => i -> GenString -> Maybe GenString
safeGenericTake i
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s i. (StringCells s, Integral i) => i -> s -> Maybe s
safeGenericTake i
n s
_s
    safeDrop :: Int -> GenString -> Maybe GenString
safeDrop Int
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => Int -> s -> Maybe s
safeDrop Int
n s
_s
    safeDrop64 :: Int64 -> GenString -> Maybe GenString
safeDrop64 Int64
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. StringCells s => Int64 -> s -> Maybe s
safeDrop64 Int64
n s
_s
    safeGenericDrop :: forall i. Integral i => i -> GenString -> Maybe GenString
safeGenericDrop i
n GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s i. (StringCells s, Integral i) => i -> s -> Maybe s
safeGenericDrop i
n s
_s
    safeUncons2 :: GenString
-> Maybe
     (StringCellChar GenString, StringCellChar GenString, GenString)
safeUncons2 GenString
_s = case GenString
_s of
        (GenString s
_s) -> (\(StringCellChar s
a, StringCellChar s
b, s
s') -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
a, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
b, forall s. Stringy s => s -> GenString
GenString s
s')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s.
StringCells s =>
s -> Maybe (StringCellChar s, StringCellChar s, s)
safeUncons2 s
_s
    safeUncons3 :: GenString
-> Maybe
     (StringCellChar GenString, StringCellChar GenString,
      StringCellChar GenString, GenString)
safeUncons3 GenString
_s = case GenString
_s of
        (GenString s
_s) -> (\(StringCellChar s
a, StringCellChar s
b, StringCellChar s
c, s
s') -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
a, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
b, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
c, forall s. Stringy s => s -> GenString
GenString s
s')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s.
StringCells s =>
s
-> Maybe (StringCellChar s, StringCellChar s, StringCellChar s, s)
safeUncons3 s
_s
    safeUncons4 :: GenString
-> Maybe
     (StringCellChar GenString, StringCellChar GenString,
      StringCellChar GenString, StringCellChar GenString, GenString)
safeUncons4 GenString
_s = case GenString
_s of
        (GenString s
_s) -> (\(StringCellChar s
a, StringCellChar s
b, StringCellChar s
c, StringCellChar s
d, s
s') -> (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
a, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
b, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
c, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
d, forall s. Stringy s => s -> GenString
GenString s
s')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s.
StringCells s =>
s
-> Maybe
     (StringCellChar s, StringCellChar s, StringCellChar s,
      StringCellChar s, s)
safeUncons4 s
_s

    cons2 :: StringCellChar GenString
-> StringCellChar GenString -> GenString -> GenString
cons2 StringCellChar GenString
a StringCellChar GenString
b GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s.
StringCells s =>
StringCellChar s -> StringCellChar s -> s -> s
cons2 (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
a) (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
b) s
_s
    cons3 :: StringCellChar GenString
-> StringCellChar GenString
-> StringCellChar GenString
-> GenString
-> GenString
cons3 StringCellChar GenString
a StringCellChar GenString
b StringCellChar GenString
c GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s.
StringCells s =>
StringCellChar s -> StringCellChar s -> StringCellChar s -> s -> s
cons3 (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
a) (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
b) (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
c) s
_s
    cons4 :: StringCellChar GenString
-> StringCellChar GenString
-> StringCellChar GenString
-> StringCellChar GenString
-> GenString
-> GenString
cons4 StringCellChar GenString
a StringCellChar GenString
b StringCellChar GenString
c StringCellChar GenString
d GenString
_s = case GenString
_s of
        (GenString s
_s) -> forall s. Stringy s => s -> GenString
GenString forall a b. (a -> b) -> a -> b
$ forall s.
StringCells s =>
StringCellChar s
-> StringCellChar s
-> StringCellChar s
-> StringCellChar s
-> s
-> s
cons4 (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
a) (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
b) (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
c) (s
_s forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar GenString
d) s
_s
    uncons2 :: GenString
-> (StringCellChar GenString, StringCellChar GenString, GenString)
uncons2 GenString
_s = case GenString
_s of
        (GenString s
_s) -> let (StringCellChar s
a, StringCellChar s
b, s
s') = forall s.
StringCells s =>
s -> (StringCellChar s, StringCellChar s, s)
uncons2 s
_s
                          in  (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
a, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
b, forall s. Stringy s => s -> GenString
GenString s
s')
    uncons3 :: GenString
-> (StringCellChar GenString, StringCellChar GenString,
    StringCellChar GenString, GenString)
uncons3 GenString
_s = case GenString
_s of
        (GenString s
_s) -> let (StringCellChar s
a, StringCellChar s
b, StringCellChar s
c, s
s') = forall s.
StringCells s =>
s -> (StringCellChar s, StringCellChar s, StringCellChar s, s)
uncons3 s
_s
                          in  (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
a, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
b, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
c, forall s. Stringy s => s -> GenString
GenString s
s')
    uncons4 :: GenString
-> (StringCellChar GenString, StringCellChar GenString,
    StringCellChar GenString, StringCellChar GenString, GenString)
uncons4 GenString
_s = case GenString
_s of
        (GenString s
_s) -> let (StringCellChar s
a, StringCellChar s
b, StringCellChar s
c, StringCellChar s
d, s
s') = forall s.
StringCells s =>
s
-> (StringCellChar s, StringCellChar s, StringCellChar s,
    StringCellChar s, s)
uncons4 s
_s
                          in  (GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
a, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
b, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
c, GenString
genStringPhantom forall s b. s -> Tagged s b -> b
`untagTypeOf` forall s c.
(StringCells s, StringCell c) =>
c -> Tagged s (StringCellChar s)
toMainChar StringCellChar s
d, forall s. Stringy s => s -> GenString
GenString s
s')

-- | Untag a type with a type restriction
--
-- The first argument is guaranteed to be ignored; thus the value 'undefined'
-- can be passed in its place.
untagTypeOf :: s -> Tagged s b -> b
untagTypeOf :: forall s b. s -> Tagged s b -> b
untagTypeOf s
_ = forall {k} (s :: k) b. Tagged s b -> b
untag

-- | Phantom, undefined value only used for convenience
--
-- Users should be careful that this value is never evaluated when using this.
genStringPhantom :: GenString
genStringPhantom :: GenString
genStringPhantom = forall a. HasCallStack => a
undefined

-- | This type is used by 'GenString' when a concrete string type is needed
type GenStringDefault = L.ByteString