{-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE Strict #-} {-# LANGUAGE StrictData #-} {-# LANGUAGE TypeFamilies #-} module Language.Cimple.TraverseAst ( traverseAst , doFiles, doFile , doNodes, doNode , doLexemes, doLexeme , doText , astActions, AstActions ) where import Data.Fix (Fix (..)) import Data.Foldable (traverse_) import Language.Cimple.Ast (Node, NodeF (..)) import Language.Cimple.Lexer (Lexeme (..)) class TraverseAst text a where traverseFileAst :: Applicative f => AstActions f text -> FilePath -> a -> f () traverseAst :: (TraverseAst text a, Applicative f) => AstActions f text -> a -> f () traverseAst :: AstActions f text -> a -> f () traverseAst = (AstActions f text -> FilePath -> a -> f ()) -> FilePath -> AstActions f text -> a -> f () forall a b c. (a -> b -> c) -> b -> a -> c flip AstActions f text -> FilePath -> a -> f () forall text a (f :: * -> *). (TraverseAst text a, Applicative f) => AstActions f text -> FilePath -> a -> f () traverseFileAst FilePath "<stdin>" data AstActions f text = AstActions { AstActions f text -> [(FilePath, [Node (Lexeme text)])] -> f () -> f () doFiles :: [(FilePath, [Node (Lexeme text)])] -> f () -> f () , AstActions f text -> (FilePath, [Node (Lexeme text)]) -> f () -> f () doFile :: (FilePath, [Node (Lexeme text)]) -> f () -> f () , AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () -> f () doNodes :: FilePath -> [Node (Lexeme text)] -> f () -> f () , AstActions f text -> FilePath -> Node (Lexeme text) -> f () -> f () doNode :: FilePath -> Node (Lexeme text) -> f () -> f () , AstActions f text -> FilePath -> [Lexeme text] -> f () -> f () doLexemes :: FilePath -> [Lexeme text] -> f () -> f () , AstActions f text -> FilePath -> Lexeme text -> f () -> f () doLexeme :: FilePath -> Lexeme text -> f () -> f () , AstActions f text -> FilePath -> text -> f () doText :: FilePath -> text -> f () } instance TraverseAst text a => TraverseAst text (Maybe a) where traverseFileAst :: AstActions f text -> FilePath -> Maybe a -> f () traverseFileAst AstActions f text _ FilePath _ Maybe a _ = () -> f () forall (f :: * -> *) a. Applicative f => a -> f a pure () astActions :: Applicative f => AstActions f text astActions :: AstActions f text astActions = AstActions :: forall (f :: * -> *) text. ([(FilePath, [Node (Lexeme text)])] -> f () -> f ()) -> ((FilePath, [Node (Lexeme text)]) -> f () -> f ()) -> (FilePath -> [Node (Lexeme text)] -> f () -> f ()) -> (FilePath -> Node (Lexeme text) -> f () -> f ()) -> (FilePath -> [Lexeme text] -> f () -> f ()) -> (FilePath -> Lexeme text -> f () -> f ()) -> (FilePath -> text -> f ()) -> AstActions f text AstActions { doFiles :: [(FilePath, [Node (Lexeme text)])] -> f () -> f () doFiles = (f () -> f ()) -> [(FilePath, [Node (Lexeme text)])] -> f () -> f () forall a b. a -> b -> a const f () -> f () forall a. a -> a id , doFile :: (FilePath, [Node (Lexeme text)]) -> f () -> f () doFile = (f () -> f ()) -> (FilePath, [Node (Lexeme text)]) -> f () -> f () forall a b. a -> b -> a const f () -> f () forall a. a -> a id , doNodes :: FilePath -> [Node (Lexeme text)] -> f () -> f () doNodes = ([Node (Lexeme text)] -> f () -> f ()) -> FilePath -> [Node (Lexeme text)] -> f () -> f () forall a b. a -> b -> a const (([Node (Lexeme text)] -> f () -> f ()) -> FilePath -> [Node (Lexeme text)] -> f () -> f ()) -> ([Node (Lexeme text)] -> f () -> f ()) -> FilePath -> [Node (Lexeme text)] -> f () -> f () forall a b. (a -> b) -> a -> b $ (f () -> f ()) -> [Node (Lexeme text)] -> f () -> f () forall a b. a -> b -> a const f () -> f () forall a. a -> a id , doNode :: FilePath -> Node (Lexeme text) -> f () -> f () doNode = (Node (Lexeme text) -> f () -> f ()) -> FilePath -> Node (Lexeme text) -> f () -> f () forall a b. a -> b -> a const ((Node (Lexeme text) -> f () -> f ()) -> FilePath -> Node (Lexeme text) -> f () -> f ()) -> (Node (Lexeme text) -> f () -> f ()) -> FilePath -> Node (Lexeme text) -> f () -> f () forall a b. (a -> b) -> a -> b $ (f () -> f ()) -> Node (Lexeme text) -> f () -> f () forall a b. a -> b -> a const f () -> f () forall a. a -> a id , doLexeme :: FilePath -> Lexeme text -> f () -> f () doLexeme = (Lexeme text -> f () -> f ()) -> FilePath -> Lexeme text -> f () -> f () forall a b. a -> b -> a const ((Lexeme text -> f () -> f ()) -> FilePath -> Lexeme text -> f () -> f ()) -> (Lexeme text -> f () -> f ()) -> FilePath -> Lexeme text -> f () -> f () forall a b. (a -> b) -> a -> b $ (f () -> f ()) -> Lexeme text -> f () -> f () forall a b. a -> b -> a const f () -> f () forall a. a -> a id , doLexemes :: FilePath -> [Lexeme text] -> f () -> f () doLexemes = ([Lexeme text] -> f () -> f ()) -> FilePath -> [Lexeme text] -> f () -> f () forall a b. a -> b -> a const (([Lexeme text] -> f () -> f ()) -> FilePath -> [Lexeme text] -> f () -> f ()) -> ([Lexeme text] -> f () -> f ()) -> FilePath -> [Lexeme text] -> f () -> f () forall a b. (a -> b) -> a -> b $ (f () -> f ()) -> [Lexeme text] -> f () -> f () forall a b. a -> b -> a const f () -> f () forall a. a -> a id , doText :: FilePath -> text -> f () doText = (text -> f ()) -> FilePath -> text -> f () forall a b. a -> b -> a const ((text -> f ()) -> FilePath -> text -> f ()) -> (text -> f ()) -> FilePath -> text -> f () forall a b. (a -> b) -> a -> b $ f () -> text -> f () forall a b. a -> b -> a const (f () -> text -> f ()) -> f () -> text -> f () forall a b. (a -> b) -> a -> b $ () -> f () forall (f :: * -> *) a. Applicative f => a -> f a pure () } instance TraverseAst text (Lexeme text) where traverseFileAst :: forall f . Applicative f => AstActions f text -> FilePath -> Lexeme text -> f () traverseFileAst :: AstActions f text -> FilePath -> Lexeme text -> f () traverseFileAst AstActions{FilePath -> text -> f () FilePath -> [Node (Lexeme text)] -> f () -> f () FilePath -> [Lexeme text] -> f () -> f () FilePath -> Node (Lexeme text) -> f () -> f () FilePath -> Lexeme text -> f () -> f () [(FilePath, [Node (Lexeme text)])] -> f () -> f () (FilePath, [Node (Lexeme text)]) -> f () -> f () doText :: FilePath -> text -> f () doLexeme :: FilePath -> Lexeme text -> f () -> f () doLexemes :: FilePath -> [Lexeme text] -> f () -> f () doNode :: FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: [(FilePath, [Node (Lexeme text)])] -> f () -> f () doText :: forall (f :: * -> *) text. AstActions f text -> FilePath -> text -> f () doLexeme :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Lexeme text -> f () -> f () doLexemes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Lexeme text] -> f () -> f () doNode :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: forall (f :: * -> *) text. AstActions f text -> (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: forall (f :: * -> *) text. AstActions f text -> [(FilePath, [Node (Lexeme text)])] -> f () -> f () ..} FilePath currentFile = FilePath -> Lexeme text -> f () -> f () doLexeme FilePath currentFile (Lexeme text -> f () -> f ()) -> (Lexeme text -> f ()) -> Lexeme text -> f () forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> \(L AlexPosn _ LexemeClass _ text s) -> FilePath -> text -> f () doText FilePath currentFile text s instance TraverseAst text [Lexeme text] where traverseFileAst :: AstActions f text -> FilePath -> [Lexeme text] -> f () traverseFileAst actions :: AstActions f text actions@AstActions{FilePath -> text -> f () FilePath -> [Node (Lexeme text)] -> f () -> f () FilePath -> [Lexeme text] -> f () -> f () FilePath -> Node (Lexeme text) -> f () -> f () FilePath -> Lexeme text -> f () -> f () [(FilePath, [Node (Lexeme text)])] -> f () -> f () (FilePath, [Node (Lexeme text)]) -> f () -> f () doText :: FilePath -> text -> f () doLexeme :: FilePath -> Lexeme text -> f () -> f () doLexemes :: FilePath -> [Lexeme text] -> f () -> f () doNode :: FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: [(FilePath, [Node (Lexeme text)])] -> f () -> f () doText :: forall (f :: * -> *) text. AstActions f text -> FilePath -> text -> f () doLexeme :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Lexeme text -> f () -> f () doLexemes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Lexeme text] -> f () -> f () doNode :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: forall (f :: * -> *) text. AstActions f text -> (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: forall (f :: * -> *) text. AstActions f text -> [(FilePath, [Node (Lexeme text)])] -> f () -> f () ..} FilePath currentFile = FilePath -> [Lexeme text] -> f () -> f () doLexemes FilePath currentFile ([Lexeme text] -> f () -> f ()) -> ([Lexeme text] -> f ()) -> [Lexeme text] -> f () forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Lexeme text -> f ()) -> [Lexeme text] -> f () forall (t :: * -> *) (f :: * -> *) a b. (Foldable t, Applicative f) => (a -> f b) -> t a -> f () traverse_ (AstActions f text -> FilePath -> Lexeme text -> f () forall text a (f :: * -> *). (TraverseAst text a, Applicative f) => AstActions f text -> FilePath -> a -> f () traverseFileAst AstActions f text actions FilePath currentFile) instance TraverseAst text (Node (Lexeme text)) where traverseFileAst :: forall f . Applicative f => AstActions f text -> FilePath -> Node (Lexeme text) -> f () traverseFileAst :: AstActions f text -> FilePath -> Node (Lexeme text) -> f () traverseFileAst actions :: AstActions f text actions@AstActions{FilePath -> text -> f () FilePath -> [Node (Lexeme text)] -> f () -> f () FilePath -> [Lexeme text] -> f () -> f () FilePath -> Node (Lexeme text) -> f () -> f () FilePath -> Lexeme text -> f () -> f () [(FilePath, [Node (Lexeme text)])] -> f () -> f () (FilePath, [Node (Lexeme text)]) -> f () -> f () doText :: FilePath -> text -> f () doLexeme :: FilePath -> Lexeme text -> f () -> f () doLexemes :: FilePath -> [Lexeme text] -> f () -> f () doNode :: FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: [(FilePath, [Node (Lexeme text)])] -> f () -> f () doText :: forall (f :: * -> *) text. AstActions f text -> FilePath -> text -> f () doLexeme :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Lexeme text -> f () -> f () doLexemes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Lexeme text] -> f () -> f () doNode :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: forall (f :: * -> *) text. AstActions f text -> (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: forall (f :: * -> *) text. AstActions f text -> [(FilePath, [Node (Lexeme text)])] -> f () -> f () ..} FilePath currentFile = FilePath -> Node (Lexeme text) -> f () -> f () doNode FilePath currentFile (Node (Lexeme text) -> f () -> f ()) -> (Node (Lexeme text) -> f ()) -> Node (Lexeme text) -> f () forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> \Node (Lexeme text) node -> case Node (Lexeme text) -> NodeF (Lexeme text) (Node (Lexeme text)) forall (f :: * -> *). Fix f -> f (Fix f) unFix Node (Lexeme text) node of PreprocInclude Lexeme text path -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text path PreprocDefine Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name PreprocDefineConst Lexeme text name Node (Lexeme text) value -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) value pure () PreprocDefineMacro Lexeme text name [Node (Lexeme text)] params Node (Lexeme text) body -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] params () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) body pure () PreprocIf Node (Lexeme text) cond [Node (Lexeme text)] thenDecls Node (Lexeme text) elseBranch -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) cond () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] thenDecls () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) elseBranch pure () PreprocIfdef Lexeme text name [Node (Lexeme text)] thenDecls Node (Lexeme text) elseBranch -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] thenDecls () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) elseBranch pure () PreprocIfndef Lexeme text name [Node (Lexeme text)] thenDecls Node (Lexeme text) elseBranch -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] thenDecls () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) elseBranch pure () PreprocElse [Node (Lexeme text)] decls -> [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] decls PreprocElif Node (Lexeme text) cond [Node (Lexeme text)] decls Node (Lexeme text) elseBranch -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) cond () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] decls () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) elseBranch pure () PreprocUndef Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name PreprocDefined Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name PreprocScopedDefine Node (Lexeme text) define [Node (Lexeme text)] stmts Node (Lexeme text) undef -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) define () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] stmts () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) undef pure () MacroBodyStmt Node (Lexeme text) stmts -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) stmts MacroBodyFunCall Node (Lexeme text) expr -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) expr MacroParam Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name StaticAssert Node (Lexeme text) cond Lexeme text msg -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) cond () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text msg pure () LicenseDecl Lexeme text license [Node (Lexeme text)] copyrights -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text license () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] copyrights pure () CopyrightDecl Lexeme text from Maybe (Lexeme text) to [Lexeme text] owner -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text from () _ <- Maybe (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Maybe (Lexeme text) to () _ <- [Lexeme text] -> f () forall a. TraverseAst text a => a -> f () recurse [Lexeme text] owner pure () Comment CommentStyle _doc Lexeme text start [Lexeme text] contents Lexeme text end -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text start () _ <- [Lexeme text] -> f () forall a. TraverseAst text a => a -> f () recurse [Lexeme text] contents () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text end pure () CommentSectionEnd Lexeme text comment -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text comment pure () Commented Node (Lexeme text) comment Node (Lexeme text) subject -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) comment () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) subject pure () ExternC [Node (Lexeme text)] decls -> [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] decls CompoundStmt [Node (Lexeme text)] stmts -> [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] stmts NodeF (Lexeme text) (Node (Lexeme text)) Break -> () -> f () forall (f :: * -> *) a. Applicative f => a -> f a pure () Goto Lexeme text label -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text label NodeF (Lexeme text) (Node (Lexeme text)) Continue -> () -> f () forall (f :: * -> *) a. Applicative f => a -> f a pure () Return Maybe (Node (Lexeme text)) value -> Maybe (Node (Lexeme text)) -> f () forall a. TraverseAst text a => a -> f () recurse Maybe (Node (Lexeme text)) value SwitchStmt Node (Lexeme text) value [Node (Lexeme text)] cases -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) value () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] cases pure () IfStmt Node (Lexeme text) cond Node (Lexeme text) thenStmts Maybe (Node (Lexeme text)) elseStmt -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) cond () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) thenStmts () _ <- Maybe (Node (Lexeme text)) -> f () forall a. TraverseAst text a => a -> f () recurse Maybe (Node (Lexeme text)) elseStmt pure () ForStmt Node (Lexeme text) initStmt Node (Lexeme text) cond Node (Lexeme text) next Node (Lexeme text) stmts -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) initStmt () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) cond () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) next () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) stmts pure () WhileStmt Node (Lexeme text) cond Node (Lexeme text) stmts -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) cond () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) stmts pure () DoWhileStmt Node (Lexeme text) stmts Node (Lexeme text) cond -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) stmts () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) cond pure () Case Node (Lexeme text) value Node (Lexeme text) stmt -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) value () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) stmt pure () Default Node (Lexeme text) stmt -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) stmt Label Lexeme text label Node (Lexeme text) stmt -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text label () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) stmt pure () ExprStmt Node (Lexeme text) expr -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) expr pure () VLA Node (Lexeme text) ty Lexeme text name Node (Lexeme text) size -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) size pure () VarDeclStmt Node (Lexeme text) decl Maybe (Node (Lexeme text)) ini -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) decl () _ <- Maybe (Node (Lexeme text)) -> f () forall a. TraverseAst text a => a -> f () recurse Maybe (Node (Lexeme text)) ini pure () VarDecl Node (Lexeme text) ty Lexeme text name [Node (Lexeme text)] arrs -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] arrs pure () DeclSpecArray Maybe (Node (Lexeme text)) size -> Maybe (Node (Lexeme text)) -> f () forall a. TraverseAst text a => a -> f () recurse Maybe (Node (Lexeme text)) size InitialiserList [Node (Lexeme text)] values -> [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] values UnaryExpr UnaryOp _op Node (Lexeme text) expr -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) expr BinaryExpr Node (Lexeme text) lhs BinaryOp _op Node (Lexeme text) rhs -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) lhs () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) rhs pure () TernaryExpr Node (Lexeme text) cond Node (Lexeme text) thenExpr Node (Lexeme text) elseExpr -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) cond () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) thenExpr () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) elseExpr pure () AssignExpr Node (Lexeme text) lhs AssignOp _op Node (Lexeme text) rhs -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) lhs () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) rhs pure () ParenExpr Node (Lexeme text) expr -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) expr CastExpr Node (Lexeme text) ty Node (Lexeme text) expr -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) expr pure () CompoundExpr Node (Lexeme text) ty Node (Lexeme text) expr -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) expr pure () SizeofExpr Node (Lexeme text) expr -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) expr SizeofType Node (Lexeme text) ty -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty LiteralExpr LiteralType _ty Lexeme text value -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text value VarExpr Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name MemberAccess Node (Lexeme text) name Lexeme text field -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) name () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text field pure () PointerAccess Node (Lexeme text) name Lexeme text field -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) name () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text field pure () ArrayAccess Node (Lexeme text) arr Node (Lexeme text) idx -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) arr () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) idx pure () FunctionCall Node (Lexeme text) callee [Node (Lexeme text)] args -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) callee () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] args pure () CommentExpr Node (Lexeme text) comment Node (Lexeme text) expr -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) comment () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) expr pure () EnumConsts Maybe (Lexeme text) name [Node (Lexeme text)] members -> do () _ <- Maybe (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Maybe (Lexeme text) name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] members pure () EnumDecl Lexeme text name [Node (Lexeme text)] members Lexeme text tyName -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] members () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text tyName pure () Enumerator Lexeme text name Maybe (Node (Lexeme text)) value -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- Maybe (Node (Lexeme text)) -> f () forall a. TraverseAst text a => a -> f () recurse Maybe (Node (Lexeme text)) value pure () AggregateDecl Node (Lexeme text) struct -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) struct pure () Typedef Node (Lexeme text) ty Lexeme text name -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name pure () TypedefFunction Node (Lexeme text) ty -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty Struct Lexeme text name [Node (Lexeme text)] members -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] members pure () Union Lexeme text name [Node (Lexeme text)] members -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] members pure () MemberDecl Node (Lexeme text) decl Maybe (Lexeme text) bits -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) decl () _ <- Maybe (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Maybe (Lexeme text) bits pure () TyConst Node (Lexeme text) ty -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty TyPointer Node (Lexeme text) ty -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty TyStruct Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name TyFunc Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name TyStd Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name TyUserDefined Lexeme text name -> Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name FunctionDecl Scope _scope Node (Lexeme text) proto -> Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) proto FunctionDefn Scope _scope Node (Lexeme text) proto Node (Lexeme text) body -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) proto () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) body pure () FunctionPrototype Node (Lexeme text) ty Lexeme text name [Node (Lexeme text)] params -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- [Node (Lexeme text)] -> f () forall a. TraverseAst text a => a -> f () recurse [Node (Lexeme text)] params pure () CallbackDecl Lexeme text ty Lexeme text name -> do () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text ty () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name pure () NodeF (Lexeme text) (Node (Lexeme text)) Ellipsis -> () -> f () forall (f :: * -> *) a. Applicative f => a -> f a pure () NonNull [Lexeme text] nonnull [Lexeme text] nullable Node (Lexeme text) f -> do () _ <- [Lexeme text] -> f () forall a. TraverseAst text a => a -> f () recurse [Lexeme text] nonnull () _ <- [Lexeme text] -> f () forall a. TraverseAst text a => a -> f () recurse [Lexeme text] nullable () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) f pure () ConstDecl Node (Lexeme text) ty Lexeme text name -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name pure () ConstDefn Scope _scope Node (Lexeme text) ty Lexeme text name Node (Lexeme text) value -> do () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) ty () _ <- Lexeme text -> f () forall a. TraverseAst text a => a -> f () recurse Lexeme text name () _ <- Node (Lexeme text) -> f () forall a. TraverseAst text a => a -> f () recurse Node (Lexeme text) value pure () where recurse :: TraverseAst text a => a -> f () recurse :: a -> f () recurse = AstActions f text -> FilePath -> a -> f () forall text a (f :: * -> *). (TraverseAst text a, Applicative f) => AstActions f text -> FilePath -> a -> f () traverseFileAst AstActions f text actions FilePath currentFile instance TraverseAst text [Node (Lexeme text)] where traverseFileAst :: AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () traverseFileAst actions :: AstActions f text actions@AstActions{FilePath -> text -> f () FilePath -> [Node (Lexeme text)] -> f () -> f () FilePath -> [Lexeme text] -> f () -> f () FilePath -> Node (Lexeme text) -> f () -> f () FilePath -> Lexeme text -> f () -> f () [(FilePath, [Node (Lexeme text)])] -> f () -> f () (FilePath, [Node (Lexeme text)]) -> f () -> f () doText :: FilePath -> text -> f () doLexeme :: FilePath -> Lexeme text -> f () -> f () doLexemes :: FilePath -> [Lexeme text] -> f () -> f () doNode :: FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: [(FilePath, [Node (Lexeme text)])] -> f () -> f () doText :: forall (f :: * -> *) text. AstActions f text -> FilePath -> text -> f () doLexeme :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Lexeme text -> f () -> f () doLexemes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Lexeme text] -> f () -> f () doNode :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: forall (f :: * -> *) text. AstActions f text -> (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: forall (f :: * -> *) text. AstActions f text -> [(FilePath, [Node (Lexeme text)])] -> f () -> f () ..} FilePath currentFile = FilePath -> [Node (Lexeme text)] -> f () -> f () doNodes FilePath currentFile ([Node (Lexeme text)] -> f () -> f ()) -> ([Node (Lexeme text)] -> f ()) -> [Node (Lexeme text)] -> f () forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Node (Lexeme text) -> f ()) -> [Node (Lexeme text)] -> f () forall (t :: * -> *) (f :: * -> *) a b. (Foldable t, Applicative f) => (a -> f b) -> t a -> f () traverse_ (AstActions f text -> FilePath -> Node (Lexeme text) -> f () forall text a (f :: * -> *). (TraverseAst text a, Applicative f) => AstActions f text -> FilePath -> a -> f () traverseFileAst AstActions f text actions FilePath currentFile) instance TraverseAst text (FilePath, [Node (Lexeme text)]) where traverseFileAst :: AstActions f text -> FilePath -> (FilePath, [Node (Lexeme text)]) -> f () traverseFileAst actions :: AstActions f text actions@AstActions{FilePath -> text -> f () FilePath -> [Node (Lexeme text)] -> f () -> f () FilePath -> [Lexeme text] -> f () -> f () FilePath -> Node (Lexeme text) -> f () -> f () FilePath -> Lexeme text -> f () -> f () [(FilePath, [Node (Lexeme text)])] -> f () -> f () (FilePath, [Node (Lexeme text)]) -> f () -> f () doText :: FilePath -> text -> f () doLexeme :: FilePath -> Lexeme text -> f () -> f () doLexemes :: FilePath -> [Lexeme text] -> f () -> f () doNode :: FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: [(FilePath, [Node (Lexeme text)])] -> f () -> f () doText :: forall (f :: * -> *) text. AstActions f text -> FilePath -> text -> f () doLexeme :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Lexeme text -> f () -> f () doLexemes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Lexeme text] -> f () -> f () doNode :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: forall (f :: * -> *) text. AstActions f text -> (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: forall (f :: * -> *) text. AstActions f text -> [(FilePath, [Node (Lexeme text)])] -> f () -> f () ..} FilePath _ tu :: (FilePath, [Node (Lexeme text)]) tu@(FilePath currentFile, [Node (Lexeme text)] _) = (FilePath, [Node (Lexeme text)]) -> f () -> f () doFile ((FilePath, [Node (Lexeme text)]) -> f () -> f ()) -> ((FilePath, [Node (Lexeme text)]) -> f ()) -> (FilePath, [Node (Lexeme text)]) -> f () forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> ([Node (Lexeme text)] -> f ()) -> (FilePath, [Node (Lexeme text)]) -> f () forall (t :: * -> *) (f :: * -> *) a b. (Foldable t, Applicative f) => (a -> f b) -> t a -> f () traverse_ (AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () forall text a (f :: * -> *). (TraverseAst text a, Applicative f) => AstActions f text -> FilePath -> a -> f () traverseFileAst AstActions f text actions FilePath currentFile) ((FilePath, [Node (Lexeme text)]) -> f ()) -> (FilePath, [Node (Lexeme text)]) -> f () forall a b. (a -> b) -> a -> b $ (FilePath, [Node (Lexeme text)]) tu instance TraverseAst text [(FilePath, [Node (Lexeme text)])] where traverseFileAst :: AstActions f text -> FilePath -> [(FilePath, [Node (Lexeme text)])] -> f () traverseFileAst actions :: AstActions f text actions@AstActions{FilePath -> text -> f () FilePath -> [Node (Lexeme text)] -> f () -> f () FilePath -> [Lexeme text] -> f () -> f () FilePath -> Node (Lexeme text) -> f () -> f () FilePath -> Lexeme text -> f () -> f () [(FilePath, [Node (Lexeme text)])] -> f () -> f () (FilePath, [Node (Lexeme text)]) -> f () -> f () doText :: FilePath -> text -> f () doLexeme :: FilePath -> Lexeme text -> f () -> f () doLexemes :: FilePath -> [Lexeme text] -> f () -> f () doNode :: FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: [(FilePath, [Node (Lexeme text)])] -> f () -> f () doText :: forall (f :: * -> *) text. AstActions f text -> FilePath -> text -> f () doLexeme :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Lexeme text -> f () -> f () doLexemes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Lexeme text] -> f () -> f () doNode :: forall (f :: * -> *) text. AstActions f text -> FilePath -> Node (Lexeme text) -> f () -> f () doNodes :: forall (f :: * -> *) text. AstActions f text -> FilePath -> [Node (Lexeme text)] -> f () -> f () doFile :: forall (f :: * -> *) text. AstActions f text -> (FilePath, [Node (Lexeme text)]) -> f () -> f () doFiles :: forall (f :: * -> *) text. AstActions f text -> [(FilePath, [Node (Lexeme text)])] -> f () -> f () ..} FilePath currentFile = [(FilePath, [Node (Lexeme text)])] -> f () -> f () doFiles ([(FilePath, [Node (Lexeme text)])] -> f () -> f ()) -> ([(FilePath, [Node (Lexeme text)])] -> f ()) -> [(FilePath, [Node (Lexeme text)])] -> f () forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> ((FilePath, [Node (Lexeme text)]) -> f ()) -> [(FilePath, [Node (Lexeme text)])] -> f () forall (t :: * -> *) (f :: * -> *) a b. (Foldable t, Applicative f) => (a -> f b) -> t a -> f () traverse_ (AstActions f text -> FilePath -> (FilePath, [Node (Lexeme text)]) -> f () forall text a (f :: * -> *). (TraverseAst text a, Applicative f) => AstActions f text -> FilePath -> a -> f () traverseFileAst AstActions f text actions FilePath currentFile)