{- 
    Copyright 2013-2017 Mario Blazevic

    License: BSD3 (see BSD3-LICENSE.txt file)
-}

-- | This module defines the 'TextualMonoid' class and several of its instances.
-- 

{-# LANGUAGE Haskell2010, FlexibleInstances #-}

module Data.Monoid.Textual (
   TextualMonoid(..)
   )
where

import qualified Data.Foldable as Foldable
import qualified Data.Traversable as Traversable
import Data.Functor -- ((<$>))
import qualified Data.List as List
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LazyText
import Data.Text (Text)
import Data.Monoid -- (Monoid(mappend, mempty))
import qualified Data.Sequence as Sequence
import Data.String (IsString(fromString))
import Data.Int (Int64)

import Data.Semigroup.Cancellative (LeftReductive)
import Data.Monoid.GCD (LeftGCDMonoid)
import Data.Monoid.Factorial (FactorialMonoid)
import qualified Data.Monoid.Factorial as Factorial

import Prelude hiding (all, any, break, concatMap, dropWhile, foldl, foldl1, foldr, foldr1, map,
                       scanl, scanl1, scanr, scanr1, span, takeWhile)

-- | The 'TextualMonoid' class is an extension of 'FactorialMonoid' specialized for monoids that can contain
-- characters. Its methods are generally equivalent to their namesake functions from "Data.List" and "Data.Text", and
-- they satisfy the following laws:
-- 
-- > unfoldr splitCharacterPrefix . fromString == id
-- > splitCharacterPrefix . primePrefix == fmap (\(c, t)-> (c, mempty)) . splitCharacterPrefix
-- >
-- > map f . fromString == fromString . List.map f
-- > concatMap (fromString . f) . fromString == fromString . List.concatMap f
-- >
-- > foldl  ft fc a . fromString == List.foldl  fc a
-- > foldr  ft fc a . fromString == List.foldr  fc a
-- > foldl' ft fc a . fromString == List.foldl' fc a
-- >
-- > scanl f c . fromString == fromString . List.scanl f c
-- > scanr f c . fromString == fromString . List.scanr f c
-- > mapAccumL f a . fromString == fmap fromString . List.mapAccumL f a
-- > mapAccumL f a . fromString == fmap fromString . List.mapAccumL f a
-- >
-- > takeWhile pt pc . fromString == fromString . takeWhile pc
-- > dropWhile pt pc . fromString == fromString . dropWhile pc
-- >
-- > mconcat . intersperse (singleton c) . split (== c) == id
-- > find p . fromString == List.find p
-- > elem c . fromString == List.elem c
--
-- A 'TextualMonoid' may contain non-character data insterspersed between its characters. Every class method that
-- returns a modified 'TextualMonoid' instance generally preserves this non-character data. Methods like 'foldr' can
-- access both the non-character and character data and expect two arguments for the two purposes. For each of these
-- methods there is also a simplified version with underscore in name (like 'foldr_') that ignores the non-character
-- data.
--
-- All of the following expressions are identities:
--
-- > map id
-- > concatMap singleton
-- > foldl  (<>) (\a c-> a <> singleton c) mempty
-- > foldr  (<>) ((<>) . singleton) mempty
-- > foldl' (<>) (\a c-> a <> singleton c) mempty
-- > scanl1 (const id)
-- > scanr1 const
-- > uncurry (mapAccumL (,))
-- > uncurry (mapAccumR (,))
-- > takeWhile (const True) (const True)
-- > dropWhile (const False) (const False)
-- > toString undefined . fromString
-- > toText undefined . fromText

class (IsString t, LeftReductive t, LeftGCDMonoid t, FactorialMonoid t) => TextualMonoid t where
   -- | Contructs a new data type instance Like 'fromString', but from a 'Text' input instead of 'String'.
   --
   -- > fromText == fromString . Text.unpack
   fromText :: Text -> t
   -- | Creates a prime monoid containing a single character.
   --
   -- > singleton c == fromString [c]
   singleton :: Char -> t
   -- | Specialized version of 'Factorial.splitPrimePrefix'. Every prime factor of a textual monoid must consist of a
   -- single character or no character at all.
   splitCharacterPrefix :: t -> Maybe (Char, t)
   -- | Extracts a single character that prefixes the monoid, if the monoid begins with a character. Otherwise returns
   -- 'Nothing'.
   --
   -- > characterPrefix == fmap fst . splitCharacterPrefix
   characterPrefix :: t -> Maybe Char
   -- | Equivalent to 'List.map' from "Data.List" with a @Char -> Char@ function. Preserves all non-character data.
   --
   -- > map f == concatMap (singleton . f)
   map :: (Char -> Char) -> t -> t
   -- | Equivalent to 'List.concatMap' from "Data.List" with a @Char -> String@ function. Preserves all non-character
   -- data.
   concatMap :: (Char -> t) -> t -> t
   -- | Returns the list of characters the monoid contains, once the argument function converts all its non-character
   -- factors into characters.
   toString :: (t -> String) -> t -> String
   -- | Converts the monoid into 'Text', given a function to convert the non-character factors into chunks of 'Text'.
   toText :: (t -> Text) -> t -> Text
   -- | Equivalent to 'List.any' from "Data.List". Ignores all non-character data.
   any :: (Char -> Bool) -> t -> Bool
   -- | Equivalent to 'List.all' from "Data.List". Ignores all non-character data.
   all :: (Char -> Bool) -> t -> Bool

   -- | The first argument folds over the non-character prime factors, the second over characters. Otherwise equivalent
   -- to 'List.foldl' from "Data.List".
   foldl   :: (a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
   -- | Strict version of 'foldl'.
   foldl'  :: (a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
   -- | The first argument folds over the non-character prime factors, the second over characters. Otherwise equivalent
   -- to 'List.foldl\'' from "Data.List".
   foldr   :: (t -> a -> a) -> (Char -> a -> a) -> a -> t -> a

   -- | Equivalent to 'List.scanl' from "Data.List" when applied to a 'String', but preserves all non-character data.
   scanl :: (Char -> Char -> Char) -> Char -> t -> t
   -- | Equivalent to 'List.scanl1' from "Data.List" when applied to a 'String', but preserves all non-character data.
   --
   -- > scanl f c == scanl1 f . (singleton c <>)
   scanl1 :: (Char -> Char -> Char) -> t -> t
   -- | Equivalent to 'List.scanr' from "Data.List" when applied to a 'String', but preserves all non-character data.
   scanr :: (Char -> Char -> Char) -> Char -> t -> t
   -- | Equivalent to 'List.scanr1' from "Data.List" when applied to a 'String', but preserves all non-character data.
   --
   -- > scanr f c == scanr1 f . (<> singleton c)
   scanr1 :: (Char -> Char -> Char) -> t -> t
   -- | Equivalent to 'List.mapAccumL' from "Data.List" when applied to a 'String', but preserves all non-character
   -- data.
   mapAccumL :: (a -> Char -> (a, Char)) -> a -> t -> (a, t)
   -- | Equivalent to 'List.mapAccumR' from "Data.List" when applied to a 'String', but preserves all non-character
   -- data.
   mapAccumR :: (a -> Char -> (a, Char)) -> a -> t -> (a, t)

   -- | The first predicate tests the non-character data, the second one the characters. Otherwise equivalent to
   -- 'List.takeWhile' from "Data.List" when applied to a 'String'.
   takeWhile :: (t -> Bool) -> (Char -> Bool) -> t -> t
   -- | The first predicate tests the non-character data, the second one the characters. Otherwise equivalent to
   -- 'List.dropWhile' from "Data.List" when applied to a 'String'.
   dropWhile :: (t -> Bool) -> (Char -> Bool) -> t -> t
   -- | 'break pt pc' is equivalent to @span (not . pt) (not . pc)@.
   break :: (t -> Bool) -> (Char -> Bool) -> t -> (t, t)
   -- | 'span pt pc t' is equivalent to @(takeWhile pt pc t, dropWhile pt pc t)@.
   span :: (t -> Bool) -> (Char -> Bool) -> t -> (t, t)
   -- | A stateful variant of 'span', threading the result of the test function as long as it returns 'Just'.
   spanMaybe :: s -> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
   -- | Strict version of 'spanMaybe'.
   spanMaybe' :: s -> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
   -- | Splits the monoid into components delimited by character separators satisfying the given predicate. The
   -- characters satisfying the predicate are not a part of the result.
   --
   -- > split p == Factorial.split (maybe False p . characterPrefix)
   split :: (Char -> Bool) -> t -> [t]
   -- | Like 'List.find' from "Data.List" when applied to a 'String'. Ignores non-character data.
   find :: (Char -> Bool) -> t -> Maybe Char
   -- | Like 'List.elem' from "Data.List" when applied to a 'String'. Ignores non-character data.
   elem :: Char -> t -> Bool

   -- | > foldl_ = foldl const
   foldl_   :: (a -> Char -> a) -> a -> t -> a
   foldl_'  :: (a -> Char -> a) -> a -> t -> a
   foldr_   :: (Char -> a -> a) -> a -> t -> a
   -- | > takeWhile_ = takeWhile . const
   takeWhile_ :: Bool -> (Char -> Bool) -> t -> t
   -- | > dropWhile_ = dropWhile . const
   dropWhile_ :: Bool -> (Char -> Bool) -> t -> t
   -- | > break_ = break . const
   break_ :: Bool -> (Char -> Bool) -> t -> (t, t)
   -- | > span_ = span . const
   span_ :: Bool -> (Char -> Bool) -> t -> (t, t)
   -- | > spanMaybe_ s = spanMaybe s (const . Just)
   spanMaybe_ :: s -> (s -> Char -> Maybe s) -> t -> (t, t, s)
   spanMaybe_' :: s -> (s -> Char -> Maybe s) -> t -> (t, t, s)


   fromText = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack
   singleton = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[])

   characterPrefix = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. TextualMonoid t => t -> Maybe (Char, t)
splitCharacterPrefix

   map Char -> Char
f = forall t. TextualMonoid t => (Char -> t) -> t -> t
concatMap (forall t. TextualMonoid t => Char -> t
singleton forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Char
f)
   concatMap Char -> t
f = forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr forall a. Monoid a => a -> a -> a
mappend (forall a. Monoid a => a -> a -> a
mappend forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> t
f) forall a. Monoid a => a
mempty
   toString t -> String
f = forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr (forall a. Monoid a => a -> a -> a
mappend forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> String
f) (:) []
   toText t -> Text
f = String -> Text
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. TextualMonoid t => (t -> String) -> t -> String
toString (Text -> String
Text.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Text
f)
   all Char -> Bool
p = forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr (forall a b. a -> b -> a
const forall a. a -> a
id) (Bool -> Bool -> Bool
(&&) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) Bool
True
   any Char -> Bool
p = forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr (forall a b. a -> b -> a
const forall a. a -> a
id) (Bool -> Bool -> Bool
(||) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) Bool
False

   foldl a -> t -> a
ft a -> Char -> a
fc = forall m a. Factorial m => (a -> m -> a) -> a -> m -> a
Factorial.foldl (\a
a t
prime-> forall b a. b -> (a -> b) -> Maybe a -> b
maybe (a -> t -> a
ft a
a t
prime) (a -> Char -> a
fc a
a) (forall t. TextualMonoid t => t -> Maybe Char
characterPrefix t
prime))
   foldr t -> a -> a
ft Char -> a -> a
fc = forall m a. Factorial m => (m -> a -> a) -> a -> m -> a
Factorial.foldr (\t
prime-> forall b a. b -> (a -> b) -> Maybe a -> b
maybe (t -> a -> a
ft t
prime) Char -> a -> a
fc (forall t. TextualMonoid t => t -> Maybe Char
characterPrefix t
prime))
   foldl' a -> t -> a
ft a -> Char -> a
fc = forall m a. Factorial m => (a -> m -> a) -> a -> m -> a
Factorial.foldl' (\a
a t
prime-> forall b a. b -> (a -> b) -> Maybe a -> b
maybe (a -> t -> a
ft a
a t
prime) (a -> Char -> a
fc a
a) (forall t. TextualMonoid t => t -> Maybe Char
characterPrefix t
prime))
   foldl_ = forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
foldl forall a b. a -> b -> a
const
   foldr_ = forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr (forall a b. a -> b -> a
const forall a. a -> a
id)
   foldl_' = forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
foldl' forall a b. a -> b -> a
const

   scanl Char -> Char -> Char
f Char
c = forall a. Monoid a => a -> a -> a
mappend (forall t. TextualMonoid t => Char -> t
singleton Char
c) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
foldl forall t. Monoid t => (t, Char) -> t -> (t, Char)
foldlOther (forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> (t, Char) -> Char -> (t, Char)
foldlChars Char -> Char -> Char
f) (forall a. Monoid a => a
mempty, Char
c)
   scanl1 Char -> Char -> Char
f t
t = case (forall m. FactorialMonoid m => m -> Maybe (m, m)
Factorial.splitPrimePrefix t
t, forall t. TextualMonoid t => t -> Maybe (Char, t)
splitCharacterPrefix t
t)
                of (Maybe (t, t)
Nothing, Maybe (Char, t)
_) -> t
t
                   (Just (t
prefix, t
suffix), Maybe (Char, t)
Nothing) -> forall a. Monoid a => a -> a -> a
mappend t
prefix (forall t. TextualMonoid t => (Char -> Char -> Char) -> t -> t
scanl1 Char -> Char -> Char
f t
suffix)
                   (Just (t, t)
_, Just (Char
c, t
suffix)) -> forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> Char -> t -> t
scanl Char -> Char -> Char
f Char
c t
suffix
   scanr Char -> Char -> Char
f Char
c = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr forall t a. Monoid t => t -> (t, a) -> (t, a)
foldrOther (forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> Char -> (t, Char) -> (t, Char)
foldrChars Char -> Char -> Char
f) (forall t. TextualMonoid t => Char -> t
singleton Char
c, Char
c)
   scanr1 Char -> Char -> Char
f = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr forall t a. Monoid t => t -> (t, a) -> (t, a)
foldrOther forall {a}.
TextualMonoid a =>
Char -> (a, Maybe Char) -> (a, Maybe Char)
fc (forall a. Monoid a => a
mempty, forall a. Maybe a
Nothing)
      where fc :: Char -> (a, Maybe Char) -> (a, Maybe Char)
fc Char
c (a
t, Maybe Char
Nothing) = (forall a. Monoid a => a -> a -> a
mappend (forall t. TextualMonoid t => Char -> t
singleton Char
c) a
t, forall a. a -> Maybe a
Just Char
c)
            fc Char
c1 (a
t, Just Char
c2) = (forall a. Monoid a => a -> a -> a
mappend (forall t. TextualMonoid t => Char -> t
singleton Char
c') a
t, forall a. a -> Maybe a
Just Char
c')
               where c' :: Char
c' = Char -> Char -> Char
f Char
c1 Char
c2
   mapAccumL a -> Char -> (a, Char)
f a
a0 = forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
foldl forall {b} {a}. Monoid b => (a, b) -> b -> (a, b)
ft forall {b}. TextualMonoid b => (a, b) -> Char -> (a, b)
fc (a
a0, forall a. Monoid a => a
mempty)
      where ft :: (a, b) -> b -> (a, b)
ft (a
a, b
t1) b
t2 = (a
a, forall a. Monoid a => a -> a -> a
mappend b
t1 b
t2)
            fc :: (a, b) -> Char -> (a, b)
fc (a
a, b
t) Char
c = (a
a', forall a. Monoid a => a -> a -> a
mappend b
t (forall t. TextualMonoid t => Char -> t
singleton Char
c'))
               where (a
a', Char
c') = a -> Char -> (a, Char)
f a
a Char
c
   mapAccumR a -> Char -> (a, Char)
f a
a0 = forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr forall {b} {a}. Monoid b => b -> (a, b) -> (a, b)
ft forall {b}. TextualMonoid b => Char -> (a, b) -> (a, b)
fc (a
a0, forall a. Monoid a => a
mempty)
      where ft :: b -> (a, b) -> (a, b)
ft b
t1 (a
a, b
t2) = (a
a, forall a. Monoid a => a -> a -> a
mappend b
t1 b
t2)
            fc :: Char -> (a, b) -> (a, b)
fc Char
c (a
a, b
t) = (a
a', forall a. Monoid a => a -> a -> a
mappend (forall t. TextualMonoid t => Char -> t
singleton Char
c') b
t)
               where (a
a', Char
c') = a -> Char -> (a, Char)
f a
a Char
c

   takeWhile t -> Bool
pt Char -> Bool
pc = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t.
TextualMonoid t =>
(t -> Bool) -> (Char -> Bool) -> t -> (t, t)
span t -> Bool
pt Char -> Bool
pc
   dropWhile t -> Bool
pt Char -> Bool
pc = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t.
TextualMonoid t =>
(t -> Bool) -> (Char -> Bool) -> t -> (t, t)
span t -> Bool
pt Char -> Bool
pc
   span t -> Bool
pt Char -> Bool
pc = forall m. FactorialMonoid m => (m -> Bool) -> m -> (m, m)
Factorial.span (\t
prime-> forall b a. b -> (a -> b) -> Maybe a -> b
maybe (t -> Bool
pt t
prime) Char -> Bool
pc (forall t. TextualMonoid t => t -> Maybe Char
characterPrefix t
prime))
   break t -> Bool
pt Char -> Bool
pc = forall m. FactorialMonoid m => (m -> Bool) -> m -> (m, m)
Factorial.break (\t
prime-> forall b a. b -> (a -> b) -> Maybe a -> b
maybe (t -> Bool
pt t
prime) Char -> Bool
pc (forall t. TextualMonoid t => t -> Maybe Char
characterPrefix t
prime))
   spanMaybe s
s0 s -> t -> Maybe s
ft s -> Char -> Maybe s
fc t
t0 = (t -> t) -> s -> t -> (t, t, s)
spanAfter forall a. a -> a
id s
s0 t
t0
      where spanAfter :: (t -> t) -> s -> t -> (t, t, s)
spanAfter t -> t
g s
s t
t = case forall m. FactorialMonoid m => m -> Maybe (m, m)
Factorial.splitPrimePrefix t
t
                              of Just (t
prime, t
rest) | Just s
s' <- forall b a. b -> (a -> b) -> Maybe a -> b
maybe (s -> t -> Maybe s
ft s
s t
prime) (s -> Char -> Maybe s
fc s
s) (forall t. TextualMonoid t => t -> Maybe Char
characterPrefix t
prime) ->
                                                        (t -> t) -> s -> t -> (t, t, s)
spanAfter (t -> t
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => a -> a -> a
mappend t
prime) s
s' t
rest
                                                    | Bool
otherwise -> (t -> t
g forall a. Monoid a => a
mempty, t
t, s
s)
                                 Maybe (t, t)
Nothing -> (t
t0, t
t, s
s)
   spanMaybe' s
s0 s -> t -> Maybe s
ft s -> Char -> Maybe s
fc t
t0 = (t -> t) -> s -> t -> (t, t, s)
spanAfter forall a. a -> a
id s
s0 t
t0
      where spanAfter :: (t -> t) -> s -> t -> (t, t, s)
spanAfter t -> t
g s
s t
t = seq :: forall a b. a -> b -> b
seq s
s forall a b. (a -> b) -> a -> b
$
                              case forall m. FactorialMonoid m => m -> Maybe (m, m)
Factorial.splitPrimePrefix t
t
                              of Just (t
prime, t
rest) | Just s
s' <- forall b a. b -> (a -> b) -> Maybe a -> b
maybe (s -> t -> Maybe s
ft s
s t
prime) (s -> Char -> Maybe s
fc s
s) (forall t. TextualMonoid t => t -> Maybe Char
characterPrefix t
prime) ->
                                                        (t -> t) -> s -> t -> (t, t, s)
spanAfter (t -> t
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => a -> a -> a
mappend t
prime) s
s' t
rest
                                                    | Bool
otherwise -> (t -> t
g forall a. Monoid a => a
mempty, t
t, s
s)
                                 Maybe (t, t)
Nothing -> (t
t0, t
t, s
s)
   takeWhile_ = forall t.
TextualMonoid t =>
(t -> Bool) -> (Char -> Bool) -> t -> t
takeWhile forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const
   dropWhile_ = forall t.
TextualMonoid t =>
(t -> Bool) -> (Char -> Bool) -> t -> t
dropWhile forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const
   break_ = forall t.
TextualMonoid t =>
(t -> Bool) -> (Char -> Bool) -> t -> (t, t)
break forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const
   span_ = forall t.
TextualMonoid t =>
(t -> Bool) -> (Char -> Bool) -> t -> (t, t)
span forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const
   spanMaybe_ s
s = forall t s.
TextualMonoid t =>
s
-> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
spanMaybe s
s (forall a b. a -> b -> a
const forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just)
   spanMaybe_' s
s = forall t s.
TextualMonoid t =>
s
-> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
spanMaybe' s
s (forall a b. a -> b -> a
const forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just)

   split Char -> Bool
p t
m = t
prefix forall a. a -> [a] -> [a]
: [t]
splitRest
      where (t
prefix, t
rest) = forall t.
TextualMonoid t =>
(t -> Bool) -> (Char -> Bool) -> t -> (t, t)
break (forall a b. a -> b -> a
const Bool
False) Char -> Bool
p t
m
            splitRest :: [t]
splitRest = case forall t. TextualMonoid t => t -> Maybe (Char, t)
splitCharacterPrefix t
rest
                        of Maybe (Char, t)
Nothing -> []
                           Just (Char
_, t
tl) -> forall t. TextualMonoid t => (Char -> Bool) -> t -> [t]
split Char -> Bool
p t
tl
   find Char -> Bool
p = forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
foldr (forall a b. a -> b -> a
const forall a. a -> a
id) (\Char
c Maybe Char
r-> if Char -> Bool
p Char
c then forall a. a -> Maybe a
Just Char
c else Maybe Char
r) forall a. Maybe a
Nothing
   elem Char
c = forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
any (forall a. Eq a => a -> a -> Bool
== Char
c)

   {-# INLINE characterPrefix #-}
   {-# INLINE concatMap #-}
   {-# INLINE dropWhile #-}
   {-# INLINE fromText #-}
   {-# INLINE map #-}
   {-# INLINE mapAccumL #-}
   {-# INLINE mapAccumR #-}
   {-# INLINE scanl #-}
   {-# INLINE scanl1 #-}
   {-# INLINE scanr #-}
   {-# INLINE scanr1 #-}
   {-# INLINE singleton #-}
   {-# INLINE spanMaybe #-}
   {-# INLINE spanMaybe' #-}
   {-# INLINE split #-}
   {-# INLINE takeWhile #-}
   {-# INLINE foldl_ #-}
   {-# INLINE foldl_' #-}
   {-# INLINE foldr_ #-}
   {-# INLINABLE spanMaybe_ #-}
   {-# INLINABLE spanMaybe_' #-}
   {-# INLINE span_ #-}
   {-# INLINE break_ #-}
   {-# INLINE takeWhile_ #-}
   {-# INLINE dropWhile_ #-}
   {-# INLINE elem #-}
   {-# INLINABLE all #-}
   {-# INLINABLE any #-}
   {-# MINIMAL splitCharacterPrefix #-}

foldlChars :: TextualMonoid t => (Char -> Char -> Char) -> (t, Char) -> Char -> (t, Char)
foldlOther :: Monoid t => (t, Char) -> t -> (t, Char)
foldrChars :: TextualMonoid t => (Char -> Char -> Char) -> Char -> (t, Char) -> (t, Char)
foldrOther :: Monoid t => t -> (t, a) -> (t, a)
foldlChars :: forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> (t, Char) -> Char -> (t, Char)
foldlChars Char -> Char -> Char
f (t
t, Char
c1) Char
c2 = (forall a. Monoid a => a -> a -> a
mappend t
t (forall t. TextualMonoid t => Char -> t
singleton Char
c'), Char
c')
   where c' :: Char
c' = Char -> Char -> Char
f Char
c1 Char
c2
foldlOther :: forall t. Monoid t => (t, Char) -> t -> (t, Char)
foldlOther (t
t1, Char
c) t
t2 = (forall a. Monoid a => a -> a -> a
mappend t
t1 t
t2, Char
c)
foldrChars :: forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> Char -> (t, Char) -> (t, Char)
foldrChars Char -> Char -> Char
f Char
c1 (t
t, Char
c2) = (forall a. Monoid a => a -> a -> a
mappend (forall t. TextualMonoid t => Char -> t
singleton Char
c') t
t, Char
c')
   where c' :: Char
c' = Char -> Char -> Char
f Char
c1 Char
c2
foldrOther :: forall t a. Monoid t => t -> (t, a) -> (t, a)
foldrOther t
t1 (t
t2, a
c) = (forall a. Monoid a => a -> a -> a
mappend t
t1 t
t2, a
c)

instance TextualMonoid String where
   fromText :: Text -> String
fromText = Text -> String
Text.unpack
   singleton :: Char -> String
singleton Char
c = [Char
c]
   splitCharacterPrefix :: String -> Maybe (Char, String)
splitCharacterPrefix (Char
c:String
rest) = forall a. a -> Maybe a
Just (Char
c, String
rest)
   splitCharacterPrefix [] = forall a. Maybe a
Nothing
   characterPrefix :: String -> Maybe Char
characterPrefix (Char
c:String
_) = forall a. a -> Maybe a
Just Char
c
   characterPrefix [] = forall a. Maybe a
Nothing
   map :: (Char -> Char) -> String -> String
map = forall a b. (a -> b) -> [a] -> [b]
List.map
   concatMap :: (Char -> String) -> String -> String
concatMap = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
List.concatMap
   toString :: (String -> String) -> String -> String
toString = forall a b. a -> b -> a
const forall a. a -> a
id
   any :: (Char -> Bool) -> String -> Bool
any = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
List.any
   all :: (Char -> Bool) -> String -> Bool
all = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
List.all

   foldl :: forall a.
(a -> String -> a) -> (a -> Char -> a) -> a -> String -> a
foldl   = forall a b. a -> b -> a
const forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl
   foldl' :: forall a.
(a -> String -> a) -> (a -> Char -> a) -> a -> String -> a
foldl'  = forall a b. a -> b -> a
const forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl'
   foldr :: forall a.
(String -> a -> a) -> (Char -> a -> a) -> a -> String -> a
foldr   = forall a b. a -> b -> a
const forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
List.foldr

   scanl :: (Char -> Char -> Char) -> Char -> String -> String
scanl = forall b a. (b -> a -> b) -> b -> [a] -> [b]
List.scanl
   scanl1 :: (Char -> Char -> Char) -> String -> String
scanl1 = forall a. (a -> a -> a) -> [a] -> [a]
List.scanl1
   scanr :: (Char -> Char -> Char) -> Char -> String -> String
scanr = forall a b. (a -> b -> b) -> b -> [a] -> [b]
List.scanr
   scanr1 :: (Char -> Char -> Char) -> String -> String
scanr1 = forall a. (a -> a -> a) -> [a] -> [a]
List.scanr1
   mapAccumL :: forall a. (a -> Char -> (a, Char)) -> a -> String -> (a, String)
mapAccumL = forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
List.mapAccumL
   mapAccumR :: forall a. (a -> Char -> (a, Char)) -> a -> String -> (a, String)
mapAccumR = forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
List.mapAccumR

   takeWhile :: (String -> Bool) -> (Char -> Bool) -> String -> String
takeWhile String -> Bool
_ = forall a. (a -> Bool) -> [a] -> [a]
List.takeWhile
   dropWhile :: (String -> Bool) -> (Char -> Bool) -> String -> String
dropWhile String -> Bool
_ = forall a. (a -> Bool) -> [a] -> [a]
List.dropWhile
   break :: (String -> Bool) -> (Char -> Bool) -> String -> (String, String)
break String -> Bool
_ = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.break
   span :: (String -> Bool) -> (Char -> Bool) -> String -> (String, String)
span String -> Bool
_ = forall a. (a -> Bool) -> [a] -> ([a], [a])
List.span
   spanMaybe :: forall s.
s
-> (s -> String -> Maybe s)
-> (s -> Char -> Maybe s)
-> String
-> (String, String, s)
spanMaybe s
s0 s -> String -> Maybe s
_ft s -> Char -> Maybe s
fc String
l = (String -> String
prefix' [], String -> String
suffix' [], s
s')
      where (String -> String
prefix', String -> String
suffix', s
s', Bool
_) = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' forall {c}.
(String -> c, String -> String, s, Bool)
-> Char -> (String -> c, String -> String, s, Bool)
g (forall a. a -> a
id, forall a. a -> a
id, s
s0, Bool
True) String
l
            g :: (String -> c, String -> String, s, Bool)
-> Char -> (String -> c, String -> String, s, Bool)
g (String -> c
prefix, String -> String
suffix, s
s, Bool
live) Char
c | Bool
live, Just s
s1 <- s -> Char -> Maybe s
fc s
s Char
c = (String -> c
prefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
cforall a. a -> [a] -> [a]
:), forall a. a -> a
id, s
s1, Bool
True)
                                          | Bool
otherwise = (String -> c
prefix, String -> String
suffix forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
cforall a. a -> [a] -> [a]
:), s
s, Bool
False)
   spanMaybe' :: forall s.
s
-> (s -> String -> Maybe s)
-> (s -> Char -> Maybe s)
-> String
-> (String, String, s)
spanMaybe' s
s0 s -> String -> Maybe s
_ft s -> Char -> Maybe s
fc String
l = (String -> String
prefix' [], String -> String
suffix' [], s
s')
      where (String -> String
prefix', String -> String
suffix', s
s', Bool
_) = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' forall {c}.
(String -> c, String -> String, s, Bool)
-> Char -> (String -> c, String -> String, s, Bool)
g (forall a. a -> a
id, forall a. a -> a
id, s
s0, Bool
True) String
l
            g :: (String -> c, String -> String, s, Bool)
-> Char -> (String -> c, String -> String, s, Bool)
g (String -> c
prefix, String -> String
suffix, s
s, Bool
live) Char
c | Bool
live, Just s
s1 <- s -> Char -> Maybe s
fc s
s Char
c = seq :: forall a b. a -> b -> b
seq s
s1 (String -> c
prefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
cforall a. a -> [a] -> [a]
:), forall a. a -> a
id, s
s1, Bool
True)
                                          | Bool
otherwise = (String -> c
prefix, String -> String
suffix forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
cforall a. a -> [a] -> [a]
:), s
s, Bool
False)
   find :: (Char -> Bool) -> String -> Maybe Char
find = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
List.find
   elem :: Char -> String -> Bool
elem = forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
List.elem

   {-# INLINE all #-}
   {-# INLINE any #-}
   {-# INLINE break #-}
   {-# INLINE characterPrefix #-}
   {-# INLINE concatMap #-}
   {-# INLINE dropWhile #-}
   {-# INLINE elem #-}
   {-# INLINE find #-}
   {-# INLINE foldl   #-}
   {-# INLINE foldl'  #-}
   {-# INLINE foldr   #-}
   {-# INLINE fromText #-}
   {-# INLINE map #-}
   {-# INLINE mapAccumL #-}
   {-# INLINE mapAccumR #-}
   {-# INLINE scanl #-}
   {-# INLINE scanl1 #-}
   {-# INLINE scanr #-}
   {-# INLINE scanr1 #-}
   {-# INLINE singleton #-}
   {-# INLINE span #-}
   {-# INLINE spanMaybe #-}
   {-# INLINE spanMaybe' #-}
   {-# INLINE splitCharacterPrefix #-}
   {-# INLINE takeWhile #-}

instance TextualMonoid Text where
   fromText :: Text -> Text
fromText = forall a. a -> a
id
   singleton :: Char -> Text
singleton = Char -> Text
Text.singleton
   splitCharacterPrefix :: Text -> Maybe (Char, Text)
splitCharacterPrefix = Text -> Maybe (Char, Text)
Text.uncons
   characterPrefix :: Text -> Maybe Char
characterPrefix Text
t = if Text -> Bool
Text.null Text
t then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (Text -> Char
Text.head Text
t)
   map :: (Char -> Char) -> Text -> Text
map = (Char -> Char) -> Text -> Text
Text.map
   concatMap :: (Char -> Text) -> Text -> Text
concatMap = (Char -> Text) -> Text -> Text
Text.concatMap
   toString :: (Text -> String) -> Text -> String
toString = forall a b. a -> b -> a
const Text -> String
Text.unpack
   toText :: (Text -> Text) -> Text -> Text
toText = forall a b. a -> b -> a
const forall a. a -> a
id
   any :: (Char -> Bool) -> Text -> Bool
any = (Char -> Bool) -> Text -> Bool
Text.any
   all :: (Char -> Bool) -> Text -> Bool
all = (Char -> Bool) -> Text -> Bool
Text.all

   foldl :: forall a. (a -> Text -> a) -> (a -> Char -> a) -> a -> Text -> a
foldl   = forall a b. a -> b -> a
const forall a. (a -> Char -> a) -> a -> Text -> a
Text.foldl
   foldl' :: forall a. (a -> Text -> a) -> (a -> Char -> a) -> a -> Text -> a
foldl'  = forall a b. a -> b -> a
const forall a. (a -> Char -> a) -> a -> Text -> a
Text.foldl'
   foldr :: forall a. (Text -> a -> a) -> (Char -> a -> a) -> a -> Text -> a
foldr   = forall a b. a -> b -> a
const forall a. (Char -> a -> a) -> a -> Text -> a
Text.foldr

   scanl :: (Char -> Char -> Char) -> Char -> Text -> Text
scanl = (Char -> Char -> Char) -> Char -> Text -> Text
Text.scanl
   scanl1 :: (Char -> Char -> Char) -> Text -> Text
scanl1 = (Char -> Char -> Char) -> Text -> Text
Text.scanl1
   scanr :: (Char -> Char -> Char) -> Char -> Text -> Text
scanr = (Char -> Char -> Char) -> Char -> Text -> Text
Text.scanr
   scanr1 :: (Char -> Char -> Char) -> Text -> Text
scanr1 = (Char -> Char -> Char) -> Text -> Text
Text.scanr1
   mapAccumL :: forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
mapAccumL = forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
Text.mapAccumL
   mapAccumR :: forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
mapAccumR = forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
Text.mapAccumR

   takeWhile :: (Text -> Bool) -> (Char -> Bool) -> Text -> Text
takeWhile Text -> Bool
_ = (Char -> Bool) -> Text -> Text
Text.takeWhile
   dropWhile :: (Text -> Bool) -> (Char -> Bool) -> Text -> Text
dropWhile Text -> Bool
_ = (Char -> Bool) -> Text -> Text
Text.dropWhile
   break :: (Text -> Bool) -> (Char -> Bool) -> Text -> (Text, Text)
break Text -> Bool
_ = (Char -> Bool) -> Text -> (Text, Text)
Text.break
   span :: (Text -> Bool) -> (Char -> Bool) -> Text -> (Text, Text)
span Text -> Bool
_ = (Char -> Bool) -> Text -> (Text, Text)
Text.span
   spanMaybe :: forall s.
s
-> (s -> Text -> Maybe s)
-> (s -> Char -> Maybe s)
-> Text
-> (Text, Text, s)
spanMaybe s
s0 s -> Text -> Maybe s
_ft s -> Char -> Maybe s
fc Text
t = case forall a. (Char -> a -> a) -> a -> Text -> a
Text.foldr Char -> ((Int, s) -> (Int, s)) -> (Int, s) -> (Int, s)
g forall a. a -> a
id Text
t (Int
0, s
s0)
                           of (Int
i, s
s') | (Text
prefix, Text
suffix) <- Int -> Text -> (Text, Text)
Text.splitAt Int
i Text
t -> (Text
prefix, Text
suffix, s
s')
      where g :: Char -> ((Int, s) -> (Int, s)) -> (Int, s) -> (Int, s)
g Char
c (Int, s) -> (Int, s)
cont (Int
i, s
s) | Just s
s' <- s -> Char -> Maybe s
fc s
s Char
c = let i' :: Int
i' = forall a. Enum a => a -> a
succ Int
i :: Int in seq :: forall a b. a -> b -> b
seq Int
i' forall a b. (a -> b) -> a -> b
$ (Int, s) -> (Int, s)
cont (Int
i', s
s')
                            | Bool
otherwise = (Int
i, s
s)
   spanMaybe' :: forall s.
s
-> (s -> Text -> Maybe s)
-> (s -> Char -> Maybe s)
-> Text
-> (Text, Text, s)
spanMaybe' s
s0 s -> Text -> Maybe s
_ft s -> Char -> Maybe s
fc Text
t = case forall a. (Char -> a -> a) -> a -> Text -> a
Text.foldr Char -> ((Int, s) -> (Int, s)) -> (Int, s) -> (Int, s)
g forall a. a -> a
id Text
t (Int
0, s
s0)
                            of (Int
i, s
s') | (Text
prefix, Text
suffix) <- Int -> Text -> (Text, Text)
Text.splitAt Int
i Text
t -> (Text
prefix, Text
suffix, s
s')
      where g :: Char -> ((Int, s) -> (Int, s)) -> (Int, s) -> (Int, s)
g Char
c (Int, s) -> (Int, s)
cont (Int
i, s
s) | Just s
s' <- s -> Char -> Maybe s
fc s
s Char
c = let i' :: Int
i' = forall a. Enum a => a -> a
succ Int
i :: Int in seq :: forall a b. a -> b -> b
seq Int
i' forall a b. (a -> b) -> a -> b
$ seq :: forall a b. a -> b -> b
seq s
s' forall a b. (a -> b) -> a -> b
$ (Int, s) -> (Int, s)
cont (Int
i', s
s')
                            | Bool
otherwise = (Int
i, s
s)
   split :: (Char -> Bool) -> Text -> [Text]
split = (Char -> Bool) -> Text -> [Text]
Text.split
   find :: (Char -> Bool) -> Text -> Maybe Char
find = (Char -> Bool) -> Text -> Maybe Char
Text.find

   {-# INLINE all #-}
   {-# INLINE any #-}
   {-# INLINE break #-}
   {-# INLINE characterPrefix #-}
   {-# INLINE concatMap #-}
   {-# INLINE dropWhile #-}
   {-# INLINE find #-}
   {-# INLINE foldl   #-}
   {-# INLINE foldl'  #-}
   {-# INLINE foldr   #-}
   {-# INLINE fromText #-}
   {-# INLINE map #-}
   {-# INLINE mapAccumL #-}
   {-# INLINE mapAccumR #-}
   {-# INLINE scanl #-}
   {-# INLINE scanl1 #-}
   {-# INLINE scanr #-}
   {-# INLINE scanr1 #-}
   {-# INLINE singleton #-}
   {-# INLINE span #-}
   {-# INLINE spanMaybe #-}
   {-# INLINE spanMaybe' #-}
   {-# INLINE split #-}
   {-# INLINE splitCharacterPrefix #-}
   {-# INLINE takeWhile #-}

instance TextualMonoid LazyText.Text where
   fromText :: Text -> Text
fromText = Text -> Text
LazyText.fromStrict
   singleton :: Char -> Text
singleton = Char -> Text
LazyText.singleton
   splitCharacterPrefix :: Text -> Maybe (Char, Text)
splitCharacterPrefix = Text -> Maybe (Char, Text)
LazyText.uncons
   characterPrefix :: Text -> Maybe Char
characterPrefix Text
t = if Text -> Bool
LazyText.null Text
t then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (Text -> Char
LazyText.head Text
t)
   map :: (Char -> Char) -> Text -> Text
map = (Char -> Char) -> Text -> Text
LazyText.map
   concatMap :: (Char -> Text) -> Text -> Text
concatMap = (Char -> Text) -> Text -> Text
LazyText.concatMap
   toString :: (Text -> String) -> Text -> String
toString = forall a b. a -> b -> a
const Text -> String
LazyText.unpack
   toText :: (Text -> Text) -> Text -> Text
toText = forall a b. a -> b -> a
const Text -> Text
LazyText.toStrict
   any :: (Char -> Bool) -> Text -> Bool
any = (Char -> Bool) -> Text -> Bool
LazyText.any
   all :: (Char -> Bool) -> Text -> Bool
all = (Char -> Bool) -> Text -> Bool
LazyText.all

   foldl :: forall a. (a -> Text -> a) -> (a -> Char -> a) -> a -> Text -> a
foldl   = forall a b. a -> b -> a
const forall a. (a -> Char -> a) -> a -> Text -> a
LazyText.foldl
   foldl' :: forall a. (a -> Text -> a) -> (a -> Char -> a) -> a -> Text -> a
foldl'  = forall a b. a -> b -> a
const forall a. (a -> Char -> a) -> a -> Text -> a
LazyText.foldl'
   foldr :: forall a. (Text -> a -> a) -> (Char -> a -> a) -> a -> Text -> a
foldr   = forall a b. a -> b -> a
const forall a. (Char -> a -> a) -> a -> Text -> a
LazyText.foldr

   scanl :: (Char -> Char -> Char) -> Char -> Text -> Text
scanl = (Char -> Char -> Char) -> Char -> Text -> Text
LazyText.scanl
   scanl1 :: (Char -> Char -> Char) -> Text -> Text
scanl1 = (Char -> Char -> Char) -> Text -> Text
LazyText.scanl1
   scanr :: (Char -> Char -> Char) -> Char -> Text -> Text
scanr = (Char -> Char -> Char) -> Char -> Text -> Text
LazyText.scanr
   scanr1 :: (Char -> Char -> Char) -> Text -> Text
scanr1 = (Char -> Char -> Char) -> Text -> Text
LazyText.scanr1
   mapAccumL :: forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
mapAccumL = forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
LazyText.mapAccumL
   mapAccumR :: forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
mapAccumR = forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
LazyText.mapAccumR

   takeWhile :: (Text -> Bool) -> (Char -> Bool) -> Text -> Text
takeWhile Text -> Bool
_ = (Char -> Bool) -> Text -> Text
LazyText.takeWhile
   dropWhile :: (Text -> Bool) -> (Char -> Bool) -> Text -> Text
dropWhile Text -> Bool
_ = (Char -> Bool) -> Text -> Text
LazyText.dropWhile
   break :: (Text -> Bool) -> (Char -> Bool) -> Text -> (Text, Text)
break Text -> Bool
_ = (Char -> Bool) -> Text -> (Text, Text)
LazyText.break
   span :: (Text -> Bool) -> (Char -> Bool) -> Text -> (Text, Text)
span Text -> Bool
_ = (Char -> Bool) -> Text -> (Text, Text)
LazyText.span
   spanMaybe :: forall s.
s
-> (s -> Text -> Maybe s)
-> (s -> Char -> Maybe s)
-> Text
-> (Text, Text, s)
spanMaybe s
s0 s -> Text -> Maybe s
_ft s -> Char -> Maybe s
fc Text
t = case forall a. (Char -> a -> a) -> a -> Text -> a
LazyText.foldr Char -> ((Int64, s) -> (Int64, s)) -> (Int64, s) -> (Int64, s)
g forall a. a -> a
id Text
t (Int64
0, s
s0)
                           of (Int64
i, s
s') | (Text
prefix, Text
suffix) <- Int64 -> Text -> (Text, Text)
LazyText.splitAt Int64
i Text
t -> (Text
prefix, Text
suffix, s
s')
      where g :: Char -> ((Int64, s) -> (Int64, s)) -> (Int64, s) -> (Int64, s)
g Char
c (Int64, s) -> (Int64, s)
cont (Int64
i, s
s) | Just s
s' <- s -> Char -> Maybe s
fc s
s Char
c = let i' :: Int64
i' = forall a. Enum a => a -> a
succ Int64
i :: Int64 in seq :: forall a b. a -> b -> b
seq Int64
i' forall a b. (a -> b) -> a -> b
$ (Int64, s) -> (Int64, s)
cont (Int64
i', s
s')
                            | Bool
otherwise = (Int64
i, s
s)
   spanMaybe' :: forall s.
s
-> (s -> Text -> Maybe s)
-> (s -> Char -> Maybe s)
-> Text
-> (Text, Text, s)
spanMaybe' s
s0 s -> Text -> Maybe s
_ft s -> Char -> Maybe s
fc Text
t = case forall a. (Char -> a -> a) -> a -> Text -> a
LazyText.foldr Char -> ((Int64, s) -> (Int64, s)) -> (Int64, s) -> (Int64, s)
g forall a. a -> a
id Text
t (Int64
0, s
s0)
                            of (Int64
i, s
s') | (Text
prefix, Text
suffix) <- Int64 -> Text -> (Text, Text)
LazyText.splitAt Int64
i Text
t -> (Text
prefix, Text
suffix, s
s')
      where g :: Char -> ((Int64, s) -> (Int64, s)) -> (Int64, s) -> (Int64, s)
g Char
c (Int64, s) -> (Int64, s)
cont (Int64
i, s
s) | Just s
s' <- s -> Char -> Maybe s
fc s
s Char
c = let i' :: Int64
i' = forall a. Enum a => a -> a
succ Int64
i :: Int64 in seq :: forall a b. a -> b -> b
seq Int64
i' forall a b. (a -> b) -> a -> b
$ seq :: forall a b. a -> b -> b
seq s
s' forall a b. (a -> b) -> a -> b
$ (Int64, s) -> (Int64, s)
cont (Int64
i', s
s')
                            | Bool
otherwise = (Int64
i, s
s)
   split :: (Char -> Bool) -> Text -> [Text]
split = (Char -> Bool) -> Text -> [Text]
LazyText.split
   find :: (Char -> Bool) -> Text -> Maybe Char
find = (Char -> Bool) -> Text -> Maybe Char
LazyText.find
   {-# INLINE all #-}
   {-# INLINE any #-}
   {-# INLINE break #-}
   {-# INLINE characterPrefix #-}
   {-# INLINE concatMap #-}
   {-# INLINE dropWhile #-}
   {-# INLINE find #-}
   {-# INLINE foldl   #-}
   {-# INLINE foldl'  #-}
   {-# INLINE foldr   #-}
   {-# INLINE fromText #-}
   {-# INLINE map #-}
   {-# INLINE mapAccumL #-}
   {-# INLINE mapAccumR #-}
   {-# INLINE scanl #-}
   {-# INLINE scanl1 #-}
   {-# INLINE scanr #-}
   {-# INLINE scanr1 #-}
   {-# INLINE singleton #-}
   {-# INLINE span #-}
   {-# INLINE spanMaybe #-}
   {-# INLINE spanMaybe' #-}
   {-# INLINE split #-}
   {-# INLINE splitCharacterPrefix #-}
   {-# INLINE takeWhile #-}

instance TextualMonoid (Sequence.Seq Char) where
   singleton :: Char -> Seq Char
singleton = forall a. a -> Seq a
Sequence.singleton
   splitCharacterPrefix :: Seq Char -> Maybe (Char, Seq Char)
splitCharacterPrefix Seq Char
s = case forall a. Seq a -> ViewL a
Sequence.viewl Seq Char
s
                            of ViewL Char
Sequence.EmptyL -> forall a. Maybe a
Nothing
                               Char
c Sequence.:< Seq Char
rest -> forall a. a -> Maybe a
Just (Char
c, Seq Char
rest)
   characterPrefix :: Seq Char -> Maybe Char
characterPrefix Seq Char
s = case forall a. Seq a -> ViewL a
Sequence.viewl Seq Char
s
                       of ViewL Char
Sequence.EmptyL -> forall a. Maybe a
Nothing
                          Char
c Sequence.:< Seq Char
_ -> forall a. a -> Maybe a
Just Char
c
   map :: (Char -> Char) -> Seq Char -> Seq Char
map = forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
Traversable.fmapDefault
   concatMap :: (Char -> Seq Char) -> Seq Char -> Seq Char
concatMap = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
Foldable.foldMap
   toString :: (Seq Char -> String) -> Seq Char -> String
toString = forall a b. a -> b -> a
const forall (t :: * -> *) a. Foldable t => t a -> [a]
Foldable.toList
   any :: (Char -> Bool) -> Seq Char -> Bool
any = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
Foldable.any
   all :: (Char -> Bool) -> Seq Char -> Bool
all = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
Foldable.all

   foldl :: forall a.
(a -> Seq Char -> a) -> (a -> Char -> a) -> a -> Seq Char -> a
foldl   = forall a b. a -> b -> a
const forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl
   foldl' :: forall a.
(a -> Seq Char -> a) -> (a -> Char -> a) -> a -> Seq Char -> a
foldl'  = forall a b. a -> b -> a
const forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl'
   foldr :: forall a.
(Seq Char -> a -> a) -> (Char -> a -> a) -> a -> Seq Char -> a
foldr   = forall a b. a -> b -> a
const forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr

   scanl :: (Char -> Char -> Char) -> Char -> Seq Char -> Seq Char
scanl = forall a b. (a -> b -> a) -> a -> Seq b -> Seq a
Sequence.scanl
   scanl1 :: (Char -> Char -> Char) -> Seq Char -> Seq Char
scanl1 Char -> Char -> Char
f Seq Char
v | forall a. Seq a -> Bool
Sequence.null Seq Char
v = forall a. Seq a
Sequence.empty
              | Bool
otherwise = forall a. (a -> a -> a) -> Seq a -> Seq a
Sequence.scanl1 Char -> Char -> Char
f Seq Char
v
   scanr :: (Char -> Char -> Char) -> Char -> Seq Char -> Seq Char
scanr = forall a b. (a -> b -> b) -> b -> Seq a -> Seq b
Sequence.scanr
   scanr1 :: (Char -> Char -> Char) -> Seq Char -> Seq Char
scanr1 Char -> Char -> Char
f Seq Char
v | forall a. Seq a -> Bool
Sequence.null Seq Char
v = forall a. Seq a
Sequence.empty
              | Bool
otherwise = forall a. (a -> a -> a) -> Seq a -> Seq a
Sequence.scanr1 Char -> Char -> Char
f Seq Char
v

   takeWhile :: (Seq Char -> Bool) -> (Char -> Bool) -> Seq Char -> Seq Char
takeWhile Seq Char -> Bool
_ = forall a. (a -> Bool) -> Seq a -> Seq a
Sequence.takeWhileL
   dropWhile :: (Seq Char -> Bool) -> (Char -> Bool) -> Seq Char -> Seq Char
dropWhile Seq Char -> Bool
_ = forall a. (a -> Bool) -> Seq a -> Seq a
Sequence.dropWhileL
   break :: (Seq Char -> Bool)
-> (Char -> Bool) -> Seq Char -> (Seq Char, Seq Char)
break Seq Char -> Bool
_ = forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
Sequence.breakl
   span :: (Seq Char -> Bool)
-> (Char -> Bool) -> Seq Char -> (Seq Char, Seq Char)
span Seq Char -> Bool
_ = forall a. (a -> Bool) -> Seq a -> (Seq a, Seq a)
Sequence.spanl
   spanMaybe :: forall s.
s
-> (s -> Seq Char -> Maybe s)
-> (s -> Char -> Maybe s)
-> Seq Char
-> (Seq Char, Seq Char, s)
spanMaybe s
s0 s -> Seq Char -> Maybe s
_ft s -> Char -> Maybe s
fc Seq Char
b = case forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr Char -> ((Int, s) -> (Int, s)) -> (Int, s) -> (Int, s)
g forall a. a -> a
id Seq Char
b (Int
0, s
s0)
                           of (Int
i, s
s') | (Seq Char
prefix, Seq Char
suffix) <- forall a. Int -> Seq a -> (Seq a, Seq a)
Sequence.splitAt Int
i Seq Char
b -> (Seq Char
prefix, Seq Char
suffix, s
s')
      where g :: Char -> ((Int, s) -> (Int, s)) -> (Int, s) -> (Int, s)
g Char
c (Int, s) -> (Int, s)
cont (Int
i, s
s) | Just s
s' <- s -> Char -> Maybe s
fc s
s Char
c = let i' :: Int
i' = forall a. Enum a => a -> a
succ Int
i :: Int in seq :: forall a b. a -> b -> b
seq Int
i' forall a b. (a -> b) -> a -> b
$ (Int, s) -> (Int, s)
cont (Int
i', s
s')
                            | Bool
otherwise = (Int
i, s
s)
   spanMaybe' :: forall s.
s
-> (s -> Seq Char -> Maybe s)
-> (s -> Char -> Maybe s)
-> Seq Char
-> (Seq Char, Seq Char, s)
spanMaybe' s
s0 s -> Seq Char -> Maybe s
_ft s -> Char -> Maybe s
fc Seq Char
b = case forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr Char -> ((Int, s) -> (Int, s)) -> (Int, s) -> (Int, s)
g forall a. a -> a
id Seq Char
b (Int
0, s
s0)
                            of (Int
i, s
s') | (Seq Char
prefix, Seq Char
suffix) <- forall a. Int -> Seq a -> (Seq a, Seq a)
Sequence.splitAt Int
i Seq Char
b -> (Seq Char
prefix, Seq Char
suffix, s
s')
      where g :: Char -> ((Int, s) -> (Int, s)) -> (Int, s) -> (Int, s)
g Char
c (Int, s) -> (Int, s)
cont (Int
i, s
s) | Just s
s' <- s -> Char -> Maybe s
fc s
s Char
c = let i' :: Int
i' = forall a. Enum a => a -> a
succ Int
i :: Int in seq :: forall a b. a -> b -> b
seq Int
i' forall a b. (a -> b) -> a -> b
$ seq :: forall a b. a -> b -> b
seq s
s' forall a b. (a -> b) -> a -> b
$ (Int, s) -> (Int, s)
cont (Int
i', s
s')
                            | Bool
otherwise = (Int
i, s
s)
   find :: (Char -> Bool) -> Seq Char -> Maybe Char
find = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
Foldable.find
   elem :: Char -> Seq Char -> Bool
elem = forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
Foldable.elem

   {-# INLINE all #-}
   {-# INLINE any #-}
   {-# INLINE break #-}
   {-# INLINE characterPrefix #-}
   {-# INLINE concatMap #-}
   {-# INLINE dropWhile #-}
   {-# INLINE elem #-}
   {-# INLINE find #-}
   {-# INLINE foldl   #-}
   {-# INLINE foldl'  #-}
   {-# INLINE foldr   #-}
   {-# INLINE map #-}
   {-# INLINE scanl #-}
   {-# INLINE scanl1 #-}
   {-# INLINE scanr #-}
   {-# INLINE scanr1 #-}
   {-# INLINE singleton #-}
   {-# INLINE span #-}
   {-# INLINE spanMaybe #-}
   {-# INLINE spanMaybe' #-}
   {-# INLINE splitCharacterPrefix #-}
   {-# INLINE takeWhile #-}