{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Unsafe #-}
module Text.Megaparsec.Debug
( dbg,
dbg',
)
where
import qualified Data.List.NonEmpty as NE
import Data.Proxy
import Debug.Trace
import Text.Megaparsec.Error
import Text.Megaparsec.Internal
import Text.Megaparsec.State
import Text.Megaparsec.Stream
dbg ::
forall e s m a.
( VisualStream s,
ShowErrorComponent e,
Show a
) =>
String ->
ParsecT e s m a ->
ParsecT e s m a
dbg :: String -> ParsecT e s m a -> ParsecT e s m a
dbg String
lbl ParsecT e s m a
p = (forall b.
State s e
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> m b)
-> ParsecT e s m a
forall e s (m :: * -> *) a.
(forall b.
State s e
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> m b)
-> ParsecT e s m a
ParsecT ((forall b.
State s e
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> m b)
-> ParsecT e s m a)
-> (forall b.
State s e
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> m b)
-> ParsecT e s m a
forall a b. (a -> b) -> a -> b
$ \State s e
s a -> State s e -> Hints (Token s) -> m b
cok ParseError s e -> State s e -> m b
cerr a -> State s e -> Hints (Token s) -> m b
eok ParseError s e -> State s e -> m b
eerr ->
let l :: DbgItem s e a -> String
l = String -> DbgItem s e a -> String
forall s e a.
(VisualStream s, ShowErrorComponent e, Show a) =>
String -> DbgItem s e a -> String
dbgLog String
lbl :: DbgItem s e a -> String
unfold :: s -> [Token s]
unfold = Int -> s -> [Token s]
forall s. Stream s => Int -> s -> [Token s]
streamTake Int
40
cok' :: a -> State s e -> Hints (Token s) -> m b
cok' a
x State s e
s' Hints (Token s)
hs =
(String -> m b -> m b) -> m b -> String -> m b
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> m b -> m b
forall a. String -> a -> a
trace (a -> State s e -> Hints (Token s) -> m b
cok a
x State s e
s' Hints (Token s)
hs) (String -> m b) -> String -> m b
forall a b. (a -> b) -> a -> b
$
DbgItem s e a -> String
l ([Token s] -> DbgItem s e a
forall s e a. [Token s] -> DbgItem s e a
DbgIn (s -> [Token s]
unfold (State s e -> s
forall s e. State s e -> s
stateInput State s e
s)))
String -> String -> String
forall a. [a] -> [a] -> [a]
++ DbgItem s e a -> String
l ([Token s] -> a -> DbgItem s e a
forall s e a. [Token s] -> a -> DbgItem s e a
DbgCOK (Int -> s -> [Token s]
forall s. Stream s => Int -> s -> [Token s]
streamTake (State s e -> State s e -> Int
forall s e. State s e -> State s e -> Int
streamDelta State s e
s State s e
s') (State s e -> s
forall s e. State s e -> s
stateInput State s e
s)) a
x)
cerr' :: ParseError s e -> State s e -> m b
cerr' ParseError s e
err State s e
s' =
(String -> m b -> m b) -> m b -> String -> m b
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> m b -> m b
forall a. String -> a -> a
trace (ParseError s e -> State s e -> m b
cerr ParseError s e
err State s e
s') (String -> m b) -> String -> m b
forall a b. (a -> b) -> a -> b
$
DbgItem s e a -> String
l ([Token s] -> DbgItem s e a
forall s e a. [Token s] -> DbgItem s e a
DbgIn (s -> [Token s]
unfold (State s e -> s
forall s e. State s e -> s
stateInput State s e
s)))
String -> String -> String
forall a. [a] -> [a] -> [a]
++ DbgItem s e a -> String
l ([Token s] -> ParseError s e -> DbgItem s e a
forall s e a. [Token s] -> ParseError s e -> DbgItem s e a
DbgCERR (Int -> s -> [Token s]
forall s. Stream s => Int -> s -> [Token s]
streamTake (State s e -> State s e -> Int
forall s e. State s e -> State s e -> Int
streamDelta State s e
s State s e
s') (State s e -> s
forall s e. State s e -> s
stateInput State s e
s)) ParseError s e
err)
eok' :: a -> State s e -> Hints (Token s) -> m b
eok' a
x State s e
s' Hints (Token s)
hs =
(String -> m b -> m b) -> m b -> String -> m b
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> m b -> m b
forall a. String -> a -> a
trace (a -> State s e -> Hints (Token s) -> m b
eok a
x State s e
s' Hints (Token s)
hs) (String -> m b) -> String -> m b
forall a b. (a -> b) -> a -> b
$
DbgItem s e a -> String
l ([Token s] -> DbgItem s e a
forall s e a. [Token s] -> DbgItem s e a
DbgIn (s -> [Token s]
unfold (State s e -> s
forall s e. State s e -> s
stateInput State s e
s)))
String -> String -> String
forall a. [a] -> [a] -> [a]
++ DbgItem s e a -> String
l ([Token s] -> a -> DbgItem s e a
forall s e a. [Token s] -> a -> DbgItem s e a
DbgEOK (Int -> s -> [Token s]
forall s. Stream s => Int -> s -> [Token s]
streamTake (State s e -> State s e -> Int
forall s e. State s e -> State s e -> Int
streamDelta State s e
s State s e
s') (State s e -> s
forall s e. State s e -> s
stateInput State s e
s)) a
x)
eerr' :: ParseError s e -> State s e -> m b
eerr' ParseError s e
err State s e
s' =
(String -> m b -> m b) -> m b -> String -> m b
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> m b -> m b
forall a. String -> a -> a
trace (ParseError s e -> State s e -> m b
eerr ParseError s e
err State s e
s') (String -> m b) -> String -> m b
forall a b. (a -> b) -> a -> b
$
DbgItem s e a -> String
l ([Token s] -> DbgItem s e a
forall s e a. [Token s] -> DbgItem s e a
DbgIn (s -> [Token s]
unfold (State s e -> s
forall s e. State s e -> s
stateInput State s e
s)))
String -> String -> String
forall a. [a] -> [a] -> [a]
++ DbgItem s e a -> String
l ([Token s] -> ParseError s e -> DbgItem s e a
forall s e a. [Token s] -> ParseError s e -> DbgItem s e a
DbgEERR (Int -> s -> [Token s]
forall s. Stream s => Int -> s -> [Token s]
streamTake (State s e -> State s e -> Int
forall s e. State s e -> State s e -> Int
streamDelta State s e
s State s e
s') (State s e -> s
forall s e. State s e -> s
stateInput State s e
s)) ParseError s e
err)
in ParsecT e s m a
-> State s e
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> m b
forall e s (m :: * -> *) a.
ParsecT e s m a
-> forall b.
State s e
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> (a -> State s e -> Hints (Token s) -> m b)
-> (ParseError s e -> State s e -> m b)
-> m b
unParser ParsecT e s m a
p State s e
s a -> State s e -> Hints (Token s) -> m b
cok' ParseError s e -> State s e -> m b
cerr' a -> State s e -> Hints (Token s) -> m b
eok' ParseError s e -> State s e -> m b
eerr'
dbg' ::
forall e s m a.
( VisualStream s,
ShowErrorComponent e
) =>
String ->
ParsecT e s m a ->
ParsecT e s m a
dbg' :: String -> ParsecT e s m a -> ParsecT e s m a
dbg' String
lbl ParsecT e s m a
p = Blind a -> a
forall x. Blind x -> x
unBlind (Blind a -> a) -> ParsecT e s m (Blind a) -> ParsecT e s m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ParsecT e s m (Blind a) -> ParsecT e s m (Blind a)
forall e s (m :: * -> *) a.
(VisualStream s, ShowErrorComponent e, Show a) =>
String -> ParsecT e s m a -> ParsecT e s m a
dbg String
lbl (a -> Blind a
forall x. x -> Blind x
Blind (a -> Blind a) -> ParsecT e s m a -> ParsecT e s m (Blind a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT e s m a
p)
newtype Blind x = Blind {Blind x -> x
unBlind :: x}
instance Show (Blind x) where
show :: Blind x -> String
show Blind x
_ = String
"NOT SHOWN"
data DbgItem s e a
= DbgIn [Token s]
| DbgCOK [Token s] a
| DbgCERR [Token s] (ParseError s e)
| DbgEOK [Token s] a
| DbgEERR [Token s] (ParseError s e)
dbgLog ::
forall s e a.
(VisualStream s, ShowErrorComponent e, Show a) =>
String ->
DbgItem s e a ->
String
dbgLog :: String -> DbgItem s e a -> String
dbgLog String
lbl DbgItem s e a
item = String -> String
prefix String
msg
where
prefix :: String -> String
prefix = [String] -> String
unlines ([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> [String] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((String
lbl String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"> ") String -> String -> String
forall a. [a] -> [a] -> [a]
++) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines
pxy :: Proxy s
pxy = Proxy s
forall k (t :: k). Proxy t
Proxy :: Proxy s
msg :: String
msg = case DbgItem s e a
item of
DbgIn [Token s]
ts ->
String
"IN: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Proxy s -> [Token s] -> String
forall s. VisualStream s => Proxy s -> [Token s] -> String
showStream Proxy s
pxy [Token s]
ts
DbgCOK [Token s]
ts a
a ->
String
"MATCH (COK): " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Proxy s -> [Token s] -> String
forall s. VisualStream s => Proxy s -> [Token s] -> String
showStream Proxy s
pxy [Token s]
ts String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\nVALUE: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
a
DbgCERR [Token s]
ts ParseError s e
e ->
String
"MATCH (CERR): " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Proxy s -> [Token s] -> String
forall s. VisualStream s => Proxy s -> [Token s] -> String
showStream Proxy s
pxy [Token s]
ts String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\nERROR:\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ ParseError s e -> String
forall s e.
(VisualStream s, ShowErrorComponent e) =>
ParseError s e -> String
parseErrorPretty ParseError s e
e
DbgEOK [Token s]
ts a
a ->
String
"MATCH (EOK): " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Proxy s -> [Token s] -> String
forall s. VisualStream s => Proxy s -> [Token s] -> String
showStream Proxy s
pxy [Token s]
ts String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\nVALUE: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
a
DbgEERR [Token s]
ts ParseError s e
e ->
String
"MATCH (EERR): " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Proxy s -> [Token s] -> String
forall s. VisualStream s => Proxy s -> [Token s] -> String
showStream Proxy s
pxy [Token s]
ts String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\nERROR:\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ ParseError s e -> String
forall s e.
(VisualStream s, ShowErrorComponent e) =>
ParseError s e -> String
parseErrorPretty ParseError s e
e
showStream :: VisualStream s => Proxy s -> [Token s] -> String
showStream :: Proxy s -> [Token s] -> String
showStream Proxy s
pxy [Token s]
ts =
case [Token s] -> Maybe (NonEmpty (Token s))
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty [Token s]
ts of
Maybe (NonEmpty (Token s))
Nothing -> String
"<EMPTY>"
Just NonEmpty (Token s)
ne ->
let (String
h, String
r) = Int -> String -> (String, String)
forall a. Int -> [a] -> ([a], [a])
splitAt Int
40 (Proxy s -> NonEmpty (Token s) -> String
forall s. VisualStream s => Proxy s -> NonEmpty (Token s) -> String
showTokens Proxy s
pxy NonEmpty (Token s)
ne)
in if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
r then String
h else String
h String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" <…>"
streamDelta ::
State s e ->
State s e ->
Int
streamDelta :: State s e -> State s e -> Int
streamDelta State s e
s0 State s e
s1 = State s e -> Int
forall s e. State s e -> Int
stateOffset State s e
s1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- State s e -> Int
forall s e. State s e -> Int
stateOffset State s e
s0
streamTake :: forall s. Stream s => Int -> s -> [Token s]
streamTake :: Int -> s -> [Token s]
streamTake Int
n s
s =
case (Tokens s, s) -> Tokens s
forall a b. (a, b) -> a
fst ((Tokens s, s) -> Tokens s)
-> Maybe (Tokens s, s) -> Maybe (Tokens s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> s -> Maybe (Tokens s, s)
forall s. Stream s => Int -> s -> Maybe (Tokens s, s)
takeN_ Int
n s
s of
Maybe (Tokens s)
Nothing -> []
Just Tokens s
chk -> Proxy s -> Tokens s -> [Token s]
forall s. Stream s => Proxy s -> Tokens s -> [Token s]
chunkToTokens (Proxy s
forall k (t :: k). Proxy t
Proxy :: Proxy s) Tokens s
chk