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

2008-04-15 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[2]: [Haskell-cafe] GC'ing file handles and other resources

2008-04-15 Thread Bulat Ziganshin
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: [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


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

2008-04-15 Thread Benjamin L. Russell
Ok; I rewrote my recursive version of hanoi,
preserving my semantics (i.e., working for lists of
length 1 or more, rather than 0 or more, to start
with) in a more Haskell-idiomatic manner; viz:

hanoi_general_recursive.hs:

hanoi :: a -> a -> a -> Int -> [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a => [(a, a)] -> String
hanoi_shower [(a, b)] = unlines ["Move " ++ show a ++
" to "++ show b ++ "."]
hanoi_shower ((a, b):moves) = unlines ["Move " ++ show
a ++ " to "++ show b ++ "."] ++ hanoi_shower moves

(I wanted to start out with lists of length 1 as a
base case before extending the base case to lists of
length 0 because Luke Palmer had already solved it for
0, and I didn't want just to copy his solution--I
can't learn anything if I just do that.)

In WinHugs:

Main> :load hanoi_general_recursive.hs
Main> putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Main> putStr (hanoi_shower (hanoi 'a' 'b' 'c' 1))
Move 'a' to 'c'.

Main> putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2.
Move 1 to 3.
Move 2 to 3.

Main> putStr (hanoi_shower (hanoi 1 2 3 1))
Move 1 to 3.


Ok; it works now.

Now that I have successfully created a recursive
version that preserves my original semantics, it is
time to extend the base case to handle lists of length
0.

(Notice that I added a base case of n == 0 to hanoi
itself as well, in addition to hanoi_shower; leaving
this out in hanoi results in an error of "ERROR - C
stack overflow" on an argument of n == 0 discs:)

hanoi_general_recursive_base_0.hs:

hanoi :: a -> a -> a -> Int -> [(a, a)]
hanoi source using dest n
| n == 0 = []
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a => [(a, a)] -> String
hanoi_shower [] = ""
hanoi_shower ((a, b):moves) = unlines ["Move " ++ show
a ++ " to "++ show b ++ "."] ++ hanoi_shower moves

Now, let's sit back and watch the fun in WinHugs:

Main> :load hanoi_general_recursive_base_0.hs
Main> putStr (hanoi_shower (hanoi 'a' 'b' 'c' 2))
Move 'a' to 'b'.
Move 'a' to 'c'.
Move 'b' to 'c'.

Main> putStr (hanoi_shower (hanoi 'a' 'b' 'c' 0))

Main> putStr (hanoi_shower (hanoi 1 2 3 2))
Move 1 to 2.
Move 1 to 3.
Move 2 to 3.

Main> putStr (hanoi_shower (hanoi 1 2 3 0))


Great!

Just for reference, here's the code for the other
versions for comparison:

hanoi_general_list_comprehension_unwords.hs [Note:
This version adds an extra space before the final '.'
on each line.]:

hanoi :: a -> a -> a -> Int -> [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a => [(a, a)] -> String
hanoi_shower moves = unlines [unwords ["Move", show a,
"to", show b, "."] | (a, b) <- moves]

--

hanoi_general_list_comprehension_unlines.hs:

hanoi :: a -> a -> a -> Int -> [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a => [(a, a)] -> String
hanoi_shower moves = unlines ["Move " ++ show a ++ "
to "++ show b ++ "." | (a, b) <- moves]

--
hanoi_general_map_unlines.hs:

hanoi :: a -> a -> a -> Int -> [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a => [(a, a)] -> String
hanoi_shower moves = unlines (map move moves)
 where move (a, b) = "Move " ++
show a ++ " to "++ show b ++ "."

--
hanoi_general_recursive.hs [Note: This version only
works for lists of length 1 or more.]:

hanoi :: a -> a -> a -> Int -> [(a, a)]
hanoi source using dest n
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  ++ hanoi source using dest 1
 ++ hanoi using source dest
(n-1)

hanoi_shower :: Show a => [(a, a)] -> String
hanoi_shower [(a, b)] = unlines ["Move " ++ show a ++
" to "++ show b ++ "."]
hanoi_shower ((a, b):moves) = unlines ["Move " ++ show
a ++ " to "++ show b ++ "."] ++ hanoi_shower moves

--
hanoi_general_recursive_base_0.hs [Note: This program
is just the program contained in the file
hanoi_general_recursive.hs, but extended to process
lists of length 0 or more.]:

hanoi :: a -> a -> a -> Int -> [(a, a)]
hanoi source using dest n
| n == 0 = []
| n == 1 = [(source, dest)]
| otherwise = hanoi source dest using (n-1) 
  

[Haskell-cafe] ANN: datapacker 1.0.0

2008-04-15 Thread John Goerzen
Hi,

I'm pleased to announce the first release of datapacker.

datapacker is a tool to pack files into a minimum number of CDs, DVDs,
or any other arbitrary bin.  It groups file by size.  It is designed
to group files such that they fill fixed-size containers (called
"bins") using the minimum number of containers. This is useful, for
instance, if you want to archive a number of files to CD or DVD, and
want to organize them such that you use the minimum possible number of
CDs or DVDs.

In many cases, datapacker executes almost instantaneously. Of
particular note, the hardlink action can be used to effectively copy
data into bins without having to actually copy the data at all.

datapacker is a tool in the traditional Unix style; it can be used in
pipes and call other tools.


More information, including downloads and a full manual, can be found
at:

  http://software.complete.org/datapacker

datapacker is also available on Hackage.


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


Re: [Haskell-cafe] Hackage being too strict?

2008-04-15 Thread John Goerzen
On Tuesday 15 April 2008 10:53:03 pm Gwern Branwen wrote:
> On 2008.04.15 22:15:29 -0500, John Goerzen <[EMAIL PROTECTED]> 
scribbled 0.7K characters:
> > When I went to make my upload of MissingH 1.0.1, Hackage rejected it,
> > saying:
> >
> > Instead of 'ghc-options: -XPatternSignatures' use 'extensions:
> > PatternSignatures'
> >
> > It hadn't rejected MissingH 1.0.0, even though it had the same thing.
> >
> > Now, my .cabal file has this:
> >
> >  -- Hack because ghc-6.6 and the Cabal the comes with ghc-6.8.1
> >  -- does not understand the PatternSignatures extension.
> >  -- The Cabal that comes with ghc-6.8.2 does understand it, so
> >  -- this hack can be dropped if we require Cabal-Version: >=1.2.3
> >  If impl(ghc >= 6.8)
> >GHC-Options: -XPatternSignatures
> >
> > which was contributed by Duncan Coutts.
> >
> > It seems arbitrary that Hackage would suddenly reject this valid
> > usage.
> >
> > Thoughts?
>
> Doesn't strike me as being any more arbitrary than demanding a Build-type:
> field.

Well, that's perhaps a problem too.  It makes it difficult to produce 
a .cabal file that can both be parsed by GHC 6.6 and uploaded to Hackage.

>
> --
> gwern
> submiss mega Audiotel meta SUBACS JSOTF NMIC EIP RAID CRA


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


Re: [Haskell-cafe] Hackage being too strict?

2008-04-15 Thread Gwern Branwen
On 2008.04.15 22:15:29 -0500, John Goerzen <[EMAIL PROTECTED]> scribbled 0.7K 
characters:
> When I went to make my upload of MissingH 1.0.1, Hackage rejected it,
> saying:
>
> Instead of 'ghc-options: -XPatternSignatures' use 'extensions: 
> PatternSignatures'
>
> It hadn't rejected MissingH 1.0.0, even though it had the same thing.
>
> Now, my .cabal file has this:
>
>  -- Hack because ghc-6.6 and the Cabal the comes with ghc-6.8.1
>  -- does not understand the PatternSignatures extension.
>  -- The Cabal that comes with ghc-6.8.2 does understand it, so
>  -- this hack can be dropped if we require Cabal-Version: >=1.2.3
>  If impl(ghc >= 6.8)
>GHC-Options: -XPatternSignatures
>
> which was contributed by Duncan Coutts.
>
> It seems arbitrary that Hackage would suddenly reject this valid
> usage.
>
> Thoughts?

Doesn't strike me as being any more arbitrary than demanding a Build-type: 
field.

--
gwern
submiss mega Audiotel meta SUBACS JSOTF NMIC EIP RAID CRA


pgpq1vmLoqRYo.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hackage being too strict?

2008-04-15 Thread John Goerzen
When I went to make my upload of MissingH 1.0.1, Hackage rejected it,
saying:

Instead of 'ghc-options: -XPatternSignatures' use 'extensions: 
PatternSignatures'

It hadn't rejected MissingH 1.0.0, even though it had the same thing.

Now, my .cabal file has this:

 -- Hack because ghc-6.6 and the Cabal the comes with ghc-6.8.1
 -- does not understand the PatternSignatures extension.
 -- The Cabal that comes with ghc-6.8.2 does understand it, so
 -- this hack can be dropped if we require Cabal-Version: >=1.2.3
 If impl(ghc >= 6.8)
   GHC-Options: -XPatternSignatures

which was contributed by Duncan Coutts.

It seems arbitrary that Hackage would suddenly reject this valid
usage.

Thoughts?

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


Re: [Haskell-cafe] monadic debugging

2008-04-15 Thread Bernie Pope


On 16/04/2008, at 10:16 AM, Thomas Davie wrote:


On 16 Apr 2008, at 00:04, Bulat Ziganshin wrote:

Hello Vasili,

Wednesday, April 16, 2008, 2:53:32 AM, you wrote:


I have an Linux executable of my Haskell library and test
case. I see there are several debuggers, e.g. Buddha, Hat, etc.
Which debugger is currently preferred for monadic (imperative)  
code? Thanks.


i use print mainly :)  btw, there is also built-in ghci debugger, i
suspect that it's closest one to the usual debuggers and most useful
one for imperative code (but i never tried anything, so don't  
trust me :)


Having worked lots on Hat, and studied all (I hope or I've got a  
hole in my research) of the debuggers out there, I'd have to say  
that debugging monadic code is still very much an unsolved  
problem.  Putting print statements in is probably your best option.


You may want to try hat-delta, or buddha's functional mapping mode  
-- both of them should be capable of reducing sequences of monadic  
operations to a single operation and a function map.


I agree with Tom, that debugging monadic code is an open problem.

From a practical level, I doubt buddha is going to be much help,  
because it has bit rotted, and is unsupported.


Hat allows you to debug the program in different ways, and it gives  
you reduction traces, which can often be useful, so you may get some  
traction there.


But I would try the ghci debugger first. Be warned: it forces you to  
be aware of lazy evaluation, which can be quite hard to understand,  
so you need a bit of practice with it. As for debugging monads, it  
depends on the complexity of the monad. If you are using standard  
monads (and that usually means transformers) then a lot of the  
plumbing will be invisible in the debugger, because breakpoints and  
stepping don't work in the libraries (you would have to copy the  
library code into your workspace, if you wanted to see the underlying  
monad code in action).


I've successfully found bugs in code using the ghci debugger, where  
the code used a continuation transformer, over a state transformer,  
over an IO monad. It was easy enough to follow because I wasn't  
forced to see the plumbing underneath. In particular I wasn't forced  
to see the continuation, or the state, which really helps. Of,  
course, if I did want to see those things then I would have been in  
trouble.


One question that has been in my head for a while now is that if you  
used the Unimo way to build monads, maybe they are easier to debug?  
The Unimo style is intentionally operational, and that may be a  
better fit to debugging, especially in the ghci debugger, which  
requires an operational way of thinking.


Here's a link to the Unimo paper: http://web.cecs.pdx.edu/~cklin/ 
papers/unimo-143.pdf


If you do make some progress with any of the debugging tools it would  
be very useful to hear how it went. We get very little feedback on  
successful debugging endeavours where tools were involved (maybe  
because the tools aren't helpful, it is hard to say).


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


[Haskell-cafe] Wrong Answer Computing Graph Dominators

2008-04-15 Thread Denis Bueno
I'm using the Data.Graph.Inductive.Query.Dominators library
(http://haskell.org/ghc/docs/latest/html/libraries/fgl/Data-Graph-Inductive-Query-Dominators.html)
with GHC 6.8.2.
 The library is a bit spare on comments, so I may or may not be using
it correctly.

My goal is to compute the set of nodes that dominate two different
nodes of a DAG, with respect to one initial node.

My approach is:

   import qualified Data.Graph.Inductive.Graph as Graph
   import qualified Data.Graph.Inductive.Query.Dominators as Dom

   uips= intersect domConfl domAssigned :: [Graph.Node] -- my goal
   domConfl= fromJust $ lookup conflNode domFromLastd --
dominators of first node
   domAssigned = fromJust $ lookup (negate conflNode) domFromLastd --
dominators of second node
   domFromLastd = Dom.dom conflGraph lastd -- source node

I compute the dominators individually and my answer is their
intersection.  When I call the dom function, my assumption is that I
need to pass it the source node, and it tells me, for any node x to
which there is a path from the source, the list of nodes for which
*any path* from source to x must touch, i.e., the list of dominators
of x.

The DAG in question is attached as a postscript file, which is
generated by `dot -Tps` using the output of the Graphviz module
directly from the graph object.  The nodes for which I'm computing
dominators are labeled -2 and 2 (that is, conflNode = 2).  The problem
is that I think the answer is wrong.  In particular I think the set of
dominators for -2 is {20, -2}, and the set for 2 is {20, 2}.  Their
intersection is {20}, which is what I expect.

But what I am getting is:
   --> uips = [-9,20]
   --> domConfl = [2,-9,20]
   --> domAssigned = [-2,-9,-12,20]
   --> lastd = 20

But -9 is not a dominator for 2, since 20,-7,8,6,2 is a path from 20
to 2 that does not touch 9.  -9 is also not a dominator for -2, since
20,-7,8,6,-2 is a path from 20 to -2 not touching 9.

Am I missing something?

I've simplified the code above slightly from the original code in
order to ignore some irrelevancies.  The original code is for
computing a learned clause in a SAT solver.  The code in the state
that will reproduce the error above is available via a git clone:

   git clone http://fid.stygian.net/dpllsat

Build via cabal, configuring with --disable-optimization
in order to enable assertions, then run:

 ./dist/build/dsat/dsat ./tests/problems/uf20/uf20-0226.cnf

The graph should be saved in conflict.dot and with `dot -Tps -o
conflict.ps conflict.dot` you should be able to turn it into the ps
file attached.  The problematic code referenced above starts on line
759.

-- 
 Denis


bad-dominators.ps
Description: PostScript document
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] monadic debugging

2008-04-15 Thread Thomas Davie


On 16 Apr 2008, at 00:04, Bulat Ziganshin wrote:

Hello Vasili,

Wednesday, April 16, 2008, 2:53:32 AM, you wrote:


I have an Linux executable of my Haskell library and test
case. I see there are several debuggers, e.g. Buddha, Hat, etc.
Which debugger is currently preferred for monadic (imperative)  
code? Thanks.


i use print mainly :)  btw, there is also built-in ghci debugger, i
suspect that it's closest one to the usual debuggers and most useful
one for imperative code (but i never tried anything, so don't trust  
me :)


Having worked lots on Hat, and studied all (I hope or I've got a hole  
in my research) of the debuggers out there, I'd have to say that  
debugging monadic code is still very much an unsolved problem.   
Putting print statements in is probably your best option.


You may want to try hat-delta, or buddha's functional mapping mode --  
both of them should be capable of reducing sequences of monadic  
operations to a single operation and a function map.


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


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

2008-04-15 Thread Conal Elliott
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


Re: [Haskell-cafe] monadic debugging

2008-04-15 Thread Bulat Ziganshin
Hello Vasili,

Wednesday, April 16, 2008, 2:53:32 AM, you wrote:

>  I have an Linux executable of my Haskell library and test
> case. I see there are several debuggers, e.g. Buddha, Hat, etc.
> Which debugger is currently preferred for monadic (imperative) code? Thanks.

i use print mainly :)  btw, there is also built-in ghci debugger, i
suspect that it's closest one to the usual debuggers and most useful
one for imperative code (but i never tried anything, so don't trust me :)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] monadic debugging

2008-04-15 Thread Galchin, Vasili
Hello,

 I have an Linux executable of my Haskell library and test case. I see
there are several debuggers, e.g. Buddha, Hat, etc. Which debugger is
currently preferred for monadic (imperative) code? Thanks.

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


Re: [Haskell-cafe] Re: semi-closed handles

2008-04-15 Thread Ryan Ingram
On 4/15/08, ChrisK <[EMAIL PROTECTED]> wrote:
> A small idiomatic nitpick:  When I see (length s) gets computed and thrown
> away I wince at the wasted effort.  I would prefer (finiteSpine s):

On every piece of hardware I've seen, the actual calculation done by
"length" is basically free.  Compared to the cache misses you'll get
from traversing the list, or especially the disk access from reading
the file, it's vanishingly small.

It's also directly from the prelude and it's usually pretty clear to a
newbie what it's doing, as compared to "foldr (const id) () s" which
is on the path to "functional languages make no sense" land.  I
consider myself moderately experienced, and assuming that it
typechecks I know what it has to mean, but I can't just look at it and
know what it does like I can with "length".

If there was a standard "seqList" or "deepSeq", I'd use that instead.

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


[Haskell-cafe] Re: I/O system brokenness with named pipes

2008-04-15 Thread Joe Buehler

John Goerzen wrote:


So I have a need to write data to a POSIX named pipe (aka FIFO).  Long
story involving a command that doesn't have an option to read data
from stdin, but can from a named pipe.


How about /dev/stdin?

--
Joe Buehler

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


[Haskell-cafe] Re: semi-closed handles

2008-04-15 Thread ChrisK

Ryan Ingram 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


A small idiomatic nitpick:  When I see (length s) gets computed and thrown away 
I wince at the wasted effort.  I would prefer (finiteSpine s):


finiteSpine = foldr (const id) ()

hStrictGetContents :: Handle -> IO String
hStrictGetContents h = do
s <- hGetContents h
finiteSpine s `seq` hClose h
return s

"finiteSpine" finds the "end" of a finite list and will hang forever on an 
infinite list.  One can even notice that the type of finiteSpine is Strategy [a]:


import Control.Parallel.Strategies(Strategy)
finiteSpine :: Strategy [a]
finiteSpine = foldr (const id) ()

And in fact "finiteSpine = seqList r0", which returns () after applying the "do 
nothing" strategy "r0" to every element.


--
Chris

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


[Haskell-cafe] Re: Module for parsing C (pre-processed header files only)?

2008-04-15 Thread benedikth

Magnus Therning schrieb:

Is there such a beast out there?

If this were a list on some OO language I'd ask for something that 
created an AST and then offered an API based around a visitor pattern.


The pre-processor (platform specific most likely, but could be cpphs of 
course) would be run prior to the tool I'm considering writing.  After 
that I only need access to declarations of C functions and definitions 
of types (structs, enums, other typedefs).


I had a quick look at the code in c2hs yesterday, but found it a little 
hard to make heads or tails of it without some guidance, so I couldn't 
tell whether it would be suitable.  Would it?

Hi Markus,
the C parser in c2hs is able to parse preprocessed C and build an AST 
for you. As c2hs also needs to extract function declarations and type 
definitions, there is also code to do that.


Actually I applied for soc project to prepare a more general library 
from c2hs' code base, which would also provide what you are asking for.


Right now, you can download the source code and have a look at 
c2hs/c/tests/CCWrapper.hs on how to invoke to parser, at c2hs/c/CAST.hs 
for the syntax tree datatypes, c2hs/c/CTrav.hs for syntax tree traversal 
and in gen/GenBind.hs to see how c2hs uses this functionality.


best regards, benedikt

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


[Haskell-cafe] Re: Installing HaXml

2008-04-15 Thread Christian Maeder
rodrigo.bonifacio wrote:
> Hi all,
> 
> I've tried to install HaXml as explained in the documentation: 
> 
>> runhaskell Setup.hs configure
> 
> However, I get as response:
>  
> dyld: Library not loaded: GNUreadline.framework/Versions/A/GNUreadline
>   Referenced from: /usr/local/bin/runhaskell
>   Reason: image not found
> Trace/BPT trap
> 
> Any idea about this problem?

You should install the frameworks
http://www.haskell.org/ghc/dist/mac_frameworks/mac_e.htm

Cheers Christian

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


Re: [Haskell-cafe] Module for parsing C (pre-processed header files only)?

2008-04-15 Thread Magnus Therning
On Tue, Apr 15, 2008 at 4:12 PM, Brian Sniffen <[EMAIL PROTECTED]> wrote:

> 2008/4/15 Magnus Therning <[EMAIL PROTECTED]>:
> > Is there such a beast out there?
>
> Well, there's CIL (http://manju.cs.berkeley.edu/cil/), an OCaml
> library attacking the same problem.  It has a very positive
> reputation.


Interesting answer on a Haskell list ;)

I've been toying with the idea of looking at OCaml though, so this might be
just the opportunity I was waiting for...

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


[Haskell-cafe] NW Functional Programming Interest Group

2008-04-15 Thread Greg Meredith
All,

Apologies for multiple listings.

It's that time again. Our growing cadre of functionally-minded north
westerners
is meeting at the

The Seattle Public Library
1000 - 4th Ave.
Seattle, WA  98104

from 18:30 - 20:00 on April 16th.

This meeting's agenda is a little more fluid, but...

   - i would like to talk about a proposal i'm mulling over around a much
   more general account of the Curry-Howard isomorphism by way of iterated
   distributive laws for monads
   - we also need to get a couple more people on the hook to give a talk

Hope to see you there.

Monadically yours,

--greg

-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
806 55th St NE
Seattle, WA 98105

+1 206.650.3740

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


[Haskell-cafe] Module for parsing C (pre-processed header files only)?

2008-04-15 Thread Magnus Therning
Is there such a beast out there?

If this were a list on some OO language I'd ask for something that created
an AST and then offered an API based around a visitor pattern.

The pre-processor (platform specific most likely, but could be cpphs of
course) would be run prior to the tool I'm considering writing.  After that
I only need access to declarations of C functions and definitions of types
(structs, enums, other typedefs).

I had a quick look at the code in c2hs yesterday, but found it a little hard
to make heads or tails of it without some guidance, so I couldn't tell
whether it would be suitable.  Would it?

Any help or pointers appreciated.

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


Re: [Haskell-cafe] Installing HaXml

2008-04-15 Thread Malcolm Wallace
"rodrigo.bonifacio" <[EMAIL PROTECTED]> wrote:

> > runhaskell Setup.hs configure
> 
> dyld: Library not loaded: GNUreadline.framework/Versions/A/GNUreadline
>   Referenced from: /usr/local/bin/runhaskell
>   Reason: image not found
> Trace/BPT trap

The problem is that 'runhaskell' invokes ghci (the interpreter), which
requires readline, which you do not have on your Mac.

Instead, you could compile Setup.hs with ghc, which will not require
readline.

ghc --make Setup
./Setup configure
./Setup build
./Setup install

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


[Haskell-cafe] Installing HaXml

2008-04-15 Thread rodrigo.bonifacio
Hi all,

I've tried to install HaXml as explained in the documentation:

> runhaskell Setup.hs configure

However, I get as response:

dyld: Library not loaded: GNUreadline.framework/Versions/A/GNUreadline
  Referenced from: /usr/local/bin/runhaskell
  Reason: image not found
Trace/BPT trap

Any idea about this problem?

Some comments about my configuration:

Mac/OS Darwin 8.11.1
GHC-6.6
Hugs - Version September 2006

Thanks in advance,

Rodrigo.

___
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] HTTP and file upload

2008-04-15 Thread Adrian Neumann

Yes

http://hpaste.org/6990

Am 14.04.2008 um 19:07 schrieb Adam Smyczek:

Is form based file upload supported in HTTP module (HTTP-3001.0.4)?

Adam


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




PGP.sig
Description: Signierter Teil der Nachricht
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help understanding sharing

2008-04-15 Thread Ryan Ingram
To add to this; sharing is not always what you want; sometimes it's a
time/space trade-off and sometimes it's actually strictly worse than
not sharing.

For example:

> f :: Integer -> [Integer]
> f x = take 1000 [x..]

> sum :: [Integer] -> Integer
> sum = foldl' (+) 0

> expensiveZero :: Integer
> expensiveZero = let (a,b) = (f 0, f 0) in sum a + sum (map negate b)

If the applications of f are unshared, "expensive" runs in small
constant memory.  But, if the applications of f are shared, it will
likely exhaust memory (if it doesn't, add another few zeroes to the
"take" in f).

Here's why.  Assume that (+) evaluates its left argument first.  Then
"sum a" is going to consume the entire list stored in "a".  If the
applications of f are unshared, the garbage collector will reclaim the
beginning of the list "a" while sum is evaluating!  But if they are
shared, it can't; b is the same list and is still live until the rhs
of the (+) gets evaluated.  So the entire list will end up in memory!

Not only that, the program will likely take longer to run than the
unshared version, because the garbage collector has so much more work
to do maintaining the live data set.

This is why most compilers use aliasing of names for sharing; it gives
the programmer control of whether a computation will be shared or not.

  -- ryan

On Mon, Apr 14, 2008 at 8:24 PM, Albert Y. C. Lai <[EMAIL PROTECTED]> wrote:
> Patrick Surry wrote:
>
> > I've seen other discussions that suggest that lists are always shared
> while in scope (so the fibs trick works).  But is that just a feature of the
> standard compilers, or is it somewhere mandated in the Hakell spec (I don't
> see anything obvious in the Haskell Report tho haven't read it cover to
> cover)?
> >
>
>  It is just a feature of most compilers. The Haskell Report does not specify
> sharing.
>
>  For most compilers, a sufficient condition for sharing is aliasing, e.g.,
>
>  let y = f x in (y,y,y,y,y)
>
>  you can be sure that most compilers share one copy of "f x" for those five
> mentions of "y".
>
>  As another example,
>
>  let x = 0:x in x
>
>  you can be sure that most compilers create a tight cyclic graph for that.
>
>  In contrast, most compilers may create redundantly new expressions for the
> following:
>
>  (f x, f x, f x, f x, f x)
>
>  -- given the definition: recurse f = f (recurse f)
>  recurse (\x -> 0:x)
>
>  ___
>  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] semi-closed handles

2008-04-15 Thread Ryan Ingram
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] Re: Embedding newlines into a string?

2008-04-15 Thread Tillmann Rendel

Benjamin L. Russel wrote:

hanoi_shower ((a, b) : moves)
| null moves = ...
| otherwise == ...


Luke Palmer wrote:

More idiomatic pedantry:  the way you will see most Haskellers write
this style of function is by pattern matching rather than guards:

hanoi_shower [] = ...
hanoi_shower ((a,b):moves) = ...


These two versions are semantically different! Benjamin's versions works 
for lists of length 1 or more, Luke's version works for lists of length 
0 or more.


Luke's version looks like a typical Haskell solution, which would be 
expressed in lispy syntax like this:


(define hanoi_shower (lambda (xs)
  (cond ((null xs) (...))
(true, (let ((a, (first (first xs)))
 (b, (rest (first xs)))
 (moves, (rest xs)))
   (...)

The pattern matching in Haskell takes care of both the cond and the let, 
there's no need for guards or to actually call null or any selector 
functions. A nice exercise may be to implement the map function using 
primitive recursion.


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