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