[Haskell-cafe] Seeking advice on a style question

Chris Kuklewicz haskell at list.mightyreason.com
Tue Dec 26 13:29:43 EST 2006


I know people just had a discussion about not answering simple questions with 
unsafe! or arrows! or OOHaskell! or oleg!  But here is an answer that uses 
Control.Arrow just for the function combinators:

Steve Schafer wrote:
> In my text/graphics formatting work, I find myself doing a lot of
> "pipeline" processing, where a data structure will undergo a number of
> step-by-step transformations from input to output. For example, I have a
> function that looks like this (the names have been changed to protect
> the innocent--and to focus on the structure):
> 
>  process :: a -> b -> c -> d -> e
>  process x1 x2 x3 x4 = 
>    let y01       = f01 x1 x2 x3;
>        y02       = f02 x1;
>        y03       = f03 y02;
>        y04       = f04 y03;
>        y05       = f05 x1 y01 y04;
>        y06       = f06 x2 y05;
>        (y07,y08) = f07 y01 y06;
>        y09       = f08 y07;
>        (y10,y11) = f09 x2 x4 y09 y08;
>        y12       = f10 y10;
>        y13       = f11 y12;
>        y14       = f12 x1 x2 x3 y01 y13;
>        y15       = f13 y14;
>        y16       = f14 y15 y11
>        in y16

>  [snip]

> The (unattainable?) ideal would be something that looks like
> this:
> 
>  process = f14 . f13 . ... . f01
> 
> or
> 
>  process = f01 >>= f02 >>= ... >>= f14
> 

You want to reduce the number of intermediate names that have to be created.

Control.Arrow allows for complicated "wiring diagrams" which the Identity arrow 
reduces to complicated function composition.

The above can be rewritten many ways.  This "process" happens (by a bit of luck) 
to be easy to rewrite fairly simply.  With some dummy function of the right shape:

> module Main where
> 
> import Control.Arrow
> 
> f01 x1 x2 x3 = [x1,x2,x3]
> f02=id
> f03=id
> f04=id
> f05 _ _ = id
> f06 _=id
> f07 y01 = id &&& (:y01)
> f08=id
> f09 _ x4 a b = (a+x4,b) 
> f10=id
> f11=id
> f12 _ _ _ y01 = (:y01)
> f13=id
> f14 = (,)
> 
> -- process :: a -> b -> c -> d -> e
> process x1 x2 x3 x4 = 
>    let y01       = f01 x1 x2 x3
>    in ($ x1) (f02 >>> f03 >>> f04 >>> f05 x1 y01 >>> f06 x2 >>> f07 y01
>                   >>> first f08 >>> uncurry (f09 x2 x4)
>                   >>> first (f10 >>> f11 >>> f12 x1 x2 x3 y01 >>> f13)
>                   >>> uncurry f14)
> 
> main = return $ process 1 2 3 4
> -- returns ([5,1,2,3],[1,1,2,3]) which is the same as your process with
> -- these dummy function definitions

The fact that some of them return a 2-tuple has been handled by using "first" to 
act on only on the fst item, while the snd is passed along until an "uncurry 
fxx" consumes two at once.

Other pipelines may be trickier, for which GHC's syntactic sugar "proc" would 
help.  Here it does not seem to (this requires knowing the syntactic sugar, see 
GHC's user manual):

> process'' = curry4 processA
>
> uncurry3 f = (\(a,b,c) -> f a b c)
> curry4 f = (\ a b c d -> f (a,b,c,d))
> 
> processA = proc (x1,x2,x3,x4) -> do y01 <- uncurry3 f01 -< (x1,x2,x3)
>                                     (f02 >>> f03 >>> f04 >>> f05 x1 y01 >>> f06 x2 >>> f07 y01
>                                          >>> first f08 >>> uncurry (f09 x2 x4)
>                                          >>> first (f10 >>> f11 >>> f12 x1 x2 x3 y01 >>> f13)
>                                          >>> uncurry f14) -<< x1


More information about the Haskell-Cafe mailing list