Polyvariadic composition

Hello, I have accidentally written my version of polyvariadic composition combinator, `mcomp`. It differs from Oleg’s version ( http://okmij.org/ftp/Haskell/polyvariadic.html#polyvar-comp ) in three aspects: a) it is simpler, b) it works without enumerating basic cases (all existing types, in other words), and c) it needs more type extensions.
{-# LANGUAGE MultiParamTypeClasses , FunctionalDependencies , FlexibleInstances , UndecidableInstances , TypeFamilies , OverlappingInstances #-}
class Mcomp a ar b br | a br -> b where mcomp :: a -> (ar -> br) -> b
instance (a ~ ar, b ~ br) => Mcomp a ar b br where mcomp a f = f a
instance (Mcomp a ar b br) => Mcomp (x -> a) ar (x -> b) br where mcomp a f = \x -> mcomp (a x) f
My question is: why doesn’t it work when I replace instance (a ~ ar, b ~ br) => Mcomp a ar b br with instance Mcomp a a b b ? I thought that equal letters mean equal types…

Works here.
GHC 7.4.2
On Jul 30, 2012, at 11:32 PM, Artyom Kazak
Hello,
I have accidentally written my version of polyvariadic composition combinator, `mcomp`. It differs from Oleg’s version ( http://okmij.org/ftp/Haskell/polyvariadic.html#polyvar-comp ) in three aspects: a) it is simpler, b) it works without enumerating basic cases (all existing types, in other words), and c) it needs more type extensions.
{-# LANGUAGE MultiParamTypeClasses , FunctionalDependencies , FlexibleInstances , UndecidableInstances , TypeFamilies , OverlappingInstances #-}
class Mcomp a ar b br | a br -> b where mcomp :: a -> (ar -> br) -> b
instance (a ~ ar, b ~ br) => Mcomp a ar b br where mcomp a f = f a
instance (Mcomp a ar b br) => Mcomp (x -> a) ar (x -> b) br where mcomp a f = \x -> mcomp (a x) f
My question is: why doesn’t it work when I replace
instance (a ~ ar, b ~ br) => Mcomp a ar b br
with
instance Mcomp a a b b
? I thought that equal letters mean equal types…
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

My completely off-the-cuff guess is that
a a b b
isn't considered more or less specific than
(x -> a) ar (x -> b) br
since they both apply some constraint on the types. For example, it's not
immediately clear that the first instance can't be used for (x -> a) (x ->
a) (x -> b) (x -> b)
Whereas when you say
a ar b br
the type
(x -> a) ar (x -> b) br
is strictly more specific, so the overlapping instance can be chosen.
Remember instance selection is done entirely via the instance head, so
instance X a a
is not the same as
instance (a ~ b) => X a b
The first case supplies an instance for any two equal types, and the second
case supplies an instance for *any two types*, then throws an error if the
compiler can't prove that the two types are equal.
For example, without overlapping instances, you can write
class X a b where foo :: a -> b
instance X a a where foo = id
instance X Int Bool where foo = (== 0)
But if instead you specify
instance (a ~ b) => X a b where foo = id
you can't specify the Int Bool instance without overlap.
-- ryan
On Mon, Jul 30, 2012 at 12:32 PM, Artyom Kazak
Hello,
I have accidentally written my version of polyvariadic composition combinator, `mcomp`. It differs from Oleg’s version ( http://okmij.org/ftp/Haskell/**polyvariadic.html#polyvar-comphttp://okmij.org/ftp/Haskell/polyvariadic.html#polyvar-comp) in three aspects: a) it is simpler, b) it works without enumerating basic cases (all existing types, in other words), and c) it needs more type extensions.
{-# LANGUAGE
MultiParamTypeClasses , FunctionalDependencies , FlexibleInstances , UndecidableInstances , TypeFamilies , OverlappingInstances #-}
class Mcomp a ar b br | a br -> b where mcomp :: a -> (ar -> br) -> b
instance (a ~ ar, b ~ br) => Mcomp a ar b br where mcomp a f = f a
instance (Mcomp a ar b br) => Mcomp (x -> a) ar (x -> b) br where mcomp a f = \x -> mcomp (a x) f
My question is: why doesn’t it work when I replace
instance (a ~ ar, b ~ br) => Mcomp a ar b br
with
instance Mcomp a a b b
? I thought that equal letters mean equal types…
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Artyom Kazak
-
MigMit
-
Ryan Ingram