<div dir="ltr">AllowAmbiguousTypes at this point only extends to signatures that are explicitly written.<div><br></div><div>This would need a new "AllowInferredAmbiguousTypes" or something.</div></div><div class="gmail_extra">
<br><br><div class="gmail_quote">On Sat, Oct 12, 2013 at 5:34 PM, adam vogt <span dir="ltr"><<a href="mailto:vogt.adam@gmail.com" target="_blank">vogt.adam@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
Hello,<br>
<br>
I have code:<br>
<br>
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses,<br>
ScopedTypeVariables, TypeFamilies #-}<br>
<br>
class C a b where c :: a -> b<br>
instance (int ~ Integer) => C Integer int where c = (+1)<br>
<br>
c2 :: forall a b c. (C a b, C b c) => a -> c<br>
c2 x = c (c x :: b)<br>
c2 x = c ((c :: a -> b) x)<br>
<br>
<br>
Why are the type signatures needed? If I leave all of them off, I get:<br>
<br>
Could not deduce (C a1 a0)<br>
arising from the ambiguity check for ‛c2’<br>
from the context (C a b, C a1 a)<br>
bound by the inferred type for ‛c2’: (C a b, C a1 a) => a1 -> b<br>
<br>
from the line: c2 x = c (c x)<br>
<br>
<br>
>From my perspective, it seems that the type signature ghc infers<br>
should be able to restrict the ambiguous types as the hand-written<br>
signature does.<br>
<br>
These concerns apply to HEAD (using -XAllowAmbiguousTypes) and ghc-7.6 too.<br>
<br>
Regards,<br>
Adam<br>
_______________________________________________<br>
Glasgow-haskell-users mailing list<br>
<a href="mailto:Glasgow-haskell-users@haskell.org">Glasgow-haskell-users@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/glasgow-haskell-users" target="_blank">http://www.haskell.org/mailman/listinfo/glasgow-haskell-users</a><br>
</blockquote></div><br></div>