
Hello Chris, Many thanks for your input. arr _ = error ... Doesn't work, because it will not be possible to use arrow notation. Today I learned that the function type is abstract and so has no constructor I can pattern match against. I don't know, why. Does something break, if Haskell would offer such a constructor? Since I want to use the arrow notation, I had a close look at the following description, taken from http://www.haskell.org/ghc/docs/latest/html/users_guide/arrow-notation.h tml And revised my problem again (sorry): ------------------------------------------------------------------------ ---- 7.7.1. do-notation for commands Another form of command is a form of do-notation. For example, you can write proc x -> do y <- f -< x+1 g -< 2*y let z = x+y t <- h -< x*z returnA -< t+z You can read this much like ordinary do-notation, but with commands in place of monadic expressions. The first line sends the value of x+1 as an input to the arrow f, and matches its output against y. In the next line, the output is discarded. The arrow returnA is defined in the Control.Arrow module as arr id. The above example is treated as an abbreviation for arr (\ x -> (x, x)) >>> first (arr (\ x -> x+1) >>> f) >>> arr (\ (y, x) -> (y, (x, y))) >>> first (arr (\ y -> 2*y) >>> g) >>> arr snd >>> arr (\ (x, y) -> let z = x+y in ((x, z), z)) >>> first (arr (\ (x, z) -> x*z) >>> h) >>> arr (\ (t, z) -> t+z) >>> returnA Note that variables not used later in the composition are projected out. After simplification using rewrite rules (see Section 7.10, "Rewrite rules ") defined in the Control.Arrow module, this reduces to arr (\ x -> (x+1, x)) >>> first f >>> arr (\ (y, x) -> (2*y, (x, y))) >>> first g >>> arr (\ (_, (x, y)) -> let z = x+y in (x*z, z)) >>> first h >>> arr (\ (t, z) -> t+z) ------------------------------------------------------------------------ --- The arrow I want to create is one to track down dependencies. This doesn't seem to work with arrow notation, because in the example above g -< 2*y isn't used in the following statements but is bound to the next arrow: first g >>> arr (\ (****here==> _ ***, (x, y)) -> let z = x+y in (x*z, z))
So, when tracking down dependencies, the result will depend on g. But it does not! In my eyes, it would be better that the whole proc x delivers an arrow of type a b (c,d) instead of a b c with d being piggy backed from g. So I can see on the wrong type of proc x that I missed out connecting something to some other bits. Another solution would be just to skip g. Can somebody tell me, why the arrow notation is as it is? Greetings Sven -----Original Message----- From: Chris Kuklewicz [mailto:haskell@list.mightyreason.com] Sent: Samstag, 28. Januar 2006 18:01 To: Sven Biedermann Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] arr f Sven Biedermann wrote:
Hello Henrik & Ross,
Man thanks for your input. I have realised that I should have explained my problem better.
So, I try...
I want to create a datatype like this:
data D a b = DepVoid (a->b) | -- a = () DepSingle (a->b) | -- a = a simple ones DepPair (a->b) | -- a = (c,d) DepTriple (a->b) | -- a = (c,d,e) ... DepFun (a->b) -- a = (c->d) ...
You have a serious typing problem in Haskell with that. Every constructor could be replaced with DepSingle.
Its easy to construct them:
mkArrVoid :: (() -> c) -> D () c mkArrVoid f = DepVoid f
mkArrPair :: ((a,b) -> c) -> D (a,b) c mkArrPair f = DepPair f
...
Now I want to make D an instance of Arrow:
instance Arrow (D) where -- my problems stems from arr f = ???
I have no clue to glue the mkArr* functions together to reach what I want: a different Dep* for different functions f. What can I pattern match, here? What can I do else?
This is not easily fixable, since (arr = DepSingle ) is always a valid choice for the compiler to make. Thus typeclass solutions badly overlap.
Greetings
Sven
I can come closer with a GADT. The serious typing problem is still there. So I made arr and pure into error messages. {-# OPTIONS -farrows -fglasgow-exts #-} import Control.Arrow -- GADT style data D x y where DepVoid :: (()->b) -> D () b DepSingle :: (a->b) -> D a b DepPair :: ((a1,a2)->b) -> D (a1,a2) b DepFun :: ( (a1->a2) -> b ) -> D (a1->a2) b -- And these are the constructors, so we could skip them mkArrVoid = DepVoid mkArrSingle = DepSingle mkArrPair = DepPair mkArrFun = DepFun -- The destructor is more annoying (template haskell would help) -- http://haskell.org/hawiki/GADT_20with_20record_20syntax might make this easier getF :: D x y -> (x -> y) getF (DepVoid f) = f getF (DepSingle f) = f getF (DepPair f) = f getF (DepFun f) = f -- This is useful for diagnosing which constructor you have, for testing getF' :: D x y -> Int getF' (DepVoid f) = 1 getF' (DepSingle f) = 2 getF' (DepPair f) = 3 getF' (DepFun f) = 4 instance Arrow D where arr _ = error "Use Dep* instead" -- or arr = DepSingle pure _ = error "Use Dep* instead" -- or pure = DepSingle first arrD = let toPair :: (x->y) -> D (x,d) (y,d) toPair f = DepPair (\(b,d) -> (f b,d) ) in toPair (getF arrD) -- (template haskell would help with defining >>>) (>>>) arr1 arr2 = let comp f = (getF arr2) . f in case arr1 of DepVoid f -> DepVoid (comp f) DepSingle f -> DepSingle (comp f) DepPair f -> DepPair (comp f) DepFun f -> DepFun (comp f) -- This >>> loses the constructor info of arr1 but is simpler (>>>>) arr1 arr2 = DepSingle ( (getF arr2) . (getF arr1) )