Safe Haskell | None |
---|---|
Language | Haskell98 |
GHC.Syb.Utils provides common utilities for the Ghc Api, either based on Data/Typeable or for use with Data.Generics over Ghc Api types.
example output of showData
on parsedSource
, renamedSource
, and
typecheckedSource
for a trivial HelloWorld
module, compared with
ppr
output:
------------------------- pretty-printed parsedSource module HelloWorld where main = putStrLn "Hello, World!" ------------------------- pretty-printed renamedSource Just (HelloWorld.main = System.IO.putStrLn "Hello, World!", [import Prelude], Nothing, Nothing, (HaddockModInfo (Nothing) (Nothing) (Nothing) (Nothing))) ------------------------- pretty-printed typecheckedSource Just <AbsBinds [] [] [HelloWorld.main <= [] main] HelloWorld.main :: GHC.IOBase.IO () [] { main = System.IO.putStrLn "Hello, World!" }> ------------------------- shown parsedSource (L {HelloWorld.hs:1:0} (HsModule (Just (L {HelloWorld.hs:1:7-16} {ModuleName: HelloWorld})) (Nothing) [] [ (L {HelloWorld.hs:2:0-30} (ValD (FunBind (L {HelloWorld.hs:2:0-3} (Unqual {OccName: main})) (False) (MatchGroup [ (L {HelloWorld.hs:2:0-30} (Match [] (Nothing) (GRHSs [ (L {HelloWorld.hs:2:7-30} (GRHS [] (L {HelloWorld.hs:2:7-30} (HsApp (L {HelloWorld.hs:2:7-14} (HsVar (Unqual {OccName: putStrLn}))) (L {HelloWorld.hs:2:16-30} (HsLit (HsString {FastString: "Hello, World!"})))))))] (EmptyLocalBinds))))] {!type placeholder here?!}) (WpHole) {!NameSet placeholder here!} (Nothing))))] (Nothing) (HaddockModInfo (Nothing) (Nothing) (Nothing) (Nothing)) (Nothing))) ------------------------- shown renamedSource ((,,,,) (HsGroup (ValBindsOut [ ((,) (NonRecursive) {Bag(Located (HsBind Name)): [ (L {HelloWorld.hs:2:0-30} (FunBind (L {HelloWorld.hs:2:0-3} {Name: HelloWorld.main}) (False) (MatchGroup [ (L {HelloWorld.hs:2:0-30} (Match [] (Nothing) (GRHSs [ (L {HelloWorld.hs:2:7-30} (GRHS [] (L {HelloWorld.hs:2:7-30} (HsApp (L {HelloWorld.hs:2:7-14} (HsVar {Name: System.IO.putStrLn})) (L {HelloWorld.hs:2:16-30} (HsLit (HsString {FastString: "Hello, World!"})))))))] (EmptyLocalBinds))))] {!type placeholder here?!}) (WpHole) {NameSet: [{Name: System.IO.putStrLn}]} (Nothing)))]})] []) [] [] [] [] [] [] [] [] []) [ (L {Implicit import declaration} (ImportDecl (L {Implicit import declaration} {ModuleName: Prelude}) (False) (False) (Nothing) (Nothing)))] (Nothing) (Nothing) (HaddockModInfo (Nothing) (Nothing) (Nothing) (Nothing))) ------------------------- shown typecheckedSource {Bag(Located (HsBind Var)): [ (L {HelloWorld.hs:2:0-30} (AbsBinds [] [] [ ((,,,) [] {Var: HelloWorld.main} {Var: main} [])] {Bag(Located (HsBind Var)): [ (L {HelloWorld.hs:2:0-30} (FunBind (L {HelloWorld.hs:2:0-3} {Var: main}) (False) (MatchGroup [ (L {HelloWorld.hs:2:0-30} (Match [] (Nothing) (GRHSs [ (L {HelloWorld.hs:2:7-30} (GRHS [] (L {HelloWorld.hs:2:7-30} (HsApp (L {HelloWorld.hs:2:7-14} (HsVar {Var: System.IO.putStrLn})) (L {HelloWorld.hs:2:16-30} (HsLit (HsString {FastString: "Hello, World!"})))))))] (EmptyLocalBinds))))] GHC.IOBase.IO ()) (WpHole) {!NameSet placeholder here!} (Nothing)))]}))]}
- nameSetElems :: NameSet -> [Name]
- showSDoc_ :: SDoc -> String
- data Stage
- = Parser
- | Renamer
- | TypeChecker
- showData :: Data a => Stage -> Int -> a -> String
- everythingStaged :: Stage -> (r -> r -> r) -> r -> GenericQ r -> GenericQ r
- everythingButStaged :: Stage -> (r -> r -> r) -> r -> GenericQ (r, Bool) -> GenericQ r
- somethingStaged :: Stage -> Maybe u -> GenericQ (Maybe u) -> GenericQ (Maybe u)
- somewhereStaged :: MonadPlus m => Stage -> GenericM m -> GenericM m
- everywhereMStaged :: Monad m => Stage -> GenericM m -> GenericM m
Documentation
nameSetElems :: NameSet -> [Name] Source
Ghc Ast types tend to have undefined holes, to be filled by later compiler phases. We tag Asts with their source, so that we can avoid such holes based on who generated the Asts.
everythingStaged :: Stage -> (r -> r -> r) -> r -> GenericQ r -> GenericQ r Source
Like everything
, but avoid known potholes, based on the Stage
that
generated the Ast.
everythingButStaged :: Stage -> (r -> r -> r) -> r -> GenericQ (r, Bool) -> GenericQ r Source
A variation of everything
, using a 'GenericQ Bool' to skip
parts of the input Data
.
everythingBut :: GenericQ Bool -> (r -> r -> r) -> r -> GenericQ r -> GenericQ r
everythingBut q k z f x
| q x = z
| otherwise = foldl k (f x) (gmapQ (everythingBut q k z f) x)
somethingStaged :: Stage -> Maybe u -> GenericQ (Maybe u) -> GenericQ (Maybe u) Source
Look up a subterm by means of a maybe-typed filter.
somewhereStaged :: MonadPlus m => Stage -> GenericM m -> GenericM m Source
Apply a monadic transformation at least somewhere.
The transformation is tried in a top-down manner and descends down if it fails to apply at the root of the term. If the transformation fails to apply anywhere within the the term, the whole operation fails.