[GHC] #12220: TypeApplications and DefaultSignatures - problems deducing type variables.
GHC
ghc-devs at haskell.org
Wed Jun 22 17:31:14 UTC 2016
#12220: TypeApplications and DefaultSignatures - problems deducing type variables.
-------------------------------------+-------------------------------------
Reporter: mkloczko | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Linux
DefaultSignatures, |
TypeApplications |
Architecture: x86_64 | Type of failure: None/Unknown
(amd64) |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following example code throws an error.
The example code:
{{{#!hs
{-#LANGUAGE TypeApplications#-}
{-#LANGUAGE MultiParamTypeClasses #-}
{-#LANGUAGE AllowAmbiguousTypes #-}
{-#LANGUAGE FlexibleInstances #-}
{-#LANGUAGE ScopedTypeVariables #-}
{-#LANGUAGE DefaultSignatures #-}
module Test1 where
-- | Type a is only used for
-- type application.
class ToUse a where
toUse :: Int -> Int
-- | The type used for
-- type application
data Default
-- | The instance using Default as type application.
-- To call use:
-- > toUse @Default
instance ToUse Default where
toUse a = 3*a
-- | Typeclass whose methods work
-- only with type application.
class (ToUse a) => Uses a b where
uses :: b -> [b]
-- | Default Signature, which generates the problem.
-- It is the same as the normal one
-- Comment it to 'fix' the bug.
default uses :: b -> [b]
uses v = [v]
-- | Normal instances, nothing special
instance Uses Default Int where
uses v = take (toUse @Default 3) $ repeat v
-- | Another normal one
instance Uses Default String where
uses v = take (toUse @Default 2) $ repeat v
-- | This one works nicely
instance (ToUse t, Uses t a, Uses t b) => Uses t (a,b) where
uses (vl,vr) = zip ls rs
where ls = uses @t vl
rs = uses @t vr
-- | But this one doesn't.
-- Unless you comment the default signature.
instance (ToUse t, Uses t a, Uses t b, Uses t c) => Uses t (a,b,c)
}}}
The error:
{{{
• Could not deduce (Uses a0 a)
arising from a use of ‘Test1.$dmuses’
from the context: (ToUse t, Uses t a, Uses t b, Uses t c)
bound by the instance declaration at Test1.hs:47:10-66
The type variable ‘a0’ is ambiguous
Relevant bindings include
uses :: (a, b, c) -> [(a, b, c)] (bound at Test1.hs:47:10)
• In the expression: Test1.$dmuses
In an equation for ‘uses’: uses = Test1.$dmuses
In the instance declaration for ‘Uses t (a, b, c)’
}}}
Commenting out the default signature fixes the problem.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12220>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list