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

Reply via email to