[GHC] #10338: GHC Forgets Constraints
GHC
ghc-devs at haskell.org
Fri Apr 24 17:33:39 UTC 2015
#10338: GHC Forgets Constraints
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by crockeea):
I've got a new test case for what I assume is this bug. Unfortunately, I
can't find a workaround in this case.
{{{#!hs
{-# LANGUAGE MultiParamTypeClasses, ScopedTypeVariables,
ConstraintKinds, KindSignatures, TypeFamilies,
FlexibleInstances #-}
import GHC.Prim
import Control.Monad
class Unsat (a :: * -> *) c
class Qux (t :: * -> *) where
type QCtx t q :: Constraint
qux :: (QCtx t q, Monad rnd)
=> v -> rnd (t q)
instance Qux t where
type QCtx t q = (Unsat t q)
class (Qux c) => C (c :: * -> *) r
mymap :: c Double -> c i
mymap = undefined
foo :: forall c z v rnd . (C c z, Monad rnd, Num z) => v -> rnd (c z)
foo svar = liftM mymap $ qux svar
I've tried a wide array of explicit type sigs on `foo`, but nothing seems
to make it find the dictionary for `Qux` inherited from `C`. I really need
a fix for this.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10338#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list