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

Victor Gorokhov me at rkit.pp.ru
Thu Jul 15 20:43:56 EDT 2010


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 2 ( s ++ )

changeField :: ( Typeable a, Num n, Data d ) => n -> ( a -> a ) -> d -> d
changeField num fun input = evalState ( gmapM f input ) 1
  where
    f a = do
    x <- get
    put $ x + 1
    mkM ( \ a -> return $ if num == x then fun a else a ) a

-- 
*Main> f "asd" $ B 123 "dsa"
B 123 "asddsa"
*Main> f "asd" ( 123, "dsa" )
(123,"asddsa")


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 functions f/g are quite similar: (x :: A) or (x :: B) 
> means that x contains some integer and string values, and f/g 
> functions take some string and prepend it to the string part of x. The 
> code for f and g has the same level of verbosity, but -- ta-dah! -- we 
> can use arrows and define f in a highly laconic manner:
>
> > import Control.Arrow
> > f' :: String -> A -> A
> > f' = second . (++)
>
> So my queastion is how I could define (g' :: String -> B -> B) in the 
> same way.
> ------------------------------------------------------------------------
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>   




More information about the Haskell-Cafe mailing list