[Haskell-cafe] Re: How to thoroughly clean up Haskell stuff on linux

2007-10-13 Thread Aaron Denney
On 2007-10-12, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:

 On Oct 12, 2007, at 17:38 , Lihn, Steve wrote:

   Installing: --prefix=~/cabal/lib/haddock-0.8/ghc-6.4 

 This looks suspicious to me:  the ~ metacharacter is only  
 understood by shells, and only in certain circumstances (i.e. only at  
 the beginning of a word, not after a =),

This likely the problem, but a reasonable shell (i.e. zsh) will expand in
this circumstance:

% echo --foo=~
--foo=/home/wnoise

-- 
Aaron Denney
--

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


[Haskell-cafe] Can every monad can be implemented with Cont? (was: New slogan for haskell.org)

2007-10-13 Thread apfelmus

Don Stewart wrote:

allbery:

Didn't someone already prove all monads can be implemented in terms  
of Cont?




Cont and StateT, wasn't it?
And the schemers have no choice about running in StateT :)


You sure? I want to see the proof :)

Last time I stumbled upon something like this, the proof was to embed 
every monad m in the type


  type Cont m a = forall b . (a - m b) - m b

with an

  instance Monad (Cont m) where ...

_independent_ of whether m is a monad or not.

The problem I see with it is that we didn't really encode  m  with it 
since we're still dependent on  return  and (=) via


  project :: Monad m = Cont m a - m a
  project f = f return

and

  inject :: Monad m = m a - Cont m a
  inject x = (x =)

I mean, the starting point for a concrete monad M are some primitive 
operations like


  get :: M s
  put :: s - M ()

and a function

  observe :: M a - (S - (a,S))

together with laws for the primitive operations (= operational semantics)

  observe (put s = x) = \_ - observe (x ()) s
  observe (get = x)   = \s - observe (x s ) s

and for return

  observe (return a)= \s - (a,s)

