Allowing Instances to Unify Types
Simon Peyton-Jones
simonpj at microsoft.com
Mon Jul 26 06:11:37 EDT 2010
Matt
I afraid I didn't understand your email well enough to offer a coherent response. For example I have no clue what "instance unifs" might mean. Nor do I understand what your program seeks to achieve.
Thomas is right to say that the type checker is in upheaval at the moment. I'm actively working on it with Dimitrios (http://darcs.haskell.org/ghc-new-tc/ghc for the over-interested), but it'll be a month or two before it gets into HEAD. However the plan is to do so for the 6.14 release.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Matt Brown
| Sent: 23 July 2010 21:47
| To: glasgow-haskell-users
| Subject: Allowing Instances to Unify Types
|
| Hi all,
| I've been hacking on GHC for a couple months now, experimenting with
| some different ideas I find interesting. One thing I'm trying to do
| is allow instance unifs (when there's an unambiguous choice, a
| question which is simplified in this case by there being only one),
| and force the required unification. Here's a simple example:
|
| {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
| FlexibleInstances, UndecidableInstances #-}
| class Apply a b c | a b -> c where
| applyInst :: a -> b -> c
|
| instance (Monad m) => Apply (a -> m b) (m a) (m b) where
| applyInst = (=<<)
|
| apply :: (Monad m) => (a -> m b) -> (m a) -> (m b)
| apply = (=<<)
|
| ioStr :: IO String
| ioStr = return "foo"
|
| printStr :: String -> IO ()
| printStr = print
|
| main = do print `apply` (return "foo")
| printStr `applyInst` ioStr
| print `applyInst` (return "bar") -- this fails
|
|
| With my code to use the unif instance enabled, I get Ambiguous type
| variable errors for "Show a" (from print) and "Monad m" (from return).
|
| My question is: in the case of apply (which isn't implemented by a
| class), how does the typechecker propagate "a ~ String" and "m ~ IO"
| to the predicates for print and return? If someone (such as myself)
| had sufficient time and energy to spend trying to achieve similar
| behavior for applyInst, where might he/I start?
|
| Thanks and Regards,
| -matt
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list