[GHC] #15649: Errors about ambiguous untouchable variable when using constraint variable in RankN type
GHC
ghc-devs at haskell.org
Sun Sep 16 05:10:00 UTC 2018
#15649: Errors about ambiguous untouchable variable when using constraint variable
in RankN type
-------------------------------------+-------------------------------------
Reporter: infinity0 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by infinity0):
Note that the error also goes away if we specialise `r` to be of kind `*`
rather than `* -> Constraint`, for example:
{{{#!haskell
-- as the first snippet, but add:
{-# LANGUAGE FlexibleContexts #-}
-- and then:
instance DynPS ((~) ()) ()
loadAll3
:: forall a r . (DynPS ((~) r) a)
=> (forall ref . r ~ ref => ref -> PSAny ((~) r))
-> a -> Maybe a
loadAll3 loader r = loadAll (DynLoad' loader :: DynLoad' ((~) r)) r
testCallable3 :: IO (Maybe ())
testCallable3 = return $ loadAll3 undefined ()
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15649#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list