G'day all.
Quoting Simon Peyton-Jones <[EMAIL PROTECTED]>:
| -- GHC rejects this. Hugs compiles it, but I can't call it as
| -- let ?foo = "Hello" in show Foo
| --
| -- Is there a good reason to disallow this?
| data Foo = Foo
|
| instance (?foo :: String) => Show Foo where
| showsPrec _ Foo = showString ?foo . showString "Foo"
This should be illegal. The way in which implicit parameters are
bound depends on the call site of teh overloaded function. E.g. the
call site of f3 above affects the value of ?foo.
Yes, I've read the manual section on this.
For completeness, here's the final solution, courtesy of int-e (whose
real name I don't know; sorry), which is much more elegant than I
expected:
-- Type hackery
import GHC.Exts (unsafeCoerce#)
newtype Mark m a = Mark { unMark :: a }
toDummy :: Mark n t -> (n -> t)
toDummy (Mark x) _ = x
fromDummy :: (n -> t) -> Mark n t
fromDummy f = Mark (f undefined)
-- And now, the real code
class StringAsType s where
reifiedString' :: Mark s String
withString :: (StringAsType s) => s -> (String -> a) -> a
withString s k = k (toDummy reifiedString' s)
getString :: (StringAsType s) => s -> String
getString s = withString s id
bindString :: (forall s. StringAsType s => Mark s a) -> String -> a
bindString = unsafeCoerce#
mkStringAsType :: String -> (forall s. StringAsType s => s -> a) -> a
mkStringAsType s f = bindString (fromDummy f) s
-- ReifiedString can now be used as an instance context
That higher-rank type makes all the difference.
Cheers,
Andrew Bromage
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe