module H.Dump where import H.Common import Hydrogen.Parsing hiding (parse, token) import Hydrogen.Syntax.Parser import Hydrogen.Syntax.Types main :: Tool main _ args = do let (_, switches, files) = getOpts args [ 'T' ~: switch "tokens" , 'L' ~: switch "layout" , 'P' ~: switch "parse" ] report = concatMap showMessage where showMessage (pos, message) = printf "%4d%4d %s\n" (sourceLine pos) (sourceColumn pos) message func | switches ? "tokens" = either report showTokens . tokenize "-" | switches ? "layout" = either report showLayout . parse "-" | switches ? "parse" = either report showLayout . parse "-" | otherwise = const "Need -T, -L, or -P" showTokens = concatMap showToken showToken (pos, token) = printf "%4d%4d %s\n" (sourceLine pos) (sourceColumn pos) (show token) showLayout = concat . showPOPs "" [] showPOPs indent backlog = \case (pos, pop) : ps -> case pop of Token t k x -> printf "%4d%4d %s%s %s %s\n" (sourceLine pos) (sourceColumn pos) indent (show t) k x : showPOPs indent backlog ps Block t x pops -> printf "%4d%4d %s%s %s\n" (sourceLine pos) (sourceColumn pos) indent (show t) x : showPOPs (" " ++ indent) (ps : backlog) pops [] | null backlog -> [] | otherwise -> showPOPs (drop 2 indent) (tail backlog) (head backlog) onFiles (putStr . func) files