Re: Question about Haskell AST

2011-02-22 Thread Ian Lynagh

Hi Jane,

On Mon, Feb 21, 2011 at 11:46:16PM -0800, Jane Ren wrote:
 
 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
  
 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?

This works for me with the 7.0 branch:

main :: IO ()
main =
defaultErrorHandler defaultDynFlags $ do
  runGhc (Just libdir) $ do
dflags - getSessionDynFlags
let dflags' = foldl xopt_set dflags 
[Opt_Cpp, Opt_ImplicitPrelude, Opt_MagicHash]
setSessionDynFlags dflags'
target - guessTarget fp Nothing
setTargets [target]
load LoadAllTargets
liftIO $ putStrLn Done

Let me know if you still have problems.


Thanks
Ian


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Question about Haskell AST

2011-02-22 Thread Simon Peyton-Jones
I think the missing piece was Opt_Cpp.  Data.List uses the C preprocessor

S

| -Original Message-
| From: cvs-ghc-boun...@haskell.org [mailto:cvs-ghc-boun...@haskell.org] On
| Behalf Of Ian Lynagh
| Sent: 22 February 2011 15:09
| To: Jane Ren
| Cc: cvs-...@haskell.org; glasgow-haskell-users@haskell.org
| Subject: Re: Question about Haskell AST
| 
| 
| Hi Jane,
| 
| On Mon, Feb 21, 2011 at 11:46:16PM -0800, Jane Ren wrote:
| 
|  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
| 
|  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?
| 
| This works for me with the 7.0 branch:
| 
| main :: IO ()
| main =
| defaultErrorHandler defaultDynFlags $ do
|   runGhc (Just libdir) $ do
| dflags - getSessionDynFlags
| let dflags' = foldl xopt_set dflags
| [Opt_Cpp, Opt_ImplicitPrelude, Opt_MagicHash]
| setSessionDynFlags dflags'
| target - guessTarget fp Nothing
| setTargets [target]
| load LoadAllTargets
| liftIO $ putStrLn Done
| 
| Let me know if you still have problems.
| 
| 
| Thanks
| Ian
| 
| 
| ___
| Cvs-ghc mailing list
| cvs-...@haskell.org
| http://www.haskell.org/mailman/listinfo/cvs-ghc


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Question about Haskell AST

2011-02-21 Thread Jane Ren
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 [simo...@microsoft.com]
Sent: Tuesday, January 25, 2011 4:00 AM
To: Jane Ren; glasgow-haskell-users@haskell.org
Cc: cvs-...@haskell.org
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:j2...@ucsd.edu]
| Sent: 24 January 2011 17:20
| To: Simon Peyton-Jones; glasgow-haskell-users@haskell.org
| 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 [simo...@microsoft.com]
| Sent: Tuesday, January 11, 2011 12:06 AM
| To: Jane Ren; glasgow-haskell-users@haskell.org
| 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: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| | users-boun...@haskell.org] On Behalf Of Jane Ren
| | Sent: 10 January 2011 17:21
| | To: glasgow-haskell-users@haskell.org
| | 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
| | Glasgow-haskell-users@haskell.org
| | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
|


___
Glasgow-haskell-users mailing list
Glasgow

Re: Question about Haskell AST

2011-02-08 Thread Christiaan Baaij
Does the following code help you out? (Do note it's for the GHC 6.12.* API)
It just uses the the default GHC driver, meaning you don't have to separately 
call the desugerar, simplifier, etc.
It's what I use for my CλaSH tool.

Cheers, Christiaan


-- External Modules
import qualified GHC.Paths

-- GHC API
import qualified DynFlags
import qualified GHC
import qualified HscTypes

-- | Loads the given files and returns the Core Bindings
loadBindings ::
  [FilePath] - -- ^ Files to load
  IO [(CoreSyn.CoreBndr, CoreSyn.CoreExpr)] -- ^ Bindings
loadBindings fileNames = do
  GHC.defaultErrorHandler DynFlags.defaultDynFlags $
GHC.runGhc (Just GHC.Paths.libdir) $ do
  -- Some dynflags trickery.. otherwise they don't get loaded properly
  dflags - GHC.getSessionDynFlags
  GHC.setSessionDynFlags dflags
  -- Run the default GHC driver
  coreModules - mapM GHC.compileToCoreSimplified fileNames
  -- Extract and flatten bindings from the modules
  let bindings = concatMap (CoreSyn.flattenBinds . HscTypes.cm_binds) 
coreModules
  return bindings


On Jan 10, 2011, at 6:21 PM, Jane Ren wrote:

 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
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Question about Haskell AST

2011-02-06 Thread Tim Chevalier
On Mon, Jan 10, 2011 at 9:21 AM, Jane Ren j2...@ucsd.edu wrote:
 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.


Sorry for the very late reply, but have you considered using External Core?
http://www.haskell.org/ghc/docs/7.0.1/html/users_guide/ext-core.html
http://hackage.haskell.org/package/extcore

IMO, it's less pain than linking with the GHC library unless your
application really needs to get transformed Core back into the GHC
back-end.

Cheers,
Tim

-- 
Tim Chevalier * http://cs.pdx.edu/~tjc/ * Often in error, never in doubt
an intelligent person fights for lost causes,realizing that others
are merely effects -- E.E. Cummings

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Question about Haskell AST

2011-02-04 Thread Jane Ren
Hi Max,

I tried adding extensionFlags = Opt_Cpp to dflags, but I still got the same 
error.

When you mentioned 
You might have to iterate a few times to find the correct set of flags., 
did you mean trying out all the data ExtensionFlag flags in 
compiler/main/DynFlags.hs and find a subset that works?

data ExtensionFlag
   = Opt_Cpp
   | Opt_OverlappingInstances
   | Opt_UndecidableInstances
   | Opt_IncoherentInstances
...

Thanks
Jane

From: omega.th...@gmail.com [omega.th...@gmail.com] On Behalf Of Max 
Bolingbroke [batterseapo...@hotmail.com]
Sent: Tuesday, January 25, 2011 1:34 AM
To: Jane Ren
Cc: Simon Peyton-Jones; glasgow-haskell-users@haskell.org
Subject: Re: Question about Haskell AST

On 24 January 2011 17:20, Jane Ren j2...@ucsd.edu wrote:
 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 looks like you need to add the CPP extension to the DynFlags:

  setSessionDynFlags dflags { extensionFlags = Opt_Cpp : extensionFlags dflags }

You might have to iterate a few times to find the correct set of flags.

Cheers,
Max

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Question about Haskell AST

2011-01-25 Thread Max Bolingbroke
On 24 January 2011 17:20, Jane Ren j2...@ucsd.edu wrote:
 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 looks like you need to add the CPP extension to the DynFlags:

  setSessionDynFlags dflags { extensionFlags = Opt_Cpp : extensionFlags dflags }

You might have to iterate a few times to find the correct set of flags.

Cheers,
Max

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Question about Haskell AST

2011-01-25 Thread Simon Peyton-Jones
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:j2...@ucsd.edu]
| Sent: 24 January 2011 17:20
| To: Simon Peyton-Jones; glasgow-haskell-users@haskell.org
| 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 [simo...@microsoft.com]
| Sent: Tuesday, January 11, 2011 12:06 AM
| To: Jane Ren; glasgow-haskell-users@haskell.org
| 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: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| | users-boun...@haskell.org] On Behalf Of Jane Ren
| | Sent: 10 January 2011 17:21
| | To: glasgow-haskell-users@haskell.org
| | 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
| | Glasgow-haskell-users@haskell.org
| | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
| 


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Question about Haskell AST

2011-01-24 Thread Jane Ren
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 [simo...@microsoft.com]
Sent: Tuesday, January 11, 2011 12:06 AM
To: Jane Ren; glasgow-haskell-users@haskell.org
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: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Jane Ren
| Sent: 10 January 2011 17:21
| To: glasgow-haskell-users@haskell.org
| 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
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Question about Haskell AST

2011-01-11 Thread Simon Peyton-Jones
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: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of Jane Ren
| Sent: 10 January 2011 17:21
| To: glasgow-haskell-users@haskell.org
| 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
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Question about Haskell AST

2011-01-10 Thread Jane Ren
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
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users