[Haskell-cafe] Re: Haskell example archive?

2005-04-25 Thread Peter Eriksen
Echo Nolan [EMAIL PROTECTED] writes:

 Hello all,
   I recently read the post about a problem using the list monad,
 and I was wondering if there was an archive of monad usecases. If there
 is one, I'd like to see it, and if not it'd be a helpful part of the
 haskell community. Something like the example of the Maybe monad from
 All About Monads.

I haven't found any comprehensive archive either, but there are examples
spread across the net and the Hakskell Wiki.  A special usecase of monads
is imperative programming.  A few examples can be found at
 
http://haskell.org/hawiki/ImperativeHaskell

Hopefully when enough examples and snippets have been written it will be
easy for someone to collect and edit a very much complete collection of
examples. 

Regards

Peter

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


Re: [Haskell-cafe] Why doesn't this work?

2005-04-25 Thread Daniel Fischer
Am Montag, 25. April 2005 08:16 schrieb Michael Vanier:
 I've been trying to generate an infinite list of random coin flips in GHC
 6.4, and I've come across some strange behavior:

 --
 import System.Random

 data Coin = H | T deriving (Eq, Show)

 -- Generate a random coin flip.
 coinFlip :: IO Coin
 coinFlip = do b - getStdRandom random
   return (bool2coin b)
where
   bool2coin True  = H
   bool2coin False = T

 -- Generate an infinite list of coin flips.
 coinFlips :: IO [Coin]
 coinFlips = sequence cfs
 where cfs = (coinFlip : cfs)

 -- Print n of them.
 test :: Int - IO ()
 test n = do f - coinFlips
 print (take n f)
 --

 Now when I do test 1 (for instance), it hangs forever.  It seems as if
 there is some kind of strictness constraint going on that I don't
 understand.  My understanding is that cfs is an infinite list of (IO Coin),
 sequence lifts this to be IO [Coin] where [Coin] is an infinite list, and
 then test should extract the infinite list of coin flips into f, take some
 number of them, and print them.  But instead, the system appears to be
 trying to compute all the coin flips before taking any of them.  Why is
 this, and how do I fix it?

 Thanks,

 Mike

How to fix it:

test n = sequence (replicate n coinFlip) = print

another way to fix it: use unsafeInterleaveIO (I would not recommend it, 
though)
import System.IO.Unsafe

coinFlips = do c - coinFlip
 cs - unsafeInterleaveIO coinFlips
 return (c:cs)

Why: because coinFlips has to be evaluated before the result can be passed to 
'print . take n' (that's part of the IO monad, executing actions in 
sequence). And this can't be done lazily with sequence:
sequence   :: Monad m = [m a] - m [a]
{-# INLINE sequence #-}
sequence ms = foldr k (return []) ms
where
  k m m' = do { x - m; xs - m'; return (x:xs) }

so 
sequence (ac:acs) = foldr k (return []) (ac:acs)
 = k ac (foldr k (return []) acs)
 = do x - ac
 xs - sequence acs
 return (x:xs)
and if sequence acs fails, the overall computation fails and nothing can be 
returned. The point is, the function 'k' from sequence is strict, and folding 
a strict function always uses the entire list (unless an error occurs before 
the end is reached).
Conclusion: sequence only finite lists, otherwise you'll get a Stack overflow.

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


Re: [Haskell-cafe] Why doesn't this work?

2005-04-25 Thread Duncan Coutts
On Sun, 2005-04-24 at 23:16 -0700, Michael Vanier wrote:
 I've been trying to generate an infinite list of random coin flips in GHC
 6.4, and I've come across some strange behavior:
 
 --
 import System.Random
 
 data Coin = H | T deriving (Eq, Show)
 
 -- Generate a random coin flip.
 coinFlip :: IO Coin
 coinFlip = do b - getStdRandom random
   return (bool2coin b)
