#5048: Wrong SrcSpan on AbsBinds
---------------------------+------------------------------------------------
    Reporter:  JPMoresmau  |       Owner:                             
        Type:  bug         |      Status:  new                        
    Priority:  normal      |   Component:  GHC API                    
     Version:  7.0.2       |    Keywords:  SrcSpan                    
    Testcase:              |   Blockedby:                             
          Os:  Windows     |    Blocking:                             
Architecture:  x86         |     Failure:  Incorrect result at runtime
---------------------------+------------------------------------------------
 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).

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5048>
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

Reply via email to