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,323
    • Issues 4,323
    • List
    • Boards
    • Labels
    • Service Desk
    • Milestones
    • Iterations
  • Merge Requests 377
    • Merge Requests 377
  • 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
  • #14289

Closed
Open
Opened Sep 27, 2017 by Ryan Scott@RyanGlScottMaintainer

Pretty-printing of derived multi-parameter classes omits necessary parentheses

Take this file:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS -ddump-splices #-}

import Language.Haskell.TH

class C a b

main :: IO ()
main = putStrLn $([d| data Foo a = Foo a deriving (C a) |] >>= stringE . show)

When this is compiled, -ddump-splices does not faithfully print back what was written by the user:

[1 of 1] Compiling Main             ( Bug.hs, interpreted )
Bug.hs:10:19-77: Splicing expression
    [d| data Foo_a4l1 a_a4l3
          = Foo_a4l2 a_a4l3
          deriving C a_a4l3 |]
      >>= stringE . show
  ======>
    "[DataD [] Foo_6989586621679026555 [PlainTV a_6989586621679026557] Nothing [NormalC Foo_6989586621679026556 [(Bang NoSourceUnpackedness NoSourceStrictness,VarT a_6989586621679026557)]] [DerivClause Nothing [AppT (ConT Main.C) (VarT a_6989586621679026557)]]]"

In particular, this pretty-prints deriving C a_a4l3, which doesn't even parse correctly. It should print deriving (C a_a4l3). Ultimately, there is an off-by-one error in the number of parentheses being printed, since if you tweak the original example by adding another set of parentheses:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS -ddump-splices #-}

import Language.Haskell.TH

class C a b

main :: IO ()
main = putStrLn $([d| data Foo a = Foo a deriving ((C a)) |] >>= stringE . show)

Then it pretty-prints exactly one set of parentheses (as opposed to two):

[1 of 1] Compiling Main             ( Bug.hs, interpreted )
Bug.hs:10:19-79: Splicing expression
    [d| data Foo_a1zI a_a1zK
          = Foo_a1zJ a_a1zK
          deriving (C a_a1zK) |]
      >>= stringE . show
  ======>
    "[DataD [] Foo_6989586621679026522 [PlainTV a_6989586621679026524] Nothing [NormalC Foo_6989586621679026523 [(Bang NoSourceUnpackedness NoSourceStrictness,VarT a_6989586621679026524)]] [DerivClause Nothing [AppT (ConT Main.C) (VarT a_6989586621679026524)]]]"

There are two suspicious parts of the GHC codebase that contribute to this bug:

  • This parser production: http://git.haskell.org/ghc.git/blob/4364f1e7543b6803cfaef321105d253e0bdf08a4:/compiler/parser/Parser.y\#l2162

    This recognizes singleton derived classes that are surrounded by a set of parentheses, and "strips off" the parentheses.

  • This Outputable instance: http://git.haskell.org/ghc.git/blob/4364f1e7543b6803cfaef321105d253e0bdf08a4:/compiler/hsSyn/HsDecls.hs\#l1102

    This code detects lists of two or more derived classes and surrounds them with extra parentheses to make up for the set that was removed during parsing. But this fails to detect the case of deriving (C a), since this only contains a single class.

    Indeed, trying to distinguish between, say, deriving T and deriving (T) at this level would be quite tricky.

Trac metadata
Trac field Value
Version 8.2.1
Type Bug
TypeOfFailure OtherFailure
Priority normal
Resolution Unresolved
Component Compiler (Parser)
Test case
Differential revisions
BlockedBy
Related
Blocking
CC alanz
Operating system
Architecture
Assignee
Assign to
None
Milestone
None
Assign milestone
Time tracking
None
Due date
None
Reference: ghc/ghc#14289