[GHC] #11358: GHC generics has differing conFixity behavior between 7.10.3 and 8.1
GHC
ghc-devs at haskell.org
Wed Jan 6 04:44:01 UTC 2016
#11358: GHC generics has differing conFixity behavior between 7.10.3 and 8.1
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: RyanGlScott
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 8.1
(CodeGen) |
Keywords: Generics | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect result
Unknown/Multiple | at runtime
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Compile the following program with GHC 7.10.3 and 8.1:
{{{#!hs
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
module Main (main) where
import GHC.Generics
infixr 1 `T`
data T a = T a a deriving Generic
instance HasFixity (T a)
data I a = a `I` a deriving Generic
instance HasFixity (I a)
class HasFixity a where
fixity :: a -> Fixity
default fixity :: (Generic a, GHasFixity (Rep a)) => a -> Fixity
fixity = gfixity . from
class GHasFixity f where
gfixity :: f a -> Fixity
instance GHasFixity f => GHasFixity (D1 d f) where
gfixity (M1 x) = gfixity x
instance Constructor c => GHasFixity (C1 c f) where
gfixity c = conFixity c
main :: IO ()
main = do
putStrLn $ show (fixity (T "a" "b")) ++ ", " ++ show (fixity ("a" `I`
"b"))
}}}
On GHC 7.10.3, it yields `Prefix, Infix LeftAssociative 9`, but on GHC
8.1, it yields `Infix RightAssociative 1, Prefix`. Why? The implementation
of `deriving Generic(1)` changed slightly in GHC 8.1. Before, it would
only assign a fixity of `Infix` if a constructor was ''declared'' infix.
But GHC 8.1 no longer checks for this—it first checks if there is a user-
supplied fixity declaration, and if so, uses that as the `Fixity`.
Otherwise, it defaults to `Prefix`, even if the datatype was declared
infix!
The design of `Fixity` perhaps leaves something to be desired, but at the
very least, we should ensure nothing `Fixity`-related breaks for now.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11358>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list