[GHC] #7785: Module-local function not specialized with ConstraintKinds
GHC
cvs-ghc at haskell.org
Fri Mar 22 07:42:19 CET 2013
#7785: Module-local function not specialized with ConstraintKinds
------------------------------------+---------------------------------------
Reporter: akio | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.6.2 | Keywords: specialisation
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: Runtime performance bug | Blockedby:
Blocking: | Related:
------------------------------------+---------------------------------------
Comment(by akio):
This can be worked around by defining a wrapper class such that the
constraint kind no longer directly shows up in the type signatures.
{{{
--- spec.hs 2013-03-22 15:41:23.000000000 +0900
+++ spec2.hs 2013-03-22 15:38:30.000000000 +0900
@@ -1,10 +1,12 @@
-{-# LANGUAGE TypeFamilies, ConstraintKinds #-}
+{-# LANGUAGE TypeFamilies, ConstraintKinds, MultiParamTypeClasses,
UndecidableInstances, FlexibleContexts, FlexibleInstances #-}
module Foo(foo, bar, foo', bar') where
import GHC.Exts
type family Domain (f :: * -> *) a :: Constraint
+class Domain f a => Domain' (f :: * -> *) a
+instance Domain f a => Domain' f a
type instance Domain [] a = ()
@@ -12,9 +14,9 @@
myfmap = map
class MyFunctor f where
- myfmap :: (Domain f a, Domain f b) => (a -> b) -> f a -> f b
+ myfmap :: (Domain' f a, Domain' f b) => (a -> b) -> f a -> f b
-shared :: (MyFunctor f, Domain f Int) => f Int -> f Int
+shared :: (MyFunctor f, Domain' f Int) => f Int -> f Int
shared = let
f = myfmap negate
in
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7785#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list