
#10634: Type class with bijective type functions -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- See the attached module. {{{ $ cat TypeFunctionBijection.hs {-# LANGUAGE TypeFamilies #-} module TypeFunctionBijection where import Data.Int (Int8, Int16, Int32) type family Up a type instance Up Int8 = Int16 type instance Up Int16 = Int32 class (Up (Down a) ~ a) => Convert a where type Down a down :: a -> Down a instance Convert Int16 where type Down Int16 = Int8 down = fromIntegral instance Convert Int32 where type Down Int32 = Int16 down = fromIntegral x :: Int8 x = down 8 }}} {{{ $ ghci-7.8.4 -Wall TypeFunctionBijection.hs GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling TypeFunctionBijection ( TypeFunctionBijection.hs, interpreted ) Ok, modules loaded: TypeFunctionBijection. *TypeFunctionBijection> :q Leaving GHCi. }}} {{{ $ ghci-7.10.1 -Wall TypeFunctionBijection.hs GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling TypeFunctionBijection ( TypeFunctionBijection.hs, interpreted ) TypeFunctionBijection.hs:24:5: Couldn't match expected type ‘Int8’ with actual type ‘Down a0’ The type variable ‘a0’ is ambiguous In the expression: down 8 In an equation for ‘x’: x = down 8 Failed, modules loaded: none. Prelude> :q Leaving GHCi. }}} Up to GHC-7.8.4 I could make a type function like `Down` a bijection by adding equality constraints to the `Convert` class. In GHC-7.10.1 this fails. Is this a bug or a feature? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10634 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler