profiling and backtracing blues
Simon Peyton-Jones
simonpj at microsoft.com
Fri Mar 16 09:03:17 CET 2012
Yes, that'll be it. You probably don't care about the annotations when doing it for this purpose? We can probably have a flag to make it ignore annotations; or always do so if the interpreter is not on. That way you would not have to comment it out.
S
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-
| users-bounces at haskell.org] On Behalf Of Ranjit Jhala
| Sent: 15 March 2012 18:30
| To: Simon Marlow
| Cc: ghc-users
| Subject: Re: profiling and backtracing blues
|
| Dear Simon,
|
| Thanks for clarifying this!
|
| > the only way to get to hscCompileCoreExpr is by compiling a module that
| contains
| > some Template Haskell or quasiquotes. Could that be the case?
|
| Looks like this is may indeed be the case. The module that is getting
| compiled (via the chain)
|
| mod_guts <- coreModule `fmap` (desugarModule =<< typecheckModule
| =<< parseModule modSummary)
|
| contains an import
|
| import MyModule
|
| which looks like this:
|
| module MyModule where
|
| {-# ANN crash "forall a . x:{v:Bool | (? v)} -> a" #-}
| crash :: Bool -> a
| crash b = undefined
|
| I'm guessing the ANN is to blame, i.e. it tickles the TH/QQ machinery?
| (Commenting the ANN line out causes the thing to work just fine...)
|
| Thanks!
|
| Ranjit.
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list