<div dir="ltr">Because that wouldn't show up in haddock or :t.</div><div class="gmail_extra"><br><div class="gmail_quote">On 22 January 2015 at 01:23,  <span dir="ltr"><<a href="mailto:amindfv@gmail.com" target="_blank">amindfv@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Considering it doesnt give you any type safety, why not just write:<br>
<br>
foo (red :: Double) (green :: Double) (blue :: Double) = undefined<br>
<br>
Tom<br>
<br>
<br>
El Jan 21, 2015, a las 10:32, Niklas Haas <<a href="mailto:haskell@nand.wakku.to">haskell@nand.wakku.to</a>> escribió:<br>
<div class="HOEnZb"><div class="h5"><br>
>> Now we're definitely getting somewhere! I'm not to thrilled about the use<br>
>> of string literals though. How about this?<br>
>><br>
>> {-# LANGUAGE TypeOperators, DataKinds, RankNTypes #-}<br>
>> type (l ∷ t) = t<br>
>><br>
>> foo :: forall red green blue. (red ∷ Double) -> (green ∷ Double) -> (blue ∷<br>
>> Double) -> IO ()<br>
>><br>
>> We just need to patch hlint to make this the suggested style.<br>
>><br>
>> - jeremy<br>
><br>
> In fact, why even bother with the explicit forall? Default behavior is<br>
> to universally quantify unused variable names, after all.<br>
><br>
> {-# LANGUAGE TypeOperators #-}<br>
><br>
> type (l ∷ t) = t<br>
><br>
> foo :: (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()<br>
><br>
> At this point, I think this is a syntax form we can surely all agree upon.<br>
> _______________________________________________<br>
> Haskell-Cafe mailing list<br>
> <a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
> <a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</div></div></blockquote></div><br></div>