[GHC] #9830: Standalone-derived Show instance for type constructor has different precedence if orphan instance

GHC ghc-devs at haskell.org
Mon Nov 24 15:50:01 UTC 2014


#9830: Standalone-derived Show instance for type constructor has different
precedence if orphan instance
-------------------------------------+-------------------------------------
              Reporter:              |            Owner:
  RyanGlScott                        |           Status:  new
                  Type:  bug         |        Milestone:
              Priority:  normal      |          Version:  7.8.3
             Component:  Compiler    |         Keywords:
            Resolution:              |     Architecture:  Unknown/Multiple
      Operating System:              |       Difficulty:  Unknown
  Unknown/Multiple                   |       Blocked By:
       Type of failure:  Incorrect   |  Related Tickets:
  result at runtime                  |
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
Description changed by RyanGlScott:

Old description:

> If you are using {{{StandaloneDeriving}}} to derive a {{{Show}}} instance
> for a data type with an infix constructor, its precedence will be
> different depending on which module the {{{deriving instance ...}}}
> declaration is in. For example, with this code:
>
> {{{#!hs
> -- InfixShow.hs
> {-# LANGUAGE StandaloneDeriving #-}
> module InfixShow where
>
> infixr 6 :?:
> data ADT a b = a :?: b deriving (Eq, Ord, Read)
>
> deriving instance (Show a, Show b) => Show (ADT a b)
> }}}
>
> {{{#!hs
> -- Main.hs
> module Main where
>
> import InfixShow
>
> main :: IO ()
> main = do
>     putStrLn $ "Prec 6:  " ++ showsPrec 6  ("test" :?: "show") ""
>     putStrLn $ "Prec 7:  " ++ showsPrec 7  ("test" :?: "show") ""
>     putStrLn $ "Prec 9:  " ++ showsPrec 9  ("test" :?: "show") ""
>     putStrLn $ "Prec 10: " ++ showsPrec 10 ("test" :?: "show") ""
> }}}
>
> Calling {{{runhaskell Main.hs}}} will produce this output, as expected:
>
> {{{
> Prec 6:  "test" :?: "show"
> Prec 7:  ("test" :?: "show")
> Prec 9:  ("test" :?: "show")
> Prec 10: ("test" :?: "show")
> }}}
>
> However, if the code is changed so that the {{{deriving instance ...}}}
> declaration is in {{{Main.hs}}} instead:
>
> {{{#!hs
> -- InfixShow.hs
> module InfixShow where
>
> infixr 6 :?:
> data ADT a b = a :?: b deriving (Eq, Ord, Read)
> }}}
>
> {{{#!hs
> -- Main.hs
> {-# LANGUAGE StandaloneDeriving #-}
> module Main where
>
> import InfixShow
>
> deriving instance (Show a, Show b) => Show (ADT a b)
>
> main :: IO ()
> main = do
>     putStrLn $ "Prec 6:  " ++ showsPrec 6  ("test" :?: "show") ""
>     putStrLn $ "Prec 7:  " ++ showsPrec 7  ("test" :?: "show") ""
>     putStrLn $ "Prec 9:  " ++ showsPrec 9  ("test" :?: "show") ""
>     putStrLn $ "Prec 10: " ++ showsPrec 10 ("test" :?: "show") ""
> }}}
>
> Then the output of {{{runhaskell Main.hs}}} is different:
>
> {{{
> Prec 6:  "test" :?: "show"
> Prec 7:  "test" :?: "show"
> Prec 9:  "test" :?: "show"
> Prec 10: ("test" :?: "show")
> }}}
>
> This seems to indicate that {{{:?:}}} has the default application
> precedence (9) instead of the precedence defined in {{{InfixShow}}} (6).

New description:

 If you are using {{{StandaloneDeriving}}} to derive a {{{Show}}} instance
 for a data type with an infix constructor, its precedence will be
 different depending on which module the {{{deriving instance ...}}}
 declaration is in. For example, with this code:

 {{{#!hs
 -- InfixShow.hs
 {-# LANGUAGE StandaloneDeriving #-}
 module InfixShow where

 infixr 6 :?:
 data ADT a b = a :?: b deriving (Eq, Ord, Read)

 deriving instance (Show a, Show b) => Show (ADT a b)
 }}}

 {{{#!hs
 -- Main.hs
 module Main where

 import InfixShow

 main :: IO ()
 main = do
     putStrLn $ "Prec 6:  " ++ showsPrec 6  ("test" :?: "show") ""
     putStrLn $ "Prec 7:  " ++ showsPrec 7  ("test" :?: "show") ""
     putStrLn $ "Prec 9:  " ++ showsPrec 9  ("test" :?: "show") ""
     putStrLn $ "Prec 10: " ++ showsPrec 10 ("test" :?: "show") ""
 }}}

 Calling {{{runhaskell Main.hs}}} will produce this output, as expected:

 {{{
 Prec 6:  "test" :?: "show"
 Prec 7:  ("test" :?: "show")
 Prec 9:  ("test" :?: "show")
 Prec 10: ("test" :?: "show")
 }}}

 However, if the code is changed so that the {{{deriving instance ...}}}
 declaration is in {{{Main.hs}}} instead:

 {{{#!hs
 -- InfixShow.hs
 module InfixShow where

 infixr 6 :?:
 data ADT a b = a :?: b deriving (Eq, Ord, Read)
 }}}

 {{{#!hs
 -- Main.hs
 {-# LANGUAGE StandaloneDeriving #-}
 module Main where

 import InfixShow

 deriving instance (Show a, Show b) => Show (ADT a b)

 main :: IO ()
 main = do
     putStrLn $ "Prec 6:  " ++ showsPrec 6  ("test" :?: "show") ""
     putStrLn $ "Prec 7:  " ++ showsPrec 7  ("test" :?: "show") ""
     putStrLn $ "Prec 9:  " ++ showsPrec 9  ("test" :?: "show") ""
     putStrLn $ "Prec 10: " ++ showsPrec 10 ("test" :?: "show") ""
 }}}

 Then the output of {{{runhaskell Main.hs}}} is different:

 {{{
 Prec 6:  "test" :?: "show"
 Prec 7:  "test" :?: "show"
 Prec 9:  "test" :?: "show"
 Prec 10: ("test" :?: "show")
 }}}

 This seems to indicate that {{{:?:}}} has the default maximum operator
 precedence (9) instead of the precedence defined in {{{InfixShow}}} (6).

--

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


More information about the ghc-tickets mailing list