Skip to content

GitLab

  • Projects
  • Groups
  • Snippets
  • Help
    • Loading...
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
GHC
GHC
  • Project overview
    • Project overview
    • Details
    • Activity
    • Releases
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,248
    • Issues 4,248
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 397
    • Merge Requests 397
  • Requirements
    • Requirements
    • List
  • CI / CD
    • CI / CD
    • Pipelines
    • Jobs
    • Schedules
  • Security & Compliance
    • Security & Compliance
    • Dependency List
    • License Compliance
  • Operations
    • Operations
    • Incidents
    • Environments
  • Analytics
    • Analytics
    • CI / CD
    • Code Review
    • Insights
    • Issue
    • Repository
    • Value Stream
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Members
    • Members
  • Collapse sidebar
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #18662

Closed
Open
Opened Sep 07, 2020 by Ryan Scott@RyanGlScottMaintainer

Properly distinguish enclosing deriving-clause parentheses in the GHC AST

Consider this program:

data D1 = MkD1 deriving Eq
data D2 = MkD2 deriving (Eq)

These two deriving clauses, while very similar, have slightly different syntax. Surprisingly, this difference is not reflected in the AST, as compiling this program with -ddump-parsed-ast will reveal that both deriving clauses are represented like so:

[({ Foo.hs:3:16-26 }
  (HsDerivingClause
   (NoExtField)
   (Nothing)
   ({ Foo.hs:3:25-26 }
    [(HsIB
      (NoExtField)
      ({ Foo.hs:3:25-26 }
       (HsTyVar
        (NoExtField)
        (NotPromoted)
        ({ Foo.hs:3:25-26 }
         (Unqual
          {OccName: Eq})))))])))]

This is rather annoying for several reasons:

  • This makes pretty-printing more laborious than it needs to be. Consider this code from GHC.Hs.Decls:

    instance OutputableBndrId p
           => Outputable (HsDerivingClause (GhcPass p)) where
      ppr (HsDerivingClause { deriv_clause_strategy = dcs
                            , deriv_clause_tys      = L _ dct })
        = hsep [ text "deriving"
               , pp_strat_before
               , pp_dct dct
               , pp_strat_after ]
          where
            -- This complexity is to distinguish between
            --    deriving Show
            --    deriving (Show)
            pp_dct [HsIB { hsib_body = ty }]
                     = ppr (parenthesizeHsType appPrec ty)
            pp_dct _ = parens (interpp'SP dct)

    As the comment indicates, we have to have a special case just for deriving clauses with one class to get the parentheses right. This doesn't even preserve the user-written syntax, however, as this would pretty-print both deriving Eq and deriving (Eq) as deriving Eq. Ugh.

    A similar problem arises in GHC.ThToHs.cvtContext, which is used to convert a deriving clause in the TH AST to that of one in the GHC AST. Currently, this code strategically inserts parentheses around LHsContexts with only one class. (See GHC.Hs.Type.parenthesizeHsContext.)

  • This omits a semantically important piece of information from the AST. GHC will parse deriving (C a), but not deriving C a. However, when GHC parses deriving (C a), it doesn't record the fact that C a was surrounded by parentheses.

  • This invites confusion between the enclosing parentheses in a deriving clause and HsParTy, which are semantically different. When one writes deriving (Eq, Show), those enclosing parentheses aren't an HsParTy, but rather an entirely different syntactic form. Unfortunately, this distinction is lost in the AST. When one writes deriving ((Eq)), this gets turned into the following AST:

    [({ Foo.hs:3:16-30 }
      (HsDerivingClause
       (NoExtField)
       (Nothing)
       ({ Foo.hs:3:25-30 }
        [(HsIB
          (NoExtField)
          ({ Foo.hs:3:26-29 }
           (HsParTy
            (NoExtField)
            ({ Foo.hs:3:27-28 }
             (HsTyVar
              (NoExtField)
              (NotPromoted)
              ({ Foo.hs:3:27-28 }
               (Unqual
                {OccName: Eq})))))))])))]

    If you're not careful, it's easily to be misled into thinking that this represents deriving (Eq)!

I propose to fix this infelicity by adding an extra field to HsDerivingClause of type DerivClauseEnclosingParens:

data DerivClauseEnclosingParens
  = Parenthesized
  | NotParenthesized

As the name suggests, this will be Parenthesized when enclosing parentheses are present and NotParenthesized otherwise. Consulting this field will avoid the need for awkward special cases when pretty-printing or converting deriving clauses and make it clearer exactly what the AST represents.

Assignee
Assign to
9.2.1
Milestone
9.2.1
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#18662