[GHC] #8634: Code valid in GHC 7.6 is impossible to move over GHC 7.7 (because of liberal coverage condition)
GHC
ghc-devs at haskell.org
Fri Dec 27 20:04:06 UTC 2013
#8634: Code valid in GHC 7.6 is impossible to move over GHC 7.7 (because of
liberal coverage condition)
-----------------------------------+---------------------------------------
Reporter: danilo2 | Owner:
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 7.7
Resolution: | Keywords:
Operating System: | Architecture: Unknown/Multiple
Unknown/Multiple | Difficulty: Unknown
Type of failure: None/Unknown | Blocked By:
Test Case: | Related Tickets: #1241, #2247, #8356
Blocking: |
-----------------------------------+---------------------------------------
Comment (by danilo2):
Replying to [comment:4 rwbarton]:
According to my previous comment, here is sample code, which uses the
function `testx` as associated metthod `method2` to datatype `Vector` (it
works under GHC 7.6 and is, as you've noted, impossible to convert to
7.7):
{{{#!haskell
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
import Data.Tuple.OneTuple
------------------------------
data Vector a = Vector {x :: a, y :: a, z :: a} deriving (Show)
newtype Vector_method1 a = Vector_method1 a
newtype Vector_method2 a = Vector_method2 a
------------------------------
testid v x = x
testf2 v x = (x,x)
------------------------------
-- problematic function:
testx v x = call (method1 x) (OneTuple "test")
------------------------------
class Method1 cls m func | cls -> m, cls -> func where
method1 :: cls -> m func
class Method2 cls m func | cls -> m, cls -> func where
method2 :: cls -> m func
class Call ptr args result | ptr args -> result where
call :: ptr -> args -> result
------------------------------
instance (out ~ (t1->t1)) => Method1 (Vector a) Vector_method1 out where
method1 = (Vector_method1 . testid)
instance (base ~ (t1 -> t2), out ~ t2) => Call (Vector_method1 base)
(OneTuple t1) out where
call (Vector_method1 val) (OneTuple arg) = val arg
instance (base ~ (String -> t2), out ~ t2) => Call (Vector_method1 base)
() out where
call (Vector_method1 val) _ = val "default string"
------------------------------
instance ( Call (m func0) (OneTuple String) b
, Method1 a m func0
, out ~ (a -> b)
) => Method2 (Vector v) Vector_method2 out where
method2 = (Vector_method2 . testx)
instance (base ~ (t1 -> t2), out ~ t2) => Call (Vector_method2 base)
(OneTuple t1) out where
call (Vector_method2 val) (OneTuple arg) = val arg
------------------------------
main = do
let v = Vector (1::Int) (2::Int) (3::Int)
print $ call (method1 v) (OneTuple "test")
print $ call (method1 v) ()
print $ call (method2 v) (OneTuple v)
}}}
Output:
{{{#!haskell
"test"
"default string"
"test"
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8634#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list