Re: [Haskell-cafe] Seeking advice on a style question

2006-12-30 Thread Steve Schafer
On Fri, 29 Dec 2006 18:39:04 +0100, you wrote:

Why not generate Haskell code from such a graph?

Well, that would indeed be a workable solution. But I don't have quite
the resources to design Yet Another Visual Programming Language.

And a textual representation of the graph would have exactly the same
kinds of problems that the textual Haskell has

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-29 Thread Tomasz Zielonka
On Tue, Dec 26, 2006 at 09:56:11PM -0500, Steve Schafer wrote:
 But that isn't quite the case. Each step consumes not only the results
 of the previous step, but also some combination of the results of
 prior steps and/or the original inputs. One way to look at this is a
 directed graph, a sort of branching pipeline; see
 http://www.dendroica.com/Scratch/process.png.

Why not generate Haskell code from such a graph?

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-29 Thread Conal Elliott

To get another perspective, let's eliminate some unnecessary naming and see
what linear pipelines emerge:

process item mediaKind mediaSize language =
 let (numberedQuestions,questionCategories) =
   numberQuestions pagemaster $
   stripUndisplayedQuestions mediaKind $
   appendEndQuestions item
 (loadPagemaster item mediaKind mediaSize) $
   coalesceParentedQuestions $
   validateQuestionContent $
   loadQuestions item
 (bands,sequenceLayouts) =
   buildLayout mediaKind language $
   coalesceNAQuestions $
   numberedQuestions
 in
flip combineRows sequenceLayouts $
paginate item mediaKind mediaSize pagemaster $
groupBands $
resolveCrossReferences $
bands

Warning: I haven't tried to type-check and may have made a clerical error.
Since questionCategories isn't used, use fst  eliminate another let.
Then, for my personal preference, and just to mix things up, switch to
where style:

process item mediaKind mediaSize language =
 flip combineRows sequenceLayouts $
 paginate item mediaKind mediaSize pagemaster $
 groupBands $
 resolveCrossReferences $
 bands
where
  (bands,sequenceLayouts) =
buildLayout mediaKind language $
coalesceNAQuestions $
fst $
numberQuestions pagemaster $
stripUndisplayedQuestions mediaKind $
appendEndQuestions item
  (loadPagemaster item mediaKind mediaSize) $
coalesceParentedQuestions $
validateQuestionContent $
loadQuestions item

Not quite a work of art yet, but the structure is getting clearer to me.




On 12/28/06, Steve Schafer [EMAIL PROTECTED] wrote:


On Tue, 26 Dec 2006 20:21:45 -0800, you wrote:

How would this example look if you named only multiply-used expressions?
I'd like to see it in a more conventional pointful style with nested
expressions.  I'm still wondering whether the awkwardness results from
your
writing style or is more inherent.  Showing the real variable names may
also
help also.

This is what it looks like for real:

 process :: Item - MediaKind - MediaSize - Language - SFO
 process item mediaKind mediaSize language =
   let pagemaster = loadPagemaster item mediaKind mediaSize;
   questions = stripUndisplayedQuestions mediaKind $
   appendEndQuestions item pagemaster $
   coalesceParentedQuestions $
   validateQuestionContent $
   loadQuestions item;
  (numberedQuestions,questionCategories) = numberQuestions pagemaster
questions;
  numberedQuestions' = coalesceNAQuestions numberedQuestions;
  (bands,sequenceLayouts) = buildLayout mediaKind language
numberedQuestions';
  bands' = resolveCrossReferences bands;
  groupedBands = groupBands bands';
  pages = paginate item mediaKind mediaSize pagemaster groupedBands;
  pages' = combineRows pages;
  sfo = pages' sequenceLayouts;
  in sfo

These are the function signatures:

 loadPagemaster :: Item - MediaKind - MediaSize - Pagemaster
 loadQuestions :: Item - [Question]
 validateQuestionContent :: [Question] - [Question]
 coalesceParentedQuestions :: [Question] - [Question]
 appendEndQuestions :: Item - Pagemaster - [Question] - [Question]
 stripUndisplayedQuestions :: MediaKind - [Question] - [Question]
 numberQuestions :: Pagemaster - [Question] -
([NumberedQuestion],[QuestionCategory])
 coalesceNAQuestions :: [NumberedQuestion] - [NumberedQuestion]
 buildLayout :: MediaKind - Language - [NumberedQuestion] -
([Band],[SequenceLayout])
 resolveCrossReferences :: [Band] - [Band]
 groupBands :: [Band] - [[Band]]
 paginate :: Item - MediaKind - MediaSize - Pagemaster - [[Band]] -
[Page]
 combineRows :: [Page] - [Page]
 createSFO :: [Page] - [SequenceLayout] - SFO

MediaKind, MediaSize and Language are simple enumerations; everything
else is a complex structure.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-29 Thread Greg Buchholz
Conal Elliott wrote:
 Warning: I haven't tried to type-check and may have made a clerical error.
 Since questionCategories isn't used, use fst  eliminate another let.
 Then, for my personal preference, and just to mix things up, switch to
 where style:
 
 process item mediaKind mediaSize language =
  flip combineRows sequenceLayouts $
  paginate item mediaKind mediaSize pagemaster $
  groupBands $
  resolveCrossReferences $
  bands
 where
   (bands,sequenceLayouts) =
 buildLayout mediaKind language $
 coalesceNAQuestions $
 fst $
 numberQuestions pagemaster $
 stripUndisplayedQuestions mediaKind $
 appendEndQuestions item
   (loadPagemaster item mediaKind mediaSize) $
 coalesceParentedQuestions $
 validateQuestionContent $
 loadQuestions item


   And just for the heck of it, trading parenthesis and layout for dollar
signs...


process item mediaKind mediaSize language =
 combineRows 
(paginate 
   item 
   mediaKind 
   mediaSize 
   pagemaster 
   (groupBands (resolveCrossReferences bands)))
sequenceLayouts 
where
 (bands,sequenceLayouts) =
   buildLayout 
 mediaKind 
 language 
 (coalesceNAQuestions 
   (fst (numberQuestions 
   pagemaster
   (stripUndisplayedQuestions 
  mediaKind 
  (appendEndQuestions 
 item
 (loadPagemaster item mediaKind mediaSize) 
 (coalesceParentedQuestions 
(validateQuestionContent (loadQuestions item

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-28 Thread Steve Schafer
On Tue, 26 Dec 2006 20:21:45 -0800, you wrote:

How would this example look if you named only multiply-used expressions?
I'd like to see it in a more conventional pointful style with nested
expressions.  I'm still wondering whether the awkwardness results from your
writing style or is more inherent.  Showing the real variable names may also
help also.

This is what it looks like for real:

 process :: Item - MediaKind - MediaSize - Language - SFO
 process item mediaKind mediaSize language =
   let pagemaster = loadPagemaster item mediaKind mediaSize;
   questions = stripUndisplayedQuestions mediaKind $
   appendEndQuestions item pagemaster $
   coalesceParentedQuestions $
   validateQuestionContent $
   loadQuestions item;
  (numberedQuestions,questionCategories) = numberQuestions pagemaster 
 questions;
  numberedQuestions' = coalesceNAQuestions numberedQuestions;
  (bands,sequenceLayouts) = buildLayout mediaKind language 
 numberedQuestions';
  bands' = resolveCrossReferences bands;
  groupedBands = groupBands bands';
  pages = paginate item mediaKind mediaSize pagemaster groupedBands;
  pages' = combineRows pages;
  sfo = pages' sequenceLayouts;
  in sfo

These are the function signatures:

 loadPagemaster :: Item - MediaKind - MediaSize - Pagemaster
 loadQuestions :: Item - [Question]
 validateQuestionContent :: [Question] - [Question]
 coalesceParentedQuestions :: [Question] - [Question]
 appendEndQuestions :: Item - Pagemaster - [Question] - [Question]
 stripUndisplayedQuestions :: MediaKind - [Question] - [Question]
 numberQuestions :: Pagemaster - [Question] - 
 ([NumberedQuestion],[QuestionCategory])
 coalesceNAQuestions :: [NumberedQuestion] - [NumberedQuestion]
 buildLayout :: MediaKind - Language - [NumberedQuestion] - 
 ([Band],[SequenceLayout])
 resolveCrossReferences :: [Band] - [Band]
 groupBands :: [Band] - [[Band]]
 paginate :: Item - MediaKind - MediaSize - Pagemaster - [[Band]] - [Page]
 combineRows :: [Page] - [Page]
 createSFO :: [Page] - [SequenceLayout] - SFO

MediaKind, MediaSize and Language are simple enumerations; everything
else is a complex structure.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-27 Thread Brian Hulley

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


Disclaimer: just re-written by hand so needs double-checking before use:

   process x1 x2 x3 x4 =
   let
   y01 = f01 x1 x2 x3
   (y07, y08) = f07 y01 (f06 x2 (f05 x1 y01 (f04 (f03 y02
   (y10, y11) = f09 x2 x4 (f08 y07) y08
   in
   f14 (f13 (f12 x1 x2 x3 y01 (f11 (f10 y10 y11

You can also make it look more like the diagram by using more indentation 
eg:


   process x1 x2 x3 x4 =
   let
   y01 =
   f01
   x1
   x2
   x3
   (y07, y08) =
   f07
   y01
   (f06
   x2
   (f05
   x1
   y01
   (f04
   (f03
   y02
   ...

Best regards, Brian.
--
http://www.metamilk.com 


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-26 Thread Steve Schafer
On Mon, 25 Dec 2006 09:52:47 -0800, you wrote:

To my eye, your example code below looks less like an imperative
program than like an intermediate form that a compiler would generate
from an expression built up from nested function applications and a
few lets.

That's very true, but the same could be said for many other examples
of the use of the State monad (and Reader and Writer as well). They
frequently don't do anything that couldn't be done purely
functionally.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-26 Thread Conal Elliott

I like monadic reformulations when they remove repetitious patterns from
code, such as reading/updating a single threaded state.  I'm not yet seeing
such a pattern in your case.  As you mentioned:

The shape of the

state isn't constant throughout the process. At any given step, new
information may be added to the state, and old information may be thrown
away, if there is no further need for it.



So I'm still doubtful that a monadic approach is going to simplify your
code.   Would you give a real example of some code you'd like to make more
manageable?  If you have real examples of State, Reader, and/or Writer
monads that strike you as similar to your example, please share that also.

Cheers, - Conal

On 12/26/06, Steve Schafer [EMAIL PROTECTED] wrote:


On Mon, 25 Dec 2006 09:52:47 -0800, you wrote:

To my eye, your example code below looks less like an imperative
program than like an intermediate form that a compiler would generate
from an expression built up from nested function applications and a
few lets.

That's very true, but the same could be said for many other examples
of the use of the State monad (and Reader and Writer as well). They
frequently don't do anything that couldn't be done purely
functionally.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-26 Thread Chris Kuklewicz
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-26 Thread Steve Schafer
On Tue, 26 Dec 2006 10:28:22 -0800, you wrote:

So I'm still doubtful that a monadic approach is going to simplify your
code.   Would you give a real example of some code you'd like to make more
manageable?  If you have real examples of State, Reader, and/or Writer
monads that strike you as similar to your example, please share that also.

I didn't mean to imply that a monadic approach would simplify the
code, only that it was _conceivable_ to me that such a thing might be
true. The code I showed _is_ a real example; I just changed the names
of everything to focus on the structure. And the reason for focusing
on the structure is that I'm looking for a _general_ principle to
apply to make the code more manageable; the process that I showed is
just one of many similarly-structured processes that are involved in
the actual application.

I think the essence of my question might have gotten lost, so I'll try
a slightly different approach: I have a process that consists of a
series of steps. If each step consumed _only_ the results of the
previous step, I could of course describe the process like this:

 process = f14 . f13 . f12 

But that isn't quite the case. Each step consumes not only the results
of the previous step, but also some combination of the results of
prior steps and/or the original inputs. One way to look at this is a
directed graph, a sort of branching pipeline; see
http://www.dendroica.com/Scratch/process.png.

Now, the advantages of this kind of visual representation of the
process are that it makes it perfectly clear what each step consumes
and how the flow of the process occurs. Another big advantage (to
me, anyway) is that the graphical representation is entirely
point-free; the picture isn't cluttered with intermediate values whose
only purpose is to hold onto things I need later, but not right now.

So here's the (restated) question: Is there some way to represent the
process in good ol' text form that preserves the elegance and
conciseness of the graphical representation?

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-26 Thread Steve Schafer
On Tue, 26 Dec 2006 18:29:43 +, you wrote:

 -- 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)

This is like what I was looking for, although it does still require at
least one temporary variable. I'll have to think about it a bit to see
how applicable it is in general. Thanks.

The tuples do make things a bit messy; they could easily be removed at
the cost of introducing a few more steps:

 (y07,y08) = f07 y01 y06;

would become

 y'  = f07 y01 y06;
 y07 = f07a y';
 y08 = f07b y';

where f07a = fst and f07b = snd.

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-26 Thread Conal Elliott

Steve,

How would this example look if you named only multiply-used expressions?
I'd like to see it in a more conventional pointful style with nested
expressions.  I'm still wondering whether the awkwardness results from your
writing style or is more inherent.  Showing the real variable names may also
help also.

You said

Each step consumes not only the results of the previous step, but also some

combination of the results of prior steps and/or the original inputs.



This description fits expression evaluation in general.  Maybe you don't
like expression-oriented programming?

 - Conal

On 12/26/06, Steve Schafer [EMAIL PROTECTED] wrote:


On Tue, 26 Dec 2006 10:28:22 -0800, you wrote:

So I'm still doubtful that a monadic approach is going to simplify your
code.   Would you give a real example of some code you'd like to make
more
manageable?  If you have real examples of State, Reader, and/or Writer
monads that strike you as similar to your example, please share that
also.

I didn't mean to imply that a monadic approach would simplify the
code, only that it was _conceivable_ to me that such a thing might be
true. The code I showed _is_ a real example; I just changed the names
of everything to focus on the structure. And the reason for focusing
on the structure is that I'm looking for a _general_ principle to
apply to make the code more manageable; the process that I showed is
just one of many similarly-structured processes that are involved in
the actual application.

I think the essence of my question might have gotten lost, so I'll try
a slightly different approach: I have a process that consists of a
series of steps. If each step consumed _only_ the results of the
previous step, I could of course describe the process like this:

process = f14 . f13 . f12 

But that isn't quite the case. Each step consumes not only the results
of the previous step, but also some combination of the results of
prior steps and/or the original inputs. One way to look at this is a
directed graph, a sort of branching pipeline; see
http://www.dendroica.com/Scratch/process.png.

Now, the advantages of this kind of visual representation of the
process are that it makes it perfectly clear what each step consumes
and how the flow of the process occurs. Another big advantage (to
me, anyway) is that the graphical representation is entirely
point-free; the picture isn't cluttered with intermediate values whose
only purpose is to hold onto things I need later, but not right now.

So here's the (restated) question: Is there some way to represent the
process in good ol' text form that preserves the elegance and
conciseness of the graphical representation?

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-26 Thread Conal Elliott

All of this code, including the original, looks like compiler output to me.
If we're talking about easy to understand reformulations, how about we start
with some compiler input instead?

On 12/26/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:


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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-25 Thread Conal Elliott

I'm not sure this example really has anything to do with state.  Is there
anything about your domain  examples that differs from standard functional
programming (or math)?  To my eye, your example code below looks less like
an imperative program than like an intermediate form that a compiler would
generate from an expression built up from nested function applications and a
few lets.

Cheers, - Conal

On 12/24/06, Steve Schafer [EMAIL PROTECTED] 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

As you can see, the process is somewhat imperative in overall
appearance, with each intermediate function f01..f14 accepting some
combination of the original input values and/or intermediate values and
returning a new value (or, in some cases, a tuple of values).

Obviously, not all of the steps need to be broken out this way. We can,
for example, skip the second and third steps and directly write:

y04 = f04 $ f03 $ f02 x1;

Laying it out this way has a couple of advantages. It makes the steps in
the process transparently clear, and if I discover at some point that I
need to make a change (e.g., a new requirement causes f13 to need access
to x2), it's perfectly obvious where to make the modifications.

Nevertheless, it also looks like something that would be amenable to
processing with a State monad, except for one thing: The shape of the
state isn't constant throughout the process. At any given step, new
information may be added to the state, and old information may be thrown
away, if there is no further need for it. In principle, it could be
managed with a bunch of nested StateT monads, but my attempts to do so
seem to get so caught up in the bookkeeping that I lose the advantages
mentioned above.

Alternatively, I can wrap all of the state up into a single universal
structure that holds everything I will ever need at every step, but
doing so seems to me to fly in the face of strong typing; at the early
stages of processing, the structure will have holes in it that don't
contain useful values and shouldn't be accessed.

So here's the question: Is there a reasonable way to express this kind
of process (where I suppose that reasonable means in keeping with
Haskell-nature) that preserves the advantages mentioned above, but
avoids having to explicitly pass all of the various bits of state
around? The (unattainable?) ideal would be something that looks like
this:

process = f14 . f13 . ... . f01

or

process = f01 = f02 = ... = f14

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Seeking advice on a style question

2006-12-24 Thread Steve Schafer
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

As you can see, the process is somewhat imperative in overall
appearance, with each intermediate function f01..f14 accepting some
combination of the original input values and/or intermediate values and
returning a new value (or, in some cases, a tuple of values).

Obviously, not all of the steps need to be broken out this way. We can,
for example, skip the second and third steps and directly write:

 y04 = f04 $ f03 $ f02 x1;

Laying it out this way has a couple of advantages. It makes the steps in
the process transparently clear, and if I discover at some point that I
need to make a change (e.g., a new requirement causes f13 to need access
to x2), it's perfectly obvious where to make the modifications.

Nevertheless, it also looks like something that would be amenable to
processing with a State monad, except for one thing: The shape of the
state isn't constant throughout the process. At any given step, new
information may be added to the state, and old information may be thrown
away, if there is no further need for it. In principle, it could be
managed with a bunch of nested StateT monads, but my attempts to do so
seem to get so caught up in the bookkeeping that I lose the advantages
mentioned above.

Alternatively, I can wrap all of the state up into a single universal
structure that holds everything I will ever need at every step, but
doing so seems to me to fly in the face of strong typing; at the early
stages of processing, the structure will have holes in it that don't
contain useful values and shouldn't be accessed.

So here's the question: Is there a reasonable way to express this kind
of process (where I suppose that reasonable means in keeping with
Haskell-nature) that preserves the advantages mentioned above, but
avoids having to explicitly pass all of the various bits of state
around? The (unattainable?) ideal would be something that looks like
this:

 process = f14 . f13 . ... . f01

or

 process = f01 = f02 = ... = f14

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-24 Thread jeff p

Hello,


Alternatively, I can wrap all of the state up into a single universal
structure that holds everything I will ever need at every step, but
doing so seems to me to fly in the face of strong typing; at the early
stages of processing, the structure will have holes in it that don't
contain useful values and shouldn't be accessed.


You might want to look at the following threads discussing how to make
variable-state monad like structures.

http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/17706

http://www.haskell.org/pipermail/haskell/2006-December/018917.html

-Jeff
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Seeking advice on a style question

2006-12-24 Thread Steve Schafer
On Sun, 24 Dec 2006 10:39:19 -0500, you wrote:

You might want to look at the following threads discussing how to make
variable-state monad like structures.

http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/17706

http://www.haskell.org/pipermail/haskell/2006-December/018917.html

Thanks. I should have realized that Oleg would have had something to say
about it. ;)

Steve Schafer
Fenestra Technologies Corp.
http://www.fenestra.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe