[GHC] #13637: Printing type operators adds extraneous parenthesis

#13637: Printing type operators adds extraneous parenthesis -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given the code: {{{ {-# LANGUAGE TypeOperators #-} type name ::: a = a f :: Int ::: Int -> Int f = id }}} In GHCi-8.0.2 I get: {{{
:t f f :: Int ::: Int -> Int }}}
But in GHCi-8.2.0.20170427 I get: {{{
:t f f :: (Int ::: Int) -> Int }}}
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13637 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13637: Printing type operators adds extraneous parenthesis -------------------------------------+------------------------------------- Reporter: darchon | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * owner: (none) => alanz -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13637#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13637: Printing type operators adds extraneous parenthesis -------------------------------------+------------------------------------- Reporter: darchon | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alanz): I am investigating this, and suspect I may not be the culprit, it deals directly with `Type`, and the printing process goes through `pprTypeForUser ty` which is {{{#!haskell pprTypeForUser :: Type -> SDoc -- The type is tidied pprTypeForUser ty = pprSigmaType tidy_ty where (_, tidy_ty) = tidyOpenType emptyTidyEnv ty -- Often the types/kinds we print in ghci are fully generalised -- and have no free variables, but it turns out that we sometimes -- print un-generalised kinds (eg when doing :k T), so it's -- better to use tidyOpenType here }} And in turn `tidyOpenType` ends up in `tidyOpenTypes`, which changed as a result of https://github.com/ghc/ghc/commit/e9bf7bb5cc9 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13637#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13637: Printing type operators adds extraneous parenthesis -------------------------------------+------------------------------------- Reporter: darchon | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by harpocrates): This seems to be by design. Taken from `BasicTypes`: {{{ Note [Type operator precedence] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We don't keep the fixity of type operators in the operator. So the pretty printer follows the following precedence order: TyConPrec Type constructor application TyOpPrec/FunPrec Operator application and function arrow We have FunPrec and TyOpPrec to represent the precedence of function arrow and type operators respectively, but currently we implement FunPred == TyOpPrec, so that we don't distinguish the two. Reason: it's hard to parse a type like a ~ b => c * d -> e - f By treating TyOpPrec = FunPrec we end up with more parens (a ~ b) => (c * d) -> (e - f) But the two are different constructors of TyPrec so we could make (->) bind more or less tightly if we wanted. }}} I propose we close this ticket - I tend to agree with the note that the extra parens increase readability. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13637#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13637: Printing type operators adds extraneous parenthesis -------------------------------------+------------------------------------- Reporter: darchon | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nfrisby): I agree that this ticket's bug should be fixed. The {{{We don't keep the fixity of type operators in the operator}}} quoted in comment:3 above is the root problem, if I understand correctly. I'm writing a plugin for type-level sets, and the extra parentheses makes the syntax much more difficult to read than it should be. {{{((('Empty :* a) :* b) :* c)}}} is worse than {{{'Empty :* a :* b :* c}}}. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13637#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC