[Haskell-cafe] Fwd: [Haskell-beginners] RankNTypes + ConstraintKinds to use Either as a "union"

Thiago Negri evohunz
Wed Oct 9 20:16:23 UTC 2013


(from thread:
http://www.haskell.org/pipermail/beginners/2013-October/012703.html)

Why type inference can't resolve this code?

> {-# LANGUAGE RankNTypes, ConstraintKinds #-}
>
> bar :: (Num a, Num b) => (forall c. Num c => c -> c) -> Either a b ->
Either a b
> bar f (Left a) = Left (f a)
> bar f (Right b) = Right (f b)
>
> bar' = bar (+ 2) -- This compiles ok
>
> foo :: (tc a, tc b) => (forall c. tc c => c -> c) -> Either a b -> Either
a b
> foo f (Left a) = Left (f a)
> foo f (Right b) = Right (f b)
>
> foo' = foo (+ 2) -- This doesn't compile because foo' does not typecheck
>
> -- Kim-Ee pointed out that this works:
> type F tc a b =  (tc a, tc b) => (forall c. tc c => c -> c) -> Either a b
-> Either a b
> foo' = (foo :: F Num a b) (+2)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131009/430d085e/attachment.htm>



More information about the Haskell-Cafe mailing list