[Haskell-cafe] Hint and Ambiguous Type issue
Daniel Fischer
daniel.is.fischer at web.de
Thu Mar 5 14:04:04 EST 2009
Am Donnerstag, 5. März 2009 19:48 schrieb Joseph Fredette:
>
> getFilterMain :: Deliverable a => FilePath -> Interpreter (Filter
> a)
> getFilterMain fMainLoc =
> do
> loadModules [fMainLoc]; setTopLevelModules [(takeWhile
> (/='.') fMainLoc)]
> fMain <- (interpret "(filterMain)" (as :: Deliverable a =>
> Filter a))
Without looking at more code, the type variable a here is a fresh type
variable, not the one from getFilterMain's signature.
> return
> (fMain)
Maybe bringing the type variable a into scope in the function body by
{-# LANGUAGE ScopedTypeVariables #-}
getFilterMain :: forall a. Deliverable a => FilePath -> Interpreter (Filter,
a)
would suffice.
>
>
> However, when I try to compile this, I get the type error:
>
> Hackmain.hs:70:43:
> Ambiguous type variable `a' in the constraint:
> `Deliverable a'
> arising from a use of `getFilterMainStuff' at
> Hackmain.hs:70:43-60
> Probable fix: add a type signature that fixes these type
> variable(s)
>
> My understanding is that a type like "Foo a => Bar a" (where Foo is a
> class and Bar is a datatype) would simply restrict
> the values of a to only those implementing Foo. But evidently I'm wrong.
> Is there a good (read, easy... :) ) fix to this?
>
> Any help would be greatly appreciated.
>
> /Joe
>
> PS. All the actual code is on patch-tag, here
> http://patch-tag.com/repo/Hackmail/home -- if anyone prefers to look at
> that directly, the relevant files are in Src, namely, Hackmain.hs,
> Filter.hs, and Deliverable.hs
More information about the Haskell-Cafe
mailing list