
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.

2010/7/15 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.
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. Cheers, Thu

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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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 -> a (d, b) (d, c) (str ++) :: [Char] -> [Char] second (str ++) :: (d, [Char]) -> (d, [Char]) All the caller can control here is what sort of "d" is passed through unchanged, not the fact that the resulting function expects a pair and returns a pair. -md

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 (->):
second :: Arrow a => a b c -> a (d, b) (d, c) (str ++) :: [Char] -> [Char] second (str ++) :: (d, [Char]) -> (d, [Char])
All the caller can control here is what sort of "d" is passed through unchanged, not the fact that the resulting function expects a pair and returns a pair.
BTW, I was only addressing whether making B an instance of Arrow would help somehow. Creating a second' function could indeed help, provided it had the right signature: second' :: (String -> String) -> B -> B second' f (B i s) = B i (f s) Then you can indeed write "g" like so: g :: String -> B -> B g = second' . (++) Also, I'm pretty sure it isn't possible to write an instance of Arrow for B in principle because the type constructor has the kind "*" and the Arrow class has functions whose types include "Arrow a => a b c", implying that instances of arrow have kind "* -> * -> *". In fact, GHC will tell you as much even without trying to give a body to "instance Arrow B": Kind mis-match Expected kind `* -> * -> *', but `B' has kind `*' In the instance declaration for `Arrow B' -md
participants (4)
-
Alexey Karakulov
-
Mike Dillon
-
Victor Gorokhov
-
Vo Minh Thu