Superclass defaults

Aleksey Khudyakov alexey.skladnoy at gmail.com
Mon Aug 29 11:11:19 CEST 2011


> "Option 3 avoids that problem but risks perplexity: if I make use of
> some cool package which introduces some Foo :: * -> *, I might notice
> that Foo is a monad and add a Monad Foo instance in my own code,
> expecting the Applicative Foo instance to be generated in concert; to
> my horror, I find my code has subtle bugs because the package
> introduced a different, non-monadic, Applicative Foo instance which
> I'm accidentally using instead."
>
> talks about "subtle bugs". Could you give an example of such a bug?
>
> I would expect that the non-monadic Applicative Foo instance is always
>  somehow "compatible" with the monadic one. However I don't have a
> clear definition of "compatible" yet...
>
I think it's something like that. Module Foo defines list and make
ZipList-like Applicative instance. Would you add standard list monad
you have a bug.

But if you add monad instance which is not compatible with existing
applicative you have bug whether you use extension or not.

module Foo where
data [a] = a : [a] | []

instance Functor [] where
  fmap = map
instamce Applicative [] where
  pure = repeat
  (<*>) = zipWith ($)

module Main where
instance Monad [] where
  return x = [x]
  (>>=) = concatMap



More information about the Glasgow-haskell-users mailing list