[Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Cetin Sert
Hi ^_^, Let's say we have the following data type and functions: data Tab a = (:↺:) | a :↓: Tab a | Tab a :↙↘: (Tab a,Tab a) deriving (Eq, Show, Read) map f (:↺:) = (:↺:) map f (a :↓: t) = f a :↓: map f t map f (h :↙↘: (l,r)) = map f h

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Miguel Mitrofanov
Well, it's certainly not possible for filter, at least, not without additional hints to the compiler. For example, consider this type: data Weird a = A | B a (Weird a) (Weird a) filter p A = A filter p (B x w1 w2) | p x = B x (filter p w1) (filter p w2) | otherwise =

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Thomas Davie
Even deriving an instance of Functor seems rather implausable, what should it do for data Wierd a b = Nil | A a (Wierd a b) | B b (Wierd a b) Should fmap's function argument operate on 'a's, 'b's, or both? Bob On 5 Jun 2008, at 10:28, Miguel Mitrofanov wrote: Well, it's certainly not

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Janis Voigtlaender
Thomas Davie wrote: Even deriving an instance of Functor seems rather implausable, what should it do for data Wierd a b = Nil | A a (Wierd a b) | B b (Wierd a b) Should fmap's function argument operate on 'a's, 'b's, or both? But for many datatypes it is quite natural. Just google for

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Miguel Mitrofanov
It can be even worse: data X a b = X (X b a - b) Here (X a) is certainly a functor, but the implementation must also act on a contravariantly: mapX :: (a - a') - X a' b - X a b mapX f (X h) = X $ h . fmap f instance Functor (X a) where fmap f (X h) = X $ f . h . mapX f On 5 Jun 2008, at

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Edsko de Vries
On Thu, Jun 05, 2008 at 10:39:16AM +0200, Thomas Davie wrote: Even deriving an instance of Functor seems rather implausable, what should it do for data Wierd a b = Nil | A a (Wierd a b) | B b (Wierd a b) Should fmap's function argument operate on 'a's, 'b's, or both? Generic Haskell can

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Jonathan Cast
On 5 Jun 2008, at 1:39 AM, Thomas Davie wrote: Even deriving an instance of Functor seems rather implausable, what should it do for data Wierd a b = Nil | A a (Wierd a b) | B b (Wierd a b) Should fmap's function argument operate on 'a's, 'b's, or both? class Functor (f :: * - *) where ...

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Neil Mitchell
Hi PS Why isn't Functor derivable? Derive can do it: http://www.cs.york.ac.uk/~ndm/derive I believe that Twan (the author of Functor deriving in Derive) is trying to get this suggested for Haskell' as a proper deriving. As for the original question, Uniplate will certainly do map, and will

Re: [Haskell-cafe] automatically deriving Map and Filter on datatypes etc.

2008-06-05 Thread Conor McBride
Hi Statutory mathematics warning: lots. On 5 Jun 2008, at 15:40, Jonathan Cast wrote: On 5 Jun 2008, at 1:39 AM, Thomas Davie wrote: Even deriving an instance of Functor seems rather implausable, what should it do for data Wierd a b = Nil | A a (Wierd a b) | B b (Wierd a b) Should