[GHC] #9628: Add Annotations to the AST to simplify source to source conversions
GHC
ghc-devs at haskell.org
Sat Oct 11 13:54:17 UTC 2014
#9628: Add Annotations to the AST to simplify source to source conversions
-------------------------------------+-------------------------------------
Reporter: alanz | Owner: alanz
Type: feature | Status: new
request | Milestone:
Priority: normal | Version: 7.9
Component: Compiler | Keywords:
Resolution: | Architecture: Unknown/Multiple
Operating System: | Difficulty: Unknown
Unknown/Multiple | Blocked By:
Type of failure: | Related Tickets:
None/Unknown |
Test Case: |
Blocking: |
Differential Revisions: D297 |
-------------------------------------+-------------------------------------
Comment (by alanz):
The multiple annotation approach seems promising, first stab results in
Annotation types
{{{
#!haskell
data AnnModule = AnnModule SrcSpan
deriving (Eq,Data,Typeable,Show)
data AnnWhere = AnnWhere SrcSpan
deriving (Eq,Data,Typeable,Show)
-- Should this be AnnBraces? The tokens are ITocurly / ITccurly
data AnnCurlies = AnnCurlies (SrcSpan,SrcSpan)
deriving (Eq,Data,Typeable,Show)
data AnnSemi = AnnSemi SrcSpan
deriving (Eq,Data,Typeable,Show)
data AnnComma = AnnComma SrcSpan
deriving (Eq,Data,Typeable,Show)
-- | Pragma declaration, e.g. '{-# SOURCE' '#-}'
data AnnPragma = AnnPragma (SrcSpan,SrcSpan)
deriving (Eq,Data,Typeable,Show)
}}}
Helper functions in parser
{{{
#!haskell
-- | Given a list of @Maybe annotation@, add the @Just@ ones to the
-- given location
ams :: Located a -> [Maybe (SrcSpan -> P ())] -> P (Located a)
ams a@(L l _) bs = (mapM_ (\a -> a l) $ catMaybes bs) >> return a
mj :: (Outputable a,Typeable a,Show a,Eq a)
=> (SrcSpan -> a) -> Located e -> Maybe (SrcSpan -> P ())
mj c l = Just (\s -> addAnnotation s (c (gl $l)))
mm :: (Outputable a,Typeable a,Show a,Eq a)
=> (SrcSpan -> a) -> Maybe SrcSpan -> Maybe (SrcSpan -> P ())
mm c Nothing = Nothing
mm c (Just l) = Just (\s -> addAnnotation s (c l))
mm2 :: (Outputable a,Typeable a,Show a,Eq a)
=> ((SrcSpan,SrcSpan) -> a) -> Maybe (SrcSpan,SrcSpan)
-> Maybe (SrcSpan -> P ())
mm2 c Nothing = Nothing
mm2 c (Just (l1,l2)) = Just (\s -> addAnnotation s (c (l1,l2)))
}}}
Example rule in parser
{{{
module :: { Located (HsModule RdrName) }
: maybedocheader 'module' modid maybemodwarning maybeexports
'where' body
{% fileSrcSpan >>= \ loc ->
ams (L loc (HsModule (Just $3) $5 (fst $ snd $7) (snd $
snd $7) $4 $1
) )
[mj AnnModule $3, mj AnnWhere $6
,mm2 AnnCurlies (fst $ fst $7),mm AnnSemi (snd $ fst
$7)] }
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9628#comment:23>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list