[GHC] #3589: Recompilation checker doesn't take into account CPP headers

GHC ghc-devs at haskell.org
Fri Nov 21 17:25:48 UTC 2014


#3589: Recompilation checker doesn't take into account CPP headers
-------------------------------------+---------------------------------
        Reporter:  simonmar          |         Owner:
            Type:  bug               |        Status:  closed
        Priority:  normal            |     Milestone:  7.4.1
       Component:  Compiler          |       Version:  6.10.4
      Resolution:  fixed             |      Keywords:
Operating System:  Unknown/Multiple  |  Architecture:  Unknown/Multiple
 Type of failure:  None/Unknown      |    Difficulty:  Unknown
       Test Case:                    |    Blocked By:
        Blocking:                    |
-------------------------------------+---------------------------------

Comment (by Austin Seipp <austin@…>):

 In [changeset:"803fc5db31f084b73713342cdceaed5a9c664267/ghc"]:
 {{{
 #!CommitTicketReference repository="ghc"
 revision="803fc5db31f084b73713342cdceaed5a9c664267"
 Add API Annotations

 Summary:
 The final design and discussion is captured at
 https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations

 This is a proof of concept implementation of a completely
 separate annotation structure, populated in the parser,and tied to the
 AST by means of a virtual "node-key" comprising the surrounding
 SrcSpan and a value derived from the specific constructor used for the
 node.

 The key parts of the design are the following.

 == The Annotations ==

 In `hsSyn/ApiAnnotation.hs`

 ```lang=haskell
 type ApiAnns = (Map.Map ApiAnnKey SrcSpan, Map.Map SrcSpan [Located
 Token])

 type ApiAnnKey = (SrcSpan,AnnKeywordId)

 -- ---------------------------------------------------------------------

 -- | Retrieve an annotation based on the @SrcSpan@ of the annotated AST
 -- element, and the known type of the annotation.
 getAnnotation :: ApiAnns -> SrcSpan -> AnnKeywordId -> Maybe SrcSpan
 getAnnotation (anns,_) span ann = Map.lookup (span,ann) anns

 -- |Retrieve the comments allocated to the current @SrcSpan@
 getAnnotationComments :: ApiAnns -> SrcSpan -> [Located Token]
 getAnnotationComments (_,anns) span =
   case Map.lookup span anns of
     Just cs -> cs
     Nothing -> []

 -- | Note: in general the names of these are taken from the
 -- corresponding token, unless otherwise noted
 data AnnKeywordId
          = AnnAs
          | AnnBang
          | AnnClass
          | AnnClose -- ^ } or ] or ) or #) etc
          | AnnComma
          | AnnDarrow
          | AnnData
          | AnnDcolon
          ....
 ```

 == Capturing in the lexer/parser ==

 The annotations are captured in the lexer / parser by extending PState to
 include a field

 In `parser/Lexer.x`

 ```lang=haskell
 data PState = PState {
         ....
         annotations :: [(ApiAnnKey,SrcSpan)]
         -- Annotations giving the locations of 'noise' tokens in the
         -- source, so that users of the GHC API can do source to
         -- source conversions.
      }
 ```

 The lexer exposes a helper function to add an annotation

 ```lang=haskell
 addAnnotation :: SrcSpan -> Ann -> SrcSpan -> P ()
 addAnnotation l a v = P $ \s -> POk s {
   annotations = ((AK l a), v) : annotations s
   } ()

 ```

 The parser also has some helper functions of the form

 ```lang=haskell
 type MaybeAnn = Maybe (SrcSpan -> P ())

 gl = getLoc
 gj x = Just (gl x)

 ams :: Located a -> [MaybeAnn] -> P (Located a)
 ams a@(L l _) bs = (mapM_ (\a -> a l) $ catMaybes bs) >> return a
 ```

 This allows annotations to be captured in the parser by means of

 ```
 ctypedoc :: { LHsType RdrName }
         : 'forall' tv_bndrs '.' ctypedoc {% hintExplicitForall (getLoc $1)
 >>
                                             ams (LL $ mkExplicitHsForAllTy
 $2 (noLoc []) $4)
                                                 [mj AnnForall $1,mj AnnDot
 $3] }
         | context '=>' ctypedoc         {% ams (LL $ mkQualifiedHsForAllTy
 $1 $3)
                                                [mj AnnDarrow $2] }
         | ipvar '::' type               {% ams (LL (HsIParamTy (unLoc $1)
 $3))
                                                [mj AnnDcolon $2] }
         | typedoc                       { $1 }
 ```

 == Parse result ==

 ```lang-haskell
 data HsParsedModule = HsParsedModule {
     hpm_module    :: Located (HsModule RdrName),
     hpm_src_files :: [FilePath],
        -- ^ extra source files (e.g. from #includes).  The lexer collects
        -- these from '# <file> <line>' pragmas, which the C preprocessor
        -- leaves behind.  These files and their timestamps are stored in
        -- the .hi file, so that we can force recompilation if any of
        -- them change (#3589)
     hpm_annotations :: ApiAnns
   }

 -- | The result of successful parsing.
 data ParsedModule =
   ParsedModule { pm_mod_summary   :: ModSummary
                , pm_parsed_source :: ParsedSource
                , pm_extra_src_files :: [FilePath]
                , pm_annotations :: ApiAnns }
 ```

 This diff depends on D426

 Test Plan: sh ./validate

 Reviewers: austin, simonpj, Mikolaj

 Reviewed By: simonpj, Mikolaj

 Subscribers: Mikolaj, goldfire, thomie, carter

 Differential Revision: https://phabricator.haskell.org/D438

 GHC Trac Issues: #9628
 }}}

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


More information about the ghc-tickets mailing list