Re: threaded red-black tree

2003-09-14 Thread Carl Witty
On Sun, 2003-09-14 at 21:48, Lex Stein wrote:
> Hi, No one responded to my question several weeks ago about a purely
> functional implementation of a threaded, red-black tree. 

I'm not sure what you mean by "threaded".  By simply ignoring that word,
I come up with the following solution :-)

There is a purely functional implementation of a red-black tree in the
MetaPRL system (www.metaprl.org), written in OCaml.  For the latest CVS
version of this red-black tree code, go to
http://cvs.metaprl.org:12000/cvsweb/metaprl/libmojave/stdlib/ (look at
lm_map.ml and lm_set.ml). 

Carl Witty

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


threaded red-black tree

2003-09-14 Thread Lex Stein

Hi, No one responded to my question several weeks ago about a purely
functional implementation of a threaded, red-black tree. My message was
sent about the same time as that flurry of silly emails about "how to
respond to homework questions". Was my message not responded to because it
was classified as a homework question? I assure you this is officework,
not homework. I ended up porting Okasaki's red-black tree implementation;
hacking it apart with a bunch of mutation for the threading of the list
through the tree. However, I'm still missing a deletion function and I
haven't been able to find a prototype (Okasaki's red-black tree module
lacks delete). My study of the RB-tree deletion routine in CLR hasn't yet
yielded an adaptation for a functional environment. Any advice would be
much appreciated.

Thanks,
Lex

--
Lex Stein http://www.eecs.harvard.edu/~stein/
[EMAIL PROTECTED]cell: 617-233-0246

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


zlib binding providing Handle to compressed file.

2003-09-14 Thread David Roundy
I've just created a binding to the gzopen function of zlib which causes it
to create a Handle.  The code currently only supports ReadMode and
WriteMode, and hFileSize won't work properly when reading a file.  In fact,
pretty much nothing but plain old reading and writing will work, but such
is life.

Anyhow in case anyone is interested, I'm attaching the code.  It creates a
pipe using pipe(2) and spawns a thread to pass the data between the pipe
and gzread or gzwrite.  It's not pretty, but it's better than any other
solution I could think of.  Suggestions or criticisms are welcome.
-- 
David Roundy
http://www.abridgegame.org/darcs
\begin{code}
module Zlib ( gzOpenFile, gzWriteFile, gzReadFile ) where

import IO
import System.IO ( hGetBuf, hPutBuf )
import Control.Concurrent ( forkIO )
import Monad ( when )
import Foreign.C.String ( CString, withCString )
import Foreign.Marshal.Array ( mallocArray, withArray, peekArray )
import Foreign.Marshal.Alloc ( free )
import Foreign.Ptr ( Ptr )
import Data.Word
import GHC.Handle ( openFd )

fdToReadHandle fd fn = openFd fd Nothing fn ReadMode False False
fdToWriteHandle fd fn = openFd fd Nothing fn WriteMode False False

gzOpenFile :: FilePath -> IOMode -> IO Handle
gzWriteFile :: FilePath -> String -> IO ()

gzOpenFile f ReadMode = 
withCString f $ \fstr -> withCString "rb" $ \rb-> do
gzf <- c_gzopen fstr rb
withArray [0,0] $ \fds -> do
  err <- c_pipe fds
  when (err /= 0) $ error "Pipe problem!"
  [infd,outfd] <- peekArray 2 fds
  writeH <- fdToWriteHandle (fromIntegral outfd) f
  buf <- mallocArray 1024
  forkIO $ gzreader gzf writeH buf
  fdToReadHandle (fromIntegral infd) f
  where gzreader gzf h buf =
do done <- hIsClosed h
   if done
  then do c_gzclose gzf
  free buf
  hClose h
  else do l <- c_gzread gzf buf 1024
  hPutBuf h buf l
  if l < 1024
 then do free buf
 c_gzclose gzf
 hClose h
 else gzreader gzf h buf
gzOpenFile f WriteMode = 
withCString f $ \fstr -> withCString "wb" $ \wb-> do
gzf <- c_gzopen fstr wb
withArray [0,0] $ \fds -> do
  err <- c_pipe fds
  when (err /= 0) $ error "Pipe problem!"
  [infd,outfd] <- peekArray 2 fds
  readH <- fdToReadHandle (fromIntegral infd) f
  buf <- mallocArray 1024
  forkIO $ gzwriter gzf readH buf
  fdToWriteHandle (fromIntegral outfd) f
  where gzwriter gzf h buf =
do done <- hIsEOF h
   if done
  then do c_gzclose gzf
  free buf
  hClose h
  else do l <- hGetBuf h buf 1024
  c_gzwrite gzf buf l
  gzwriter gzf h buf

gzWriteFile f s = do h <- gzOpenFile f WriteMode
 hPutStr h s
 hClose h

gzReadFile f s = do h <- gzOpenFile f WriteMode
hGetContents h

foreign import ccall unsafe "static unistd.h pipe" c_pipe
:: Ptr Int -> IO Int
foreign import ccall unsafe "static unistd.h read" c_read
:: Ptr Word8 -> Int -> IO Int

foreign import ccall unsafe "static zlib.h gzopen" c_gzopen
:: CString -> CString -> IO (Ptr ())
foreign import ccall unsafe "static zlib.h gzclose" c_gzclose
:: Ptr () -> IO ()
foreign import ccall unsafe "static zlib.h gzread" c_gzread
:: Ptr () -> Ptr Word8 -> Int -> IO Int
foreign import ccall unsafe "static zlib.h gzwrite" c_gzwrite
:: Ptr () -> Ptr Word8 -> Int -> IO ()
\end{code}
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: An IO Question from a Newbie

2003-09-14 Thread Brandon Michael Moore


On Sun, 14 Sep 2003, Glynn Clements wrote:

>
> Brandon Michael Moore wrote:
>
> > Hal was pretty terse, so I'll explain why switching to putStrLn will help.
> >
> > stdout is line buffered.
> >
> > At least by default (see hSetBuffering). That means output will only be
> > flushed to the screen once a newline is written. Your prompt wasn't
> > printed because it didn't have a newline, so it was buffered until the
> > second print provided one (read from the user, by way of s).
> >
> > This is hardly specific to Haskell. Try this C program:
>
> But there's one significant difference between C and Haskell, which is
> applicable in the case of Matt's program. In C, any line-buffered
> output streams are automatically flushed when a read from an
> unbuffered or line-buffered stream can't be satisfied from its buffer.

Interesting. I didn't know this. Maybe we should match this behaviour, or
provide a write-string-and-flush function. It seems like this issue
is causing an undue amound of trouble.

> Also, it seemed fairly clear from Matt's original message that:
>
> a) he didn't want to have to force a new-line (he noted that doing so
> eliminated the problem), and

I should note here that there is a gnu readline binding distributed with
GHC. It's undocumented, but it seems to follow the C API pretty closely,
and you can make a decent interface using only two of the functions.

> b) he understood the concept of flushing, but presumably didn't know
> how to do it in Haskell.
>
> While we're on the subject, I'll point out a couple of other
> differences between the buffering in ANSI C's stdio library and
> Haskell's:
>
> 1. In Haskell, you can change the buffering mode at any point; in C,
> you have to change it before any data is read from or written to the
> stream, otherwise the behaviour is undefined.
>
> 2. For an input stream which is associated with a tty, changing the
> buffering mode may also change the terminal settings (setting it to
> unbuffered disables canonical mode while setting it to line-buffered
> or fully-buffered enables it).
>
> --
> Glynn Clements <[EMAIL PROTECTED]>
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

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


Re: An IO Question from a Newbie

2003-09-14 Thread Glynn Clements

Brandon Michael Moore wrote:

> Hal was pretty terse, so I'll explain why switching to putStrLn will help.
> 
> stdout is line buffered.
> 
> At least by default (see hSetBuffering). That means output will only be
> flushed to the screen once a newline is written. Your prompt wasn't
> printed because it didn't have a newline, so it was buffered until the
> second print provided one (read from the user, by way of s).
> 
> This is hardly specific to Haskell. Try this C program:

But there's one significant difference between C and Haskell, which is
applicable in the case of Matt's program. In C, any line-buffered
output streams are automatically flushed when a read from an
unbuffered or line-buffered stream can't be satisfied from its buffer.

Also, it seemed fairly clear from Matt's original message that:

a) he didn't want to have to force a new-line (he noted that doing so
eliminated the problem), and

b) he understood the concept of flushing, but presumably didn't know
how to do it in Haskell.

While we're on the subject, I'll point out a couple of other
differences between the buffering in ANSI C's stdio library and
Haskell's:

1. In Haskell, you can change the buffering mode at any point; in C,
you have to change it before any data is read from or written to the
stream, otherwise the behaviour is undefined.

2. For an input stream which is associated with a tty, changing the
buffering mode may also change the terminal settings (setting it to
unbuffered disables canonical mode while setting it to line-buffered
or fully-buffered enables it).

-- 
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


YAHT Problem

2003-09-14 Thread Mark Espinoza
Hello,

  I am going through YAHT again, using galeon and redhat 7.3.Galeon is
apparently using xpdf to diaplay the tutorial. There are some things
that are not displayed. For example, in 3.1 Arithmetic, on about the
sixth line, it says : For instance, the number   is an _expression_ (its
value is  ).Does anyone have an idea why I'm not seeing the number and
its value, and how I can fix this? Thank you.

Sincerely,

Mark

Get your free e-mail address at   http://felinemail.zzn.com__http://www.zzn.com
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: No safety in numbers

2003-09-14 Thread Marcin 'Qrczak' Kowalczyk
Dnia czw 21. sierpnia 2003 22:30, Konrad Hinsen napisał:

> k_B = 0.0083144708636327096
>
> The trouble is that k_B then becomes "Double" by default (or any other
> type I declare it to be).

Declare it as
k_B :: Fractional a => a

Performance may suffer even in GHC if optimization is turned off.

BTW, Hugs incorrectly converts such numbers through Double which it 
represents as C float.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/

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


Re: An IO Question from a Newbie

2003-09-14 Thread Brandon Michael Moore
Hal was pretty terse, so I'll explain why switching to putStrLn will help.

stdout is line buffered.

At least by default (see hSetBuffering). That means output will only be
flushed to the screen once a newline is written. Your prompt wasn't
printed because it didn't have a newline, so it was buffered until the
second print provided one (read from the user, by way of s).

This is hardly specific to Haskell. Try this C program:

#import 
#import 
int main(int a,char** b) {
  fputs("test",stdout);
  sleep(1);
  fputs("boo!\n",stdout);
  return 0;
}

on my system this sleeps a second then prints "testboo!". I used fputs
rather than puts becuase puts appends a newline and fputs doesn't.
Similarly, putStrLn appends a newline and putStr doesn't.

This change does mean input will be entered on the next line, rather then
on the same line as the prompt. This should be acceptable. If you really
need to have a prompt at the start of the line then consider hFlush or
hSetBuffering.

Every time I've seen this question asked people post responses that only
mention hFlush, implying you need it to display output when you want it.
Please don't give newbies the impression you need hFlush for basic IO.
Monadic IO is scary enough to begin with.

This seems to be a common problem so I added some comments about it on the
Wiki, under UsingIO in the FrequentlyAskedQuestions.

Brandon

On Fri, 12 Sep 2003, Hal Daume III wrote:

> This is a buffering problem.  Use hSetBuffering to fix this (see Chapter 3
> in YAHT -- www.isi.edu/~hdaume/htut/).  Alternatively, use:
>
> > main = do putStrLn "Type Something:"
> >   ...
>
>
> in which case the "Ln" part will force it to be printed.
>
>  - Hal
>
> On Fri, 12 Sep 2003, Matt O'Connor wrote:
>
> > Hello all.  I'm new to functional programming and Haskell, but have been
> > programming in C and Java for a while.  I've been going through the tutorials
> > and whatnot on haskell.org.  I've read from the Gentle Introduction to
> > Haskell about IO and some of the other stuff and I have a question about it.
> >
> > main = do putStr "Type Something: "
> >   str <- getLine
> >   putStrLn ("You typed: " ++ str)
> >
> > When compile and run this code the "Type Something: " isn't displayed until
> > the putStrLn.  So there is no prompt.  The output looks like this.
> >
> > s
> > Type Something: You typed: s
> >
> > But if I change the putStr "Type Something: " to a putStrLn or put a \n at the
> > end of the string it displays the text immediately (ie, when I want it to).
> > Is there a good reason for this?  Am I doing something wrong?  Or do I need
> > to call some kind of standard output flush?  Thanks.
> >
> > Oh, I'm using ghc.
> >
> >
> > Matt
> >
> >
>
> --
>  Hal Daume III   | [EMAIL PROTECTED]
>  "Arrest this man, he talks in maths."   | www.isi.edu/~hdaume
>
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

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