[GHC] #10588: BangPat gets wrong SrcSpan.

GHC ghc-devs at haskell.org
Mon Jun 29 17:10:00 UTC 2015


#10588: BangPat gets wrong SrcSpan.
-------------------------------------+-------------------------------------
              Reporter:  mpickering  |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.10.1
              Keywords:              |  Operating System:  Unknown/Multiple
          Architecture:              |   Type of failure:  None/Unknown
  Unknown/Multiple                   |        Blocked By:
             Test Case:              |   Related Tickets:
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 In this simple file

 {{{#!hs
 {-# LANGUAGE BangPatterns #-}

 baz !"a" = bang
 }}}

 It can be seen that on line 28 the `BangPat` has the wrong `SrcSpan`.

 {{{#!hs annotations=lineno
 ({ typetest.hs:1:1 }
  Just (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnEofPos),DP (1,0))])
  (HsModule
   (Nothing)
   (Nothing)
   []
   [
    ({ typetest.hs:3:1-15 }
     Just (Ann (DP (2,1)) (ColDelta 1) DP (2,1) [(Comment {commentPos = DP
 (0,29), commentContents = "{-# LANGUAGE BangPatterns #-}",
 commentIdentifier = RealSrcSpan SrcSpanOneLine "typetest.hs" 1 1 30,
 commentOrigin = Nothing},DP (0,0))] [])
     (ValD
      (FunBind
       ({ typetest.hs:3:1-3 }
        Just (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnVal),DP
 (0,0))])
        (Unqual {OccName: baz}))
       (False)
       (MG
        [
         ({ typetest.hs:3:1-15 }
          Just (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnEqual),DP
 (0,1)),((AnnList <no location info> NotNeeded),DP (0,0))])
          (Match
           (Just
            ((,)
             ({ typetest.hs:3:1-3 }
              Just (Ann (DP (0,0)) (ColDelta 1) DP (0,0) [] [((G AnnVal),DP
 (0,0))])
              (Unqual {OccName: baz}))
             (False)))
           [
            ({ typetest.hs:3:1-8 }
             Just (Ann (DP (0,-3)) (ColDelta 1) DP (0,-3) [] [((G
 AnnBang),DP (0,1))])
             (BangPat
              ({ typetest.hs:3:6-8 }
               Just (Ann (DP (0,0)) (ColDelta 6) DP (0,0) [] [((G
 AnnVal),DP (0,0))])
               (LitPat
                (HsString "\"a\"" {FastString: "a"})))))]
           (Nothing)
           (GRHSs
            [
             ({ typetest.hs:3:10-15 }
              Just (Ann (DP (0,-1)) (ColDelta 10) DP (0,-1) [] [])
              (GRHS
               []
               ({ typetest.hs:3:12-15 }
                Just (Ann (DP (0,1)) (ColDelta 12) DP (0,1) [] [((G
 AnnVal),DP (0,0))])
                (HsVar
                 (Unqual {OccName: bang})))))]
            (EmptyLocalBinds))))]
        []
        (PlaceHolder)
        (FromSource))
       (WpHole)
       (PlaceHolder)
       [])))]
   (Nothing)
   (Nothing)))
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10588>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list