diff options
-rw-r--r-- | compiler/hsSyn/HsDumpAst.hs | 160 | ||||
-rw-r--r-- | compiler/main/HscMain.hs | 4 | ||||
-rw-r--r-- | compiler/typecheck/TcRnDriver.hs | 4 | ||||
-rw-r--r-- | testsuite/tests/parser/should_compile/DumpParsedAst.stderr | 373 | ||||
-rw-r--r-- | testsuite/tests/parser/should_compile/DumpRenamedAst.stderr | 355 | ||||
-rw-r--r-- | testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr | 558 | ||||
-rw-r--r-- | utils/check-ppr/Main.hs | 7 |
7 files changed, 745 insertions, 716 deletions
diff --git a/compiler/hsSyn/HsDumpAst.hs b/compiler/hsSyn/HsDumpAst.hs index e2244312d0..8ab9cd40fa 100644 --- a/compiler/hsSyn/HsDumpAst.hs +++ b/compiler/hsSyn/HsDumpAst.hs @@ -16,7 +16,6 @@ module HsDumpAst ( ) where import Data.Data hiding (Fixity) -import Data.List import Bag import BasicTypes import FastString @@ -28,8 +27,7 @@ import HsSyn import OccName hiding (occName) import Var import Module -import DynFlags -import Outputable hiding (space) +import Outputable import qualified Data.ByteString as B @@ -39,11 +37,11 @@ data BlankSrcSpan = BlankSrcSpan | NoBlankSrcSpan -- | Show a GHC syntax tree. This parameterised because it is also used for -- comparing ASTs in ppr roundtripping tests, where the SrcSpan's are blanked -- out, to avoid comparing locations, only structure -showAstData :: Data a => BlankSrcSpan -> a -> String -showAstData b = showAstData' 0 +showAstData :: Data a => BlankSrcSpan -> a -> SDoc +showAstData b a0 = blankLine $$ showAstData' a0 where - showAstData' :: Data a => Int -> a -> String - showAstData' n = + showAstData' :: Data a => a -> SDoc + showAstData' = generic `ext1Q` list `extQ` string `extQ` fastString `extQ` srcSpan @@ -54,118 +52,118 @@ showAstData b = showAstData' 0 `extQ` bagName `extQ` bagRdrName `extQ` bagVar `extQ` nameSet `extQ` fixity `ext2Q` located - where generic :: Data a => a -> String - generic t = indent n ++ "(" ++ showConstr (toConstr t) - ++ space (unwords (gmapQ (showAstData' (n+1)) t)) ++ ")" - space "" = "" - space s = ' ':s + where generic :: Data a => a -> SDoc + generic t = parens $ text (showConstr (toConstr t)) + $$ vcat (gmapQ showAstData' t) - indent i = "\n" ++ replicate i ' ' + string :: String -> SDoc + string = text . normalize_newlines . show - string :: String -> String - string = normalize_newlines . show + fastString :: FastString -> SDoc + fastString s = braces $ + text "FastString: " + <> text (normalize_newlines . show $ s) - fastString :: FastString -> String - fastString = ("{FastString: "++) . (++"}") . normalize_newlines - . show + bytestring :: B.ByteString -> SDoc + bytestring = text . normalize_newlines . show - bytestring :: B.ByteString -> String - bytestring = normalize_newlines . show - - list l = indent n ++ "[" - ++ intercalate "," (map (showAstData' (n+1)) l) - ++ "]" + list [] = brackets empty + list [x] = brackets (showAstData' x) + list (x1 : x2 : xs) = (text "[" <> showAstData' x1) + $$ go x2 xs + where + go y [] = text "," <> showAstData' y <> text "]" + go y1 (y2 : ys) = (text "," <> showAstData' y1) $$ go y2 ys -- Eliminate word-size dependence - lit :: HsLit GhcPs -> String + lit :: HsLit GhcPs -> SDoc lit (HsWordPrim s x) = numericLit "HsWord{64}Prim" x s lit (HsWord64Prim s x) = numericLit "HsWord{64}Prim" x s lit (HsIntPrim s x) = numericLit "HsInt{64}Prim" x s lit (HsInt64Prim s x) = numericLit "HsInt{64}Prim" x s lit l = generic l - litr :: HsLit GhcRn -> String + litr :: HsLit GhcRn -> SDoc litr (HsWordPrim s x) = numericLit "HsWord{64}Prim" x s litr (HsWord64Prim s x) = numericLit "HsWord{64}Prim" x s litr (HsIntPrim s x) = numericLit "HsInt{64}Prim" x s litr (HsInt64Prim s x) = numericLit "HsInt{64}Prim" x s litr l = generic l - litt :: HsLit GhcTc -> String + litt :: HsLit GhcTc -> SDoc litt (HsWordPrim s x) = numericLit "HsWord{64}Prim" x s litt (HsWord64Prim s x) = numericLit "HsWord{64}Prim" x s litt (HsIntPrim s x) = numericLit "HsInt{64}Prim" x s litt (HsInt64Prim s x) = numericLit "HsInt{64}Prim" x s litt l = generic l - numericLit :: String -> Integer -> SourceText -> String - numericLit tag x s = indent n ++ unwords [ "{" ++ tag - , generic x - , generic s ++ "}" ] + numericLit :: String -> Integer -> SourceText -> SDoc + numericLit tag x s = braces $ hsep [ text tag + , generic x + , generic s ] - name :: Name -> String - name = ("{Name: "++) . (++"}") . showSDocDebug_ . ppr + name :: Name -> SDoc + name nm = braces $ text "Name: " <> ppr nm - occName = ("{OccName: "++) . (++"}") . OccName.occNameString + occName n = braces $ + text "OccName: " + <> text (OccName.occNameString n) - moduleName :: ModuleName -> String - moduleName = ("{ModuleName: "++) . (++"}") . showSDoc_ . ppr + moduleName :: ModuleName -> SDoc + moduleName m = braces $ text "ModuleName: " <> ppr m - srcSpan :: SrcSpan -> String + srcSpan :: SrcSpan -> SDoc srcSpan ss = case b of - BlankSrcSpan -> "{ "++ "ss" ++"}" - NoBlankSrcSpan -> - "{ "++ showSDoc_ (hang (ppr ss) (n+2) - -- TODO: show annotations here - (text "") - ) - ++"}" - - var :: Var -> String - var = ("{Var: "++) . (++"}") . showSDocDebug_ . ppr - - dataCon :: DataCon -> String - dataCon = ("{DataCon: "++) . (++"}") . showSDoc_ . ppr - - bagRdrName:: Bag (Located (HsBind GhcPs)) -> String - bagRdrName = ("{Bag(Located (HsBind GhcPs)): "++) . (++"}") - . list . bagToList - - bagName :: Bag (Located (HsBind GhcRn)) -> String - bagName = ("{Bag(Located (HsBind Name)): "++) . (++"}") - . list . bagToList - - bagVar :: Bag (Located (HsBind GhcTc)) -> String - bagVar = ("{Bag(Located (HsBind Var)): "++) . (++"}") - . list . bagToList - - nameSet = ("{NameSet: "++) . (++"}") . list . nameSetElemsStable - - fixity :: Fixity -> String - fixity = ("{Fixity: "++) . (++"}") . showSDoc_ . ppr - - located :: (Data b,Data loc) => GenLocated loc b -> String - located (L ss a) = - indent n ++ "(" - ++ case cast ss of + BlankSrcSpan -> text "{ ss }" + NoBlankSrcSpan -> braces $ char ' ' <> + (hang (ppr ss) 1 + -- TODO: show annotations here + (text "")) + + var :: Var -> SDoc + var v = braces $ text "Var: " <> ppr v + + dataCon :: DataCon -> SDoc + dataCon c = braces $ text "DataCon: " <> ppr c + + bagRdrName:: Bag (Located (HsBind GhcPs)) -> SDoc + bagRdrName bg = braces $ + text "Bag(Located (HsBind GhcPs)):" + $$ (list . bagToList $ bg) + + bagName :: Bag (Located (HsBind GhcRn)) -> SDoc + bagName bg = braces $ + text "Bag(Located (HsBind Name)):" + $$ (list . bagToList $ bg) + + bagVar :: Bag (Located (HsBind GhcTc)) -> SDoc + bagVar bg = braces $ + text "Bag(Located (HsBind Var)):" + $$ (list . bagToList $ bg) + + nameSet ns = braces $ + text "NameSet:" + $$ (list . nameSetElemsStable $ ns) + + fixity :: Fixity -> SDoc + fixity fx = braces $ + text "Fixity: " + <> ppr fx + + located :: (Data b,Data loc) => GenLocated loc b -> SDoc + located (L ss a) = parens $ + case cast ss of Just (s :: SrcSpan) -> srcSpan s - Nothing -> "nnnnnnnn" - ++ showAstData' (n+1) a - ++ ")" + Nothing -> text "nnnnnnnn" + $$ showAstData' a normalize_newlines :: String -> String normalize_newlines ('\\':'r':'\\':'n':xs) = '\\':'n':normalize_newlines xs normalize_newlines (x:xs) = x:normalize_newlines xs normalize_newlines [] = [] -showSDoc_ :: SDoc -> String -showSDoc_ = normalize_newlines . showSDoc unsafeGlobalDynFlags - -showSDocDebug_ :: SDoc -> String -showSDocDebug_ = normalize_newlines . showSDocDebug unsafeGlobalDynFlags - {- ************************************************************************ * * diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index c514e5b017..44e33acad9 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -340,7 +340,7 @@ hscParse' mod_summary liftIO $ dumpIfSet_dyn dflags Opt_D_dump_parsed "Parser" $ ppr rdr_module liftIO $ dumpIfSet_dyn dflags Opt_D_dump_parsed_ast "Parser AST" $ - text (showAstData NoBlankSrcSpan rdr_module) + showAstData NoBlankSrcSpan rdr_module liftIO $ dumpIfSet_dyn dflags Opt_D_source_stats "Source Statistics" $ ppSourceStats False rdr_module @@ -1713,7 +1713,7 @@ hscParseThingWithLocation source linenumber parser str logWarningsReportErrors (getMessages pst dflags) liftIO $ dumpIfSet_dyn dflags Opt_D_dump_parsed "Parser" (ppr thing) liftIO $ dumpIfSet_dyn dflags Opt_D_dump_parsed_ast "Parser AST" $ - text $ showAstData NoBlankSrcSpan thing + showAstData NoBlankSrcSpan thing return thing diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 8189a7833c..ab80cf90df 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -2514,7 +2514,7 @@ rnDump :: (Outputable a, Data a) => a -> TcRn () -- Dump, with a banner, if -ddump-rn rnDump rn = do { traceOptTcRn Opt_D_dump_rn (mkDumpDoc "Renamer" (ppr rn)) ; traceOptTcRn Opt_D_dump_rn_ast - (mkDumpDoc "Renamer" (text (showAstData NoBlankSrcSpan rn))) } + (mkDumpDoc "Renamer" (showAstData NoBlankSrcSpan rn)) } tcDump :: TcGblEnv -> TcRn () tcDump env @@ -2535,7 +2535,7 @@ tcDump env full_dump = pprLHsBinds (tcg_binds env) -- NB: foreign x-d's have undefined's in their types; -- hence can't show the tc_fords - ast_dump = text (showAstData NoBlankSrcSpan (tcg_binds env)) + ast_dump = showAstData NoBlankSrcSpan (tcg_binds env) -- It's unpleasant having both pprModGuts and pprModDetails here pprTcGblEnv :: TcGblEnv -> SDoc diff --git a/testsuite/tests/parser/should_compile/DumpParsedAst.stderr b/testsuite/tests/parser/should_compile/DumpParsedAst.stderr index ad3680e578..5c20f29123 100644 --- a/testsuite/tests/parser/should_compile/DumpParsedAst.stderr +++ b/testsuite/tests/parser/should_compile/DumpParsedAst.stderr @@ -2,236 +2,243 @@ ==================== Parser AST ==================== ({ DumpParsedAst.hs:1:1 } - (HsModule - (Just - ({ DumpParsedAst.hs:3:8-20 }{ModuleName: DumpParsedAst})) - (Nothing) - [] - [ - ({ DumpParsedAst.hs:5:1-30 } - (TyClD - (DataDecl + (HsModule + (Just + ({ DumpParsedAst.hs:3:8-20 } + {ModuleName: DumpParsedAst})) + (Nothing) + [] + [({ DumpParsedAst.hs:5:1-30 } + (TyClD + (DataDecl ({ DumpParsedAst.hs:5:6-10 } - (Unqual {OccName: Peano})) - (HsQTvs - (PlaceHolder) - [] - (PlaceHolder)) - (Prefix) - (HsDataDefn - (DataType) + (Unqual + {OccName: Peano})) + (HsQTvs + (PlaceHolder) + [] + (PlaceHolder)) + (Prefix) + (HsDataDefn + (DataType) ({ <no location info> } - []) - (Nothing) - (Nothing) - [ - ({ DumpParsedAst.hs:5:14-17 } - (ConDeclH98 + []) + (Nothing) + (Nothing) + [({ DumpParsedAst.hs:5:14-17 } + (ConDeclH98 ({ DumpParsedAst.hs:5:14-17 } - (Unqual {OccName: Zero})) - (Nothing) - (Just + (Unqual + {OccName: Zero})) + (Nothing) + (Just ({ <no location info> } - [])) - (PrefixCon - []) - (Nothing))), - ({ DumpParsedAst.hs:5:21-30 } - (ConDeclH98 + [])) + (PrefixCon + []) + (Nothing))) + ,({ DumpParsedAst.hs:5:21-30 } + (ConDeclH98 ({ DumpParsedAst.hs:5:21-24 } - (Unqual {OccName: Succ})) - (Nothing) - (Just + (Unqual + {OccName: Succ})) + (Nothing) + (Just ({ <no location info> } - [])) - (PrefixCon - [ - ({ DumpParsedAst.hs:5:26-30 } - (HsTyVar - (NotPromoted) + [])) + (PrefixCon + [({ DumpParsedAst.hs:5:26-30 } + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:5:26-30 } - (Unqual {OccName: Peano}))))]) - (Nothing)))] + (Unqual + {OccName: Peano}))))]) + (Nothing)))] ({ <no location info> } - [])) - (PlaceHolder) - (PlaceHolder)))), - ({ DumpParsedAst.hs:7:1-39 } - (TyClD - (FamDecl - (FamilyDecl - (ClosedTypeFamily - (Just - [ - ({ DumpParsedAst.hs:8:3-36 } - (TyFamEqn + [])) + (PlaceHolder) + (PlaceHolder)))) + ,({ DumpParsedAst.hs:7:1-39 } + (TyClD + (FamDecl + (FamilyDecl + (ClosedTypeFamily + (Just + [({ DumpParsedAst.hs:8:3-36 } + (TyFamEqn ({ DumpParsedAst.hs:8:3-8 } - (Unqual {OccName: Length})) - (HsIB - (PlaceHolder) - [ - ({ DumpParsedAst.hs:8:10-17 } - (HsParTy + (Unqual + {OccName: Length})) + (HsIB + (PlaceHolder) + [({ DumpParsedAst.hs:8:10-17 } + (HsParTy ({ DumpParsedAst.hs:8:11-16 } - (HsAppsTy - [ - ({ DumpParsedAst.hs:8:11 } - (HsAppPrefix + (HsAppsTy + [({ DumpParsedAst.hs:8:11 } + (HsAppPrefix ({ DumpParsedAst.hs:8:11 } - (HsTyVar - (NotPromoted) + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:8:11 } - (Unqual {OccName: a})))))), - ({ DumpParsedAst.hs:8:13 } - (HsAppInfix + (Unqual + {OccName: a})))))) + ,({ DumpParsedAst.hs:8:13 } + (HsAppInfix ({ DumpParsedAst.hs:8:13 } - (Exact {Name: ghc-prim:GHC.Types.:{(w) d}})))), - ({ DumpParsedAst.hs:8:15-16 } - (HsAppPrefix + (Exact + {Name: :})))) + ,({ DumpParsedAst.hs:8:15-16 } + (HsAppPrefix ({ DumpParsedAst.hs:8:15-16 } - (HsTyVar - (NotPromoted) + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:8:15-16 } - (Unqual {OccName: as}))))))]))))] - (PlaceHolder)) - (Prefix) + (Unqual + {OccName: as}))))))]))))] + (PlaceHolder)) + (Prefix) ({ DumpParsedAst.hs:8:21-36 } - (HsAppsTy - [ - ({ DumpParsedAst.hs:8:21-24 } - (HsAppPrefix + (HsAppsTy + [({ DumpParsedAst.hs:8:21-24 } + (HsAppPrefix ({ DumpParsedAst.hs:8:21-24 } - (HsTyVar - (NotPromoted) + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:8:21-24 } - (Unqual {OccName: Succ})))))), - ({ DumpParsedAst.hs:8:26-36 } - (HsAppPrefix + (Unqual + {OccName: Succ})))))) + ,({ DumpParsedAst.hs:8:26-36 } + (HsAppPrefix ({ DumpParsedAst.hs:8:26-36 } - (HsParTy + (HsParTy ({ DumpParsedAst.hs:8:27-35 } - (HsAppsTy - [ - ({ DumpParsedAst.hs:8:27-32 } - (HsAppPrefix + (HsAppsTy + [({ DumpParsedAst.hs:8:27-32 } + (HsAppPrefix ({ DumpParsedAst.hs:8:27-32 } - (HsTyVar - (NotPromoted) + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:8:27-32 } - (Unqual {OccName: Length})))))), - ({ DumpParsedAst.hs:8:34-35 } - (HsAppPrefix + (Unqual + {OccName: Length})))))) + ,({ DumpParsedAst.hs:8:34-35 } + (HsAppPrefix ({ DumpParsedAst.hs:8:34-35 } - (HsTyVar - (NotPromoted) + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:8:34-35 } - (Unqual {OccName: as}))))))]))))))])))), - ({ DumpParsedAst.hs:9:3-24 } - (TyFamEqn + (Unqual + {OccName: as}))))))]))))))])))) + ,({ DumpParsedAst.hs:9:3-24 } + (TyFamEqn ({ DumpParsedAst.hs:9:3-8 } - (Unqual {OccName: Length})) - (HsIB - (PlaceHolder) - [ - ({ DumpParsedAst.hs:9:10-12 } - (HsExplicitListTy - (Promoted) - (PlaceHolder) - []))] - (PlaceHolder)) - (Prefix) + (Unqual + {OccName: Length})) + (HsIB + (PlaceHolder) + [({ DumpParsedAst.hs:9:10-12 } + (HsExplicitListTy + (Promoted) + (PlaceHolder) + []))] + (PlaceHolder)) + (Prefix) ({ DumpParsedAst.hs:9:21-24 } - (HsAppsTy - [ - ({ DumpParsedAst.hs:9:21-24 } - (HsAppPrefix + (HsAppsTy + [({ DumpParsedAst.hs:9:21-24 } + (HsAppPrefix ({ DumpParsedAst.hs:9:21-24 } - (HsTyVar - (NotPromoted) + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:9:21-24 } - (Unqual {OccName: Zero}))))))]))))])) + (Unqual + {OccName: Zero}))))))]))))])) ({ DumpParsedAst.hs:7:13-18 } - (Unqual {OccName: Length})) - (HsQTvs - (PlaceHolder) - [ - ({ DumpParsedAst.hs:7:20-30 } - (KindedTyVar + (Unqual + {OccName: Length})) + (HsQTvs + (PlaceHolder) + [({ DumpParsedAst.hs:7:20-30 } + (KindedTyVar ({ DumpParsedAst.hs:7:21-22 } - (Unqual {OccName: as})) + (Unqual + {OccName: as})) ({ DumpParsedAst.hs:7:27-29 } - (HsAppsTy - [ - ({ DumpParsedAst.hs:7:27-29 } - (HsAppPrefix + (HsAppsTy + [({ DumpParsedAst.hs:7:27-29 } + (HsAppPrefix ({ DumpParsedAst.hs:7:27-29 } - (HsListTy + (HsListTy ({ DumpParsedAst.hs:7:28 } - (HsAppsTy - [ - ({ DumpParsedAst.hs:7:28 } - (HsAppPrefix + (HsAppsTy + [({ DumpParsedAst.hs:7:28 } + (HsAppPrefix ({ DumpParsedAst.hs:7:28 } - (HsTyVar - (NotPromoted) + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:7:28 } - (Unqual {OccName: k}))))))]))))))]))))] - (PlaceHolder)) - (Prefix) + (Unqual + {OccName: k}))))))]))))))]))))] + (PlaceHolder)) + (Prefix) ({ DumpParsedAst.hs:7:32-39 } - (KindSig + (KindSig ({ DumpParsedAst.hs:7:35-39 } - (HsAppsTy - [ - ({ DumpParsedAst.hs:7:35-39 } - (HsAppPrefix + (HsAppsTy + [({ DumpParsedAst.hs:7:35-39 } + (HsAppPrefix ({ DumpParsedAst.hs:7:35-39 } - (HsTyVar - (NotPromoted) + (HsTyVar + (NotPromoted) ({ DumpParsedAst.hs:7:35-39 } - (Unqual {OccName: Peano}))))))])))) - (Nothing))))), - ({ DumpParsedAst.hs:11:1-23 } - (ValD - (FunBind + (Unqual + {OccName: Peano}))))))])))) + (Nothing))))) + ,({ DumpParsedAst.hs:11:1-23 } + (ValD + (FunBind ({ DumpParsedAst.hs:11:1-4 } - (Unqual {OccName: main})) - (MG + (Unqual + {OccName: main})) + (MG ({ DumpParsedAst.hs:11:1-23 } - [ - ({ DumpParsedAst.hs:11:1-23 } - (Match - (FunRhs + [({ DumpParsedAst.hs:11:1-23 } + (Match + (FunRhs ({ DumpParsedAst.hs:11:1-4 } - (Unqual {OccName: main})) - (Prefix) - (NoSrcStrict)) - [] - (Nothing) - (GRHSs - [ - ({ DumpParsedAst.hs:11:6-23 } - (GRHS - [] + (Unqual + {OccName: main})) + (Prefix) + (NoSrcStrict)) + [] + (Nothing) + (GRHSs + [({ DumpParsedAst.hs:11:6-23 } + (GRHS + [] ({ DumpParsedAst.hs:11:8-23 } - (HsApp + (HsApp ({ DumpParsedAst.hs:11:8-15 } - (HsVar + (HsVar ({ DumpParsedAst.hs:11:8-15 } - (Unqual {OccName: putStrLn})))) + (Unqual + {OccName: putStrLn})))) ({ DumpParsedAst.hs:11:17-23 } - (HsLit - (HsString - (SourceText "\"hello\"") {FastString: "hello"})))))))] + (HsLit + (HsString + (SourceText + "\"hello\"") + {FastString: "hello"})))))))] ({ <no location info> } - (EmptyLocalBinds)))))]) - [] - (PlaceHolder) - (FromSource)) - (WpHole) - (PlaceHolder) - [])))] - (Nothing) + (EmptyLocalBinds)))))]) + [] + (PlaceHolder) + (FromSource)) + (WpHole) + (PlaceHolder) + [])))] + (Nothing) (Nothing))) diff --git a/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr b/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr index c873ee148b..e677fc5de9 100644 --- a/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr +++ b/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr @@ -1,193 +1,208 @@ ==================== Renamer ==================== -(HsGroup - (ValBindsOut - [ - ((,) - (NonRecursive) {Bag(Located (HsBind Name)): - [ - ({ DumpRenamedAst.hs:11:1-23 } - (FunBind - ({ DumpRenamedAst.hs:11:1-4 }{Name: main:DumpRenamedAst.main{v}}) - (MG - ({ DumpRenamedAst.hs:11:1-23 } - [ - ({ DumpRenamedAst.hs:11:1-23 } - (Match - (FunRhs - ({ DumpRenamedAst.hs:11:1-4 }{Name: main:DumpRenamedAst.main{v}}) - (Prefix) - (NoSrcStrict)) - [] - (Nothing) - (GRHSs - [ - ({ DumpRenamedAst.hs:11:6-23 } - (GRHS - [] - ({ DumpRenamedAst.hs:11:8-23 } - (HsApp - ({ DumpRenamedAst.hs:11:8-15 } - (HsVar - ({ DumpRenamedAst.hs:11:8-15 }{Name: base:System.IO.putStrLn{v}}))) - ({ DumpRenamedAst.hs:11:17-23 } - (HsLit - (HsString - (SourceText "\"hello\"") {FastString: "hello"})))))))] - ({ <no location info> } - (EmptyLocalBinds)))))]) - [] - (PlaceHolder) - (FromSource)) - (WpHole) {NameSet: - []} - []))]})] - []) - [] - [ - (TyClGroup - [ - ({ DumpRenamedAst.hs:5:1-30 } - (DataDecl - ({ DumpRenamedAst.hs:5:6-10 }{Name: main:DumpRenamedAst.Peano{tc}}) - (HsQTvs - [] - [] {NameSet: - []}) - (Prefix) - (HsDataDefn - (DataType) +(HsGroup + (ValBindsOut + [((,) + (NonRecursive) + {Bag(Located (HsBind Name)): + [({ DumpRenamedAst.hs:11:1-23 } + (FunBind + ({ DumpRenamedAst.hs:11:1-4 } + {Name: DumpRenamedAst.main}) + (MG + ({ DumpRenamedAst.hs:11:1-23 } + [({ DumpRenamedAst.hs:11:1-23 } + (Match + (FunRhs + ({ DumpRenamedAst.hs:11:1-4 } + {Name: DumpRenamedAst.main}) + (Prefix) + (NoSrcStrict)) + [] + (Nothing) + (GRHSs + [({ DumpRenamedAst.hs:11:6-23 } + (GRHS + [] + ({ DumpRenamedAst.hs:11:8-23 } + (HsApp + ({ DumpRenamedAst.hs:11:8-15 } + (HsVar + ({ DumpRenamedAst.hs:11:8-15 } + {Name: putStrLn}))) + ({ DumpRenamedAst.hs:11:17-23 } + (HsLit + (HsString + (SourceText + "\"hello\"") + {FastString: "hello"})))))))] + ({ <no location info> } + (EmptyLocalBinds)))))]) + [] + (PlaceHolder) + (FromSource)) + (WpHole) + {NameSet: + []} + []))]})] + []) + [] + [(TyClGroup + [({ DumpRenamedAst.hs:5:1-30 } + (DataDecl + ({ DumpRenamedAst.hs:5:6-10 } + {Name: DumpRenamedAst.Peano}) + (HsQTvs + [] + [] + {NameSet: + []}) + (Prefix) + (HsDataDefn + (DataType) ({ <no location info> } - []) - (Nothing) - (Nothing) - [ - ({ DumpRenamedAst.hs:5:14-17 } - (ConDeclH98 - ({ DumpRenamedAst.hs:5:14-17 }{Name: main:DumpRenamedAst.Zero{d}}) - (Nothing) - (Just + []) + (Nothing) + (Nothing) + [({ DumpRenamedAst.hs:5:14-17 } + (ConDeclH98 + ({ DumpRenamedAst.hs:5:14-17 } + {Name: DumpRenamedAst.Zero}) + (Nothing) + (Just ({ <no location info> } - [])) - (PrefixCon - []) - (Nothing))), - ({ DumpRenamedAst.hs:5:21-30 } - (ConDeclH98 - ({ DumpRenamedAst.hs:5:21-24 }{Name: main:DumpRenamedAst.Succ{d}}) - (Nothing) - (Just + [])) + (PrefixCon + []) + (Nothing))) + ,({ DumpRenamedAst.hs:5:21-30 } + (ConDeclH98 + ({ DumpRenamedAst.hs:5:21-24 } + {Name: DumpRenamedAst.Succ}) + (Nothing) + (Just ({ <no location info> } - [])) - (PrefixCon - [ - ({ DumpRenamedAst.hs:5:26-30 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:5:26-30 }{Name: main:DumpRenamedAst.Peano{tc}})))]) - (Nothing)))] + [])) + (PrefixCon + [({ DumpRenamedAst.hs:5:26-30 } + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:5:26-30 } + {Name: DumpRenamedAst.Peano})))]) + (Nothing)))] ({ <no location info> } - [])) - (True) {NameSet: - [{Name: main:DumpRenamedAst.Peano{tc}}]}))] - [] - []), - (TyClGroup - [ - ({ DumpRenamedAst.hs:7:1-39 } - (FamDecl - (FamilyDecl - (ClosedTypeFamily - (Just - [ - ({ DumpRenamedAst.hs:8:3-36 } - (TyFamEqn - ({ DumpRenamedAst.hs:8:3-8 }{Name: main:DumpRenamedAst.Length{tc}}) - (HsIB - [{Name: a{tv}},{Name: as{tv}}] - [ - ({ DumpRenamedAst.hs:8:10-17 } - (HsParTy + [])) + (True) + {NameSet: + [{Name: DumpRenamedAst.Peano}]}))] + [] + []) + ,(TyClGroup + [({ DumpRenamedAst.hs:7:1-39 } + (FamDecl + (FamilyDecl + (ClosedTypeFamily + (Just + [({ DumpRenamedAst.hs:8:3-36 } + (TyFamEqn + ({ DumpRenamedAst.hs:8:3-8 } + {Name: DumpRenamedAst.Length}) + (HsIB + [{Name: a} + ,{Name: as}] + [({ DumpRenamedAst.hs:8:10-17 } + (HsParTy ({ DumpRenamedAst.hs:8:11-16 } - (HsOpTy + (HsOpTy ({ DumpRenamedAst.hs:8:11 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:8:11 }{Name: a{tv}}))) - ({ DumpRenamedAst.hs:8:13 }{Name: ghc-prim:GHC.Types.:{(w) d}}) + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:8:11 } + {Name: a}))) + ({ DumpRenamedAst.hs:8:13 } + {Name: :}) ({ DumpRenamedAst.hs:8:15-16 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:8:15-16 }{Name: as{tv}})))))))] - (True)) - (Prefix) + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:8:15-16 } + {Name: as})))))))] + (True)) + (Prefix) ({ DumpRenamedAst.hs:8:21-36 } - (HsAppTy + (HsAppTy ({ DumpRenamedAst.hs:8:21-24 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:8:21-24 }{Name: main:DumpRenamedAst.Succ{d}}))) + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:8:21-24 } + {Name: DumpRenamedAst.Succ}))) ({ DumpRenamedAst.hs:8:26-36 } - (HsParTy + (HsParTy ({ DumpRenamedAst.hs:8:27-35 } - (HsAppTy + (HsAppTy ({ DumpRenamedAst.hs:8:27-32 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:8:27-32 }{Name: main:DumpRenamedAst.Length{tc}}))) + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:8:27-32 } + {Name: DumpRenamedAst.Length}))) ({ DumpRenamedAst.hs:8:34-35 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:8:34-35 }{Name: as{tv}}))))))))))), - ({ DumpRenamedAst.hs:9:3-24 } - (TyFamEqn - ({ DumpRenamedAst.hs:9:3-8 }{Name: main:DumpRenamedAst.Length{tc}}) - (HsIB - [] - [ - ({ DumpRenamedAst.hs:9:10-12 } - (HsExplicitListTy - (Promoted) - (PlaceHolder) - []))] - (True)) - (Prefix) + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:8:34-35 } + {Name: as}))))))))))) + ,({ DumpRenamedAst.hs:9:3-24 } + (TyFamEqn + ({ DumpRenamedAst.hs:9:3-8 } + {Name: DumpRenamedAst.Length}) + (HsIB + [] + [({ DumpRenamedAst.hs:9:10-12 } + (HsExplicitListTy + (Promoted) + (PlaceHolder) + []))] + (True)) + (Prefix) ({ DumpRenamedAst.hs:9:21-24 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:9:21-24 }{Name: main:DumpRenamedAst.Zero{d}})))))])) - ({ DumpRenamedAst.hs:7:13-18 }{Name: main:DumpRenamedAst.Length{tc}}) - (HsQTvs - [{Name: k{tv}}] - [ - ({ DumpRenamedAst.hs:7:20-30 } - (KindedTyVar - ({ DumpRenamedAst.hs:7:21-22 }{Name: as{tv}}) + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:9:21-24 } + {Name: DumpRenamedAst.Zero})))))])) + ({ DumpRenamedAst.hs:7:13-18 } + {Name: DumpRenamedAst.Length}) + (HsQTvs + [{Name: k}] + [({ DumpRenamedAst.hs:7:20-30 } + (KindedTyVar + ({ DumpRenamedAst.hs:7:21-22 } + {Name: as}) ({ DumpRenamedAst.hs:7:27-29 } - (HsListTy + (HsListTy ({ DumpRenamedAst.hs:7:28 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:7:28 }{Name: k{tv}})))))))] {NameSet: - []}) - (Prefix) + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:7:28 } + {Name: k})))))))] + {NameSet: + []}) + (Prefix) ({ DumpRenamedAst.hs:7:32-39 } - (KindSig + (KindSig ({ DumpRenamedAst.hs:7:35-39 } - (HsTyVar - (NotPromoted) - ({ DumpRenamedAst.hs:7:35-39 }{Name: main:DumpRenamedAst.Peano{tc}}))))) - (Nothing))))] - [] - [])] - [] - [] - [] - [] - [] - [] - [] - [] + (HsTyVar + (NotPromoted) + ({ DumpRenamedAst.hs:7:35-39 } + {Name: DumpRenamedAst.Peano}))))) + (Nothing))))] + [] + [])] + [] + [] + [] + [] + [] + [] + [] + [] []) diff --git a/testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr b/testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr index d96c448cf9..ff6379f957 100644 --- a/testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr +++ b/testsuite/tests/parser/should_compile/DumpTypecheckedAst.stderr @@ -1,280 +1,286 @@ ==================== Typechecker ==================== -{Bag(Located (HsBind Var)): -[ - ({ <no location info> } - (VarBind {Var: (main:DumpTypecheckedAst.$tcPeano{v} [lidx] :: ghc-prim:GHC.Types.TyCon{tc})} - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsLit - {HsWord{64}Prim - (14073232900889011755) - (NoSourceText)})))) - ({ <no location info> } - (HsLit - {HsWord{64}Prim - (2739668351064589274) - (NoSourceText)})))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: (main:DumpTypecheckedAst.$trModule{v} [lidx] :: ghc-prim:GHC.Types.Module{tc})}))))) - ({ <no location info> } - (HsPar - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsLit - (HsStringPrim - (NoSourceText) "Peano"))))))))) - ({ <no location info> } - (HsLit - {HsInt{64}Prim - (0) - (SourceText "0")})))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: (ghc-prim:GHC.Types.krep$*{v} [gid] :: ghc-prim:GHC.Types.KindRep{tc})}))))) - (False))), - ({ <no location info> } - (VarBind {Var: (main:DumpTypecheckedAst.$tc'Zero{v} [lidx] :: ghc-prim:GHC.Types.TyCon{tc})} - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsLit - {HsWord{64}Prim - (13760111476013868540) - (NoSourceText)})))) - ({ <no location info> } - (HsLit - {HsWord{64}Prim - (12314848029315386153) - (NoSourceText)})))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: (main:DumpTypecheckedAst.$trModule{v} [lidx] :: ghc-prim:GHC.Types.Module{tc})}))))) - ({ <no location info> } - (HsPar - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsLit - (HsStringPrim - (NoSourceText) "'Zero"))))))))) - ({ <no location info> } - (HsLit - {HsInt{64}Prim - (0) - (SourceText "0")})))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: ($krep{v} [lid] :: ghc-prim:GHC.Types.KindRep{tc})}))))) - (False))), - ({ <no location info> } - (VarBind {Var: (main:DumpTypecheckedAst.$tc'Succ{v} [lidx] :: ghc-prim:GHC.Types.TyCon{tc})} - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsLit - {HsWord{64}Prim - (1143980031331647856) - (NoSourceText)})))) - ({ <no location info> } - (HsLit - {HsWord{64}Prim - (14802086722010293686) - (NoSourceText)})))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: (main:DumpTypecheckedAst.$trModule{v} [lidx] :: ghc-prim:GHC.Types.Module{tc})}))))) - ({ <no location info> } - (HsPar - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsLit - (HsStringPrim - (NoSourceText) "'Succ"))))))))) - ({ <no location info> } - (HsLit - {HsInt{64}Prim - (0) - (SourceText "0")})))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: ($krep{v} [lid] :: ghc-prim:GHC.Types.KindRep{tc})}))))) - (False))), - ({ <no location info> } - (VarBind {Var: ($krep{v} [lid] :: ghc-prim:GHC.Types.KindRep{tc})} - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: ($krep{v} [lid] :: ghc-prim:GHC.Types.KindRep{tc})}))))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: ($krep{v} [lid] :: ghc-prim:GHC.Types.KindRep{tc})}))))) - (False))), - ({ <no location info> } - (VarBind {Var: ($krep{v} [lid] :: ghc-prim:GHC.Types.KindRep{tc})} - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsVar - ({ <no location info> }{Var: (main:DumpTypecheckedAst.$tcPeano{v} [lidx] :: ghc-prim:GHC.Types.TyCon{tc})}))))) - ({ <no location info> } - (HsWrap - (WpTyApp - (TyConApp - ({abstract:TyCon}) - [])) - (HsConLikeOut - ({abstract:ConLike})))))) - (False))), - ({ <no location info> } - (VarBind {Var: (main:DumpTypecheckedAst.$trModule{v} [lidx] :: ghc-prim:GHC.Types.Module{tc})} - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsPar - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsLit - (HsStringPrim - (NoSourceText) "main"))))))))) - ({ <no location info> } - (HsPar - ({ <no location info> } - (HsApp - ({ <no location info> } - (HsConLikeOut - ({abstract:ConLike}))) - ({ <no location info> } - (HsLit - (HsStringPrim - (NoSourceText) "DumpTypecheckedAst"))))))))) - (False))), - ({ DumpTypecheckedAst.hs:11:1-23 } - (AbsBinds - [] - [] - [ - (ABE {Var: (main:DumpTypecheckedAst.main{v} [lid] :: ghc-prim:GHC.Types.IO{tc} - ())} {Var: (main{v} [lid] :: ghc-prim:GHC.Types.IO{tc} ())} - (WpHole) - (SpecPrags - []))] - [ - ({abstract:TcEvBinds})] {Bag(Located (HsBind Var)): - [ - ({ DumpTypecheckedAst.hs:11:1-23 } - (FunBind - ({ DumpTypecheckedAst.hs:11:1-4 }{Var: (main{v} [lid] :: ghc-prim:GHC.Types.IO{tc} ())}) - (MG - ({ DumpTypecheckedAst.hs:11:1-23 } - [ - ({ DumpTypecheckedAst.hs:11:1-23 } - (Match - (FunRhs - ({ DumpTypecheckedAst.hs:11:1-4 }{Name: main:DumpTypecheckedAst.main{v}}) - (Prefix) - (NoSrcStrict)) - [] - (Nothing) - (GRHSs - [ - ({ DumpTypecheckedAst.hs:11:6-23 } - (GRHS - [] - ({ DumpTypecheckedAst.hs:11:8-23 } - (HsApp - ({ DumpTypecheckedAst.hs:11:8-15 } - (HsVar - ({ <no location info> }{Var: (base:System.IO.putStrLn{v} [gid] :: base:GHC.Base.String{tc} - -> ghc-prim:GHC.Types.IO{tc} ())}))) - ({ DumpTypecheckedAst.hs:11:17-23 } - (HsLit - (HsString - (SourceText "\"hello\"") {FastString: "hello"})))))))] + +{Bag(Located (HsBind Var)): + [({ <no location info> } + (VarBind + {Var: DumpTypecheckedAst.$tcPeano} + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsLit + {HsWord{64}Prim (14073232900889011755) (NoSourceText)})))) + ({ <no location info> } + (HsLit + {HsWord{64}Prim (2739668351064589274) (NoSourceText)})))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: DumpTypecheckedAst.$trModule}))))) + ({ <no location info> } + (HsPar + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsLit + (HsStringPrim + (NoSourceText) + "Peano"))))))))) + ({ <no location info> } + (HsLit + {HsInt{64}Prim (0) (SourceText + "0")})))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: GHC.Types.krep$*}))))) + (False))) + ,({ <no location info> } + (VarBind + {Var: DumpTypecheckedAst.$tc'Zero} + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsLit + {HsWord{64}Prim (13760111476013868540) (NoSourceText)})))) + ({ <no location info> } + (HsLit + {HsWord{64}Prim (12314848029315386153) (NoSourceText)})))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: DumpTypecheckedAst.$trModule}))))) + ({ <no location info> } + (HsPar ({ <no location info> } - (EmptyLocalBinds)))))]) - [] - (TyConApp - ({abstract:TyCon}) - [ - (TyConApp - ({abstract:TyCon}) - [])]) - (FromSource)) - (WpHole) {NameSet: - []} - []))]} - (False)))]} + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsLit + (HsStringPrim + (NoSourceText) + "'Zero"))))))))) + ({ <no location info> } + (HsLit + {HsInt{64}Prim (0) (SourceText + "0")})))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: $krep}))))) + (False))) + ,({ <no location info> } + (VarBind + {Var: DumpTypecheckedAst.$tc'Succ} + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsLit + {HsWord{64}Prim (1143980031331647856) (NoSourceText)})))) + ({ <no location info> } + (HsLit + {HsWord{64}Prim (14802086722010293686) (NoSourceText)})))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: DumpTypecheckedAst.$trModule}))))) + ({ <no location info> } + (HsPar + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsLit + (HsStringPrim + (NoSourceText) + "'Succ"))))))))) + ({ <no location info> } + (HsLit + {HsInt{64}Prim (0) (SourceText + "0")})))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: $krep}))))) + (False))) + ,({ <no location info> } + (VarBind + {Var: $krep} + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: $krep}))))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: $krep}))))) + (False))) + ,({ <no location info> } + (VarBind + {Var: $krep} + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsVar + ({ <no location info> } + {Var: DumpTypecheckedAst.$tcPeano}))))) + ({ <no location info> } + (HsWrap + (WpTyApp + (TyConApp + ({abstract:TyCon}) + [])) + (HsConLikeOut + ({abstract:ConLike})))))) + (False))) + ,({ <no location info> } + (VarBind + {Var: DumpTypecheckedAst.$trModule} + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsPar + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsLit + (HsStringPrim + (NoSourceText) + "main"))))))))) + ({ <no location info> } + (HsPar + ({ <no location info> } + (HsApp + ({ <no location info> } + (HsConLikeOut + ({abstract:ConLike}))) + ({ <no location info> } + (HsLit + (HsStringPrim + (NoSourceText) + "DumpTypecheckedAst"))))))))) + (False))) + ,({ DumpTypecheckedAst.hs:11:1-23 } + (AbsBinds + [] + [] + [(ABE + {Var: main} + {Var: main} + (WpHole) + (SpecPrags + []))] + [({abstract:TcEvBinds})] + {Bag(Located (HsBind Var)): + [({ DumpTypecheckedAst.hs:11:1-23 } + (FunBind + ({ DumpTypecheckedAst.hs:11:1-4 } + {Var: main}) + (MG + ({ DumpTypecheckedAst.hs:11:1-23 } + [({ DumpTypecheckedAst.hs:11:1-23 } + (Match + (FunRhs + ({ DumpTypecheckedAst.hs:11:1-4 } + {Name: main}) + (Prefix) + (NoSrcStrict)) + [] + (Nothing) + (GRHSs + [({ DumpTypecheckedAst.hs:11:6-23 } + (GRHS + [] + ({ DumpTypecheckedAst.hs:11:8-23 } + (HsApp + ({ DumpTypecheckedAst.hs:11:8-15 } + (HsVar + ({ <no location info> } + {Var: putStrLn}))) + ({ DumpTypecheckedAst.hs:11:17-23 } + (HsLit + (HsString + (SourceText + "\"hello\"") + {FastString: "hello"})))))))] + ({ <no location info> } + (EmptyLocalBinds)))))]) + [] + (TyConApp + ({abstract:TyCon}) + [(TyConApp + ({abstract:TyCon}) + [])]) + (FromSource)) + (WpHole) + {NameSet: + []} + []))]} + (False)))]} diff --git a/utils/check-ppr/Main.hs b/utils/check-ppr/Main.hs index 2fd44b2be0..a5aeee2f1d 100644 --- a/utils/check-ppr/Main.hs +++ b/utils/check-ppr/Main.hs @@ -31,7 +31,8 @@ testOneFile :: FilePath -> String -> IO () testOneFile libdir fileName = do p <- parseOneFile libdir fileName let - origAst = showAstData BlankSrcSpan (pm_parsed_source p) + origAst = showSDoc unsafeGlobalDynFlags + $ showAstData BlankSrcSpan (pm_parsed_source p) pped = pragmas ++ "\n" ++ pp (pm_parsed_source p) anns = pm_annotations p pragmas = getPragmas anns @@ -45,7 +46,9 @@ testOneFile libdir fileName = do p' <- parseOneFile libdir newFile - let newAstStr = showAstData BlankSrcSpan (pm_parsed_source p') + let newAstStr :: String + newAstStr = showSDoc unsafeGlobalDynFlags + $ showAstData BlankSrcSpan (pm_parsed_source p') writeFile newAstFile newAstStr if origAst == newAstStr |