Hi Simon,
Did you mean I have to include the dflags like below to get the parsetree of a
base library file like libraries/base/GHC/List.lhs
setSessionDynFlags dflags { extensionFlags = Opt_ImplicitPrelude :
Opt_ForeignFunctionInterface : Opt_Cpp : Opt_MagicH\
ash : Opt_ExistentialQuantification : Opt_Rank2Types : Opt_ScopedTypeVariables
: Opt_UnboxedTuples : Opt_ForeignFunctionInterf\
ace : Opt_UnliftedFFITypes : Opt_DeriveDataTypeable :
Opt_GeneralizedNewtypeDeriving : Opt_FlexibleInstances : Opt_Standalone\
Deriving : Opt_PatternGuards : Opt_EmptyDataDecls : extensionFlags dflags }
I am stilling getting the same error
AstWalker: panic! (the 'impossible' happened)
(GHC version 7.0.1 for x86_64-apple-darwin):
lexical error at character 'i'
my code is "...
setSessionDynFlags ...
target <- guessTarget targetFile Nothing
setTargets [target]
load LoadAllTargets"
Would you have any other suggestions?
Thanks
________________________________________
From: Simon Peyton-Jones [[email protected]]
Sent: Tuesday, January 25, 2011 4:00 AM
To: Jane Ren; [email protected]
Cc: [email protected]
Subject: RE: Question about Haskell AST
My guess is that the base-package modules need language extensions to compile.
These extensions are specified in libraries/base/base.cabal (search for
"extensions"). I don't think you are including these extensions in the dflags
you are using.
Personally I think it'd be better if each base-package module specified its own
extensions (using {-# LANGUAGE MagicHash #-} etc); then it'd be more
self-describing. But my (untested) guess is that you need to extend dflags
with these extension flags to tell GHC how to compile them.
S
| -----Original Message-----
| From: Jane Ren [mailto:[email protected]]
| Sent: 24 January 2011 17:20
| To: Simon Peyton-Jones; [email protected]
| Subject: RE: Question about Haskell AST
|
| Hi Simon,
|
| That is exactly what I needed. However, although I was able to get the
| patterns from the parse tree for test modules that I wrote, I was not able to
| get the parsetrees for the Haskell base library modules.
| For example, I am trying to use Data/List.hs as a test. Here's the code
|
| defaultErrorHandler defaultDynFlags $ do
| runGhc (Just libdir) $ do
| dflags <- getSessionDynFlags
| setSessionDynFlags dflags
| target <- guessTarget targetFile Nothing
| setTargets [target]
| load LoadAllTargets
| modSum <- getModSummary $ mkModuleName "Data.List"
|
| When I try this, I get
| "AstWalker: panic! (the 'impossible' happened)
| (GHC version 7.0.1 for x86_64-apple-darwin):
| lexical error at character 'i'
| "
|
| It appears this error comes from "load LoadAllTargets"
|
| Any ideas how I can get parse trees for the Haskell base modules?
|
| Sure, I can augment that wiki page.
|
| Thanks
| Jane
| ________________________________________
| From: Simon Peyton-Jones [[email protected]]
| Sent: Tuesday, January 11, 2011 12:06 AM
| To: Jane Ren; [email protected]
| Subject: RE: Question about Haskell AST
|
| desugarModule returns a GHC.DesugaredModule
| Inside a DesugaredModule is a field dm_core_module :: HscTypes.ModGuts
| Inside a ModGuts is a field mg_binds :: [CoreSyn.CoreBind]
|
| And there are your bindings! Does that tell you what you wanted to know?
|
| Simon
|
| PS: When you have it clear, would you like to augment the Wiki
| http://haskell.org/haskellwiki/GHC/As_a_library to describe what you learned?
| That way others can benefit.
|
| | -----Original Message-----
| | From: [email protected] [mailto:glasgow-haskell-
| | [email protected]] On Behalf Of Jane Ren
| | Sent: 10 January 2011 17:21
| | To: [email protected]
| | Subject: Question about Haskell AST
| |
| | Hi,
| |
| | I need to be able to take a piece of Haskell source code and get an
| | simplified, typed, intermediate representation of the AST, which means I
| need
| | to use compiler/coreSyn/CoreSyn.lhs
| |
| | So I'm first trying to get the desguaredModule of the source code with
| | ...
| | modSum <- getModSummary $ mkModuleName "..."
| | p <- parseModule modSum
| | t <- typecheckModule p
| | d <- desugarModule t
| |
| | Now I'm really stuck on figuring out how to connect the variable d of type
| | desugaredModule to compiler/coreSyn/CoreSyn.lhs to get Expr patterns like
| | App, Let, Case, etc.
| |
| | Also, is it correct to get the deguaredModule first? At least CoreSyn.lhs
| | seems to suggest this.
| |
| | Any suggestions would be greatly apprecia
| | _______________________________________________
| | Glasgow-haskell-users mailing list
| | [email protected]
| | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
|
_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users