[Haskell-cafe] point-free ADT pattern matching ?

2010-07-15 Thread Alexey Karakulov
I wonder if pattern matching could be less verbose. Maybe this sounds weird, but here is example of what I mean: type A = (Int, String) f :: String - A - A f s (i,s') = (i, s ++ s') data B = B Int String deriving Show g :: String - B - B g s (B i s') = B i $ s ++ s' Types A/B and

Re: [Haskell-cafe] point-free ADT pattern matching ?

2010-07-15 Thread Vo Minh Thu
2010/7/15 Alexey Karakulov ankaraku...@gmail.com: I wonder if pattern matching could be less verbose. Maybe this sounds weird, but here is example of what I mean: type A = (Int, String) f :: String - A - A f s (i,s') = (i, s ++ s') data B = B Int String deriving Show g :: String - B - B

Re: [Haskell-cafe] point-free ADT pattern matching ?

2010-07-15 Thread Victor Gorokhov
Generics can help. But they are much slower than pattern matching. {-# LANGUAGE DeriveDataTypeable #-} import Data.Generics import Control.Monad.State type A = ( Int, String ) data B = B Int String deriving ( Show, Typeable, Data ) f :: ( Typeable a, Data d ) = [ a ] - d - d f s = changeField

Re: [Haskell-cafe] point-free ADT pattern matching ?

2010-07-15 Thread Mike Dillon
begin Vo Minh Thu quotation: I guess it is short because you make use of second... so you can define second' for your B data type, or make B an instance of Arrow. I don't think that's the case. The code for f is making use of the Arrow instance for (-): second :: Arrow a = a b c -

Re: [Haskell-cafe] point-free ADT pattern matching ?

2010-07-15 Thread Mike Dillon
begin Mike Dillon quotation: begin Vo Minh Thu quotation: I guess it is short because you make use of second... so you can define second' for your B data type, or make B an instance of Arrow. I don't think that's the case. The code for f is making use of the Arrow instance for (-):