Now, implementing a monad means to come up with a type M and functions 
(=) and  return  that fulfill the monad laws. (In general, the result 
type of observe is _not_ M a !) This can be done with the standard trick 
of implementing stuff as constructors (see Unimo for details 
http://web.cecs.pdx.edu/~cklin/papers/unimo-143.pdf).


But - and that's the problem - I don't see how it can be done with Cont 
in all cases. It works for the above state monad (*) but what about 
primitives like


  mplus  :: m a - m a - m a
  callcc :: ((a - m r) - m r) - m a

that have monadic arguments in a contravariant position (possibly even 
universally quantified)?



Regards,
apfelmus

*: Here you go:

  type Observe s a = s - (a,s)
  type State s a   = Cont (Observe s) a

  get   = \x - (\s - observe (x s ) s)  -- law for get
  put s = \x - (\_ - observe (x ()) s)  -- law for put

  observe f = f $ \a - (\s - (a,s))  -- law for  observe (return a)

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


[Haskell-cafe] Re: more functions to evaluate

2007-10-13 Thread Aaron Denney
On 2007-10-12, Dan Weston [EMAIL PROTECTED] wrote:
 applyNtimes f n | n  0 = f . applyNtimes f (n-1)
 | otherwise = id

Why not some variant of:

applyNtimes f n = foldl' (.) id (replicate n f)

-- 
Aaron Denney
--

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


[Haskell-cafe] Re: How to thoroughly clean up Haskell stuff on linux

2007-10-13 Thread Jon Fairbairn
Lihn, Steve [EMAIL PROTECTED] writes:

 Hi,
 I have been hacking the Haskell installation a few days on Redhat Linux.
   GHC 6.6 - 6.6.1 - Lambdabot does not work.

[...]


 Anyway, now my question is, how do I thoroughly clean up Haskell? (And
 maybe try again after a few days of rest.)


Is there some reason why you can't use RPMs, given that it's
a redhat system?

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Fri, 2007-10-12 at 20:25 -0700, Stefan O'Rear wrote:
 On Sat, Oct 13, 2007 at 12:09:57AM +0200, ntupel wrote:
  setup :: (Ord a, IArray a2 a, IArray a1 e, Num a) = [e] - [a] - (a1 Int 
  e, a1 Int e, a2 Int a)
  calcAlias :: (Ord e, Num e, IArray a e, Ix i, IArray a2 e1, IArray a1 e1) 
  = a2 i e1 - a1 i e1 - a i e - [i] - [i] - (a1 i e1, a i e)
  next :: (IArray a2 e1, IArray a e1, Ord e, IArray a1 e, RandomGen t, Random 
  e) = (a Int e1, a2 Int e1, a1 Int e) - t - (e1, t)
  randomList :: (Random e, RandomGen t1, IArray a2 e, Ord e, IArray a t, 
  IArray a1 t) = (a Int t, a1 Int t, a2 Int e) - t1 - [t]
 
...
 I would try specializing to StdGen, UArray, and Int, for RandomGen,
 IArray, and Random respectively.


Thanks for your reply Stefan. Unfortunately I could measure only a
relatively small improvement by changing to concrete types, e.g. using

setup :: [a] - [Double] - (Array Int a, Array Int a, UArray Int
Double)

calcAlias :: Array Int a - Array Int a - UArray Int Double - [Int] -
[Int] - (Array Int a, UArray Int Double)

next :: (Array Int a, Array Int a, UArray Int Double) - StdGen - (a,
StdGen)

randomList :: (Array Int a, Array Int a, UArray Int Double) - StdGen -
[a]

the sample code was about one second faster when compiled with -O2.
Profiling again indicated that most time was spend in random and randomR
(I manually added cost centers into next):

   main +RTS -p -RTS

total time  =8.00 secs   (160 ticks @ 50 ms)
total alloc = 2,430,585,728 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

random Random60.0   54.5
randomRRandom20.0   23.3
next   Random17.5   17.0
main   Main   1.92.5
randomList Random 0.62.8


previously (i.e. with long class contexts) it looked like this:


   main +RTS -p -RTS

total time  =7.85 secs   (157 ticks @ 50 ms)
total alloc = 2,442,579,716 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

random Random58.6   54.5
randomRRandom22.9   23.3
next   Random14.6   16.5
main   Main   2.52.5
randomList Random 1.33.1


Many thanks again,
Thoralf


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


Re: [Haskell-cafe] WinAmp plugin?

2007-10-13 Thread Peter Verswyvelen
Yes that would be cool. Similarly, Haskell could also be used to create 
something like http://www.soundspectrum.com/g-force. Would be cool to 
translate the vector-field code to the GPU, and that has already been 
done in Haskell (Vertigo?)


Conal Elliott wrote:
sounds like great fun to me.  i'll contribute some functional graphics 
expertise.  dons  others have learned how to get good performance out 
of elegant code. does anyone have WinAmp plugin know-how?  - Conal


On 10/12/07, *Andrew Coppin* [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


Does anybody here know WinAmp?

[I feel sure the answer must be yes!]

How hard would it be to write a visualisation plugin in Haskell?

I think this would be a neat way of demonstrating that Haskell isn't
slow. Also, WinAmp plugins (and, actually, WinAmp) are notoriously
buggy and unstable. Would be a nice place to show off how reliable
Haskell programs are.

OTOH, I have no idea about this kind of thing, so...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto: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] more functions to evaluate

2007-10-13 Thread Rodrigo Queiro
Dan: Sorry, I forgot to Reply to All.

On 12/10/2007, Dan Weston [EMAIL PROTECTED] wrote:
...
 We don't want to make an intermediate list of zeroes and append, since
 that could be wasteful. Just keep adding a zero to the head of our list
 until it gets big enough. Our list is not copied (i.e. it is shared with
 the tail of the result) this way, saving making a copy during reverse.

It's actually much less efficient to create a big function that
prepends a list of zeroes than just to create that list of zeroes and
prepend it.

You will be much better of just using (replicate n e ++) than
(applyNtimes (e:) n).

Contrived benchmark:
Prelude sum . map length $ [replicate i 0 ++ [1..10] | i - [1..2000]]
2021000
(0.19 secs, 114581032 bytes)
Prelude sum . map length $ [applyNtimes (0:) i [1..10] | i - [1..2000]]
2021000
(2.51 secs, 242780204 bytes)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: How to thoroughly clean up Haskell stuff on linux

2007-10-13 Thread Brandon S. Allbery KF8NH


On Oct 13, 2007, at 3:51 , Aaron Denney wrote:


On 2007-10-12, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:


On Oct 12, 2007, at 17:38 , Lihn, Steve wrote:


  Installing: --prefix=~/cabal/lib/haddock-0.8/ghc-6.4 


This looks suspicious to me:  the ~ metacharacter is only
understood by shells, and only in certain circumstances (i.e. only at
the beginning of a word, not after a =),


This likely the problem, but a reasonable shell (i.e. zsh) will  
expand in

this circumstance:


zsh only does so with setopt magicequalsubst.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread Brandon S. Allbery KF8NH


On Oct 13, 2007, at 6:52 , ntupel wrote:


On Fri, 2007-10-12 at 20:25 -0700, Stefan O'Rear wrote:

On Sat, Oct 13, 2007 at 12:09:57AM +0200, ntupel wrote:
setup :: (Ord a, IArray a2 a, IArray a1 e, Num a) = [e] - [a] - 
 (a1 Int e, a1 Int e, a2 Int a)
calcAlias :: (Ord e, Num e, IArray a e, Ix i, IArray a2 e1,  
IArray a1 e1) = a2 i e1 - a1 i e1 - a i e - [i] - [i] - (a1  
i e1, a i e)
next :: (IArray a2 e1, IArray a e1, Ord e, IArray a1 e, RandomGen  
t, Random e) = (a Int e1, a2 Int e1, a1 Int e) - t - (e1, t)
randomList :: (Random e, RandomGen t1, IArray a2 e, Ord e, IArray  
a t, IArray a1 t) = (a Int t, a1 Int t, a2 Int e) - t1 - [t]



...

I would try specializing to StdGen, UArray, and Int, for RandomGen,
IArray, and Random respectively.


Thanks for your reply Stefan. Unfortunately I could measure only a
relatively small improvement by changing to concrete types, e.g. using

(...)

COST CENTREMODULE   %time %alloc

random Random60.0   54.5
randomRRandom20.0   23.3
next   Random17.5   17.0
main   Main   1.92.5
randomList Random 0.62.8


Now you need to start forcing things; given laziness, things tend to  
only get forced when in IO, which leads to time being accounted to  
the routine where the forcing happened.  If random / randomR are  
invoked with large unevaluated thunks, their forcing will generally  
be attributed to them, not to functions within the thunks.


(Yes, this means profiling lazy programs is a bit of a black art.)

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Dual Parser Failure???

2007-10-13 Thread Brent Yorgey
On 10/12/07, PR Stanley [EMAIL PROTECTED] wrote:

 Hi
 failure :: (Parser a) failure = \inp - []
 The code might contain some syntax errors and I'd be grateful for any
 corrections.
 What is a dual parser failure?


You should probably put the definition on a separate line, thus:

failure :: (Parser a)
failure = \inp - []

If that doesn't work, you could send along the definition of the Parser
type.

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


Re: [Haskell-cafe] Re: Type-level arithmetic

2007-10-13 Thread Roberto Zunino
Andrew Coppin wrote:
 I was actually thinking more along the lines of a programming language
 where you can just write
 
  head :: (n  1) = List n x - x

Current GHC can approximate this with a GADT:

==
{-# OPTIONS -fglasgow-exts #-}
module SafeHead where

data Z
data S a

data List n a where
  Nil  :: List Z a
  Cons :: a - List n a - List (S n) a

head1 :: List (S n) a - a
head1 (Cons x _) = x
-- head1 Nil = undefined   -- error: inaccessible

-- test0 = head1 Nil   -- error: Z /= S n
test1 = head1 (Cons 'a' Nil)
==

For more complex type arithmetic, you need the GHC 6.8RC for type families:

==
data TT  -- true
data FF  -- false

type family Geq a b -- a = b
type instance Geq a Z = TT
type instance Geq Z (S n) = FF
type instance Geq (S n) (S m) = Geq n m

head2 :: Geq n (S Z) ~ TT = List n a - a
head2 (Cons x _) = x
-- head2 Nil = undefined   -- no error, but useless

-- test2 = head2 Nil   -- error: TT /= Geq Z (S Z)
test3 = head2 (Cons 'a' Nil)
==

Of course, the downside is that using the List GADT can be inconvenient
since you need to be able to express _in a static way_ the length of the
lists:

(++) :: List n a - List m a - List (Sum n m) a

(\\) :: List n a - List m a - List (???) a

The (\\) case is impossible to predict (if you know only the lengths),
so you probably need to return a simple [a] there. Of course, you can
recover a better type with un-time checks, as in (roughly)

checkLength :: [a] - n - Maybe (List n a)

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


Re: [Haskell-cafe] Can every monad can be implemented with Cont? (was: New slogan for haskell.org)

2007-10-13 Thread jeff p
Hello,

  Didn't someone already prove all monads can be implemented in terms
  of Cont?
 
 
  Cont and StateT, wasn't it?
  And the schemers have no choice about running in StateT :)

 You sure? I want to see the proof :)

I think this is referring to Andrzej Filinski's paper Representing
Layered Monads in which it shown that stacks of monads can be
implemented directly (no layering) by using call/cc and mutable state.

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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Sat, 2007-10-13 at 09:56 -0400, Brandon S. Allbery KF8NH wrote:
 Now you need to start forcing things; given laziness, things tend to  
 only get forced when in IO, which leads to time being accounted to  
 the routine where the forcing happened.  If random / randomR are  
 invoked with large unevaluated thunks, their forcing will generally  
 be attributed to them, not to functions within the thunks.

But AFAIK random and randomR only take a StdGen (plus a range argument
in case of randomR) as argument so I don't understand where the
unevaluated thunks might be actually? (Maybe I should have said that
random and randomR are the ones from GHC's System.Random module.)

Thanks,
Thoralf


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


Re: [Haskell-cafe] Can every monad can be implemented with Cont? (was: New slogan for haskell.org)

2007-10-13 Thread Albert Y. C. Lai

jeff p wrote:

I think this is referring to Andrzej Filinski's paper Representing
Layered Monads in which it shown that stacks of monads can be
implemented directly (no layering) by using call/cc and mutable state.


I have been unable to see how to bring its crucial reify and reflect 
to Haskell. In particular reflect:


reflect :: m a - a

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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread Brandon S. Allbery KF8NH


On Oct 13, 2007, at 11:40 , ntupel wrote:


On Sat, 2007-10-13 at 09:56 -0400, Brandon S. Allbery KF8NH wrote:

Now you need to start forcing things; given laziness, things tend to
only get forced when in IO, which leads to time being accounted to
the routine where the forcing happened.  If random / randomR are
invoked with large unevaluated thunks, their forcing will generally
be attributed to them, not to functions within the thunks.


But AFAIK random and randomR only take a StdGen (plus a range argument
in case of randomR) as argument so I don't understand where the
unevaluated thunks might be actually? (Maybe I should have said that
random and randomR are the ones from GHC's System.Random module.)


Your apparently simple StdGen argument is actually a sort of program  
state (represented by unevaluated thunks, not by a state monad; see  
below) which gets altered with every invocation of random.  If  
nothing is forced until the very end, it in effect becomes an  
expression which produces the desired StdGen, with the uses of the  
previous StdGen values as side effects of its computation that  
occur when the thunk is evaluated at the end.  I'm not sure I'm up to  
working through an example of what this looks like.


Suffice it to say that in a lazy language like Haskell, almost any  
simple expression can in practice end up being a suspended  
computation (a thunk) consisting of whatever is supposed to produce  
it.  And in the general case (e.g. you don't use strictness  
annotations) the only way to force evaluation is to do I/O, so it's  
quite normal for a naive program to end up being one big thunk  
dangling off a PutStrLn.  So why does random get tagged for it?   
Because it's a state-like function (that is, a function of the form s  
- (a,s); compare to the definition of the State monad) which takes a  
StdGen and produces a modified StdGen, so when Haskell finally  
evaluates the thunk most of the activity happens in the context of  
evaluating that modification.


Hopefully someone reading -cafe can explain it better; I'm pretty  
lousy at it, as you can probably tell.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Can every monad can be implemented with Cont? (was: New slogan for haskell.org)

2007-10-13 Thread Dan Doel
On Saturday 13 October 2007, Albert Y. C. Lai wrote:
 jeff p wrote:
  I think this is referring to Andrzej Filinski's paper Representing
  Layered Monads in which it shown that stacks of monads can be
  implemented directly (no layering) by using call/cc and mutable state.

 I have been unable to see how to bring its crucial reify and reflect
 to Haskell. In particular reflect:

 reflect :: m a - a

 It looks very magical.

Here: http://cs.ioc.ee/mpc-amast06/msfp/filinski-slides.pdf

are some slides Filinski made about doing monadic reflection in Haskell (there 
might be a corresponding paper, but a cursory googling didn't find it).

The thing is, 'reflect' in Haskell doesn't have type 'm a - a' It has type 
something like:

  m a - ContState a

However, in the languages he usually works with, everything is already 
implicitly in a ContState monad, in that they have mutable references and 
native continuations. Hence the type 'm a - a' there.

At least, I think that's the explanation.

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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Sat, 2007-10-13 at 12:42 -0400, Brandon S. Allbery KF8NH wrote:
 Your apparently simple StdGen argument is actually a sort of program  
 state (represented by unevaluated thunks, not by a state monad; see  
 below) which gets altered with every invocation of random.  If  
 nothing is forced until the very end, it in effect becomes an  
 expression which produces the desired StdGen, with the uses of the  
 previous StdGen values as side effects of its computation that  
 occur when the thunk is evaluated at the end.  I'm not sure I'm up to  
 working through an example of what this looks like.

Thanks Brandon. I understand your argument but I don't know how to put
it into practice, i.e. how to force the evaluation of StdGen.

- Thoralf


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread Brandon S. Allbery KF8NH


On Oct 13, 2007, at 13:30 , ntupel wrote:


On Sat, 2007-10-13 at 12:42 -0400, Brandon S. Allbery KF8NH wrote:

Your apparently simple StdGen argument is actually a sort of program
state (represented by unevaluated thunks, not by a state monad; see
below) which gets altered with every invocation of random.  If
nothing is forced until the very end, it in effect becomes an
expression which produces the desired StdGen, with the uses of the
previous StdGen values as side effects of its computation that
occur when the thunk is evaluated at the end.  I'm not sure I'm up to
working through an example of what this looks like.


Thanks Brandon. I understand your argument but I don't know how to put
it into practice, i.e. how to force the evaluation of StdGen.


For starters, look into seq. Try applying it to any expression  
using a generated random number.  This should force evaluation to  
occur somewhere other than when random is trying to figure out what  
StdGen value it's been told to use as its initial state.


Alternately you can put all the uses in IO and use  
Control.Exception.evaluate (or even print).  This is probably not  
what you want to do in your actual production code, however.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Sat, 2007-10-13 at 13:35 -0400, Brandon S. Allbery KF8NH wrote:
 For starters, look into seq. Try applying it to any expression  
 using a generated random number.  This should force evaluation to  
 occur somewhere other than when random is trying to figure out what  
 StdGen value it's been told to use as its initial state.
 

Ok, but I still wonder where that might be. random and randomR are used
in a function named next as show here:

next :: (Array Int a, Array Int a, UArray Int Double) - StdGen - (a,
StdGen)
next (xs, as, rs) g =
let n = length $ indices xs
(x1, g1) = randomR (0, n - 1) g
(x2, g2) = random g1
r = rs!x1
in
if x2 = r 
then (xs!x1, g2) 
else (as!x1, g2)


x1 and x2 are used in the same function so I assume this already
requires their evaluation. The only function that calls next is
randomList:

randomList :: (Array Int a, Array Int a, UArray Int Double) - StdGen -
[a]
randomList t g = 
let (n, g') = next t g
in 
n:randomList t g'

Cf. my original e-mail for the complete program. 

 Alternately you can put all the uses in IO and use  
 Control.Exception.evaluate (or even print).  This is probably not  
 what you want to do in your actual production code, however.
 

Right. This is not what I want.

Many thanks again,
Thoralf


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


[Haskell-cafe] do

2007-10-13 Thread PR Stanley

Hi
do, what's its role?
I know a few uses for it but can't quite understand the semantics - 
e.g. do putStrLn bla bla

So, what does do, do?
Thanks, Paul

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


Re: [Haskell-cafe] do

2007-10-13 Thread Henning Thielemann


On Sat, 13 Oct 2007, PR Stanley wrote:


Hi
do, what's its role?
I know a few uses for it but can't quite understand the semantics - e.g. do 
putStrLn bla bla

So, what does do, do?


It's syntactic sugar.

http://www.haskell.org/onlinereport/exps.html#sect3.14
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Filesystem questions

2007-10-13 Thread Yitzchak Gale
Andrew Coppin wrote:
 Is there a way to get rid of . and .. in the results?

Brandon S. Allbery wrote:
 Manual filtering is always required, whether C, Perl, Haskell, etc.
 I dunno, maybe python filters them for you or something.

Correct, Python filters them out. This is clearly the correct
behavior. That is what is needed in the vast majority
of cases, and it is still reasonably easy to deal
with the unusual cases.

It is too bad that Haskell is among the many languages
that get this wrong.

Python also has os.walk, a very convenient functional (sort of)
tool for recursing through directories. (It sounds trivial, but
it is not, there are enough annoying details that this function
saves huge amounts of time.) Very embarrassing that Haskell
is missing this.

How about a built-in function that represents a directory tree
as a lazy Data.Tree?

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


Re: [Haskell-cafe] do

2007-10-13 Thread Luke Palmer
On 10/13/07, PR Stanley [EMAIL PROTECTED] wrote:
 Hi
 do, what's its role?
 I know a few uses for it but can't quite understand the semantics -
 e.g. do putStrLn bla bla
 So, what does do, do?

In this example, do doesn't do anything.  do doesn't do anything to a
single expression (well, I think it enforces that its return value is
a monad...).  It's only when you give it multiple expressions that it
rewrites them into more formal notation.  For example:

do putStrLn bla
   putStrLn blah

Will be rewritten into:

putStrLn bla  putStrLn blah

It introduces a block of sequential actions (in a monad), to do each
action one after another.  Both of these (since they're equivalent)
mean print bla *and then* print blah.

do also allows a more imperative-feeling variable binding:

do line - getLine
   putStr You said: 
   putStrLn line

Will be rewritten into:

getLine = (\line - putStr You said:   putStrLn line)

Looking at the do notation again: execute getLine and bind the return
value to the (newly introduced) variable 'line', then print You said:
, then print the value in the variable line.

You can think of the last line in the block as the return value of the
block.  So you can do something like:

do line - do putStr Say something: 
  getLine
   putStr You said: 
   putStrLn line

In this example it's kind of silly, but there are cases where this is useful.

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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread Isaac Dupree

ntupel wrote:

Thanks for your reply Stefan. Unfortunately I could measure only a
relatively small improvement by changing to concrete types



the sample code was about one second faster when compiled with -O2.
Profiling again indicated that most time was spend in random and randomR


GHC StdGen's random and randomR are somewhat slow.  I found that 
changing to a custom ((x*a + b) `mod` c) random-generator (instance of 
RandomGen) much sped things up (since nothing depended on the random 
numbers being good quality).  (Then I switched to a small C function to 
do the randomization and make all the OpenGL calls, and it sped up by 
another factor of 4.)


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread Don Stewart
isaacdupree:
 ntupel wrote:
 Thanks for your reply Stefan. Unfortunately I could measure only a
 relatively small improvement by changing to concrete types
 
 the sample code was about one second faster when compiled with -O2.
 Profiling again indicated that most time was spend in random and randomR
 
 GHC StdGen's random and randomR are somewhat slow.  I found that 
 changing to a custom ((x*a + b) `mod` c) random-generator (instance of 
 RandomGen) much sped things up (since nothing depended on the random 
 numbers being good quality).  (Then I switched to a small C function to 
 do the randomization and make all the OpenGL calls, and it sped up by 
 another factor of 4.)
 

I've seen similar results switching to the SIMD mersenne twister C
implementation for randoms:

http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/SFMT/index.html

If there's interest, I can package up the bindings for hackage.

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


Re: [Haskell-cafe] Filesystem questions

2007-10-13 Thread Henning Thielemann


On Sat, 13 Oct 2007, Yitzchak Gale wrote:


Andrew Coppin wrote:

Is there a way to get rid of . and .. in the results?


Brandon S. Allbery wrote:

Manual filtering is always required, whether C, Perl, Haskell, etc.
I dunno, maybe python filters them for you or something.


Correct, Python filters them out. This is clearly the correct
behavior. That is what is needed in the vast majority
of cases, and it is still reasonably easy to deal
with the unusual cases.

It is too bad that Haskell is among the many languages
that get this wrong.


me too


Python also has os.walk, a very convenient functional (sort of)
tool for recursing through directories. (It sounds trivial, but
it is not, there are enough annoying details that this function
saves huge amounts of time.) Very embarrassing that Haskell
is missing this.


Maybe it is already in one of the Haskell for scripting packages?

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


Re: [Haskell-cafe] do

2007-10-13 Thread Henning Thielemann


On Sat, 13 Oct 2007, Henning Thielemann wrote:


On Sat, 13 Oct 2007, PR Stanley wrote:


Hi
do, what's its role?
I know a few uses for it but can't quite understand the semantics - e.g. do 
putStrLn bla bla

So, what does do, do?


It's syntactic sugar.

http://www.haskell.org/onlinereport/exps.html#sect3.14



http://syntaxfree.wordpress.com/2006/12/12/do-notation-considered-harmful/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] more functions to evaluate

2007-10-13 Thread Derek Elkins
On Fri, 2007-10-12 at 16:20 -0700, Dan Weston wrote:
 I like that name, and will henceforth use it myself until someone sees 
 fit to add it to the Prelude!
 
 Maxime Henrion wrote:
  Isaac Dupree wrote:
  Dan Weston wrote:
  applyNtimes :: (a - a) - Int - a - a
 
  This sounds like it should be in the library somewhere
  agree, I've used it a few times (mostly for testing things) - modulo 
  argument order and Int vs. Integer vs. (Num a = a)
  
  What do you think about calling it iterateN instead?

The type of foldr:
foldr :: (a - b - b) - b - [a] - b
Church encoding [a]
[a] = forall b.(a - b - b) - b - b
Permuting arguments, foldr is one way of an isomorphism between [a] and
it's Church encoding, i.e. \c n - foldr c n list is the Church encoded
version of list.
Church encoding of Nat
Nat = forall a.(a - a) - a - a
iterateN is foldNat up to permutations of arguments and ignoring
negative values

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


Re: [Haskell-cafe] do

2007-10-13 Thread jerzy . karczmarczuk


PR Stanley wrote:



Hi
do, what's its role?
I know a few uses for it but can't quite understand the semantics - e.g. 
do putStrLn bla bla

So, what does do, do?



On Sat, 13 Oct 2007, Henning Thielemann wrote:


It's syntactic sugar. 


http://www.haskell.org/onlinereport/exps.html#sect3.14


etc. 


Actually, there is a SURGEON GENERAL'S WARNING: the do construct is a
syntactic Monosodium Glutamate (MSG), known sometimes as Syntactic
Ajinomoto. Whether it is responsable for the Syntactic Chinese Restaurant
Syndrom or not, is under investigation. 


Whether it increases really the flavour of the Monosod... argh... Monadic
meals, it depends on your metabolism, and of your preferred table tools.
People enjoying the consumption of long, long spaghetti use rarely
chopstics, and prefer efficient forks like =, ===, etc. 

Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] Filesystem questions

2007-10-13 Thread Magnus Therning
On Sat, Oct 13, 2007 at 23:27:13 +0200, Yitzchak Gale wrote:
Andrew Coppin wrote:
 Is there a way to get rid of . and .. in the results?

Brandon S. Allbery wrote:
 Manual filtering is always required, whether C, Perl, Haskell, etc.
 I dunno, maybe python filters them for you or something.

Correct, Python filters them out. This is clearly the correct
behavior. That is what is needed in the vast majority
of cases, and it is still reasonably easy to deal
with the unusual cases.

It is too bad that Haskell is among the many languages
that get this wrong.

Python also has os.walk, a very convenient functional (sort of)
tool for recursing through directories. (It sounds trivial, but
it is not, there are enough annoying details that this function
saves huge amounts of time.) Very embarrassing that Haskell
is missing this.

How about a built-in function that represents a directory tree
as a lazy Data.Tree?

http://therning.org/magnus/index.php?tag=haskellpaged=3

Not really what you're looking for, but hopefully it's a good place to
start.

/M

-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus.therning@gmail.com
http://therning.org/magnus


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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread ntupel
On Sat, 2007-10-13 at 14:37 -0700, Don Stewart wrote:
 I've seen similar results switching to the SIMD mersenne twister C
 implementation for randoms:
 
 http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/SFMT/index.html
 
 If there's interest, I can package up the bindings for hackage.
 

I would definitely be interested.

Many thanks,
Thoralf


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


Re: [Haskell-cafe] do

2007-10-13 Thread PR Stanley

Thanks for the very clear explanation. More questions:
What is the role of ?
How is  different to =? I am aware that = is used for 
sequencing parsers but that's all I know about it.

Thanks, Paul

At 22:28 13/10/2007, you wrote:

On 10/13/07, PR Stanley [EMAIL PROTECTED] wrote:
 Hi
 do, what's its role?
 I know a few uses for it but can't quite understand the semantics -
 e.g. do putStrLn bla bla
 So, what does do, do?

In this example, do doesn't do anything.  do doesn't do anything to a
single expression (well, I think it enforces that its return value is
a monad...).  It's only when you give it multiple expressions that it
rewrites them into more formal notation.  For example:

do putStrLn bla
   putStrLn blah

Will be rewritten into:

putStrLn bla  putStrLn blah

It introduces a block of sequential actions (in a monad), to do each
action one after another.  Both of these (since they're equivalent)
mean print bla *and then* print blah.

do also allows a more imperative-feeling variable binding:

do line - getLine
   putStr You said: 
   putStrLn line

Will be rewritten into:

getLine = (\line - putStr You said:   putStrLn line)

Looking at the do notation again: execute getLine and bind the return
value to the (newly introduced) variable 'line', then print You said:
, then print the value in the variable line.

You can think of the last line in the block as the return value of the
block.  So you can do something like:

do line - do putStr Say something: 
  getLine
   putStr You said: 
   putStrLn line

In this example it's kind of silly, but there are cases where this is useful.

Luke


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


Re: [Haskell-cafe] do

2007-10-13 Thread Luke Palmer
Disclaimer:  I'm explaining all of this in terms of actions, which
are only one way of looking at monads, and the view only works for
certain ones (IO, State, ...).  Without futher ado...

An action does two things:  it has a side-effect and then it has a
return value.  The type IO Int is an I/O action which does something
then returns an Int.

() :: m a - m b - m b

x  y  first does x, *discards* its return value, then does y.  You
can see that the return value of x is discarded by the absence of the
type variable a in the return value of ().  So if you said:

getLine  putStrLn Hello

This is an action which gets a line from the user and then throws it
away, never to be retrieved again, only to print Hello.

(=) :: m a - (a - m b) - m b

But what if you want to do something with the return value?  That's
what (=) is for.  (=) takes an action on its left side and a
function which returns an action on its right, and then pipes one
into the other.

getLine = (\x - putStrLn x)

This gets a line from the user and then executes the function on the
right given the return value from getLine as an argument; i.e. x is
bound to the return value of getLine.  The above can also be written
as:

getLine = putStrLn

Because of currying.  This action echoes one line.

Using this you can do more complex actions, like, for instance, adding
two numbers:

readLine = (\x - readLine = (\y - print (x + y)))

Take a moment to grok that...

Which you might like to write:

do x - readLine
   y - readLine
   print (x + y)

The parser sequencing thing is probably from the List monad (unless
you're using Parsec or something).  List was the first monad I really
understood (before IO even), thanks to this great tutorial:

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

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


Re: [Haskell-cafe] do

2007-10-13 Thread Isaac Dupree

Luke Palmer wrote:

Using this you can do more complex actions, like, for instance, adding
two numbers:

readLine = (\x - readLine = (\y - print (x + y)))

Take a moment to grok that...

Which you might like to write:

do x - readLine
   y - readLine
   print (x + y)


you can leave out the parentheses and make it similarly readable, still 
without do (at least, readable once you get used to the style, which 
might look almost as weird as do-notation)


  readLine = \x -
  readLine = \y -
  print (x + y)

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


Re: [Haskell-cafe] Performance problem with random numbers

2007-10-13 Thread Isaac Dupree

Don Stewart wrote:

I've seen similar results switching to the SIMD mersenne twister C
implementation for randoms:

http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/SFMT/index.html

If there's interest, I can package up the bindings for hackage.


looks nice... at least for those of us who have non-old computer 
CPUs Is there a decent way to implement 'split'? A way that doesn't 
take too long to run, and produces fairly independent generators?


Isaac

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


Re: [Haskell-cafe] Filesystem questions

2007-10-13 Thread Bryan O'Sullivan

Yitzchak Gale wrote:


Python also has os.walk, a very convenient functional (sort of)
tool for recursing through directories. (It sounds trivial, but
it is not, there are enough annoying details that this function
saves huge amounts of time.) Very embarrassing that Haskell
is missing this.


See System.FilePath.Find in 
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/FileManip-0.2



How about a built-in function that represents a directory tree
as a lazy Data.Tree?


Not a very good idea.  Representing a directory structure as a tree 
makes people think they can manipulate it as if it were a tree, which 
leads to all kinds of nasty bugs when the real world bleeds through the 
holes in the abstraction.


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