where
   bool2coin True  = H
   bool2coin False = T
 
 -- Generate an infinite list of coin flips.
 coinFlips :: IO [Coin]
 coinFlips = sequence cfs
 where cfs = (coinFlip : cfs)
 
 -- Print n of them.
 test :: Int - IO ()
 test n = do f - coinFlips
 print (take n f)
 --
 
 Now when I do test 1 (for instance), it hangs forever.  It seems as if
 there is some kind of strictness constraint going on that I don't
 understand.  My understanding is that cfs is an infinite list of (IO Coin),
 sequence lifts this to be IO [Coin] where [Coin] is an infinite list, and
 then test should extract the infinite list of coin flips into f, take some
 number of them, and print them.  But instead, the system appears to be
 trying to compute all the coin flips before taking any of them.  Why is
 this, and how do I fix it?

My first guess is that this is because sequence is strict in it's list.
This is the normal behaviour that you would expect for this function
since otherwise the side effects from all the IO actions are not going
to happen before it returns (which is the ordinary behaviour for IO
actions; one of the main purposes of the IO monad is for sequencing side
effects).

You can lazily defer IO actions using unsafeInterleaveIO.

However in this case that's probably not the most elegant approach. It
might be better to make the coinFlip function pure (ie not in the IO
monad) and instead to pass it a random number generator which it returns
as an extra component of the result (having extracted a random value
using 'random'). Then you can use getStdGen once and pass the result to
a function which generates an infinite lazy list of random numbers by
threading the generator between calls to coinFlip. (Or if you want to
cheat you can use randoms which will do all this for you)

See:
http://haskell.org/ghc/docs/latest/html/libraries/base/System.Random.html

Duncan

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


[Haskell-cafe] String search algorithms

2005-04-25 Thread Bayley, Alistair
I'm a bit puzzled to find no sub-string search in the Haskell libraries
(unless there's some neat composition of the existing Data.List functions
that I've missed). Google doesn't help much either. I've found a KMP
implementation:
  http://haskell.org/hawiki/RunTimeCompilation

I'm after something that'll report the position of the first occurrence,
like Java's String.indexOf().

Alistair.

-
*
Confidentiality Note: The information contained in this   message, and any
attachments, may contain confidential   and/or privileged material. It is
intended solely for the   person(s) or entity to which it is addressed. Any
review,   retransmission, dissemination, or taking of any action in
reliance upon this information by persons or entities other   than the
intended recipient(s) is prohibited. If you received  this in error, please
contact the sender and delete the   material from any computer.
*

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


Re: [Haskell-cafe] String search algorithms

2005-04-25 Thread Henning Thielemann
On Mon, 25 Apr 2005, Bayley, Alistair wrote:
I'm a bit puzzled to find no sub-string search in the Haskell libraries
(unless there's some neat composition of the existing Data.List functions
that I've missed). Google doesn't help much either. I've found a KMP
implementation:
 http://haskell.org/hawiki/RunTimeCompilation
I'm after something that'll report the position of the first occurrence,
like Java's String.indexOf().
List.findIndex (List.isPrefixOf bla) (List.tails dfvbdbblaesre)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] String search algorithms

2005-04-25 Thread Bayley, Alistair
 From: Henning Thielemann [mailto:[EMAIL PROTECTED] 
 
  (unless there's some neat composition of the existing 
 Data.List functions
 
 List.findIndex (List.isPrefixOf bla) (List.tails dfvbdbblaesre)

Oh, so there is. Thanks.

-
*
Confidentiality Note: The information contained in this   message, and any
attachments, may contain confidential   and/or privileged material. It is
intended solely for the   person(s) or entity to which it is addressed. Any
review,   retransmission, dissemination, or taking of any action in
reliance upon this information by persons or entities other   than the
intended recipient(s) is prohibited. If you received  this in error, please
contact the sender and delete the   material from any computer.
*

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


Re: [Haskell-cafe] String search algorithms

2005-04-25 Thread Henning Thielemann
On Mon, 25 Apr 2005, Henning Thielemann wrote:
On Mon, 25 Apr 2005, Bayley, Alistair wrote:
I'm a bit puzzled to find no sub-string search in the Haskell libraries
(unless there's some neat composition of the existing Data.List functions
that I've missed). Google doesn't help much either. I've found a KMP
implementation:
 http://haskell.org/hawiki/RunTimeCompilation
I'm after something that'll report the position of the first occurrence,
like Java's String.indexOf().
List.findIndex (List.isPrefixOf bla) (List.tails dfvbdbblaesre)
But I'm curious if you really need the index. Working with indexes on 
lists is quite inefficient. E.g. if you want to replace substrings you 
may want to use this implementation:

replace :: forall a. (Eq a) = [a] - [a] - [a] - [a]
replace src dst =
   foldr (\x xs - let y=x:xs
   in  if isPrefixOf src y
 then dst ++ drop (length src) y
 else y) []
Prelude Data.List replace ocu orcu hocuspocus
horcusporcus
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] String search algorithms

2005-04-25 Thread Bayley, Alistair
 From: Henning Thielemann [mailto:[EMAIL PROTECTED] 
 
 But I'm curious if you really need the index. Working with indexes on 
 lists is quite inefficient. E.g. if you want to replace 
 substrings you 
 may want to use this implementation:


I'm not mutating the list, but I am extracting sublists. I'm toying with
porting FIT and I'm starting with the Parse class, as recommended (
http://fit.c2.com/wiki.cgi?TipsForCoreImplementors ). They warn against
using a generic parser:

  Parse is the internal representation of the test data. Don't be seduced
by generalized html/xml parsers. This one has unique features. Make it work.
Consider replacing it only after you've used this one a while.

Their parser is in Java, and makes heavy use of String.indexOf(), and I'm
just trying to port it more-or-less as-is. I appreciate that'll be somewhat
inefficient, but until I understand all of the wrinkles in their
implementation, I'll take the simplest approach.

Alistair.

-
*
Confidentiality Note: The information contained in this   message, and any
attachments, may contain confidential   and/or privileged material. It is
intended solely for the   person(s) or entity to which it is addressed. Any
review,   retransmission, dissemination, or taking of any action in
reliance upon this information by persons or entities other   than the
intended recipient(s) is prohibited. If you received  this in error, please
contact the sender and delete the   material from any computer.
*

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


RE: [Haskell-cafe] FFI and pointers to pointers

2005-04-25 Thread Simon Marlow
On 22 April 2005 16:18, Dimitry Golubovsky wrote:

 I am trying to generalize my knowledge about FFI declarations when
 dealing with pointers to pointers (import from C to Haskell). Maybe
 these are silly questions, but It seems to me, I am missing some
 understanding.
 
 Per the FFI Addendum:
 
 For a variable, we use  import:
 
 int bar;
 
 foreign import ccall  bar :: Ptr CInt

The syntax you want is

  foreign import ccall bar :: Ptr CInt

But note that GHC 6.4 has a bug whereby this doesn't work as expected
when compiling via C.  Either use the native code generator (-fasm) or
wait for 6.4.1.

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


RE: [Haskell-cafe] FFI and pointers to pointers

2005-04-25 Thread Simon Marlow
On 25 April 2005 12:51, Simon Marlow wrote:

 On 22 April 2005 16:18, Dimitry Golubovsky wrote:
 
 I am trying to generalize my knowledge about FFI declarations when
 dealing with pointers to pointers (import from C to Haskell). Maybe
 these are silly questions, but It seems to me, I am missing some
 understanding. 
 
 Per the FFI Addendum:
 
 For a variable, we use  import:
 
 int bar;
 
 foreign import ccall  bar :: Ptr CInt
 
 The syntax you want is
 
   foreign import ccall bar :: Ptr CInt

oops, never mind.  Your version was fine.

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


[Haskell-cafe] How to debug GHC

2005-04-25 Thread Monique Louise de Barros Monteiro
Hi, all,
 I'm developing a back end for GHC and I have the following problem:
my program is throwing an empty list exception due to head [] and I
need to compile GHC with -prof -auto-all in order to see the stack
trace when running it with +RTS -xc -RTS.  I changed the makefile but
the option +RTS -xc -RTS was not recognized as an available RTS option
Does anyone have any idea about how I can do that ?
Thanks in advance,

__
Monique Louise Monteiro
Mestranda em Ciencia da Computacao
Centro de Informatica - CIn - UFPE
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe