[GHC] #8644: 'Untouchable' error with constraint variable in rank-2 type
GHC
ghc-devs at haskell.org
Tue Dec 31 22:13:12 UTC 2013
#8644: 'Untouchable' error with constraint variable in rank-2 type
-------------------------------------+-------------------------------------
Reporter: sbarclay | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.7
checker) | Operating System: Unknown/Multiple
Keywords: | Type of failure: GHC rejects
Architecture: Unknown/Multiple | valid program
Difficulty: Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: |
-------------------------------------+-------------------------------------
The following program compiles fine with GHC 7.6.3:
{{{#!haskell
{-# LANGUAGE ConstraintKinds, RankNTypes, GADTs #-}
data Dict c where Dict :: c => Dict c
foo :: Dict c -> (c => r) -> r
foo Dict x = x
bar :: Dict ()
bar = Dict
main :: IO ()
main = print $ foo bar "Hello"
}}}
However, it produces the following error with HEAD:
{{{
ConstraintIssue.hs:12:8:
No instance for (Show s0) arising from a use of ‛print’
The type variable ‛s0’ is ambiguous
Note: there are several potential instances:
instance Show Double -- Defined in ‛GHC.Float’
instance Show Float -- Defined in ‛GHC.Float’
instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
-- Defined in ‛GHC.Real’
...plus 24 others
In the expression: print
In the expression: print $ foo bar "Hello"
In an equation for ‛main’: main = print $ foo bar "Hello"
ConstraintIssue.hs:12:24:
Couldn't match expected type ‛s0’ with actual type ‛[Char]’
‛s0’ is untouchable
inside the constraints (())
bound by a type expected by the context: (()) => s0
at ConstraintIssue.hs:12:16-30
In the second argument of ‛foo’, namely ‛"Hello"’
In the second argument of ‛($)’, namely ‛foo bar "Hello"’
In the expression: print $ foo bar "Hello"
}}}
If the type signature of 'main' is removed, the code compiles OK.
If the empty constraint () is replaced with an equality constraint such as
Int ~ Int, then the above error occurs with both 7.6.3 and HEAD, which I
guess is intended behaviour.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8644>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list