[Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen

Hello café,

I've never written an Alternative instance for a newtype yet that 
doesn't look like this:



instance Alternative T where
  empty = T empty
  T x | T y = T (x | y)


Why does newtype deriving not work for Alternative? (It works fine for 
Monoid.)


Thanks,

Martijn.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Ryan Ingram
Works for me on GHC6.10.4:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module NewtypeDerive where
import Control.Applicative

newtype Foo f a = Foo (f a) deriving (Functor, Applicative, Alternative)
newtype Bar a = Bar [a] deriving (Functor, Applicative, Alternative)

  -- ryan

On Wed, Oct 14, 2009 at 2:16 PM, Martijn van Steenbergen 
mart...@van.steenbergen.nl wrote:

 Hello café,

 I've never written an Alternative instance for a newtype yet that doesn't
 look like this:

  instance Alternative T where
  empty = T empty
  T x | T y = T (x | y)


 Why does newtype deriving not work for Alternative? (It works fine for
 Monoid.)

 Thanks,

 Martijn.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen

You guys are right. I was being silly. Thanks. :-)

Ryan Ingram wrote:

Works for me on GHC6.10.4:


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Martijn van Steenbergen

It doesn't work for this one:


newtype Split a = Split { runSplit :: [Either a (Char, Split a) ]}


But my handwritten instance remains identical.

Groetjes,

Martijn.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Jake McArthur

Martijn van Steenbergen wrote:

It doesn't work for this one:


newtype Split a = Split { runSplit :: [Either a (Char, Split a) ]}


But my handwritten instance remains identical.


The instance has the form [], not the form [Either _ (Char, Split _)]. 
Since they don't match exactly, it won't give you an instance 
automagically. It could have been the case that you intended some other 
instance besides []'s. All generalized newtype deriving does is derive 
instances for newtypes that wrap exactly what the instance is defined over.


- Jake
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe