Re: [Haskell-cafe] constant functions

2006-12-29 Thread ajb
G'day all.

Quoting Matthew Brecknell [EMAIL PROTECTED]:

 Yes. Function application (-) is right-associative in a type
 expression. What about a value expression?

 f a b === (f a) b

 Looks like an inconsistency? Not if you think about it. :-)

And if you don't want to think about it, this should make everything
clear:

f :: A - (B - (C - D))
f a :: B - (C - D)
(f a) b :: C - D
((f a) b) c :: d

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


Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Donald Bruce Stewart
pphetra:
 
 I would like to write a program that can do something like this.
  
 ;; lisp syntax
 * (my-flatten '(1 (2 (3 4) 5)))
 (1 2 3 4 5)
 
 I end up like this.
 
 data Store a = E a | S [Store a]
  deriving (Show)
 
 flat :: [Store a] - [a]
 flat [] = []
 flat ((E x):xs) = [x] ++ flat xs
 flat ((S x):xs) = flat x ++ flat xs
 
 so
 *Main flat [E 1, S[E 2, S[E 3, E 4], E 5]]
 [1,2,3,4,5]
 
 Compare to a Lisp solution, It 's not looking good.
 Any suggestion.



Since this data type:

 data Store a = E a | S [Store a]
  deriving (Show)

Is isomorphic to the normal Data.Tree type anyway, so we'll use that:

 data Tree a = N a [Tree a]
   deriving Show

to define a new tree:

 tree = N 1 [N 2 [N 3 [], N 4 []], N 5 []]

Now we can flatten by folding:

 flatten t = go t []
   where go (N x ts) xs = x : foldr go xs ts

So we can flatten our test tree:

 list = flatten tree

Even run it:

 main = print (flatten tree)

Or in GHCi:

*Main flatten tree
[1,2,3,4,5]

Based on Data.Tree in the base library.

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


Re: [Haskell-cafe] constant functions

2006-12-29 Thread Tomasz Zielonka
On Fri, Dec 29, 2006 at 03:36:45AM -0500, [EMAIL PROTECTED] wrote:
 And if you don't want to think about it, this should make everything
 clear:
 
 f :: A - (B - (C - D))
 f a :: B - (C - D)
 (f a) b :: C - D
 ((f a) b) c :: d

Nice illustration. It's as if the letters jumped over the colons from
the type world to the value world. Now if you can't sleep, you can count
jumping types instead of sheep ;-)

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


Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Tomasz Zielonka
On Fri, Dec 29, 2006 at 07:58:54PM +1100, Donald Bruce Stewart wrote:
 Since this data type:
 
  data Store a = E a | S [Store a]
   deriving (Show)
 
 Is isomorphic to the normal Data.Tree type anyway, so we'll use that:

It's a bit different - store has labels only in its leaves.

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


Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread Neil Mitchell

Hi


  f1 :: [Int] - [[Int]]
   f1 [] = []
  f1 (a:as) = [a] : f1 as


f1 is simply a map


  f3 la lb = let a = head la
  b = head lb
 in if sum a = sum b then
a : f3 (tail la) lb
 else
b : f3 la (tail lb)


Why not use pattern matching to split up la and lb, rather than head/tail?

I would have thought the whole function could be written as a nice
foldr merge, where merge :: [Int] - [Int] - [Int]. Thats only a
guess at the top of my head though, not worked out properly.

Is this homework? If so its useful to state when you post the question :)

Thanks

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


Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Stefan O'Rear
On Thu, Dec 28, 2006 at 11:56:58PM -0800, pphetra wrote:
 data Store a = E a | S [Store a]
  deriving (Show)
 
 flat :: [Store a] - [a]
 flat [] = []
 flat ((E x):xs) = [x] ++ flat xs
 flat ((S x):xs) = flat x ++ flat xs
 
 so
 *Main flat [E 1, S[E 2, S[E 3, E 4], E 5]]
 [1,2,3,4,5]

Since this problem is fundimentally tied to Lisp's dynamic
typing, it is no suprise it can be done very easily using
Haskell's support for dynamic typing:

 import Data.Typeable

 data D = forall a. Typeable a = D a  deriving(Typeable)

 flat :: D - [D]
 flat (D x) = maybe [D x] (= flat) (cast x)

To use: map (\ (D x) - cast x) flat (D [D 1, D [D 2, D 3], D 4]) :: [Maybe 
Integer]

The 'D' defines an existantial type, which can hold a value
of any type subject to the Typeable constraint.

Typeable allows the typesafe cast function, which returns
Nothing if the types were different.

maybe and = are prelude functions used to make the definition
shorter; without them:

 flat (D x) = case (cast x) of Just xs - concatMap flat xs
   Nothing - [D x]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Coverage Condition?

2006-12-29 Thread Simon Peyton-Jones
GHC is simply being more conservative.  GHC 6.4.2 was straying too close to 
non-termination, as our paper shows:
http://research.microsoft.com/~simonpj/papers/fd-chr

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:haskell-cafe-
| [EMAIL PROTECTED] On Behalf Of [EMAIL PROTECTED]
| Sent: 27 December 2006 00:02
| To: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] Coverage Condition?
|
| Hi folks,
|
| I'm working on a program that I've been dabbling with for years. For
| the first time, I tried to compile it with GHC 6.6, and got an error,
| explaining that I was violating the Coverage Condition in my instance
| declaration. The instance declaration looks like this:
|
| instance MonadReader r m = MonadReader r (CPST o m) where ...
|
| The MonadReader class definition, which doesn't appear to have changed
| since 6.4.2, looks like this:
|
| class Monad m = MonadReader r m | m - r where ...
|
| Apparently, the Coverage Condition disallows my instance declaration,
| because the variable 'r' is not mentioned in the '(CPST o m)' term. Now
| this would make sense to me if I didn't have the assertion 'MonadReader
| r m'. Because of that assertion, m - r, so '(CPST o m)' shouldn't need
| to explicitly mention 'r'.
|
| I will try using -fallow-undecidable-instances, and see if the message
| goes away. But can someone explain to me why this is wrong, and what
| would be the preferred way to write it? I've attached the two relevant
| source files. (Try compiling both files.)
|
| Thanks,
| Lyle
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-12-29 Thread Bulat Ziganshin
Hello Steve,

Friday, December 29, 2006, 5:41:40 AM, you wrote:

 then I can't avoid naming and using an intermediate variable. And that
 annoys me. The u in process2 is of no more value to me (pardon the
 pun) as the one in process1, but I am forced to use it simply because
 the data flow is no longer strictly linear.

it force you to give names to intermediate results which is considered as
good programing style - program becomes more documented. alternatively, you
can give simple names like a b c



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-29 Thread Bulat Ziganshin
Hello Grady,

Friday, December 29, 2006, 10:12:12 AM, you wrote:

 not get that in the way I want.  I suppose there may have to be some
 slowdown -- if the compiler specializes every piece of code for every
 instance of a typeclass it might encounter, it could bloat the
 executable beyond all reason.  I'll have to do some tests to see if I
 notice an effect in practice.

yes. ghc makes specialization only in cases when you used SPECIALIZE/INLINE
pragma and when function is small enough to be inlined. otherwise, each (+)
operation will make a function call which is very slow thing in Haskell

i propose you to use INLINE pragma:

{-# INLINE foo #-}

unless your function is recursive. in this case, you should use SPECIALIZE
pragma:

{-# SPECIALIZE foo :: Double - Double - Double #-}



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Conor McBride

Hi

pphetra wrote:


Compare to a Lisp solution, It 's not looking good.
Any suggestion.



I'm trying to understand what your issue is here. What's not looking
good?


I would like to write a program that can do something like this.



;; lisp syntax


I suppose, if it were the implementation of flattening that was the issue,
you'd have shown us the Lisp version.


I end up like this.

data Store a = E a | S [Store a]
 deriving (Show)

flat :: [Store a] - [a]
flat [] = []
flat ((E x):xs) = [x] ++ flat xs
flat ((S x):xs) = flat x ++ flat xs


That's a reasonable datatype to pick for finitely-branching trees. You're
working a little hard on the function. Here's mine

flat1 :: Store a - [a]
flat1 (E a)   = return a
flat1 (S xs)  = xs = flat1

Your (flat xs) on a list of stores becomes my (xs = flat1), systematically
lifting the operation on a single store to lists of them and concatenating the
results. The return operation makes a singleton from an element. This way of
working with lists by singleton and concatenation is exactly the monadic
structure which goes with the list type, so you get it from the library by
choosing to work with list types. In Haskell, when you choose a typed
representation for data, you are not only choosing a way of containing the data
but also a way to structure the computations you can express on that data.

Or is your issue more superficial? Is it just that


* (my-flatten '(1 (2 (3 4) 5)))
(1 2 3 4 5)


looks shorter than


so
*Main flat [E 1, S[E 2, S[E 3, E 4], E 5]]
[1,2,3,4,5]


because finitely branching trees of atoms is more-or-less the native data
structure of Lisp? Is it the Es and Ss which offend? No big deal, surely.
It just makes test input a little more tedious to type.

I'm guessing your Lisp implementation of my-flatten is using some sort of atom
test to distinguish between elements and sequences, where the Haskell version
explicitly codes the result of that test, together with its meaning: pattern
matching combines discrimination with selection. The payoff for explicitly
separating E from S is that the program becomes abstract with respect to 
elements.
What if you wanted to flatten a nested list of expressions where the expressions
did not have an atomic representation?

The point, I guess, is that type system carries the structure of the 
computation.
If you start from less structured Lisp data, you need to dig out more of the
structure by ad hoc methods. There's more structure hiding in this example, 
which
would make it even neater, hence the exercises at the end...

But I hope this helps to make the trade-offs clearer.

All the best

Conor

PS exercises for the over-enthusiastic

 import Data.Foldable
 import Data.Traversable
 import Control.Applicative
 import Data.Monoid

Now consider (or discover!) the 'free monad' construction:

 data Free sig a = Var a | Op (sig (Free sig a))

(1) Show that if sig is a Functor then Free sig is a Monad, with (=) behaving
like substitution for terms built over the signature sig.

(2) Show that if sig is Traversable then Free sig is Traversable.

(3) Replace the above 'Store' with a type synonym by substituting other 
characters
for ? in

 type Store = Free ??

(4) Replace the ?s with other characters to complete the following definition
 
 splat :: (Traversable f, Applicative a, Monoid (a x)) = f x - a x

 splat = 

in such a way that the special case

 splat :: Store a - [a]

behaves like flat1 above.


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


Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Paul Moore

On 12/29/06, Conor McBride [EMAIL PROTECTED] wrote:

Or is your issue more superficial? Is it just that

 * (my-flatten '(1 (2 (3 4) 5)))
 (1 2 3 4 5)

looks shorter than

 so
 *Main flat [E 1, S[E 2, S[E 3, E 4], E 5]]
 [1,2,3,4,5]


Speaking as a relative newbie to Haskell, the thing that tripped me up
was the fact that you can't have nested lists like the Lisp '(1 (2 (3
4) 5)) example in Haskell, because its type is not well-defined.
Haskell lists are homogeneous, where Lisp ones aren't.

I don't know whether the OP was confused by the same thing as me, but
it felt to me that stating the problem was the hard part, rather than
implementing a solution. OTOH, it's not entirely clear to me if the
issue would come up in real code. Slinging about arbitrarily nested
lists feels quite natural in Lisp, but isn't really idiomatic Haskell.

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


Re: [Haskell-cafe] flatten a nested list

2006-12-29 Thread Tomasz Zielonka
On Fri, Dec 29, 2006 at 02:06:32PM +, Paul Moore wrote:
 Speaking as a relative newbie to Haskell, the thing that tripped me up
 was the fact that you can't have nested lists like the Lisp '(1 (2 (3
 4) 5)) example in Haskell, because its type is not well-defined.

More precisely: You can't ununiformly nest standard [] lists. By
ununiformly I mean: with leaves on different depths.

You can do it with another list (or rather tree) implementation.

You can nest [] lists uniformly, ie. [[1], [2,3,4]] is a nested list.

 OTOH, it's not entirely clear to me if the issue would come up in
 real code.

It depends on what you mean by issue. If syntactical overhead is an
issue, then it comes up. For me it's a small issue, if at all.

 Slinging about arbitrarily nested lists feels quite natural in Lisp,
 but isn't really idiomatic Haskell.

Nested lists are trees and using tree-like structures in Haskell is
very idiomatic.

Perhaps you would want some syntactic sugar for trees. If [] lists
didn't have sugar in Haskell, they would be as cumbersome to use as
trees.

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


Re: Re[2]: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-29 Thread Kirsten Chevalier

On 12/29/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:

i propose you to use INLINE pragma:

{-# INLINE foo #-}

unless your function is recursive. in this case, you should use SPECIALIZE
pragma:

{-# SPECIALIZE foo :: Double - Double - Double #-}



I suggest *not* using these pragmas unless a combination of profiling
and reading intermediate code dumps suggests that foo -- and its
un-specialized nature -- is truly a bottleneck. Excessive amounts of
SPECIALIZE pragmas can make your code ugly without actually improving
performance if you optimize prematurely (and I speak from experience).
Think *first*, add pragmas later; again, people on the mailing lists
and IRC channel are usually happy to provide guidance with this.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
To be free is not to have the power to do anything you like; it is to be able
to surpass the given towards an open future...--Simone de Beauvoir
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-12-29 Thread Greg Buchholz
Steve Schafer wrote:
 
 Here's the essence of the problem. If I have this:
 
  process1 x y =
let u = foo x y;
v = bar u;
w = baz v
in  w
 
 I can easily rewrite it in point-free style:
 
  process1 = baz . bar . foo

Not unless you have a much fancier version of function composition,
like...

http://okmij.org/ftp/Haskell/types.html#polyvar-comp

 
 But if I have this:
 
  process2 x y =
let u = foo x y;
v = bar u;
w = baz v u
in  w
 
 then I can't avoid naming and using an intermediate variable. And that
 annoys me. The u in process2 is of no more value to me (pardon the
 pun) as the one in process1, but I am forced to use it simply because
 the data flow is no longer strictly linear.
 
 The reason I brought up monads as a possible means of managing this
 problem is that the State, Reader and Writer monads already handle
 certain specific shapes of nonlinear data flow, which suggested to
 me that maybe there was a monadic approach to managing nonlinear data
 flow in a more general way. Of course, if there is a non-monadic,
 purely functional way to do it, that would be even better, but I've
 never seen such a thing (short of doing lots of tupling and
 un-tupling).

-- Use combinators which automate the tupling/un-tupling.
-- See also, the Joy language...
-- http://www.latrobe.edu.au/philosophy/phimvt/joy/j00rat.html

main = process2 test

process2 = baz . bar . dup . foo

foo = mul . (push 2) . mul

bar = rep . swap . (push 'A')

baz = add . len 

test = (2,(3,()))::(Int,(Int,()))


dup (a,b) = (a,(a,b))
swap (a,(b,c)) = (b,(a,c))
push a b = (a,b)

lift1 f (a,b) = (f a,b)
lift2 f (a,(b,c)) = (f a b,c)

len = lift1 length 
add = lift2 (+)
mul = lift2 (*)
rep = lift2 replicate


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


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

2006-12-29 Thread Steve Schafer
On Fri, 29 Dec 2006 09:01:37 -0800, you wrote:

Steve Schafer wrote:
 
 I can easily rewrite it in point-free style:
 
  process1 = baz . bar . foo

Not unless you have a much fancier version of function composition,
like...

http://okmij.org/ftp/Haskell/types.html#polyvar-comp


Sorry; I obviously got a little carried away there:

 process1 x =
   let u = foo x;
   v = bar u;
   w = baz v
   in  w

 process1 = baz . bar . foo

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: Re[2]: [Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread Steve Schafer
On Fri, 29 Dec 2006 14:23:20 +0300, you wrote:

it force you to give names to intermediate results which is considered as
good programing style - program becomes more documented.

But that would imply that function composition and in-line function
definition are also Bad Style.

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] Combine list of sorted lists

2006-12-29 Thread Neil Mitchell

Hi Quan



I am not sure how to express f1 with map?  how do I say
(lambda (ls)
(map (lambda (x) (list x))
ls))
in Haskell?  map ([])  ?


map (:[]), :[] takes a single element and puts it into a list. Some
people refer to this as box

The final f3 clause can be made a bit neater:


f3 la@(a:as) lb@(b:bs) | sum a = sum b = a : f3 as lb

   | otherwise = b : f3 la bs

Additionally, if it was me I'd refer to a:as on the RHS, rather than
giving it a name with the @ pattern, but thats a personal question of
style.

Thanks

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


Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread David House

Sorry to Neil for multiple copies.

On 29/12/06, Neil Mitchell [EMAIL PROTECTED] wrote:

 I am not sure how to express f1 with map?  how do I say
 (lambda (ls)
 (map (lambda (x) (list x))
 ls))
 in Haskell?  map ([])  ?

map (:[]), :[] takes a single element and puts it into a list. Some
people refer to this as box


You can pretty much directly translate your Lisp:

\ls - map (\x - [x]) ls

Which eta-reduces to:

map (\x - [x])

Now the inner lambda can be written as:

\x - x : []

Or,

(: [])

That's a section on the ':' operator. So the whole thing becomes:

map (:[])

Hope that helps.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread Bryan Burgers

 I am not sure how to express f1 with map?  how do I say
 (lambda (ls)
 (map (lambda (x) (list x))
 ls))
 in Haskell?  map ([])  ?

map (:[]), :[] takes a single element and puts it into a list. Some
people refer to this as box


Another way to express f1 with map is:

f1 xs = map (\x - [x]) xs

The (\x - [x]) is a lambda that takes an x and puts it in a list.
This is semantically the same as (\x - x:[]), where (:) puts x at the
front of the empty list ([]). So, this is where Niel gets his method
(:[]) -- ie, just like (\x - x+1) is semantically the same as (+1),
so (\x - x:[]) is semantically the same as (:[]).

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


Re: Re[2]: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-29 Thread Grady Lemoine

I've performed some experiments in GHCi, and it looks like even for a
simple function (+) (which should be the worst case, since if the
computation is simple, any extra time required to dispatch the call
will show up more strongly in comparison) it doesn't really matter.  I
get essentially the same execution times no matter which of the
definitions below I use, although sometimes one time (apparently at
random) is 2-3 times as large as the others; I presume this is the
garbage collector at work, or something.  Given these results, I'm
inclined to make my function types as general as possible, with
typeclasses galore, and only use pragmas if profiling reveals a good
reason to.

I'm attaching my test code for reference.  Clumsy noob Haskell code
below (I'm still pretty new to Haskell, and this is the first time
I've programmed in a monad):


TypeClassTest.lhs
Test of what effect (if any) using a typeclass in GHC has on performance



module TypeClassTest where
import System.CPUTime



l :: [Double]
l = [0.0,1.0..1e5]


Fully specialized:


addDouble :: Double - Double - Double
addDouble = (+)


Generic, but with inlining:


{-# INLINE addInline #-}
addInline :: Num a = a - a - a
addInline = (+)


Generic, but with specialization:


{-# SPECIALIZE addSpecialize :: Double - Double - Double #-}
addSpecialize :: Num a = a - a - a
addSpecialize = (+)


Generic, with no compiler pragmas:


addGeneric :: Num a = a - a - a
addGeneric = (+)




main :: IO ()
main = do putStrLn $ Summing  ++ length l ++  floating-point values in various 
ways...
  foldTime Double list with addDouble addDouble l
  foldTime Double list with addInline addInline l
  foldTime Double list with addSpecialized addSpecialize l
  foldTime Double list with addGeneric addGeneric l
  return ()



foldTime :: String - (a - a - a) - [a] - IO a
foldTime desc f l = do start  - getCPUTime
   result - (return $! foldr1 f l)
   end- getCPUTime
   putStrLn $ Time for  ++ desc ++  per list element:   
++ show ((end-start) `div` (fromIntegral $ length l))
   return result


--Grady Lemoine

On 12/29/06, Kirsten Chevalier [EMAIL PROTECTED] wrote:

On 12/29/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 i propose you to use INLINE pragma:

 {-# INLINE foo #-}

 unless your function is recursive. in this case, you should use SPECIALIZE
 pragma:

 {-# SPECIALIZE foo :: Double - Double - Double #-}


I suggest *not* using these pragmas unless a combination of profiling
and reading intermediate code dumps suggests that foo -- and its
un-specialized nature -- is truly a bottleneck. Excessive amounts of
SPECIALIZE pragmas can make your code ugly without actually improving
performance if you optimize prematurely (and I speak from experience).
Think *first*, add pragmas later; again, people on the mailing lists
and IRC channel are usually happy to provide guidance with this.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
To be free is not to have the power to do anything you like; it is to be able
to surpass the given towards an open future...--Simone de Beauvoir


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


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

2006-12-29 Thread apfelmus
 I assume that your proper goal is not to structure pipeline processes
 in full generality, but to simplify the current one at hand.

 No, I'm looking for full generality.  ;)
 I have dozens of these kinds of quasi-pipelines, all similar in
 overall appearance, but different in detail.

Ah, the names help a lot and they confirm my uneasy feeling about the
quasi-pipeline: I think it's ad-hoc. What I want to say is that I
suggest refactoring the pipeline to become expressible as a point-free
function concatenation by decoupling data dependencies instead of trying
to find a way to express arbitrary interlinked quasi-pipelines. So I'd
eliminate the problem by switching to a different one :) Of course, this
decoupling needs the concrete names and types, that's why I wanted to
know them.

So, let's have look on the data dependencies, taking the information
from your web-site into account. I'll formulate some guesses and
questions, you don't need to comment on them; they're just meant as
hints. The point is that its *type* and not so much its name should
guide what a functions does. This way, dependencies on unnecessary
parameters automatically go away.


 process :: Item - MediaKind - MediaSize - Language - SFO
Item doesn't tell me anything. Seems to be an XML-File containing the
questions and such.

 process item mediaKind mediaSize language =
   let pagemaster = loadPagemaster item mediaKind mediaSize;

Mh, I cannot guess what a pagemaster might do, but from its arguments,
it looks like the ink guy responsible for actual printing (or
on-screen display). So he might know about graphics, colors and inches
but not about content.

 validateQuestionContent :: [Question] - [Question]
   questions = stripUndisplayedQuestions mediaKind $

Ok, mediaKind is indispensable because on-screen and print forms are
utterly different. Maybe one should write
  filter willBeDisplayedQuestion $
instead, but I think the name 'stripUndisplayedQuestions' says it all.

   appendEndQuestions item pagemaster $

Uh, why do questions depend on pagemaster and thus on mediaSize? Are
these some floating questions appearing on every page, like the name of
the guy to be questioned? Those should be treated somewhere else.
Here, one could also write
  (++ endquestions ...) $
so that everybody sees what's going on, but again 'appendEnd' is
adequate. The dependency on the full item is too much, I think.

 coalesceParentedQuestions :: [Question] - [Question]
   coalesceParentedQuestions $

This makes me suspicious whether [Question] is the right type. Apparently,
   data Question = GroupedQuestions [String]
or something like that, so that a Question may well be a tree of
questions. Guessing that this function resolves some tree structure that
got specified by explicitly naming nodes, I'd suggest a type
'[QuestionTaggedWithLevel] - Tree Question' instead. Note that one also
has fold and filter on Trees for further processing.

 validateQuestionContent :: [Question] - [Question]
   validateQuestionContent $

Uh, I think the type is plain wrong. Doesn't the name suggest 'Question
- Bool' and a fatal error when a question content is invalid?

   loadQuestions item;

'loadQuestions' is a strange name (too imperative) but that's personal
taste and maybe a hint to the fact that 'item' is stored inside a file.

  (numberedQuestions,questionCategories) = numberQuestions pagemaster 
 questions;

Yet again the pagemaster. I don't think that mere numbering should
depend on mediaSize, not even implicitly. Why must questionCategories be
collected? Aren't they inherent in 'Tree Question', so that every Branch
has a unique category? Automatic numbering is fine, though.

  numberedQuestions' = coalesceNAQuestions numberedQuestions;
Does 'NA' mean not answered? Isn't that either a fatal error or a
Maybe-Answer? 'coalesce' makes me suspicious, I could live with a 'filter'.

  (bands,sequenceLayouts) = buildLayout mediaKind language 
 numberedQuestions';
Ah, there's no pagemaster, only mediaKind and language, although the
pagemaster would be tempting here. I guess that layout builds for
'endless paper' (band).

  bands' = resolveCrossReferences bands;
Mh, cross reference for thing x on page y? But there aren't any pages
yet. Likely that I just don't know what bands are.

  groupedBands = groupBands bands';
(can't guess on that)

  pages = paginate item mediaKind mediaSize pagemaster groupedBands;
Now, the dependence on mediaSize is fine. But it's duplicated by pagemaster.

  pages' = combineRows pages;
  sfo = createSFO pages' sequenceLayouts;
  in sfo
(can't guess on that)


In summary, I think that the dependencies on the pagemaster are not
adequate, he mixes too many concerns that should be separated. If he
goes, there's much more function concatenation possible. If really
necessary, the MediaKind stuff can go into a MonadReader. Btw, IMHO the
explicitely named 

Re: [Haskell-cafe] Combine list of sorted lists

2006-12-29 Thread Quan Ta

On 12/29/06, Neil Mitchell [EMAIL PROTECTED] wrote:



map (:[]), :[] takes a single element and puts it into a list. Some
people refer to this as box

The final f3 clause can be made a bit neater:

 f3 la@(a:as) lb@(b:bs) | sum a = sum b = a : f3 as lb
| otherwise = b : f3 la bs


Hi Neal,


Neat tricks on both counts - thanks!

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


Re: [Haskell-cafe] constant functions

2006-12-29 Thread David House

On 29/12/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:

And if you don't want to think about it, this should make everything
clear:


My additions displayed below:

f :: A - B - C - D

f :: A - (B - (C - D))

By right-associativity of f.

f a :: B - (C - D)
(f a) b :: C - D
((f a) b) c :: d

s/d/D/

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Strange type behavior in GHCi 6.4.2

2006-12-29 Thread Lennart Augustsson

Before you start adding pragmas, try compiling with -O, it does a lot
of the specialization automatically.

-- Lennart

On Dec 29, 2006, at 15:00 , Grady Lemoine wrote:


I've performed some experiments in GHCi, and it looks like even for a
simple function (+) (which should be the worst case, since if the
computation is simple, any extra time required to dispatch the call
will show up more strongly in comparison) it doesn't really matter.  I
get essentially the same execution times no matter which of the
definitions below I use, although sometimes one time (apparently at
random) is 2-3 times as large as the others; I presume this is the
garbage collector at work, or something.  Given these results, I'm
inclined to make my function types as general as possible, with
typeclasses galore, and only use pragmas if profiling reveals a good
reason to.

I'm attaching my test code for reference.  Clumsy noob Haskell code
below (I'm still pretty new to Haskell, and this is the first time
I've programmed in a monad):

** 
**

TypeClassTest.lhs
Test of what effect (if any) using a typeclass in GHC has on  
performance
** 
**



module TypeClassTest where
import System.CPUTime



l :: [Double]
l = [0.0,1.0..1e5]


Fully specialized:


addDouble :: Double - Double - Double
addDouble = (+)


Generic, but with inlining:


{-# INLINE addInline #-}
addInline :: Num a = a - a - a
addInline = (+)


Generic, but with specialization:


{-# SPECIALIZE addSpecialize :: Double - Double - Double #-}
addSpecialize :: Num a = a - a - a
addSpecialize = (+)


Generic, with no compiler pragmas:


addGeneric :: Num a = a - a - a
addGeneric = (+)




main :: IO ()
main = do putStrLn $ Summing  ++ length l ++  floating-point  
values in various ways...

  foldTime Double list with addDouble addDouble l
  foldTime Double list with addInline addInline l
  foldTime Double list with addSpecialized addSpecialize l
  foldTime Double list with addGeneric addGeneric l
  return ()



foldTime :: String - (a - a - a) - [a] - IO a
foldTime desc f l = do start  - getCPUTime
   result - (return $! foldr1 f l)
   end- getCPUTime
   putStrLn $ Time for  ++ desc ++  per  
list element:   ++ show ((end-start) `div` (fromIntegral $ length  
l))

   return result


--Grady Lemoine

On 12/29/06, Kirsten Chevalier [EMAIL PROTECTED] wrote:

On 12/29/06, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 i propose you to use INLINE pragma:

 {-# INLINE foo #-}

 unless your function is recursive. in this case, you should use  
SPECIALIZE

 pragma:

 {-# SPECIALIZE foo :: Double - Double - Double #-}


I suggest *not* using these pragmas unless a combination of profiling
and reading intermediate code dumps suggests that foo -- and its
un-specialized nature -- is truly a bottleneck. Excessive amounts of
SPECIALIZE pragmas can make your code ugly without actually improving
performance if you optimize prematurely (and I speak from  
experience).

Think *first*, add pragmas later; again, people on the mailing lists
and IRC channel are usually happy to provide guidance with this.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error,  
never in doubt
To be free is not to have the power to do anything you like; it  
is to be able

to surpass the given towards an open future...--Simone de Beauvoir


___
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] Idiomatic Haskell equivalent of keyword arguments to functions

2006-12-29 Thread Paul Moore

I'm thinking around the design of a couple of things, and am hitting
an issue which I know how I would solve in Python, but I'm not sure
what a good idiomatic Haskell approach would be.

The problem is that I am trying to write a function which takes a
rather large number of arguments, many of which are optional (ie, have
sensible defaults). The canonical example of this is creating a GUI
window, which involves a lot of style options, most of which would
typically be left to default. In Python, this type of interface is
often handled either as a function with many keyword arguments, or as
a mutable object which has attributes set, and then a method called to
handle the function call. Neither of these approaches seems plausible
in Haskell.

I looked at wxHaskell for inspiration - its approach (button f [text
:= Quit, on command := close f]) looks quite readable, but slightly
unusual (to me) for Haskell. It also seems fairly complex to implement
(ie, my head hurt when I tried to follow the types involved, but maybe
that's just because it's getting late :-))

To make things concrete, the example I'm really thinking of is a send
an email function, which would take a subject, a body, a list of
recipients, optional lists of cc and bcc recipients, an optional
mailserver (default localhost), an optional port (default 25), and
possibly optional authentication details. I found a couple of Haskell
modules implementing a SMTP client, but they both just used a list of
positional parameters, which I'm not really happy with. At the very
least, I'd like to wrap them in a nicer interface for my code.

I'd appreciate any ideas about how to think of this sort of problem -
I'm pretty sure that what I need to do is think differently about the
issue, rather than just mechanically translating the code I'd write in
Python. But I don't really know how. Any pointers would be very
helpful!

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


Re: [Haskell-cafe] Idiomatic Haskell equivalent of keyword arguments to functions

2006-12-29 Thread Neil Mitchell

Hi Paul,


To make things concrete, the example I'm really thinking of is a send
an email function, which would take a subject, a body, a list of
recipients, optional lists of cc and bcc recipients, an optional
mailserver (default localhost), an optional port (default 25), and
possibly optional authentication details.


Records are your friend.

data Email = Email {subject :: String, body :: String, to ::
[Address], cc = [Address], bcc = [Address], mailserver :: String, port
:: Int}

defaultEmail = Email{subject = No subject, body = , to = [], cc =
[], bcc = [], mailserver = localhost, port = 25}

The user can then go:

sendEmail defaultEmail{subject=Subject here, body = body here, to
= [haskell-cafe], mailserver = server.haskell.org}

Now things which are't specified (port) keep their default value.

The other alternative is:

data EmailParams = Body String
   | Port Int
   | Mailserver String
 ...

then:

sendEmail [Body body here, To haskell-cafe, Mailserver
server.haskell.org ...]

I prefer the first, but the second can also be done.

Thanks

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


Re: [Haskell-cafe] Idiomatic Haskell equivalent of keyword arguments to functions

2006-12-29 Thread David House

On 29/12/06, Paul Moore [EMAIL PROTECTED] wrote:

I looked at wxHaskell for inspiration - its approach (button f [text
:= Quit, on command := close f]) looks quite readable, but slightly
unusual (to me) for Haskell. It also seems fairly complex to implement
(ie, my head hurt when I tried to follow the types involved, but maybe
that's just because it's getting late :-))


This is actually a really nice solution, if you think about it:

1) You don't have to memorise the order the parameters come in (you
can put the parameters in any order in that list).
2) It's self-documenting, f arg1 arg2 arg3 doesn't say what arg1, arg2
and arg3 do, but this way you get an idea.
3) If you had a function in another language with 10 parameters, all
of which are optional, but you want to specify the last one, you have
to include the default values (which may involve looking up what they
are) of the first 9; no such problems here.

Try again to understand the typing, hopefully you'll see this is
probably The Best Way. If you have any questions about the typing
itself, just post them here.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Idiomatic Haskell equivalent of keyword arguments to functions

2006-12-29 Thread David House

On 29/12/06, Paul Moore [EMAIL PROTECTED] wrote:

I looked at wxHaskell for inspiration - its approach (button f [text
:= Quit, on command := close f]) looks quite readable, but slightly
unusual (to me) for Haskell. It also seems fairly complex to implement
(ie, my head hurt when I tried to follow the types involved, but maybe
that's just because it's getting late :-))


I forgot one - it's extensible, so if you want to add extra parameters
you don't need to change the type of the function, and you don't need
to change every single call site either.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread jeff p

Hello,


breakUp s
| L.null s = []
| otherwise = h:(breakUp r) where
(h,r) = L.splitAt 72 s

Running this on the 2G file blows up the stack pretty quickly, taking
the first 1 million records (there are 20M of them) with a big stack
parameter gives about 25% productivity, with GC taking the other 75%.

My understanding is that while this looks tail recursive, it isn't
really because of laziness.  I've tried throwing seq operators
around, but they don't seem to do much to help the efficiency.


The function is not tail-recursive as written (you're returning
h:breakUp r) but that shouldn't be a problem because of lazy
evaluation.

Can you give more context, particularly what happens to the result of breakUp?

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


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

2006-12-29 Thread Udo Stenzel
Steve Schafer wrote:
 Here's the essence of the problem. If I have this:
 
  process1 x y =
let u = foo x y;
v = bar u;
w = baz v
in  w
 
 I can easily rewrite it in point-free style:
 
  process1 = baz . bar . foo

That should have been

  process1 = (.) (baz . bar) . foo

or something similar.  You might want to define suitable combinators if
you have this pattern more often:

  infix 8 .
  (.) = (.) . (.)
  process1 = baz . bar . foo


 But if I have this:
 
  process2 x y =
let u = foo x y;
v = bar u;
w = baz v u
in  w
 
 then I can't avoid naming and using an intermediate variable.

Turns out you can.

  process2 = \x y - (\u - baz (bar u) u) (foo x y)
   = \x y - (\u - (baz . bar) u u) (foo x y)
   = \x y - liftM2 (baz . bar) (foo x y)
   = liftM2 (baz . bar) . foo

In fact, you never need named values.  Read How to Mock a Mockingbird
by Richard Bird (if memory serves) or the documentation for the Unlamda
(esoteric) programming language to find out how or let Lambdabot do the
transformation to pointless style for you.

You don't need to go fully points free in every case.  In your original
example, only one intermediate (y01) was actually used more than once
and deserves naming.  Everything else can be composed with the help of
'uncurry'.  'liftM2' is also surprisingly useful, but it's use at the
type constructor (r -) as in the last example probably deserves a name
of its own.


 The u in process2 is of no more value to me (pardon the
 pun) as the one in process1, but I am forced to use it simply because
 the data flow is no longer strictly linear.

Instead you could define intermediate functions by composing functions
with the help of a few combinators.  I guess, the construction (liftM2
(baz . bar)) could have a very meaningful name.  Some combinators might
also vanish if you reorder and/or tuple some of the arguments to
existing functions.

 
 The reason I brought up monads as a possible means of managing this
 problem is that the State, Reader and Writer monads already handle
 certain specific shapes of nonlinear data flow

Uhm... that could be said of Reader, but is no good description of the
others.  If you like, you could plug your y01 into a Reader Monad, but I
don't think it simplifies anything.  Sometimes naming values is simply
the right thing to do.


-Udo
-- 
Even if you're on the right track, you'll get run over if you just sit there.
-- Will Rogers


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


Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Stefan O'Rear
On Fri, Dec 29, 2006 at 04:56:34PM -0800, Ranjan Bagchi wrote:
 I'm loading a big file (~2G), again, with 72-byte C structs.  I've  
 done pretty well [thanks to everyone] interpreting the fields, but  
 I'm finding the traversal of the file to be pretty inefficient.
 
 breakUp s
   | L.null s = []
   | otherwise = h:(breakUp r) where
   (h,r) = L.splitAt 72 s
 
 My understanding is that while this looks tail recursive, it isn't  
 really because of laziness.  I've tried throwing seq operators  
 around, but they don't seem to do much to help the efficiency.

That looks like the correct lazy way to do it; by itself that breakUp
should be virtually instantaneous and consume neglible stack because
of laziness.  What kind of list consumer are you using?  (ie don't use
foldl, use foldl' or foldr, foldl is very prone to high stack use.)

Also, your breakUp is an unfold:

\begin{code}
import Data.List(unfoldr)

breakUp = unfoldr takeChunk where
takeChunk s | L.null s  = Nothing
| otherwise = Just $ L.splitAt 72 s
\end{code}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie question

2006-12-29 Thread Pieter Laeremans

Hi,

I'm reading the Haskell school of expression by Paul Hudok. Great book.

However I would like some feedback about a solution to an exercise

The problem is quite simple :

define f1 and f2 (using higher order functions ) such that

f1 (f2 (*) [1..4]) 5 = [5,10,15,20]

I have come up with the following solution :

f2 :: (a-b)-[a] - [b]
f2 f xs = map f xs
f1 fs a = map (applyOp a) fs
applyOp  b f = f b


But I guess there must be some more elegant way. f2 isn't at all  
original.

And the applyOp sounds silly.

Any comments or suggestions are welcome.

thanks,

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


Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Matthew Brecknell
 breakUp s
   | L.null s = []
   | otherwise = h:(breakUp r) where
   (h,r) = L.splitAt 72 s
 
 Running this on the 2G file blows up the stack pretty quickly, taking  
 the first 1 million records (there are 20M of them) with a big stack  
 parameter gives about 25% productivity, with GC taking the other 75%.
 
 My understanding is that while this looks tail recursive, it isn't  
 really because of laziness.  I've tried throwing seq operators  
 around, but they don't seem to do much to help the efficiency.

This function by itself doesn't really have any particular behaviour
with respect to stack and heap usage, since it is just a linear mapping
from one lazy sequence to another. To understand the stack blowout,
you'll need to look at what you are doing with the result of this
function.

For example, a foldl over the result might be building a big thunk on
the heap, which could blow the stack when evaluated*. If this is the
case, you might avoid building the big thunk by using foldl', a version
of foldl which evaluates as it folds.

Invoking GHC with optimisation might also help, since the strictness
evaluator can often do the equivalent of converting foldl to foldl' at
the appropriate places.

Have you looked at the Performance pages on the Wiki, in particular, the
Strictness and Laziness pages?

http://www.haskell.org/haskellwiki/Performance

In my (limited) Haskell experience, I was continually being surprised by
inexplicable stack blowouts until I spent a little time doing some
focussed experiments, mainly involving folds over large lists. If you
haven't done that, I would recommend it.

* - Note that foldl is tail recursive, so clearly tail recursion doesn't
necessarily result in a well-behaved loop in a lazy implementation!

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


Re: [Haskell-cafe] Newbie question

2006-12-29 Thread Bernie Pope


On 30/12/2006, at 1:33 PM, Pieter Laeremans wrote:


Hi,

I'm reading the Haskell school of expression by Paul Hudok. Great  
book.


Hudak. And I  concur, a great book.



However I would like some feedback about a solution to an exercise

The problem is quite simple :

define f1 and f2 (using higher order functions ) such that

f1 (f2 (*) [1..4]) 5 = [5,10,15,20]

I have come up with the following solution :

f2 :: (a-b)-[a] - [b]
f2 f xs = map f xs


That's fine, but what you are really saying is that f2 is the same as  
map, so you can make

that connection more obvious like this:

   f2 = map


f1 fs a = map (applyOp a) fs
applyOp  b f = f b


That's also fine. You can avoid applyOp in numerous ways. One way is  
to use the

function called $ from the Prelude; it implements function application.

f $ x = f x

So you could write:

   f1 fs a = map ($ a) fs

Of course, there are also other ways of implementing f1 and f2 such  
that you get the
desired result, but the map approach seems to be what the question  
was angling for.


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


Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Bernie Pope


On 30/12/2006, at 1:32 PM, Matthew Brecknell wrote:



In my (limited) Haskell experience, I was continually being  
surprised by

inexplicable stack blowouts until I spent a little time doing some
focussed experiments, mainly involving folds over large lists. If you
haven't done that, I would recommend it.


I think this is very good advice.

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


Re: [Haskell-cafe] Idiomatic Haskell equivalent of keyword argumentsto functions

2006-12-29 Thread Brian Hulley

Paul Moore wrote:

I'm thinking around the design of a couple of things, and am hitting
an issue which I know how I would solve in Python, but I'm not sure
what a good idiomatic Haskell approach would be.

The problem is that I am trying to write a function which takes a
rather large number of arguments, many of which are optional (ie, have
sensible defaults).


There's an interesting solution to this in section 15 (starting page 53) of 
Magnus Carlsson and Thomas Hallgren's Fudgets thesis available online at: 
http://www.cs.chalmers.se/~hallgren/Thesis/ (Fudgets main page is at 
http://www.cs.chalmers.se/ComputingScience/Research/Functional/Fudgets/ ).


Basically the idea is that for any function which takes lots of params, the 
params are gathered together into a datatype whose details are hidden from 
the user of the function. For each parameter, the user is given a function 
called a Customiser in the thesis, which takes a value of the hidden 
datatype and modifies it by setting the relevant parameter. Multiple params 
can therefore be specified by chaining Customisers together in any order 
with the usual function composition. The original function, instead of 
taking lots of params, now just takes a single parameter: a Customiser, 
which is used to turn the default params into the customised params.
This is similar to the idea of using records but has the advantage that by 
judicious use of typeclasses of which the param data is an instance, you 
don't need to keep on inventing different names for the same thing (eg to 
specify colour for the background of a label control in a GUI or colour for 
a font you could use the name setColour in both cases).
(A possible disadvantage is the overhead of having to create a whole new 
modified version of the parameter record for each Customiser in the 
composition so if efficiency were an issue you'd have to see if the compiler 
could inline the composition of the customiser functions to make it as 
efficient as the built in multiple field record update using rec{a=a', c=c'} 
syntax)



To make things concrete, the example I'm really thinking of is a send
an email function, which would take a subject, a body, a list of
recipients, optional lists of cc and bcc recipients, an optional
mailserver (default localhost), an optional port (default 25), and
possibly optional authentication details. I found a couple of Haskell
modules implementing a SMTP client, but they both just used a list of
positional parameters, which I'm not really happy with. At the very
least, I'd like to wrap them in a nicer interface for my code.



-- hidden from clients
data EmailParams =
   EmailParams
   { subject :: String
   , body :: String
   , recipients :: [Recipient]
   , cc :: [Recipient]
   , bcc :: [Recipient]
   , mailserver :: Mailserver
   , port :: Port
   , authentication :: Authentication
   }

-- record syntax elided to save space
defaultEmailParams = EmailParams   [] [] [] defaultMailserver 
defaultPort defaultAuthentication


--a Customiser visible to clients
setSubject :: String - EmailParams - EmailParams
setSubject s ep = ep{subject = s}

-- etc

send :: (EmailParams - EmailParams) - IO ()
send f = sendInternal (f defaultEmailParams)
   where
   sendInternal :: EmailParams - IO ()
   sendInternal = ...

-- In user code:

main = send (setSubject Test . setBody A test email)

Brian.
--
http://www.metamilk.com 


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


Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Ranjan Bagchi


On Dec 29, 2006, at 6:32 PM, Matthew Brecknell wrote:


breakUp s
| L.null s = []
| otherwise = h:(breakUp r) where
(h,r) = L.splitAt 72 s

Running this on the 2G file blows up the stack pretty quickly, taking
the first 1 million records (there are 20M of them) with a big stack
parameter gives about 25% productivity, with GC taking the other 75%.

My understanding is that while this looks tail recursive, it isn't
really because of laziness.  I've tried throwing seq operators
around, but they don't seem to do much to help the efficiency.


This function by itself doesn't really have any particular behaviour
with respect to stack and heap usage, since it is just a linear  
mapping

from one lazy sequence to another. To understand the stack blowout,
you'll need to look at what you are doing with the result of this
function.

For example, a foldl over the result might be building a big thunk on
the heap, which could blow the stack when evaluated*. If this is the
case, you might avoid building the big thunk by using foldl', a  
version

of foldl which evaluates as it folds.


I guess the consumer's really important (Didn't even occur to me, I  
was concentrating on how I was generating the list).

I was trying to de-lazy the list, I did the following:

bs = [...]
recs' = (take 100) breakUp bs
recs = foldr seq recs' recs'
print $ length recs

Would the fold be blowing the stack?

Ranjan

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


[Haskell-cafe] Literate Haskell source files. How do I turn them into something I can read?

2006-12-29 Thread Michael T. Richter
I'm trying to wrap my mind around the darcs source code as a preliminary
to looking into GHC's guts.  All of darcs is written as .lhs files which
have bizarre mark-up in them which distracts me from the actual Haskell
source I'm trying to figure out and get used to.  Apparently the GHC
compiler can take .lhs files, strip them with unlit (a utility which I
finally found buried deep in the GHC installation -- off-path) and then
compile them normally.  The problem I have is that unlit leaves behind
instead these huge gaping (and highly distracting) stretches of
whitespace while it takes out the markup.

Are there any tools which I can use to render .lhs files readable?  I'm
fine with having them converted into documented source (i.e. source code
embedded in documentation) or as pure Haskell source (but without the
huge whitespace gaps) -- but I can't figure out how to get either.

-- 
Michael T. Richter
Email: [EMAIL PROTECTED], [EMAIL PROTECTED]
MSN: [EMAIL PROTECTED], [EMAIL PROTECTED]; YIM:
michael_richter_1966; AIM: YanJiahua1966; ICQ: 241960658; Jabber:
[EMAIL PROTECTED]

I think it is very beautiful for the poor to accept their lot [...]. I
think the world is being much helped by the suffering of the poor
people. --Mother Theresa


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient way to break up a lazy bytestring

2006-12-29 Thread Cale Gibbard

On 30/12/06, Ranjan Bagchi [EMAIL PROTECTED] wrote:

I guess the consumer's really important (Didn't even occur to me, I
was concentrating on how I was generating the list).
I was trying to de-lazy the list, I did the following:

bs = [...]
recs' = (take 100) breakUp bs
recs = foldr seq recs' recs'
print $ length recs

Would the fold be blowing the stack?

Ranjan


Is there a really good reason to de-lazy the list? That's usually a
bad idea if the list is long. If your application can do any kind of
stream processing at all, then it's a better idea to allow it to work
with the list lazily. If it can't, and you're basically producing some
kind of summary of the input data, you're probably better off using a
strict left fold and consuming the list in a strict fashion, but not
forcing it earlier than actually needed. By strictifying the list,
you're making it impossible to work with the first cons without
computing the last one. That means that the following consumption of
the list by length can't even start until it's finished building the
whole thing in memory (you're wasting both time and space). Holding a
large list like that in memory all at once has few benefits. If you're
currently doing lazy IO and are concerned about the file changing as
you're processing it, you're better off copying the whole file into
memory as one big block and still building the list lazily from that
copy in memory.

If you're coming from any sort of imperative background, you can
basically think of a list as a loop which has not yet happened. If you
can generate the indices for the loop on the fly, you're probably not
going to want to waste time putting them all in memory beforehand,
regardless of what that loop is doing (how the list is being
consumed).

There are a few cases where strictifying production of data is good,
but it's far more common to want strict consumption and lazy
production.

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


Re: [Haskell-cafe] Literate Haskell source files. How do I turn them into something I can read?

2006-12-29 Thread Cale Gibbard

On 30/12/06, Michael T. Richter [EMAIL PROTECTED] wrote:


 I'm trying to wrap my mind around the darcs source code as a preliminary to looking into 
GHC's guts.  All of darcs is written as .lhs files which have bizarre mark-up in them 
which distracts me from the actual Haskell source I'm trying to figure out and get used 
to.  Apparently the GHC compiler can take .lhs files, strip them with unlit 
(a utility which I finally found buried deep in the GHC installation -- off-path) and 
then compile them normally.  The problem I have is that unlit leaves behind instead these 
huge gaping (and highly distracting) stretches of whitespace while it takes out the 
markup.

 Are there any tools which I can use to render .lhs files readable?  I'm fine 
with having them converted into documented source (i.e. source code embedded in 
documentation) or as pure Haskell source (but without the huge whitespace gaps) 
-- but I can't figure out how to get either.


Assuming that it's LaTeX-based literate source, you usually run
pdflatex on it to get a pdf of the code, but I'm not familiar with the
darcs code in particular, and whether anything special needs to be
done, or whether they have a specialised build for that.

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