module Data.Attoparsec.Internal.Types
(
Parser
, DirParser(..)
, State
, DirState
, Failure
, Success
, DirFailure
, DirSuccess
, Pos
, IResult(..)
, More(..)
, (<>)
, Chunk(..)
, DirChunk(..)
, Dir(..)
, DirPos(..)
, DirectedPlus(..)
) where
import Control.Applicative as App (Applicative(..))
import Control.Applicative (Alternative(..))
import Control.DeepSeq (NFData(rnf))
import Control.Monad (MonadPlus(..))
import qualified Control.Monad.Fail as Fail (MonadFail(..))
import Data.Monoid as Mon (Monoid(..))
import Data.Word (Word8)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.ByteString.Internal (w2c)
import Data.Tagged (Tagged(..), untag)
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Text.Unsafe (Iter(..))
import Debug.TraceEmbrace (tw)
import Prelude hiding (succ)
import Data.Attoparsec.ByteString.Buffer (Dir (..))
import qualified Data.Attoparsec.ByteString.Buffer as B
import qualified Data.Attoparsec.Text.Buffer as T
newtype DirPos (d :: Dir) = Pos { forall (d :: Dir). DirPos d -> Int
fromPos :: Int }
deriving (DirPos d -> DirPos d -> Bool
(DirPos d -> DirPos d -> Bool)
-> (DirPos d -> DirPos d -> Bool) -> Eq (DirPos d)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (d :: Dir). DirPos d -> DirPos d -> Bool
$c== :: forall (d :: Dir). DirPos d -> DirPos d -> Bool
== :: DirPos d -> DirPos d -> Bool
$c/= :: forall (d :: Dir). DirPos d -> DirPos d -> Bool
/= :: DirPos d -> DirPos d -> Bool
Eq, Eq (DirPos d)
Eq (DirPos d) =>
(DirPos d -> DirPos d -> Ordering)
-> (DirPos d -> DirPos d -> Bool)
-> (DirPos d -> DirPos d -> Bool)
-> (DirPos d -> DirPos d -> Bool)
-> (DirPos d -> DirPos d -> Bool)
-> (DirPos d -> DirPos d -> DirPos d)
-> (DirPos d -> DirPos d -> DirPos d)
-> Ord (DirPos d)
DirPos d -> DirPos d -> Bool
DirPos d -> DirPos d -> Ordering
DirPos d -> DirPos d -> DirPos d
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (d :: Dir). Eq (DirPos d)
forall (d :: Dir). DirPos d -> DirPos d -> Bool
forall (d :: Dir). DirPos d -> DirPos d -> Ordering
forall (d :: Dir). DirPos d -> DirPos d -> DirPos d
$ccompare :: forall (d :: Dir). DirPos d -> DirPos d -> Ordering
compare :: DirPos d -> DirPos d -> Ordering
$c< :: forall (d :: Dir). DirPos d -> DirPos d -> Bool
< :: DirPos d -> DirPos d -> Bool
$c<= :: forall (d :: Dir). DirPos d -> DirPos d -> Bool
<= :: DirPos d -> DirPos d -> Bool
$c> :: forall (d :: Dir). DirPos d -> DirPos d -> Bool
> :: DirPos d -> DirPos d -> Bool
$c>= :: forall (d :: Dir). DirPos d -> DirPos d -> Bool
>= :: DirPos d -> DirPos d -> Bool
$cmax :: forall (d :: Dir). DirPos d -> DirPos d -> DirPos d
max :: DirPos d -> DirPos d -> DirPos d
$cmin :: forall (d :: Dir). DirPos d -> DirPos d -> DirPos d
min :: DirPos d -> DirPos d -> DirPos d
Ord, Int -> DirPos d -> ShowS
[DirPos d] -> ShowS
DirPos d -> String
(Int -> DirPos d -> ShowS)
-> (DirPos d -> String) -> ([DirPos d] -> ShowS) -> Show (DirPos d)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (d :: Dir). Int -> DirPos d -> ShowS
forall (d :: Dir). [DirPos d] -> ShowS
forall (d :: Dir). DirPos d -> String
$cshowsPrec :: forall (d :: Dir). Int -> DirPos d -> ShowS
showsPrec :: Int -> DirPos d -> ShowS
$cshow :: forall (d :: Dir). DirPos d -> String
show :: DirPos d -> String
$cshowList :: forall (d :: Dir). [DirPos d] -> ShowS
showList :: [DirPos d] -> ShowS
Show, Integer -> DirPos d
DirPos d -> DirPos d
DirPos d -> DirPos d -> DirPos d
(DirPos d -> DirPos d -> DirPos d)
-> (DirPos d -> DirPos d -> DirPos d)
-> (DirPos d -> DirPos d -> DirPos d)
-> (DirPos d -> DirPos d)
-> (DirPos d -> DirPos d)
-> (DirPos d -> DirPos d)
-> (Integer -> DirPos d)
-> Num (DirPos d)
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
forall (d :: Dir). Integer -> DirPos d
forall (d :: Dir). DirPos d -> DirPos d
forall (d :: Dir). DirPos d -> DirPos d -> DirPos d
$c+ :: forall (d :: Dir). DirPos d -> DirPos d -> DirPos d
+ :: DirPos d -> DirPos d -> DirPos d
$c- :: forall (d :: Dir). DirPos d -> DirPos d -> DirPos d
- :: DirPos d -> DirPos d -> DirPos d
$c* :: forall (d :: Dir). DirPos d -> DirPos d -> DirPos d
* :: DirPos d -> DirPos d -> DirPos d
$cnegate :: forall (d :: Dir). DirPos d -> DirPos d
negate :: DirPos d -> DirPos d
$cabs :: forall (d :: Dir). DirPos d -> DirPos d
abs :: DirPos d -> DirPos d
$csignum :: forall (d :: Dir). DirPos d -> DirPos d
signum :: DirPos d -> DirPos d
$cfromInteger :: forall (d :: Dir). Integer -> DirPos d
fromInteger :: Integer -> DirPos d
Num)
class DirectedPlus (d :: Dir) where
there :: DirPos d -> DirPos d
instance DirectedPlus Forward where
there :: DirPos 'Forward -> DirPos 'Forward
there = DirPos 'Forward -> DirPos 'Forward
forall a. a -> a
id
instance DirectedPlus Backward where
there :: DirPos 'Backward -> DirPos 'Backward
there = DirPos 'Backward -> DirPos 'Backward
forall a. Num a => a -> a
negate
type Pos = DirPos Forward
data IResult i r =
Fail i [String] String
| Partial (i -> IResult i r)
| Done i r
instance (Show i, Show r) => Show (IResult i r) where
showsPrec :: Int -> IResult i r -> ShowS
showsPrec Int
d IResult i r
ir = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
case IResult i r
ir of
(Fail i
t [String]
stk String
msg) -> String -> ShowS
showString String
"Fail" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> ShowS
forall a. Show a => a -> ShowS
f i
t ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> ShowS
forall a. Show a => a -> ShowS
f [String]
stk ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
forall a. Show a => a -> ShowS
f String
msg
(Partial i -> IResult i r
_) -> String -> ShowS
showString String
"Partial _"
(Done i
t r
r) -> String -> ShowS
showString String
"Done" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> ShowS
forall a. Show a => a -> ShowS
f i
t ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. r -> ShowS
forall a. Show a => a -> ShowS
f r
r
where f :: Show a => a -> ShowS
f :: forall a. Show a => a -> ShowS
f a
x = Char -> ShowS
showChar Char
' ' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 a
x
instance (NFData i, NFData r) => NFData (IResult i r) where
rnf :: IResult i r -> ()
rnf (Fail i
t [String]
stk String
msg) = i -> ()
forall a. NFData a => a -> ()
rnf i
t () -> () -> ()
forall a b. a -> b -> b
`seq` [String] -> ()
forall a. NFData a => a -> ()
rnf [String]
stk () -> () -> ()
forall a b. a -> b -> b
`seq` String -> ()
forall a. NFData a => a -> ()
rnf String
msg
rnf (Partial i -> IResult i r
_) = ()
rnf (Done i
t r
r) = i -> ()
forall a. NFData a => a -> ()
rnf i
t () -> () -> ()
forall a b. a -> b -> b
`seq` r -> ()
forall a. NFData a => a -> ()
rnf r
r
{-# INLINE rnf #-}
instance Functor (IResult i) where
fmap :: forall a b. (a -> b) -> IResult i a -> IResult i b
fmap a -> b
_ (Fail i
t [String]
stk String
msg) = i -> [String] -> String -> IResult i b
forall i r. i -> [String] -> String -> IResult i r
Fail i
t [String]
stk String
msg
fmap a -> b
f (Partial i -> IResult i a
k) = (i -> IResult i b) -> IResult i b
forall i r. (i -> IResult i r) -> IResult i r
Partial ((a -> b) -> IResult i a -> IResult i b
forall a b. (a -> b) -> IResult i a -> IResult i b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (IResult i a -> IResult i b)
-> (i -> IResult i a) -> i -> IResult i b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> IResult i a
k)
fmap a -> b
f (Done i
t a
r) = i -> b -> IResult i b
forall i r. i -> r -> IResult i r
Done i
t (a -> b
f a
r)
newtype DirParser (d :: Dir) i a = Parser {
forall (d :: Dir) i a.
DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
runParser :: forall r.
DirState d i -> DirPos d -> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
}
type Parser = DirParser Forward
type family DirState (d :: Dir) i
type instance DirState Forward ByteString = B.Buffer
type instance DirState Backward ByteString = B.DirBuffer Backward
type instance DirState Forward Text = T.Buffer
type State x = DirState Forward x
type DirFailure d i t r =
t -> DirPos d -> More -> [String] -> String -> IResult i r
type DirSuccess d i t a r =
t -> DirPos d -> More -> a -> IResult i r
type Success i t a r = DirSuccess Forward i t a r
type Failure i t r = DirFailure Forward i t r
data More = Complete | Incomplete
deriving (More -> More -> Bool
(More -> More -> Bool) -> (More -> More -> Bool) -> Eq More
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: More -> More -> Bool
== :: More -> More -> Bool
$c/= :: More -> More -> Bool
/= :: More -> More -> Bool
Eq, Int -> More -> ShowS
[More] -> ShowS
More -> String
(Int -> More -> ShowS)
-> (More -> String) -> ([More] -> ShowS) -> Show More
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> More -> ShowS
showsPrec :: Int -> More -> ShowS
$cshow :: More -> String
show :: More -> String
$cshowList :: [More] -> ShowS
showList :: [More] -> ShowS
Show)
instance Semigroup More where
c :: More
c@More
Complete <> :: More -> More -> More
<> More
_ = More
c
More
_ <> More
m = More
m
instance Mon.Monoid More where
mappend :: More -> More -> More
mappend = More -> More -> More
forall a. Semigroup a => a -> a -> a
(<>)
mempty :: More
mempty = More
Incomplete
instance Monad (DirParser d i) where
#if !(MIN_VERSION_base(4,13,0))
fail = Fail.fail
{-# INLINE fail #-}
#endif
return :: forall a. a -> DirParser d i a
return = a -> DirParser d i a
forall a. a -> DirParser d i a
forall (f :: * -> *) a. Applicative f => a -> f a
App.pure
{-# INLINE return #-}
DirParser d i a
m >>= :: forall a b.
DirParser d i a -> (a -> DirParser d i b) -> DirParser d i b
>>= a -> DirParser d i b
k = (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) b r
-> IResult i r)
-> DirParser d i b
forall (d :: Dir) i a.
(forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
Parser ((forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) b r
-> IResult i r)
-> DirParser d i b)
-> (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) b r
-> IResult i r)
-> DirParser d i b
forall a b. (a -> b) -> a -> b
$ \DirState d i
t !DirPos d
pos More
more DirFailure d i (DirState d i) r
lose DirSuccess d i (DirState d i) b r
succ ->
let succ' :: DirState d i -> DirPos d -> More -> a -> IResult i r
succ' DirState d i
t' !DirPos d
pos' More
more' a
a = DirParser d i b
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) b r
-> IResult i r
forall (d :: Dir) i a.
DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
runParser (a -> DirParser d i b
k a
a) DirState d i
t' DirPos d
pos' More
more' DirFailure d i (DirState d i) r
lose DirSuccess d i (DirState d i) b r
succ
in DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
forall (d :: Dir) i a.
DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
runParser DirParser d i a
m DirState d i
t DirPos d
pos More
more DirFailure d i (DirState d i) r
lose DirState d i -> DirPos d -> More -> a -> IResult i r
succ'
{-# INLINE (>>=) #-}
>> :: forall a b. DirParser d i a -> DirParser d i b -> DirParser d i b
(>>) = DirParser d i a -> DirParser d i b -> DirParser d i b
forall a b. DirParser d i a -> DirParser d i b -> DirParser d i b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
(*>)
{-# INLINE (>>) #-}
instance Fail.MonadFail (DirParser d i) where
fail :: forall a. String -> DirParser d i a
fail String
err = (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
forall (d :: Dir) i a.
(forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
Parser ((forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a)
-> (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
forall a b. (a -> b) -> a -> b
$ \DirState d i
t DirPos d
pos More
more DirFailure d i (DirState d i) r
lose DirSuccess d i (DirState d i) a r
_succ -> DirFailure d i (DirState d i) r
lose DirState d i
t DirPos d
pos More
more [] String
msg
where msg :: String
msg = String
"Failed reading: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
err
{-# INLINE fail #-}
plus :: DirParser d i a -> DirParser d i a -> DirParser d i a
plus :: forall (d :: Dir) i a.
DirParser d i a -> DirParser d i a -> DirParser d i a
plus DirParser d i a
f DirParser d i a
g = (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
forall (d :: Dir) i a.
(forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
Parser ((forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a)
-> (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
forall a b. (a -> b) -> a -> b
$ \DirState d i
t DirPos d
pos More
more DirFailure d i (DirState d i) r
lose DirSuccess d i (DirState d i) a r
succ ->
let lose' :: DirFailure d i (DirState d i) r
lose' DirState d i
t' DirPos d
_pos' More
more' [String]
_ctx String
_msg = DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
forall (d :: Dir) i a.
DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
runParser DirParser d i a
g DirState d i
t' DirPos d
pos More
more' DirFailure d i (DirState d i) r
lose DirSuccess d i (DirState d i) a r
succ
in DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
forall (d :: Dir) i a.
DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
runParser DirParser d i a
f DirState d i
t DirPos d
pos More
more DirFailure d i (DirState d i) r
lose' DirSuccess d i (DirState d i) a r
succ
{-# INLINE plus #-}
type BsBackParser a = DirParser Backward ByteString a
plusBack :: BsBackParser a -> BsBackParser a -> BsBackParser a
plusBack :: forall a. BsBackParser a -> BsBackParser a -> BsBackParser a
plusBack BsBackParser a
f BsBackParser a
g =
(forall r.
DirState 'Backward ByteString
-> DirPos 'Backward
-> More
-> DirFailure
'Backward ByteString (DirState 'Backward ByteString) r
-> DirSuccess
'Backward ByteString (DirState 'Backward ByteString) a r
-> IResult ByteString r)
-> BsBackParser a
forall (d :: Dir) i a.
(forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
Parser ((forall r.
DirState 'Backward ByteString
-> DirPos 'Backward
-> More
-> DirFailure
'Backward ByteString (DirState 'Backward ByteString) r
-> DirSuccess
'Backward ByteString (DirState 'Backward ByteString) a r
-> IResult ByteString r)
-> BsBackParser a)
-> (forall r.
DirState 'Backward ByteString
-> DirPos 'Backward
-> More
-> DirFailure
'Backward ByteString (DirState 'Backward ByteString) r
-> DirSuccess
'Backward ByteString (DirState 'Backward ByteString) a r
-> IResult ByteString r)
-> BsBackParser a
forall a b. (a -> b) -> a -> b
$ \DirState 'Backward ByteString
t DirPos 'Backward
pos More
more DirFailure 'Backward ByteString (DirState 'Backward ByteString) r
lose DirSuccess 'Backward ByteString (DirState 'Backward ByteString) a r
succ' ->
let lose' :: DirBuffer 'Backward
-> DirPos 'Backward
-> More
-> [String]
-> String
-> IResult ByteString r
lose' DirBuffer 'Backward
t' DirPos 'Backward
_pos' More
more' [String]
_ctx String
_msg =
let !tDrift :: Int
tDrift = $(tw "t drift/") (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ DirBuffer 'Backward -> Int
forall (d :: Dir). HasDrift d => DirBuffer d -> Int
B.getDrift DirBuffer 'Backward
DirState 'Backward ByteString
t
!t'Drift :: Int
t'Drift = $(tw "t' drift/") (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ DirBuffer 'Backward -> Int
forall (d :: Dir). HasDrift d => DirBuffer d -> Int
B.getDrift DirBuffer 'Backward
t'
!dd :: Int
dd = $(tw "dd/") (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
t'Drift Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
tDrift
pos' :: DirPos 'Backward
pos' = $(tw "pos'/pos") (DirPos 'Backward -> DirPos 'Backward)
-> DirPos 'Backward -> DirPos 'Backward
forall a b. (a -> b) -> a -> b
$ DirPos 'Backward
pos DirPos 'Backward -> DirPos 'Backward -> DirPos 'Backward
forall a. Num a => a -> a -> a
+ (forall (d :: Dir). Int -> DirPos d
Pos @Backward Int
dd)
in BsBackParser a
-> forall r.
DirState 'Backward ByteString
-> DirPos 'Backward
-> More
-> DirFailure
'Backward ByteString (DirState 'Backward ByteString) r
-> DirSuccess
'Backward ByteString (DirState 'Backward ByteString) a r
-> IResult ByteString r
forall (d :: Dir) i a.
DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
runParser BsBackParser a
g DirBuffer 'Backward
DirState 'Backward ByteString
t' DirPos 'Backward
pos' More
more' DirFailure 'Backward ByteString (DirState 'Backward ByteString) r
lose DirSuccess 'Backward ByteString (DirState 'Backward ByteString) a r
succ'
in BsBackParser a
-> forall r.
DirState 'Backward ByteString
-> DirPos 'Backward
-> More
-> DirFailure
'Backward ByteString (DirState 'Backward ByteString) r
-> DirSuccess
'Backward ByteString (DirState 'Backward ByteString) a r
-> IResult ByteString r
forall (d :: Dir) i a.
DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
runParser BsBackParser a
f DirState 'Backward ByteString
t DirPos 'Backward
pos More
more DirBuffer 'Backward
-> DirPos 'Backward
-> More
-> [String]
-> String
-> IResult ByteString r
DirFailure 'Backward ByteString (DirState 'Backward ByteString) r
lose' DirSuccess 'Backward ByteString (DirState 'Backward ByteString) a r
succ'
{-# INLINE plusBack #-}
instance MonadPlus (DirParser Forward i) where
mzero :: forall a. DirParser 'Forward i a
mzero = String -> DirParser 'Forward i a
forall a. String -> DirParser 'Forward i a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"mzero"
{-# INLINE mzero #-}
mplus :: forall a.
DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
mplus = DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
forall (d :: Dir) i a.
DirParser d i a -> DirParser d i a -> DirParser d i a
plus
{-# INLINE mplus #-}
instance MonadPlus (DirParser Backward ByteString) where
mzero :: forall a. DirParser 'Backward ByteString a
mzero = String -> DirParser 'Backward ByteString a
forall a. String -> DirParser 'Backward ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"mzero"
{-# INLINE mzero #-}
mplus :: forall a. BsBackParser a -> BsBackParser a -> BsBackParser a
mplus = BsBackParser a -> BsBackParser a -> BsBackParser a
forall a. BsBackParser a -> BsBackParser a -> BsBackParser a
plusBack
{-# INLINE mplus #-}
instance Functor (DirParser d i) where
fmap :: forall a b. (a -> b) -> DirParser d i a -> DirParser d i b
fmap a -> b
f DirParser d i a
p = (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) b r
-> IResult i r)
-> DirParser d i b
forall (d :: Dir) i a.
(forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
Parser ((forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) b r
-> IResult i r)
-> DirParser d i b)
-> (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) b r
-> IResult i r)
-> DirParser d i b
forall a b. (a -> b) -> a -> b
$ \DirState d i
t DirPos d
pos More
more DirFailure d i (DirState d i) r
lose DirSuccess d i (DirState d i) b r
succ ->
let succ' :: DirState d i -> DirPos d -> More -> a -> IResult i r
succ' DirState d i
t' DirPos d
pos' More
more' a
a = DirSuccess d i (DirState d i) b r
succ DirState d i
t' DirPos d
pos' More
more' (a -> b
f a
a)
in DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
forall (d :: Dir) i a.
DirParser d i a
-> forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r
runParser DirParser d i a
p DirState d i
t DirPos d
pos More
more DirFailure d i (DirState d i) r
lose DirState d i -> DirPos d -> More -> a -> IResult i r
succ'
{-# INLINE fmap #-}
apP :: DirParser d i (a -> b) -> DirParser d i a -> DirParser d i b
apP :: forall (d :: Dir) i a b.
DirParser d i (a -> b) -> DirParser d i a -> DirParser d i b
apP DirParser d i (a -> b)
d DirParser d i a
e = do
b <- DirParser d i (a -> b)
d
a <- e
return (b a)
{-# INLINE apP #-}
instance Applicative (DirParser d i) where
pure :: forall a. a -> DirParser d i a
pure a
v = (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
forall (d :: Dir) i a.
(forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
Parser ((forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a)
-> (forall r.
DirState d i
-> DirPos d
-> More
-> DirFailure d i (DirState d i) r
-> DirSuccess d i (DirState d i) a r
-> IResult i r)
-> DirParser d i a
forall a b. (a -> b) -> a -> b
$ \DirState d i
t !DirPos d
pos More
more DirFailure d i (DirState d i) r
_lose DirSuccess d i (DirState d i) a r
succ -> DirSuccess d i (DirState d i) a r
succ DirState d i
t DirPos d
pos More
more a
v
{-# INLINE pure #-}
<*> :: forall a b.
DirParser d i (a -> b) -> DirParser d i a -> DirParser d i b
(<*>) = DirParser d i (a -> b) -> DirParser d i a -> DirParser d i b
forall (d :: Dir) i a b.
DirParser d i (a -> b) -> DirParser d i a -> DirParser d i b
apP
{-# INLINE (<*>) #-}
DirParser d i a
m *> :: forall a b. DirParser d i a -> DirParser d i b -> DirParser d i b
*> DirParser d i b
k = DirParser d i a
m DirParser d i a -> (a -> DirParser d i b) -> DirParser d i b
forall a b.
DirParser d i a -> (a -> DirParser d i b) -> DirParser d i b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
_ -> DirParser d i b
k
{-# INLINE (*>) #-}
DirParser d i a
x <* :: forall a b. DirParser d i a -> DirParser d i b -> DirParser d i a
<* DirParser d i b
y = DirParser d i a
x DirParser d i a -> (a -> DirParser d i a) -> DirParser d i a
forall a b.
DirParser d i a -> (a -> DirParser d i b) -> DirParser d i b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
a -> DirParser d i b
y DirParser d i b -> DirParser d i a -> DirParser d i a
forall a b. DirParser d i a -> DirParser d i b -> DirParser d i b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> a -> DirParser d i a
forall a. a -> DirParser d i a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
{-# INLINE (<*) #-}
instance Semigroup (DirParser Forward i a) where
<> :: DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
(<>) = DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
forall (d :: Dir) i a.
DirParser d i a -> DirParser d i a -> DirParser d i a
plus
{-# INLINE (<>) #-}
instance Semigroup (BsBackParser a) where
<> :: BsBackParser a -> BsBackParser a -> BsBackParser a
(<>) = BsBackParser a -> BsBackParser a -> BsBackParser a
forall a. BsBackParser a -> BsBackParser a -> BsBackParser a
plusBack
{-# INLINE (<>) #-}
instance Monoid (DirParser Forward i a) where
mempty :: DirParser 'Forward i a
mempty = String -> DirParser 'Forward i a
forall a. String -> DirParser 'Forward i a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"mempty"
{-# INLINE mempty #-}
mappend :: DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
mappend = DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
forall a. Semigroup a => a -> a -> a
(<>)
{-# INLINE mappend #-}
instance Monoid (BsBackParser a) where
mempty :: BsBackParser a
mempty = String -> BsBackParser a
forall a. String -> DirParser 'Backward ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"mempty"
{-# INLINE mempty #-}
mappend :: BsBackParser a -> BsBackParser a -> BsBackParser a
mappend = BsBackParser a -> BsBackParser a -> BsBackParser a
forall a. Semigroup a => a -> a -> a
(<>)
{-# INLINE mappend #-}
instance Alternative (DirParser Forward i) where
empty :: forall a. DirParser 'Forward i a
empty = String -> DirParser 'Forward i a
forall a. String -> DirParser 'Forward i a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"empty"
{-# INLINE empty #-}
<|> :: forall a.
DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
(<|>) = DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
forall (d :: Dir) i a.
DirParser d i a -> DirParser d i a -> DirParser d i a
plus
{-# INLINE (<|>) #-}
many :: forall a. DirParser 'Forward i a -> DirParser 'Forward i [a]
many DirParser 'Forward i a
v = DirParser 'Forward i [a]
many_v
where
many_v :: DirParser 'Forward i [a]
many_v = DirParser 'Forward i [a]
some_v DirParser 'Forward i [a]
-> DirParser 'Forward i [a] -> DirParser 'Forward i [a]
forall a.
DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> DirParser 'Forward i [a]
forall a. a -> DirParser 'Forward i a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
some_v :: DirParser 'Forward i [a]
some_v = (:) (a -> [a] -> [a])
-> DirParser 'Forward i a -> DirParser 'Forward i ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DirParser 'Forward i a
v DirParser 'Forward i ([a] -> [a])
-> DirParser 'Forward i [a] -> DirParser 'Forward i [a]
forall a b.
DirParser 'Forward i (a -> b)
-> DirParser 'Forward i a -> DirParser 'Forward i b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DirParser 'Forward i [a]
many_v
{-# INLINE many #-}
some :: forall a. DirParser 'Forward i a -> DirParser 'Forward i [a]
some DirParser 'Forward i a
v = DirParser 'Forward i [a]
some_v
where
many_v :: DirParser 'Forward i [a]
many_v = DirParser 'Forward i [a]
some_v DirParser 'Forward i [a]
-> DirParser 'Forward i [a] -> DirParser 'Forward i [a]
forall a.
DirParser 'Forward i a
-> DirParser 'Forward i a -> DirParser 'Forward i a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> DirParser 'Forward i [a]
forall a. a -> DirParser 'Forward i a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
some_v :: DirParser 'Forward i [a]
some_v = (:) (a -> [a] -> [a])
-> DirParser 'Forward i a -> DirParser 'Forward i ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DirParser 'Forward i a
v DirParser 'Forward i ([a] -> [a])
-> DirParser 'Forward i [a] -> DirParser 'Forward i [a]
forall a b.
DirParser 'Forward i (a -> b)
-> DirParser 'Forward i a -> DirParser 'Forward i b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DirParser 'Forward i [a]
many_v
{-# INLINE some #-}
instance Alternative (DirParser Backward ByteString) where
empty :: forall a. DirParser 'Backward ByteString a
empty = String -> DirParser 'Backward ByteString a
forall a. String -> DirParser 'Backward ByteString a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"empty"
{-# INLINE empty #-}
<|> :: forall a. BsBackParser a -> BsBackParser a -> BsBackParser a
(<|>) = BsBackParser a -> BsBackParser a -> BsBackParser a
forall a. BsBackParser a -> BsBackParser a -> BsBackParser a
plusBack
{-# INLINE (<|>) #-}
many :: forall a.
DirParser 'Backward ByteString a
-> DirParser 'Backward ByteString [a]
many DirParser 'Backward ByteString a
v = DirParser 'Backward ByteString [a]
many_v
where
many_v :: DirParser 'Backward ByteString [a]
many_v = DirParser 'Backward ByteString [a]
some_v DirParser 'Backward ByteString [a]
-> DirParser 'Backward ByteString [a]
-> DirParser 'Backward ByteString [a]
forall a. BsBackParser a -> BsBackParser a -> BsBackParser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> DirParser 'Backward ByteString [a]
forall a. a -> DirParser 'Backward ByteString a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
some_v :: DirParser 'Backward ByteString [a]
some_v = (:) (a -> [a] -> [a])
-> DirParser 'Backward ByteString a
-> DirParser 'Backward ByteString ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DirParser 'Backward ByteString a
v DirParser 'Backward ByteString ([a] -> [a])
-> DirParser 'Backward ByteString [a]
-> DirParser 'Backward ByteString [a]
forall a b.
DirParser 'Backward ByteString (a -> b)
-> DirParser 'Backward ByteString a
-> DirParser 'Backward ByteString b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DirParser 'Backward ByteString [a]
many_v
{-# INLINE many #-}
some :: forall a.
DirParser 'Backward ByteString a
-> DirParser 'Backward ByteString [a]
some DirParser 'Backward ByteString a
v = DirParser 'Backward ByteString [a]
some_v
where
many_v :: DirParser 'Backward ByteString [a]
many_v = DirParser 'Backward ByteString [a]
some_v DirParser 'Backward ByteString [a]
-> DirParser 'Backward ByteString [a]
-> DirParser 'Backward ByteString [a]
forall a. BsBackParser a -> BsBackParser a -> BsBackParser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [a] -> DirParser 'Backward ByteString [a]
forall a. a -> DirParser 'Backward ByteString a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
some_v :: DirParser 'Backward ByteString [a]
some_v = (:) (a -> [a] -> [a])
-> DirParser 'Backward ByteString a
-> DirParser 'Backward ByteString ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DirParser 'Backward ByteString a
v DirParser 'Backward ByteString ([a] -> [a])
-> DirParser 'Backward ByteString [a]
-> DirParser 'Backward ByteString [a]
forall a b.
DirParser 'Backward ByteString (a -> b)
-> DirParser 'Backward ByteString a
-> DirParser 'Backward ByteString b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DirParser 'Backward ByteString [a]
many_v
{-# INLINE some #-}
class Monoid c => Chunk c where
type ChunkElem c
nullChunk :: c -> Bool
chunkElemToChar :: c -> ChunkElem c -> Char
instance Chunk ByteString where
type ChunkElem ByteString = Word8
nullChunk :: ByteString -> Bool
nullChunk = ByteString -> Bool
BS.null
{-# INLINE nullChunk #-}
chunkElemToChar :: ByteString -> ChunkElem ByteString -> Char
chunkElemToChar ByteString
_ = Word8 -> Char
ChunkElem ByteString -> Char
w2c
{-# INLINE chunkElemToChar #-}
instance Chunk Text where
type ChunkElem Text = Char
nullChunk :: Text -> Bool
nullChunk = Text -> Bool
Text.null
{-# INLINE nullChunk #-}
chunkElemToChar :: Text -> ChunkElem Text -> Char
chunkElemToChar Text
_ = Char -> Char
ChunkElem Text -> Char
forall a. a -> a
id
{-# INLINE chunkElemToChar #-}
class (DirectedPlus d, Chunk c, Show (DirState d c)) => DirChunk (d :: Dir) c where
type DirChunkElem d c
notAtBufferEnd :: c -> DirPos d -> DirState d c -> Bool
bufferElemAt :: c -> DirPos d -> DirState d c -> Maybe (DirChunkElem d c, Int)
shiftPositionOnBufferExtend :: DirPos d -> c -> DirPos d
pappendChunk :: DirState d c -> Tagged d c -> DirState d c
concatReverse :: [Tagged d c] -> Tagged d c
instance DirChunk Forward ByteString where
type DirChunkElem Forward ByteString = Word8
notAtBufferEnd :: ByteString
-> DirPos 'Forward -> DirState 'Forward ByteString -> Bool
notAtBufferEnd ByteString
_ (Pos Int
p) DirState 'Forward ByteString
t = Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Buffer -> Int
forall (d :: Dir). DirBuffer d -> Int
B.length Buffer
DirState 'Forward ByteString
t
{-# INLINE notAtBufferEnd #-}
bufferElemAt :: ByteString
-> DirPos 'Forward
-> DirState 'Forward ByteString
-> Maybe (DirChunkElem 'Forward ByteString, Int)
bufferElemAt ByteString
_ (Pos Int
i) DirState 'Forward ByteString
buf
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Buffer -> Int
forall (d :: Dir). DirBuffer d -> Int
B.length Buffer
DirState 'Forward ByteString
buf = (Word8, Int) -> Maybe (Word8, Int)
forall a. a -> Maybe a
Just (Buffer -> Int -> Word8
forall (d :: Dir). DirBuffer d -> Int -> Word8
B.unsafeIndex Buffer
DirState 'Forward ByteString
buf Int
i, Int
1)
| Bool
otherwise = Maybe (Word8, Int)
Maybe (DirChunkElem 'Forward ByteString, Int)
forall a. Maybe a
Nothing
{-# INLINE bufferElemAt #-}
shiftPositionOnBufferExtend :: DirPos 'Forward -> ByteString -> DirPos 'Forward
shiftPositionOnBufferExtend DirPos 'Forward
a ByteString
_ = DirPos 'Forward
a
{-# INLINE shiftPositionOnBufferExtend #-}
pappendChunk :: DirState 'Forward ByteString
-> Tagged 'Forward ByteString -> DirState 'Forward ByteString
pappendChunk DirState 'Forward ByteString
buf Tagged 'Forward ByteString
t = Buffer -> ByteString -> Buffer
B.pappend Buffer
DirState 'Forward ByteString
buf (Tagged 'Forward ByteString -> ByteString
forall {k} (s :: k) b. Tagged s b -> b
untag Tagged 'Forward ByteString
t)
{-# INLINE pappendChunk #-}
concatReverse :: [Tagged 'Forward ByteString] -> Tagged 'Forward ByteString
concatReverse [Tagged 'Forward ByteString
x] = Tagged 'Forward ByteString
x
concatReverse [Tagged 'Forward ByteString]
xs = [Tagged 'Forward ByteString] -> Tagged 'Forward ByteString
forall a. Monoid a => [a] -> a
mconcat ([Tagged 'Forward ByteString] -> [Tagged 'Forward ByteString]
forall a. [a] -> [a]
reverse [Tagged 'Forward ByteString]
xs)
{-# INLINE concatReverse #-}
instance DirChunk Backward ByteString where
type DirChunkElem Backward ByteString = Word8
notAtBufferEnd :: ByteString
-> DirPos 'Backward -> DirState 'Backward ByteString -> Bool
notAtBufferEnd ByteString
_ DirPos 'Backward
p DirState 'Backward ByteString
t = DirPos 'Backward
p DirPos 'Backward -> DirPos 'Backward -> Bool
forall a. Ord a => a -> a -> Bool
>= DirPos 'Backward
0 Bool -> Bool -> Bool
&& DirBuffer 'Backward -> Int
forall (d :: Dir). DirBuffer d -> Int
B.length DirBuffer 'Backward
DirState 'Backward ByteString
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
{-# INLINE notAtBufferEnd #-}
bufferElemAt :: ByteString
-> DirPos 'Backward
-> DirState 'Backward ByteString
-> Maybe (DirChunkElem 'Backward ByteString, Int)
bufferElemAt ByteString
_ (Pos Int
i) DirState 'Backward ByteString
buf
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 = (Word8, Int) -> Maybe (Word8, Int)
forall a. a -> Maybe a
Just (DirBuffer 'Backward -> Int -> Word8
forall (d :: Dir). DirBuffer d -> Int -> Word8
B.unsafeIndex DirBuffer 'Backward
DirState 'Backward ByteString
buf Int
i, Int
1)
| Bool
otherwise = Maybe (Word8, Int)
Maybe (DirChunkElem 'Backward ByteString, Int)
forall a. Maybe a
Nothing
{-# INLINE bufferElemAt #-}
shiftPositionOnBufferExtend :: DirPos 'Backward -> ByteString -> DirPos 'Backward
shiftPositionOnBufferExtend DirPos 'Backward
a ByteString
s = DirPos 'Backward
a DirPos 'Backward -> DirPos 'Backward -> DirPos 'Backward
forall a. Num a => a -> a -> a
+ Int -> DirPos 'Backward
forall (d :: Dir). Int -> DirPos d
Pos (ByteString -> Int
BS.length ByteString
s)
{-# INLINE shiftPositionOnBufferExtend #-}
pappendChunk :: DirState 'Backward ByteString
-> Tagged 'Backward ByteString -> DirState 'Backward ByteString
pappendChunk DirState 'Backward ByteString
buf Tagged 'Backward ByteString
t = DirBuffer 'Backward -> ByteString -> DirBuffer 'Backward
B.pepreppend DirBuffer 'Backward
DirState 'Backward ByteString
buf (Tagged 'Backward ByteString -> ByteString
forall {k} (s :: k) b. Tagged s b -> b
untag Tagged 'Backward ByteString
t)
{-# INLINE pappendChunk #-}
concatReverse :: [Tagged 'Backward ByteString] -> Tagged 'Backward ByteString
concatReverse [Tagged 'Backward ByteString
x] = Tagged 'Backward ByteString
x
concatReverse [Tagged 'Backward ByteString]
xs = [Tagged 'Backward ByteString] -> Tagged 'Backward ByteString
forall a. Monoid a => [a] -> a
mconcat [Tagged 'Backward ByteString]
xs
{-# INLINE concatReverse #-}
instance DirChunk Forward Text where
type DirChunkElem Forward Text = Char
notAtBufferEnd :: Text -> DirPos 'Forward -> DirState 'Forward Text -> Bool
notAtBufferEnd Text
_ (Pos Int
p) DirState 'Forward Text
t = Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Buffer -> Int
T.length Buffer
DirState 'Forward Text
t
{-# INLINE notAtBufferEnd #-}
bufferElemAt :: Text
-> DirPos 'Forward
-> DirState 'Forward Text
-> Maybe (DirChunkElem 'Forward Text, Int)
bufferElemAt Text
_ (Pos Int
i) DirState 'Forward Text
buf
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Buffer -> Int
T.length Buffer
DirState 'Forward Text
buf = let Iter Char
c Int
l = Buffer -> Int -> Iter
T.iter Buffer
DirState 'Forward Text
buf Int
i in (Char, Int) -> Maybe (Char, Int)
forall a. a -> Maybe a
Just (Char
c, Int
l)
| Bool
otherwise = Maybe (Char, Int)
Maybe (DirChunkElem 'Forward Text, Int)
forall a. Maybe a
Nothing
{-# INLINE bufferElemAt #-}
shiftPositionOnBufferExtend :: DirPos 'Forward -> Text -> DirPos 'Forward
shiftPositionOnBufferExtend DirPos 'Forward
a Text
_ = DirPos 'Forward
a
{-# INLINE shiftPositionOnBufferExtend #-}
pappendChunk :: DirState 'Forward Text
-> Tagged 'Forward Text -> DirState 'Forward Text
pappendChunk DirState 'Forward Text
buf Tagged 'Forward Text
t = Buffer -> Text -> Buffer
T.pappend Buffer
DirState 'Forward Text
buf (Tagged 'Forward Text -> Text
forall {k} (s :: k) b. Tagged s b -> b
untag Tagged 'Forward Text
t)
{-# INLINE pappendChunk #-}
concatReverse :: [Tagged 'Forward Text] -> Tagged 'Forward Text
concatReverse [Tagged 'Forward Text
x] = Tagged 'Forward Text
x
concatReverse [Tagged 'Forward Text]
xs = [Tagged 'Forward Text] -> Tagged 'Forward Text
forall a. Monoid a => [a] -> a
mconcat ([Tagged 'Forward Text] -> [Tagged 'Forward Text]
forall a. [a] -> [a]
reverse [Tagged 'Forward Text]
xs)
{-# INLINE concatReverse #-}