开发者

How do I resolve this compile error: Ambiguous type variable `a1' in the constraint

One could think of this case as follows: The application dynamically loads a module, or there is a list of functions from which the user chooses, etc. We have a mechanism for determining whether a certain type will successfully work with a function in that module. So now we want to call into that function. We need to force it to make the call. The function could take a concrete type, or a polymorphic one and it's the case below with just a type class constraint that I'm running into probl开发者_StackOverflow中文版ems with it.

The following code results in the errors below. I think it could be resolved by specifying concrete types but I do not want to do that. The code is intended to work with any type that is an instance of the class. Specifying a concrete type defeats the purpose.

This is simulating one part of a program that does not know about the other and does not know the types of what it's dealing with. I have a separate mechanism that allows me to be sure that the types do match up properly, that the value sent in really is an instance of the type class. That's why in this case, I don't mind using unsafeCoerce. But basically I need a way to tell the compiler that I really do know it's ok and do it anyway even though it doesn't know enough to type check.

{-# LANGUAGE ExistentialQuantification, RankNTypes, TypeSynonymInstances #-}
module Main where

import Unsafe.Coerce

main = do
  --doTest1 $ Hider "blue"
  doTest2 $ Hider "blue"

doTest1 :: Hider -> IO ()
doTest1 hh@(Hider h) =
  test $ unsafeCoerce h

doTest2 :: Hider -> IO ()
doTest2 hh@(Hider h) =
  test2 hh

test :: HasString a => a -> IO ()
test x = print $ toString x

test2 :: Hider -> IO ()
test2 (Hider x) = print $ toString (unsafeCoerce x)

data Hider = forall a. Hider a

class HasString a where
  toString :: a -> String

instance HasString String where
  toString = id

Running doTest1

[1 of 1] Compiling Main             ( Test.hs, Test.o )

Test.hs:12:3:
    Ambiguous type variable `a1' in the constraint:
      (HasString a1) arising from a use of `test'
    Probable fix: add a type signature that fixes these type variable(s)
    In the expression: test
    In the expression: test $ unsafeCoerce h
    In an equation for `doTest1':
        doTest1 hh@(Hider h) = test $ unsafeCoerce h

Running doTest2

[1 of 1] Compiling Main             ( Test.hs, Test.o )

Test.hs:12:3:
    Ambiguous type variable `a1' in the constraint:
      (HasString a1) arising from a use of `test'
    Probable fix: add a type signature that fixes these type variable(s)
    In the expression: test
    In the expression: test $ unsafeCoerce h
    In an equation for `doTest1':
        doTest1 hh@(Hider h) = test $ unsafeCoerce h


I think it could be resolved by specifying concrete types but I do not want to do that.

There's no way around it though with unsafeCoerce. In this particular case, the compiler can't infer the type of unsafeCoerce, because test is still to polymorphic. Even though there is just one instance of HasString, the type system won't use that fact to infer the type.

I don't have enough information about your particular application of this pattern, but I'm relatively sure that you need to rethink the way you use the type system in your program. But if you really want to do this, you might want to look into Data.Typeable instead of unsafeCoerce.


Modify your data type slightly:

data Hider = forall a. HasString a => Hider a

Make it an instance of the type class in the obvious way:

instance HasString Hider where
    toString (Hider x) = toString x

Then this should work, without use of unsafeCoerce:

doTest3 :: Hider -> IO ()
doTest3 hh = print $ toString hh

This does mean that you can no longer place a value into a Hider if it doesn't implement HasString, but that's probably a good thing.

There's probably a name for this pattern, but I can't think what it is off the top of my head.

0

上一篇:

下一篇:

精彩评论

暂无评论...
验证码 换一张
取 消

最新问答

问答排行榜