#5048: Wrong SrcSpan on AbsBinds
---------------------------+------------------------------------------------
Reporter: JPMoresmau | Owner:
Type: bug | Status: infoneeded
Priority: normal | Milestone:
Component: GHC API | Version: 7.0.2
Keywords: SrcSpan | Testcase:
Blockedby: | Difficulty:
Os: Windows | Blocking:
Architecture: x86 | Failure: Incorrect result at runtime
---------------------------+------------------------------------------------
Changes (by simonpj):
* status: new => infoneeded
Old description:
> I have the following code:
>
> {-# LANGUAGE RankNTypes #-}
>
> module Folder1.ForAll where
>
> import Data.Char
>
> fun :: t -> [Char] -> [Char]
> fun _=reverse . map toUpper
>
> And the TypecheckedSource gives me something like (using the
> ghc-syb-utils package to dump it:)
>
> {Bag(Located (HsBind Var)):
> [
> (L {src\Folder1\ForAll.hs:8:1-29}
> (AbsBinds
> [{Var: t}]
> []
> [
> ((,,,)
> [{Var: t}] {Var: Folder1.ForAll.fun} {Var: fun}
> (SpecPrags
> []))]
> ({abstract:TcEvBinds}) {Bag(Located (HsBind Var)):
> [
> (L {src\Folder1\ForAll.hs:9:1-27}
> (FunBind
> (L {src\Folder1\ForAll.hs:9:1-3} {Var: fun})
> (False)
> (MatchGroup
>
> The issue here is that the AbsBinds has a SrcSpan that only covers the
> type signature, and not the rest of the code, hence (I think) we never go
> down the contents, and Scion cannot resolve anything when a user asks it
> to.
> If the type signature is not present, the problem doesn't occur: the
> AbsBinds location covers all the source code.
> If the type signature is present but without any type variable, there is
> no AbsBinds and no problem (the FunBind covers all the code).
New description:
I have the following code:
{{{
{-# LANGUAGE RankNTypes #-}
module Folder1.ForAll where
import Data.Char
fun :: t -> [Char] -> [Char]
fun _=reverse . map toUpper
}}}
And the `TypecheckedSource` gives me something like (using the
`ghc-syb-utils` package to dump it:)
{{{
{Bag(Located (HsBind Var)):
[
(L {src\Folder1\ForAll.hs:8:1-29}
(AbsBinds
[{Var: t}]
[]
[
((,,,)
[{Var: t}] {Var: Folder1.ForAll.fun} {Var: fun}
(SpecPrags
[]))]
({abstract:TcEvBinds}) {Bag(Located (HsBind Var)):
[
(L {src\Folder1\ForAll.hs:9:1-27}
(FunBind
(L {src\Folder1\ForAll.hs:9:1-3} {Var: fun})
(False)
(MatchGroup
}}}
The issue here is that the `AbsBinds` has a `SrcSpan` that only covers the
type signature, and not the rest of the code, hence (I think) we never go
down the contents, and Scion cannot resolve anything when a user asks it
to.
If the type signature is not present, the problem doesn't occur: the
`AbsBinds` location covers all the source code.
If the type signature is present but without any type variable, there is
no `AbsBinds` and no problem (the `FunBind` covers all the code).
--
Comment:
I think this should fix it
{{{
Thu Mar 31 11:23:15 BST 2011 [email protected]
* Fix Trac #5048: location on AbsBinds
This patch just puts a better SrcSpan on the AbsBinds
produced by the type checker
M ./compiler/basicTypes/SrcLoc.lhs -13 +11
M ./compiler/typecheck/TcBinds.lhs -4 +6
}}}
No one had ever looked at that `SrcSpan` before!
Can you try now, and close if ok?
Simon
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5048#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs