Re: [Haskell-cafe] Literal programming in Haskell with rst-literals

2008-06-23 Thread Abhay Parvate
Hello,

You might already know this, but in case you don't: there is another
literate style:

... non-code ...
\begin{code}
... code ...
\end{code}
... non-code ...

in which you do not put prefixes to each line. (In fact the standard says
somewhere it is not recommended to mix the two styles if I remember right.)

I hope I am not being redundant!
Abhay


On Sat, Jun 21, 2008 at 11:48 PM, Martin Blais [EMAIL PROTECTED] wrote:


 Hello Haskell community!

 I just did a marginally cool thing and I wanted to share it
 with you.

 rst-literals is a small program I wrote a while ago in
 order to write documents in reStructuredText format that
 would embed SQL code for data models in them, a form of
 literal programming for SQL if you will; I would describe my
 needs for the schema in prose, and reST literal-blocks were
 used to embed SQL code, blocks that look like this::

  CLASS Employee (
 firstname VARCHAR,
 lastname VARCHAR
  )

 I wrote the script to be entirely generic: it parses the
 reST documents using the docutils code and outputs only the
 literal-blocks, with indentation removed; you can then run
 your favourite interpreter/compiler on the result (in that
 case, psql to initialize a database).

 Recently, while experimenting with Haskell, I started using
 both the literal (.lhs) and non-literal (.hs) styles of
 Haskell input, and I found the literal style a bit
 unpleasant to use, in particular, I don't like to have to
 prefix every line of code I write, despite the help that
 Emacs' haskell-mode provides.

 So I tried pulling a similar trick and embedding Haskell
 code in literal-blocks within reST documents, extracting
 that code using rst-literals, and it turns out that it works
 like a charm. Here is an example makefile for doing this::

  .SUFFIXES: .rst .hs

  all: chap6

  .rst.hs:
  rst-literals $  $@

  chap6: chap6.hs
  ghc --make chap6.hs

 An example reST document with some embedded Haskell code
 follows this email. Note that since rst-literals is using
 the docutils parser, you can make use of all of the
 recursive reST syntax, sections, bulleted items and much
 more. Only the literal-blocks are extracted, anywhere they
 appear. You can also easily process the reST source into
 HTML pages or LaTeX documents using the tools that come with
 docutils.

 You can find rst-literals here:
 http://furius.ca/pubcode/

 Enjoy,




 --
 Martin

 P.S. If there is a way to output cpp-like directives for
 GHC, like #line filename lineno, it would be easy to
 modify rst-literals to generate those, so that compilation
 errors could refer to the source reST document instead of
 the extracted source.



 chap6.hs:
 --

 ===
   Exercises from Hutton book, Chapter 6
 ===

 .. contents::
 ..
1  Introduction
2  Exercise 1
3  Exercise 2
4  Exercise 3
5  Exercise 4
6  Exercise 5
7  Exercise 6


 Introduction
 

 Bla bla bla blablablablablabla bla bla blabla. Bla bla bla
 blablablablablabla bla bla blabla. Bla bla bla blablablablablabla bla
 bla blabla. Bla bla bla blablablablablabla bla bla blabla. Bla bla bla
 blablablablablabla bla bla blabla. Bla bla bla blablablablablabla bla
 bla blabla.


 Exercise 1
 ==
 ::

  myexp :: Int - Int - Int
  myexp b 0 = 1
  myexp b (n+1) = b * (myexp b n)


 Exercise 2
 ==

 (Exercise 2 consisted in derivations, so we mark the literal
 blocks as another type of block with #!example, so that
 they don't get included in the output when only the
 default literal blocks get extracted. See rst-literals
 docstring for details.)

 Length::

#!example
1 + (length [2, 3])
1 + 1 + (length [3])
1 + 1 + (1)
3

 Drop::

  #!example
  drop 3 [1, 2, 3, 4, 5]
  [] ++ drop 3 [2, 3, 4, 5]
  [] ++ [] ++ drop 3 [3, 4, 5]
  [] ++ [] ++ [] ++ [4, 5]
  [4, 5]

 Init::

  #!example
  init [1, 2, 3]
  [1] ++ init [2, 3]
  [1] ++ [2] ++ init [3]
  [1] ++ [2] ++ []
  [1, 2]


 Exercise 3
 ==

 These are alternate versions of the example functions defined in the
 text::

  and' :: [Bool] - Bool
  and' [x] = x
  and' (x:xs) = x  and' xs

  concat' :: [[a]] - [a]
  concat' [] = []
  concat' (x:xs) = x ++ concat' xs

  replicate' :: Int - a - [a]
  replicate' 0 x = []
  replicate' (n+1) x = (x : replicate' n x)

  select' :: [a] - Int - a
  select' (x:xs) 0 = x
  select' (x:xs) (n+1) = select' xs n

  elem' :: Eq a = a - [a] - Bool
  elem' _ [] = False
  elem' y (x:xs) | x == y = True
 | otherwise = elem' y xs

 Exercise 4
 ==

 The exercise asked to implement a function to merge two lists::

  merge :: Ord a = [a] - [a] - [a]
  merge xs [] = xs
  merge [] xs = xs
  merge (x:xs) (y:ys) | x  y = (x : merge xs (y:ys))
  | otherwise = (y : merge (x:xs) ys)


 Exercise 5
 ==
 ::

  msort :: Ord a = [a] - 

Re: [Haskell-cafe] Lazy IO.

2008-06-16 Thread Abhay Parvate
hGetContents reads the entire contents of the stream till the end (although
lazily). The return value of hGetContents is logically the entire contents
of the stream. That it has not read it completely is only a part of its
laziness, so the result does not depend upon when the caller stops consuming
the result. That is why the handle is semi-closed; logically the handle is
already at the end of the stream.

A complete parser to parse the header and the body has to be used on the
entire contents, or some function which knows how to find the header end and
stop there has to be used.

Regards,
Abhay

On Sat, Jun 14, 2008 at 9:48 PM, Sebastiaan Visser [EMAIL PROTECTED]
wrote:

 Hi,

 I've got a question about lazy IO in Haskell. The most well known
 function to do lazy IO is the `hGetContents', which lazily reads all the
 contents from a handle and returns this as a regular [Char].

 The thing with hGetContents is that is puts the Handle in a semi-closed
 state, no one can use the handle anymore. This behaviour is
 understandable from the point of safety; it is not yet determined when
 the result of hGetContents will actually be computed, using the handle
 in the meantime is undesirable.

 The point is, I think I really have a situation in which I want to use
 the handle again `after' a call to hGetContents. I think I can best
 explain this using a code example.

  readHttpMessage :: IO (Headers, Data.ByteString.Lazy.ByteString)
  readHttpMessage = do
myStream - accept http connection from client
request - hGetContents myStream
header - parseHttpHeader request
bs - Data.ByteString.Lazy.hGetContents myStream
return (header, body)

 The Data.ByteString.Lazy.hGetContents in the example above obviously
 fails because the handle is semi-closed.

 So, what I am trying to do here is apply a parser (on that consumes
 Char's) to the input stream until it has succeeded. After this I want to
 collect the remainings of the stream in a lazy ByteString, or maybe even
 something else.

 I tried to open the handler again using some internal handle hackery,
 but this failed (luckily). In the module GHC.IO there is a function
 `lazyRead' that more or less seems to do what I want. But I'll guess
 there is a good reason for not exporting it.

 Does anyone know a pattern in which I can do this easily?

 Thanks,

 --
 Sebastiaan

 ___
 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] Re: appending an element to a list

2008-06-01 Thread Abhay Parvate
I somehow thought it would be easy to talk about complexity of calculating
individual elements in an infinite list should be sufficient, but that seems
to be involved, and my over-generalization doesn't seem to work. Thanks for
the link; particularly it has reference to Wadler's papers exactly on this
problem.

Abhay

On Sun, Jun 1, 2008 at 1:07 PM, apfelmus [EMAIL PROTECTED] wrote:

 Tillmann Rendel wrote:

 Abhay Parvate wrote:

 I think I would like to make another note: when we talk about the
 complexity
 of a function, we are talking about the time taken to completely evaluate
 the result. Otherwise any expression in haskell will be O(1), since it
 just creates a thunk.


 I don't like this notion of complexity, since it seems not very suited for
 the analysis of composite expression in Haskell.

 Is this intuitive view generalizable to arbitrary datatypes (instead of
 lists) and formalized somewhere?


 See also the thread section beginning with

  http://thread.gmane.org/gmane.comp.lang.haskell.cafe/34398/focus=34435



 Regards,
 apfelmus


 ___
 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] Re: appending an element to a list

2008-05-30 Thread Abhay Parvate
I think I would like to make another note: when we talk about the complexity
of a function, we are talking about the time taken to completely evaluate
the result. Otherwise any expression in haskell will be O(1), since it just
creates a thunk.
And then the user of the program is to be blamed for running the program,
since that is what caused evaluation of those thunks :)


Abhay

2008/5/31 Martin Geisler [EMAIL PROTECTED]:

 Tillmann Rendel [EMAIL PROTECTED] writes:

 Hi! (Cool, another guy from DAIMI on haskell-cafe!)

  Another (n - 1) reduction steps for the second ++ to go away.
 
  last (o ++ l)
  A)  ~  last ('o' :  ++ l))
  L)  ~  last ( ++ l)
  A)  ~  last (l)
  L)  ~  'l'
 
  And the third and fourth ++ go away with (n - 2) and (n - 3) reduction
  steps. Counting together, we had to use
 
n + (n - 1) + (n - 2) + ... = n!
 
  reduction steps to get rid of the n calls to ++, which lies in O(n^2).
  Thats what we expected of course, since we know that each of the ++
  would need O(n) steps.

 I really liked the excellent and very clear analysis! But the last
 formula should be:

   n + (n - 1) + (n - 2) + ... = n * (n+1) / 2

 which is still of order n^2.

 --
 Martin Geisler

 VIFF (Virtual Ideal Functionality Framework) brings easy and efficient
 SMPC (Secure Multi-Party Computation) to Python. See: http://viff.dk/.

 ___
 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] appending an element to a list

2008-05-29 Thread Abhay Parvate
On Thu, May 29, 2008 at 11:48 PM, Tillmann Rendel [EMAIL PROTECTED]
wrote:



 Adrian Neumann wrote:

 Hello,

 I was wondering how expensive appending something to a list really is. Say
 I write

 I'd say longList ++ [5] stays unevaluated until I consumed the whole
 list and then appending should go in O(1). Similarly when concatenating two
 lists.

 Is that true, or am I missing something?


 I think that is true and you are missing something: You have to push the
 call to ++ through the whole longList while consuming it wholy one element
 at a time! So when longList has n elements, you have (n+1) calls of ++, each
 returning after O(1) steps. The first n calls return a list with the ++
 pushed down, and the last returns [5]. Summed together, that makes O(n)
 actual calls of ++ for one written by the programmer.

  Tillmann


In other words, if you look at the prototype of ++ given in the prelude, it
generates a new list with first (length longList) elements same as those of
longList, followed by the second list. So when you are accessing elements of
(longList ++ s), you are actually accessing the elements of this newly
generated list, which are generated as and when you access them, so that by
the time you reach the first element of s, you have generated (length
longList) elements of the result of ++.



 ___
 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] Type Coercion

2008-05-28 Thread Abhay Parvate
To add to this: There are other constants which are polymorphic, not only
numbers. Examples where you could add type signatures to make the type
explicit are the empty list '[]' and the 'Nothing' constructor of 'Maybe a'.
Adding type signatures to these will not be type casts, but telling the
compiler that you want to specialize the given polymorphic entity.

Abhay


On Wed, May 28, 2008 at 1:27 PM, Salvatore Insalaco [EMAIL PROTECTED]
wrote:

 2008/5/28 PR Stanley [EMAIL PROTECTED]:
  Hi
  (16 :: Float) is a perfectly legitimate statement although I'm surprised
  that it's allowed in a type strong language such as Haskell. It's a bit
 like
  casting in good old C. What's going on here?

 Don't worry: it's not a cast.
 Numeric constants like 16 in Haskell have polymorphic types:
 Prelude :t 16
 16 :: (Num t) = t
 Prelude :t 16.6
 16.6 :: (Fractional t) = t

 Writing 16 :: Float you are simply making the type explicit, and you
 can do it only in the context of the typeclass.

 Prelude :t (16 :: Integer)
 (16 :: Integer) :: Integer

 This works because Integer is a type of the typeclass Num, but:
 Prelude :t (16.5 :: Integer)
 interactive:1:1:
No instance for (Fractional Integer)
  arising from the literal `16.5' at interactive:1:1-4
Possible fix: add an instance declaration for (Fractional Integer)

 This doesn't work. So everything is done at compile time, no casting
 (i.e. believe me compiler, this it a Float) involved.

 Notice that during binding the numeric constants' type is always made
 explicit (if you want to know more, look for section 4.3.4 in the
 Haskell Report):
 Prelude let a = 3
 Prelude :t a
 a :: Integer

 Prelude let b = 3.3
 Prelude :t b
 b :: Double

 Prelude b :: Float
 interactive:1:0:
Couldn't match expected type `Float' against inferred type `Double'
In the expression: b :: Float
In the definition of `it': it = b :: Float


 Salvatore
 ___
 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] elem of infinite set of tuple

2008-05-16 Thread Abhay Parvate
It's not exactly a question of Haskell's behaviour. The list [ (a,b) | a -
[0..], b - [0..] ]
is such that apart from pairs starting with zero, no other pair is
associated with a finite index. In other words, [ (a,b) | a - [0..], b -
[0..] ] is not a correct 'enumeration' of all pairs of nonnegative integers.
You need to reorder them if you need a finite index associated with every
pair.

On Fri, May 16, 2008 at 5:12 PM, leledumbo [EMAIL PROTECTED]
wrote:


 I don't know how Haskell should behave on this. Consider this function:
 elemOf (x,y) = (x,y) `elem` [ (a,b) | a - [0..], b - [0..] ]

 If I try to query elemOf (1,1), the program keeps searching and searching
 but it never makes it. But if I query elemOf (0,1) (or anything as long as
 the first element is 0), it can find it easily. I wonder how it's handled.

 From my point of view, instead of starting from (1,0), the program starts
 from (0,0), which will never finish since the limit of the second element
 is
 infinite.
 --
 View this message in context:
 http://www.nabble.com/elem-of-infinite-set-of-tuple-tp17272802p17272802.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.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] Short circuiting and the Maybe monad

2008-05-13 Thread Abhay Parvate
Yes, I had always desired that the operator = should have been right
associative for this short cut even when written without the 'do' notation.

On Tue, May 13, 2008 at 3:39 AM, John Hamilton [EMAIL PROTECTED] wrote:

 I'm trying to understand how short circuiting works with the Maybe monad.
 Take the expression n = f = g = h, which can be written as
 (((n = f) = g) = h) because = is left associative.  If n is
 Nothing, this implies that (n = f) is Nothing, and so on, each nested
 sub-expression easily evaluating to Nothing, but without there being a
 quick way to short circuit at the beginning.

 Now take the example

   do x - xs
  y - ys
  z - zs
  return (x, y, z)

 which I believe desugars like

xs = (\x - ys = (\y - zs = (\z - return (x, y, z

 Here the associativity of = no longer matters, and if xs is Nothing the
 whole expression can quickly be determined to be Nothing, because Nothing
 = _ = Nothing.  Am I looking at this correctly?

 - John
 ___
 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] GHC predictability

2008-05-13 Thread Abhay Parvate
I don't know why, but perhaps beginners may expect too much from the
laziness, almost to the level of magic (me too, in the beginning!). In an
eager language, a function like

mean :: (Fractional a) = [a] - a

expects the *whole* list before it can calculate the mean, and the question
of the 'mean' function consuming memory does not arise. We look for other
methods of finding the mean of very long lists. We do not expect such a
function in C or Scheme to succeed when the number of numbers is more than
that can fit the memory. (It will not even be called; the list creation
itself will not succeed.) Lazy languages allow us to use the same
abstraction while allowing doing more. But it is not magic, it is plain
normal order evaluation. Just as every Scheme programmer or C programmer
must understand the consequences of the fact that the arguments to a
function will be evaluated first, a Haskell programmer must understand the
consequences of the fact that the arguments to a function will be evaluated
only when needed/forced. Perhaps an early emphasis on an understanding of
normal order evaluation is needed while learning Haskell in order to stop
expecting magic, especially when one comes prejudiced from eager languages.

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


Re: [Haskell-cafe] GHC predictability

2008-05-12 Thread Abhay Parvate
As a beginner, I had found the behaviour quite unpredictable. But with time
I found that I could reason out the behaviour with my slowly growing
knowledge of laziness. I don't spot all the places in my program that will
suck while writing a program, but post facto many things become clear. (And
then there is the profiler!)

GHC's internal details had been never necessary to me! I aspire to write
computationally heavy programs in haskell in future, and I have been
successful in reaching factors of 3 to 5 with C programs (though I have not
been upto factors of 1 for which I find claims here and there) without any
knowledge of GHC internals. But the GHC user guide is immensely valuable.

I would like to note that beginners' codes are many times time/memory
consuming even in slighly complicated cases, and it may be a big source of
frustration and turn-away if they don't stick up and pursue. This is not a
problem of GHC, or even Haskell; it generally applies to functional
programming.

These are my opinions; I am only an advanced beginner :)

2008/5/10 Jeff Polakow [EMAIL PROTECTED]:


 Hello,

 One frequent criticism of Haskell (and by extension GHC) is that it has
 unpredictable performance and memory consumption. I personally do not find
 this to be the case. I suspect that most programmer confusion is rooted in
 shaky knowledge of lazy evaluation; and I have been able to fix, with
 relative ease, the various performance problems I've run into. However I am
 not doing any sort of performance critical computing (I care about minutes
 or seconds, but not about milliseconds).


 I would like to know what others think about this. Is GHC predictable? Is a
 thorough knowledge of lazy evaluation good enough to write efficient
 (whatever that means to you) code? Or is intimate knowledge of GHC's innards
 necessary?

 thanks,
   Jeff

 PS I am conflating Haskell and GHC because I use GHC (with its extensions)
 and it produces (to my knowledge) the fastest code.

 ---

 This e-mail may contain confidential and/or privileged information. If you
 are not the intended recipient (or have received this e-mail in error)
 please notify the sender immediately and destroy this e-mail. Any
 unauthorized copying, disclosure or distribution of the material in this
 e-mail is strictly forbidden.
 ___
 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] Re: Control.Exception.evaluate - 'correct definition' not so correct

2008-05-08 Thread Abhay Parvate
Thanks both for the the explanation and the link. The wikibook is really
growing fast!

Abhay

On Wed, May 7, 2008 at 5:05 PM, apfelmus [EMAIL PROTECTED] wrote:

 Abhay Parvate wrote:

  Just for curiocity, is there a practically useful computation that uses
  'seq' in an essential manner, i.e. apart from the efficiency reasons?
 

 I don't think so because you can always replace  seq  with  const id .
 In fact, doing so will get you more results, i.e. a computation that
 did not terminate may do so now.

 In other words, we have

  seq _|_ = _|_
  seq x   = idfor  x  _|_

 but

  (const id) _|_ = id
  (const id) x   = id   for  x  _|_

 So, (const id) is always more defined () than  seq  .


 For more about _|_ and the semantic approximation order, see

  http://en.wikibooks.org/wiki/Haskell/Denotational_semantics



 Regards,
 apfelmus


 ___
 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] Re: Control.Exception.evaluate - 'correct definition' not so correct

2008-05-07 Thread Abhay Parvate
Just for curiocity, is there a practically useful computation that uses
'seq' in an essential manner, i.e. apart from the efficiency reasons?

Abhay

On Wed, May 7, 2008 at 2:48 PM, apfelmus [EMAIL PROTECTED] wrote:

 Luke Palmer wrote:

  It seems that there is a culture developing where people intentionally
  ignore the existence of seq when reasoning about Haskell.  Indeed I've
  heard many people argue that it shouldn't be in the language as it is
  now, that instead it should be a typeclass.
 
  I wonder if it's possible for the compiler to do more aggressive
  optimizations if it, too, ignored the existence of seq.  Would it make
  it easier to do various sorts of lambda lifting, and would it make
  strictness analysis easier?
 

 The introduction of  seq  has several implications.

 The first problem is that parametricity would dictate that the only
 functions of type

   forall a,b. a - b - b

 are

   const id
   const _|_
   _|_

 Since  seq  is different from these, giving it this polymorphic type
 weakens parametricity. This does have implications for optimizations, in
 particular for fusion, see also

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

 Parametricity can be restored with a class constraint

  seq :: Eval a = a - b - b

 In fact, that's how Haskell 1.3 and 1.4 did it.


 The second problem are function types. With  seq  on functions,
 eta-expansion is broken, i.e. we no longer have

  f = \x.f x

 because  seq  can be used to distinguish

  _|_  and  \x. _|_

 One of the many consequences of this is that simple laws like

  f = f . id

 no longer hold, which is a pity.


 But then again, _|_ complicates reasoning anyway and we most often pretend
 that we are only dealing with total functions. Unsurprisingly, this usually
 works. This can even be justified formally to some extend, see also

  N.A.Danielsson, J.Hughes, P.Jansson, J.Gibbons.
  Fast and Loose Reasoning is Morally Correct.

 http://www.comlab.ox.ac.uk/people/jeremy.gibbons/publications/fast+loose.pdf


 Regards,
 apfelmus


 ___
 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] A common pattern

2008-05-05 Thread Abhay Parvate
Hi Andrew,

I don't know whether it's intentional, but the patterns for case line of
are not exaustive. Are you sure you do not expect anything else apart from a
single . or a line starting with '#'?

More below:

On Mon, May 5, 2008 at 1:45 PM, Andrew Coppin [EMAIL PROTECTED]
wrote:

 Neil Mitchell wrote:

  hGetContents might be a different way to write a similar thing:
 
  read_args h = do
  src - hGetContents h
  let (has,rest) = span (# `isPrefixOf`) $ lines src
  return (map tail has)
 
  Of course, depending on exactly the kind of IO control you need to do,
  it may not work.
 

 Please correct me if I am wrong; but the rest of the contents from the
handle h will be unavailable after the evaluation of this function: it goes
into a semi-closed state. (Correctly so: 'src' is supposed to have the
entire contents obtained from h if needed.)

Another minor observation: if the partial pattern in the original code was
intentional, then this is not exactly the same.

what about

read_args' :: [String] - ([String],[String])
read_args' src = span (# `isPrefixOf`) $ lines src

and then using

s - hGetContents
let (arg, rest) = read_args' $ lines s
...

So that you can get both the result and the remaining list of lines, in case
you need them. Again, this does not exactly stop where there is a . on a
single line; it stops as soon as it gets a line without a '#'.

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


Re: Re[2]: [Haskell-cafe] GC'ing file handles and other resources

2008-04-16 Thread Abhay Parvate
I am not saying that it should claim it as soon as it is unused; all I am
saying that as soon as a priority object becomes unreferenced, it should be
the first choice for collecting in the next collect.
Further I was under the impression (I may be wrong) that it uses a
generational GC and therefore scans allocated memory incrementally; not the
whole at a time. Please correct me if I am wrong.

Regards,
Abhay

On Wed, Apr 16, 2008 at 11:55 AM, Bulat Ziganshin [EMAIL PROTECTED]
wrote:

 Hello Abhay,

 Wednesday, April 16, 2008, 9:30:34 AM, you wrote:

 i think it will not work with current ghc GC - it scans entire
 memory/nursery when garbage collected so anyway you will need to wait
 until next GC event occurs

  Your mail gives me an idea, though I am not an iota familiar with
  compiler/garbage collector internals. Can we have some sort of
  internally maintained priority associated with allocated objects?
  The garbage collector should look at these objects first when it
  tries to free anything. The objects which hold other system
  resources apart from memory, such as file handles, video memory, and
  so on could be allocated as higher priority objects. Is such a thing
 possible?
 
  2008/4/16 Conal Elliott [EMAIL PROTECTED]:
   Are Haskell folks satisfied with the practical necessity of
  imperatively  explicitly reclaiming resources such as file handles,
  fonts  brushes, video memory chunks, etc?  Doesn't explicit freeing
  of these resources have the same modularity and correctness problems
  as explicit freeing of system memory (C/C++ programming)?
 
  I wrote a lovely purely functional graphics library that used video
  memory to lazily compute and cache infinite-resolution images, and I
  found that I don't know how to get my finalizers to run anytime soon
  after video memory chunks become inaccessible.  Explicit freeing
  isn't an option, since the interface is functional, not imperative (IO).
 
  I guess I'm wondering a few things:

  * Are Haskell programmers generally content with imperative and
  bug-friendly interfaces involving explicit freeing/closing of resources?
  * Do people assume that these resources (or handling them frugally)
  aren't useful in purely functional interfaces?
   * Are there fundamental reasons why GC algorithms cannot usefully
  apply to resources like video memory, file descriptors, etc?
  * Are there resource management techniques that have the
  flexibility, efficiency, and accuracy of GC that I could be using for
 these other resources?
 
  Thanks,
- Conal

  2008/4/14 Abhay Parvate [EMAIL PROTECTED]:
   Hello,

  In describing the Handle type, the GHC documentation says (in the
 System.IO documentation):

  GHC note: a Handle will be automatically closed when the garbage
  collector detects that it has become unreferenced by the program.
  However, relying on this behaviour is not generally recommended:
  the garbage collector is unpredictable.  If possible, use explicit
  an explicit hClose to close Handles when they are no longer
  required.  GHC does not currently attempt to free up file
  descriptors when they have run out, it is your responsibility to  ensure
 that this doesn't happen.

  But one cannot call hClose on Handles on which something like
  hGetContents has been called; it just terminates the character list
  at the point till which it has already read. Further the manual says
  that hGetContents puts the handle in the semi-closed state, and further,
 
  A semi-closed handle becomes closed:
   if hClose is applied to it;  if an I/O error occurs when reading
  an item from the handle;  or once the entire contents of the handle has
 been read.
  So do I safely assume here, according to the third point above,
  that it's fine if I do not call hClose explicitly as far as I am
  consuming all the contents returned by hGetContents?

  Thanks,
  Abhay
 
  ___
   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
 


 


 --
 Best regards,
  Bulatmailto:[EMAIL PROTECTED]


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


Re: Re[4]: [Haskell-cafe] GC'ing file handles and other resources

2008-04-16 Thread Abhay Parvate
Thanks, both for the summary and for the link. Will try to go through it.

Regards,
Abhay

On Wed, Apr 16, 2008 at 12:37 PM, Bulat Ziganshin [EMAIL PROTECTED]
wrote:

 Hello Abhay,

 Wednesday, April 16, 2008, 10:51:07 AM, you wrote:

  I am not saying that it should claim it as soon as it is unused;
  all I am saying that as soon as a priority object becomes
  unreferenced, it should be the first choice for collecting in the next
 collect.

 on the GC, all unreferenced objects are collected. there is no
 difference which ones will be collected first - anyway program is
 stopped until whole GC will be finished

  Further I was under the impression (I may be wrong) that it uses a
  generational GC and therefore scans allocated memory incrementally;
  not the whole at a time. Please correct me if I am wrong.

 yes, it uses generational GC. data are first allocated in small 256k block
 and when it is filled, GC for this small block occurs. data that are
 still alive then moved to the global heap. this minor GC doesn't scan
 global heap. if it will do this, each minor GC will become as slow as
 major ones

 Generational garbage collection for Haskell
 http://research.microsoft.com/~simonpj/Papers/gen-gc-for-haskell.ps.gzhttp://research.microsoft.com/%7Esimonpj/Papers/gen-gc-for-haskell.ps.gz

 
  Regards,
  Abhay

  On Wed, Apr 16, 2008 at 11:55 AM, Bulat Ziganshin
  [EMAIL PROTECTED] wrote:
   Hello Abhay,
 
   Wednesday, April 16, 2008, 9:30:34 AM, you wrote:
 
   i think it will not work with current ghc GC - it scans entire
   memory/nursery when garbage collected so anyway you will need to wait
   until next GC event occurs
 

   Your mail gives me an idea, though I am not an iota familiar with
   compiler/garbage collector internals. Can we have some sort of
   internally maintained priority associated with allocated objects?
   The garbage collector should look at these objects first when it
   tries to free anything. The objects which hold other system
   resources apart from memory, such as file handles, video memory, and
   so on could be allocated as higher priority objects. Is such a thing
 possible?
  
   2008/4/16 Conal Elliott [EMAIL PROTECTED]:
Are Haskell folks satisfied with the practical necessity of
   imperatively  explicitly reclaiming resources such as file handles,
   fonts  brushes, video memory chunks, etc?  Doesn't explicit freeing
   of these resources have the same modularity and correctness problems
   as explicit freeing of system memory (C/C++ programming)?
  
   I wrote a lovely purely functional graphics library that used video
   memory to lazily compute and cache infinite-resolution images, and I
   found that I don't know how to get my finalizers to run anytime soon
   after video memory chunks become inaccessible.  Explicit freeing
   isn't an option, since the interface is functional, not imperative
 (IO).
  
   I guess I'm wondering a few things:
 
   * Are Haskell programmers generally content with imperative and
   bug-friendly interfaces involving explicit freeing/closing of
 resources?
   * Do people assume that these resources (or handling them frugally)
   aren't useful in purely functional interfaces?
* Are there fundamental reasons why GC algorithms cannot usefully
   apply to resources like video memory, file descriptors, etc?
   * Are there resource management techniques that have the
   flexibility, efficiency, and accuracy of GC that I could be using for
 these other resources?
  
   Thanks,
 - Conal
 
   2008/4/14 Abhay Parvate [EMAIL PROTECTED]:
Hello,
 
   In describing the Handle type, the GHC documentation says (in the
 System.IO documentation):
 
   GHC note: a Handle will be automatically closed when the garbage
   collector detects that it has become unreferenced by the program.
   However, relying on this behaviour is not generally recommended:
   the garbage collector is unpredictable.  If possible, use explicit
   an explicit hClose to close Handles when they are no longer
   required.  GHC does not currently attempt to free up file
   descriptors when they have run out, it is your responsibility to
  ensure that this doesn't happen.
 
   But one cannot call hClose on Handles on which something like
   hGetContents has been called; it just terminates the character list
   at the point till which it has already read. Further the manual says
   that hGetContents puts the handle in the semi-closed state, and
 further,
  
   A semi-closed handle becomes closed:
if hClose is applied to it;  if an I/O error occurs when reading
   an item from the handle;  or once the entire contents of the handle
 has been read.
   So do I safely assume here, according to the third point above,
   that it's fine if I do not call hClose explicitly as far as I am
   consuming all the contents returned by hGetContents?
 
   Thanks,
   Abhay
  
   ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] semi-closed handles

2008-04-15 Thread Abhay Parvate
Thanks! I was worried about how/where would I place hClose!

On Mon, Apr 14, 2008 at 10:58 PM, Brent Yorgey [EMAIL PROTECTED] wrote:


 2008/4/14 Abhay Parvate [EMAIL PROTECTED]:

 Hello,
 
  In describing the Handle type, the GHC documentation says (in the
  System.IO documentation):
 
  GHC note: a Handle will be automatically closed when the garbage
  collector detects that it has become unreferenced by the program. However,
  relying on this behaviour is not generally recommended: the garbage
  collector is unpredictable. If possible, use explicit an explicit hClose to
  close Handles when they are no longer required. GHC does not currently
  attempt to free up file descriptors when they have run out, it is your
  responsibility to ensure that this doesn't happen.
 
  But one cannot call hClose on Handles on which something like
  hGetContents has been called; it just terminates the character list at the
  point till which it has already read. Further the manual says that
  hGetContents puts the handle in the semi-closed state, and further,
 
  A semi-closed handle becomes closed:
 
 - if hClose is applied to it;
 - if an I/O error occurs when reading an item from the handle;
 - or once the entire contents of the handle has been read.
 
  So do I safely assume here, according to the third point above, that
  it's fine if I do not call hClose explicitly as far as I am consuming all
  the contents returned by hGetContents?
 

 Yes, not only is it fine, it's recommended!  Calling hClose explicitly on
 a handle after calling hGetContents is a sure way to introduce bugs.

 -Brent


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


Re: [Haskell-cafe] semi-closed handles

2008-04-15 Thread Abhay Parvate
Thanks Ryan, this will definitely not leak handles. I had thought about
making a strict version of hGetContents, though on a bit different lines.

My question was that since the documentation says that the semi-closed
handle becomes closed as soon as the entire contents have been read; can I
conclude that as far as I consume the string, I am not leaking handles?

I am still interested in using hGetContents, since these contents are going
soon through hPutStr, which will consume it anyway. And hGetContents being
lazy will not occupy memory of the order of size of the input file. That's
why the question.

Regards,
Abhay

On Tue, Apr 15, 2008 at 1:07 PM, Ryan Ingram [EMAIL PROTECTED] wrote:

 I usually use something like this instead:

 hStrictGetContents :: Handle - IO String
 hStrictGetContents h = do
s - hGetContents h
length s `seq` hClose h
return s

 This guarantees the following:
 1) The whole file is read before hStrictGetContents exits (could be
 considered bad, but usually it's The Right Thing)
 2) You guarantee that you don't leak file handles (good benefit!)

 A slightly better version:

 import qualified Data.ByteString.Char8 as B

 hStrictGetContents :: Handle - IO String
 hStrictGetContents h = do
bs - B.hGetContents h
hClose h -- not sure if this is required; ByteString documentation
 isn't clear.
return $ B.unpack bs -- lazy unpack into String

 This saves a ton of memory for big reads; a String is ~12 bytes per
 character, this is only 1 byte per character + fixed overhead.  Then,
 assuming the function consuming the String doesn't leak, you'll end up
 with a much smaller space requirement.

  -- ryan

 2008/4/14 Abhay Parvate [EMAIL PROTECTED]:
  Thanks! I was worried about how/where would I place hClose!
 
 
 
  On Mon, Apr 14, 2008 at 10:58 PM, Brent Yorgey [EMAIL PROTECTED]
 wrote:
  
  
   2008/4/14 Abhay Parvate [EMAIL PROTECTED]:
  
  
  
  
Hello,
   
In describing the Handle type, the GHC documentation says (in the
  System.IO documentation):
   
   
GHC note: a Handle will be automatically closed when the garbage
  collector detects that it has become unreferenced by the program.
 However,
  relying on this behaviour is not generally recommended: the garbage
  collector is unpredictable. If possible, use explicit an explicit hClose
 to
  close Handles when they are no longer required. GHC does not currently
  attempt to free up file descriptors when they have run out, it is your
  responsibility to ensure that this doesn't happen.
   
But one cannot call hClose on Handles on which something like
  hGetContents has been called; it just terminates the character list at
 the
  point till which it has already read. Further the manual says that
  hGetContents puts the handle in the semi-closed state, and further,
   
   
A semi-closed handle becomes closed:
   
if hClose is applied to it;
if an I/O error occurs when reading an item from the handle;
or once the entire contents of the handle has been read. So do I
 safely
  assume here, according to the third point above, that it's fine if I do
 not
  call hClose explicitly as far as I am consuming all the contents
 returned by
  hGetContents?
   
  
  
   Yes, not only is it fine, it's recommended!  Calling hClose explicitly
 on
  a handle after calling hGetContents is a sure way to introduce bugs.
  
   -Brent
  
  
 
 
  ___
   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] GC'ing file handles and other resources

2008-04-15 Thread Abhay Parvate
Your mail gives me an idea, though I am not an iota familiar with
compiler/garbage collector internals. Can we have some sort of internally
maintained priority associated with allocated objects? The garbage collector
should look at these objects first when it tries to free anything. The
objects which hold other system resources apart from memory, such as file
handles, video memory, and so on could be allocated as higher priority
objects. Is such a thing possible?

2008/4/16 Conal Elliott [EMAIL PROTECTED]:

 Are Haskell folks satisfied with the practical necessity of imperatively 
 explicitly reclaiming resources such as file handles, fonts  brushes, video
 memory chunks, etc?  Doesn't explicit freeing of these resources have the
 same modularity and correctness problems as explicit freeing of system
 memory (C/C++ programming)?

 I wrote a lovely purely functional graphics library that used video memory
 to lazily compute and cache infinite-resolution images, and I found that I
 don't know how to get my finalizers to run anytime soon after video memory
 chunks become inaccessible.  Explicit freeing isn't an option, since the
 interface is functional, not imperative (IO).

 I guess I'm wondering a few things:

 * Are Haskell programmers generally content with imperative and
 bug-friendly interfaces involving explicit freeing/closing of resources?
 * Do people assume that these resources (or handling them frugally) aren't
 useful in purely functional interfaces?
 * Are there fundamental reasons why GC algorithms cannot usefully apply to
 resources like video memory, file descriptors, etc?
 * Are there resource management techniques that have the flexibility,
 efficiency, and accuracy of GC that I could be using for these other
 resources?

 Thanks,
   - Conal

 2008/4/14 Abhay Parvate [EMAIL PROTECTED]:

  Hello,
 
  In describing the Handle type, the GHC documentation says (in the
  System.IO documentation):
 
  GHC note: a Handle will be automatically closed when the garbage
  collector detects that it has become unreferenced by the program. However,
  relying on this behaviour is not generally recommended: the garbage
  collector is unpredictable. If possible, use explicit an explicit hClose to
  close Handles when they are no longer required. GHC does not currently
  attempt to free up file descriptors when they have run out, it is your
  responsibility to ensure that this doesn't happen.
 
  But one cannot call hClose on Handles on which something like
  hGetContents has been called; it just terminates the character list at the
  point till which it has already read. Further the manual says that
  hGetContents puts the handle in the semi-closed state, and further,
 
  A semi-closed handle becomes closed:
 
 - if hClose is applied to it;
 - if an I/O error occurs when reading an item from the handle;
 - or once the entire contents of the handle has been read.
 
  So do I safely assume here, according to the third point above, that
  it's fine if I do not call hClose explicitly as far as I am consuming all
  the contents returned by hGetContents?
 
  Thanks,
  Abhay
 
  ___
  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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] semi-closed handles

2008-04-14 Thread Abhay Parvate
Hello,

In describing the Handle type, the GHC documentation says (in the System.IO
documentation):

GHC note: a Handle will be automatically closed when the garbage collector
detects that it has become unreferenced by the program. However, relying on
this behaviour is not generally recommended: the garbage collector is
unpredictable. If possible, use explicit an explicit hClose to close Handles
when they are no longer required. GHC does not currently attempt to free up
file descriptors when they have run out, it is your responsibility to ensure
that this doesn't happen.

But one cannot call hClose on Handles on which something like hGetContents
has been called; it just terminates the character list at the point till
which it has already read. Further the manual says that hGetContents puts
the handle in the semi-closed state, and further,

A semi-closed handle becomes closed:

   - if hClose is applied to it;
   - if an I/O error occurs when reading an item from the handle;
   - or once the entire contents of the handle has been read.

So do I safely assume here, according to the third point above, that it's
fine if I do not call hClose explicitly as far as I am consuming all the
contents returned by hGetContents?

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


Re: [Haskell-cafe] Re: Embedding newlines into a string?

2008-04-14 Thread Abhay Parvate
Yes, they are. That's what perhaps Neil Mitchell means by

mapM_ putStrLn == putStr . unlines

And whether the trailing newline is to be called the last blank line depends
upon the convention; The string that is output in both the cases contains a
single newline character. Are you calling that a blank line at end?

And I actually meant to reply to haskell-cafe as well; omitted haskell-cafe
by mistake. Anyway, you got the same answer from two people! This time I am
including haskell-cafe in the recipients.

Regards,
Abhay

On Mon, Apr 14, 2008 at 4:05 PM, Benjamin L. Russell [EMAIL PROTECTED]
wrote:

 Abhay Parvate,

 Thank you; that answered my question.

 Then, the following two lines of code should be
 equivalent:

 In hanoi.hs:
 hanoi n = mapM_ putStrLn (hanoi_helper 'a' 'b' 'c' n)

 In hanoi_unlines.hs:
 hanoi n = putStr (unlines(hanoi_helper 'a' 'b' 'c' n))

 I tested them both out on WinHugs (Version Sep 2006);
 they both generated one blank line at the end.

 Benjamin L. Russell

 --- Abhay Parvate [EMAIL PROTECTED] wrote:

  unlines puts newline after each string; putStrLn
  puts newline after the
  given string. As a result, the output contains two
  newlines in the end. You
  can use putStr instead, since the resultant string
  from 'unlines' will have
  a newline at the end.
 
  On Mon, Apr 14, 2008 at 2:12 PM, Benjamin L. Russell
  [EMAIL PROTECTED]
  wrote:
 
   Ok; much better.  Here's my new type signature and
   definition:
  
   hanoi.hs:
   hanoi :: Int - IO ()
   hanoi n = mapM_ putStrLn (hanoi_helper 'a' 'b' 'c'
  n)
  
   hanoi_helper :: Char - Char - Char - Int -
   [String]
   hanoi_helper source using dest n
  | n == 1 = [Move  ++ show source ++  to  ++
   show dest ++ .]
  | otherwise = hanoi_helper source dest using
  (n-1)
  
++ hanoi_helper source using dest
  1
   ++ hanoi_helper using
  source
   dest (n-1)
  
   Then in WinHugs (Version Sep 2006):
  
   Hugs :load hanoi.hs
   Main hanoi 2
   Move 'a' to 'b'.
   Move 'a' to 'c'.
   Move 'b' to 'c'.
  
   Great!
  
   One minor question:  I tried out both of your
   following suggestions:
  
mapM_ putStrLn (hanoi 2) -- outputs each
  move
in a new line
putStrLn (unlines (hanoi 2)) -- same as
previous line
  
   and discovered that putStrLn with unlines (the
  lower
   option) in fact generates one extra blank line at
  the
   end.  Just curious as to why
  
   Benjamin L. Russell
  
   --- Tillmann Rendel [EMAIL PROTECTED] wrote:
  
Benjamin L. Russell wrote:
 but got stuck on outputting newlines as part
  of
the string;
   
quoting is done by the show function in Haskell,
  so
you have to take
care to avoid calling show. your code calls show
  at
two positions:
(1) when you insert the newline into the string
(2) when you output the string
   
with respect to (1):
   
you use (show '\n') to create a newline-only
  string,
which produces a
machine-readable (!) textual representation of
  '\n'.
try the difference
between
   
'\n'
   
and
   
show '\n'
   
to see what I mean. instead of using (show
  '\n'),
you should simply use
\n to encode the string of length 1 containing
  a
newline character.
   
with respect to (2):
   
the type of your top-level expression is String,
which is automatically
print'ed by the interpreter. but print x =
  putStrLn
(show x), so there
is another call to show at this point. to avoid
  this
call, write an IO
action yourself. try the difference between
   
   putStrLn (hanoi ...)
   
and
   
   print (hanoi ...)
   
to see what I mean.
   
Last, but not least, I would like to point out a
different aproach to
multiline output which is often used by Haskell
programmers: The worker
functions in this aproach produces a list of
strings, which is joined
together with newlines by the unlines function.
  In
your case:
   
   hanoi_helper :: ... - [String]
 | ... = [Move  ++ ...]
 | otherwise = hanoi_helper ... ++
  hanoi_helper
...
   
   hanoi n = hanoi_helper 'a' 'b' 'c' n
   
and in the interpreter one of these:
   
hanoi 2 -- outputs a list
mapM_ putStrLn (hanoi 2) -- outputs each
  move
in a new line
putStrLn (unlines (hanoi 2)) -- same as
previous line
   
Tillmann
___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] do construct in wxhaskell

2008-04-12 Thread Abhay Parvate
The indentation is not right; all the statements after the 'do' keyword need
to start exactly at the same column. In particular, the 'f' in fileContent
and 's' in set should be one below the other. And the 'return ()' also seems
to be displaced; perhaps you want that also exactly below the last 'set' if
it's the part of the last case.

Hope it helps
Abhay

2008/4/12 Jodi-Ann Prince [EMAIL PROTECTED]:

  hi, im working ona project, and im having problem loading some code in
 wxhaskell:


 onOpen :: Frame a - TextCtrl b - MenuItem c - StatusField - IO ()
 onOpen f sw mclose status = do   mbfname - fileOpenDialog f False True
 Open image fileTypes  
   case  (mbfname) of
   (Nothing)  - return ()
   (Just (fname)) - do
 fileContent - readFile fname

 set sw [text := fileContent]

 set mclose [enabled := True]

 set status [text := fname]
   return ()

 i keep getting the error : the last statement in a 'do' construct must be
 an expression.
 ive tried rearranging it many times, but i still get the same error. any
 help would be greatly appreciated.

 --
 Connect to the next generation of MSN Messenger  Get it now!
 http://imagine-msn.com/messenger/launch80/default.aspx?locale=en-ussource=wlmailtagline

 ___
 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] Why does GHC limit stack size?

2007-11-03 Thread Abhay Parvate
Hello all,

Why is there a limitation on the stack size in GHC? Like heap where we can
limit the size by -M RTS option but the default is unlimited, why not let
the program use as big a stack as required? If not by default, then by a
separate option?

Some of the functions that we write in recursive fashion will usually cause
a stack overflow, but will work fine if there is more stack (suppose we are
not worried about efficiency). And these functions generally look nicer and
compact than their tail recursive versions.

Is this is a technical hurdle, or just a checkpoint for runaway programs?
Can we have an RTS flag allowing unlimited stack size?

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