[Haskell-cafe] Re: Trees

2007-12-03 Thread apfelmus

Adrian Neumann wrote:


  data Tree a = Leaf a | Node a [Tree a]

But now the assignments require more than a simple top-down traversal. 
For example: given a tree t and two nodes u,v, find the first common 
ancestor.


Well, this problem doesn't make much sense in Haskell. How do you 
specify the subtrees u and v in the first place?



Regards,
apfelmus

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


[Haskell-cafe] Re: Possible Improvements

2007-12-03 Thread apfelmus

PR Stanley wrote:


data Tree = Leaf Int | Node Tree Int Tree

occurs :: Int - Tree - Bool
occurs m (Leaf n) = m == n
occurs m (Node l n r) = m == n || occurs m l || occurs m r

It works but I'd like to know if it can be improved in any way.


That's entirely fine.

The logical or || doesn't evaluate it's second argument  occurs m r  if 
the first argument  occurs m l  turns out to be already True. In other 
words, thanks to lazy evaluation, the search stops if  m  has been found 
in the left subtree, it won't search the right subtree anymore.



Regards,
apfelmus

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


Re: [Haskell-cafe] Possible Improvements

2007-12-03 Thread Johan Tibell
 I agree that (in this context, beginning learning Haskell) it is a
 somewhat minor issue.  But I disagree that this is something you should
 ignore until it becomes a problem and I do think that it should be part
 of learning Haskell.  Properly using strictness is an important part of
 using Haskell.  It makes the difference between code that stack
 overflows and code that doesn't, code that takes 100 seconds and code
 that takes 10, code that uses 3MB of RAM and code that uses 600.  At
 least the first of these is not, in my mind, the difference between
 optimized and unoptimized, but rather the difference between correct
 and incorrect.  Writing better code at the beginning is much easier than
 trying to figure out what the problem is later.  Furthermore, writing
 better code is not more difficult.  In this case it merely means adding
 two characters.  Of late, the rules of thumb for this sort of thing
 are becoming more widely known.  Such things need to be instinctively
 part of how you write code, much like writing code tail-recursively or
 not using (++) left associatively.  It's not that you should immediately
 know that this is better, but (more strongly) that you should not even
 think of the worse ways to begin with in many cases.

It would be great if someone could exemplify these rules of thumb,
e.g. Primitive types such as Int should be strict unless in the three
canonical examples X, Y and Z. My strictness radar is still quite
poor and I feel I can't make informed decisions on when I need to make
something more strict or lazy.

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


Re: [Haskell-cafe] Possible Improvements

2007-12-03 Thread PR Stanley
That's a very good point. Yes, let's have some detailed explanations 
accompanied by some good examples.

Cheers, Paul
At 08:43 03/12/2007, you wrote:

 I agree that (in this context, beginning learning Haskell) it is a
 somewhat minor issue.  But I disagree that this is something you should
 ignore until it becomes a problem and I do think that it should be part
 of learning Haskell.  Properly using strictness is an important part of
 using Haskell.  It makes the difference between code that stack
 overflows and code that doesn't, code that takes 100 seconds and code
 that takes 10, code that uses 3MB of RAM and code that uses 600.  At
 least the first of these is not, in my mind, the difference between
 optimized and unoptimized, but rather the difference between correct
 and incorrect.  Writing better code at the beginning is much easier than
 trying to figure out what the problem is later.  Furthermore, writing
 better code is not more difficult.  In this case it merely means adding
 two characters.  Of late, the rules of thumb for this sort of thing
 are becoming more widely known.  Such things need to be instinctively
 part of how you write code, much like writing code tail-recursively or
 not using (++) left associatively.  It's not that you should immediately
 know that this is better, but (more strongly) that you should not even
 think of the worse ways to begin with in many cases.

It would be great if someone could exemplify these rules of thumb,
e.g. Primitive types such as Int should be strict unless in the three
canonical examples X, Y and Z. My strictness radar is still quite
poor and I feel I can't make informed decisions on when I need to make
something more strict or lazy.

-- Johan
___
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] Re: New slogan for haskell.org

2007-12-03 Thread apfelmus

Stefan O'Rear wrote:


In my C programming, I've taken to using gdb as a REPL:


Ah, that's a nice trick, thanks!

I wish I there had been a gdb on MacOS 8.5 back then ;)


Regards,
apfelmus

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


Re: [Haskell-cafe] Monads

2007-12-03 Thread Radosław Grzanka
Hi,

2007/12/3, PR Stanley [EMAIL PROTECTED]:
 Hi
 Does the list consider
 http://en.wikibooks.org/w/index.php?title=Haskell/Understanding_monadsoldid=933545
 a reliable tutorial on monads and, if not, could you recommend an
 onlien alternative please?

I really enjoyed All about Monads by Jeff Newbern
http://www.haskell.org/all_about_monads/html/index.html

Cheers,
  Radek.

-- 
Codeside: http://codeside.org/
Przedszkole Miejskie nr 86 w Lodzi: http://www.pm86.pl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible Improvements

2007-12-03 Thread Bulat Ziganshin
Hello PR,

Monday, December 3, 2007, 8:20:35 AM, you wrote:
 occurs m (Node l n r) = m == n || occurs m l || occurs m r

in terms of style, i can prefer

occurs m (Node l n r)   =   or [m==n, occurs m l, occurs m r]


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Monads

2007-12-03 Thread PR Stanley

Hi
Does the list consider
http://en.wikibooks.org/w/index.php?title=Haskell/Understanding_monadsoldid=933545
a reliable tutorial on monads and, if not, could you recommend an 
onlien alternative please?

Thanks,
Paul

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


Re: [Haskell-cafe] Possible Improvements

2007-12-03 Thread Ketil Malde
Johan Tibell [EMAIL PROTECTED] writes:

 It would be great if someone could exemplify these rules of thumb,
 e.g. Primitive types such as Int should be strict unless in the three
 canonical examples X, Y and Z. My strictness radar is still quite
 poor and I feel I can't make informed decisions on when I need to make
 something more strict or lazy.

I find that I often need to add strictness when:

 left thumb)  parsing [Char] into something more compact, i.e. almost
  all cases.
 right thumb) storing data into maps, especially when the values are produced by
  multiple updates - i.e. doing word frequency counts.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Array copying

2007-12-03 Thread Reinier Lamers

ChrisK wrote:


For GHC 6.6 I created

 


foreign import ccall unsafe memcpy
   memcpy :: MutableByteArray# RealWorld - MutableByteArray# RealWorld - Int# 
- IO ()
   



 


{-# INLINE copySTU #-}
copySTU :: (Show i,Ix i,MArray (STUArray s) e (ST s)) = STUArray s i e - 
STUArray s i e - ST s ()
copySTU (STUArray _ _ msource) (STUArray _ _ mdest) =
-- do b1 - getBounds s1
--  b2 - getBounds s2
--  when (b1/=b2) (error (\n\nWTF copySTU: ++show (b1,b2)))
 ST $ \s1# -
   case sizeofMutableByteArray# msourceof { n# -
   case unsafeCoerce# memcpy mdest msource n# s1# of { (# s2#, () #) -
   (# s2#, () #) }}
   



To allow efficient copying of STUArrays.
 

How does this guarantee that it doesn't overflow the buffer of the 
destination array?


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


Re: [Haskell-cafe] A tale of three shootout entries

2007-12-03 Thread Don Stewart
s.clover:
Was this with tossing the partial sums code into the optimised bangs
program? Weird. I wonder if profiling will help explain why? In any case,
If nobody comes up with any other tweaks, I'll probably submit the
optimised bangs version to the shootout this weekend.
 

Please go ahead and submit. :) and remember to upload also to our wiki,
so we have a permanent record of the attempt,

http://haskell.org/haskellwiki/Shootout

Note down any ideas you have.

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



[Haskell-cafe] Parallelise now! Was: Re: Possible Improvements

2007-12-03 Thread Don Stewart
dons:
 Strict in the elements, lazy in the spine:
 
 data Tree = Leaf !Int | Node Tree !Int Tree
 
 $ time ./A 25  
 49
 ./A 25  14.41s user 0.03s system 99% cpu 14.442 total
  ^^
 3056K heap use.

And, finally, we can get a little speedup again over the basic
element-strict, -funboxed-strict-fields tree by parallelising 
some of the traversals. Nothing great, but I didn't try very hard:

Serial code:

{-# OPTIONS -O2 -funbox-strict-fields #-}

import System.Environment

data Tree = Leaf !Int | Node Tree !Int Tree

main = do
n - getArgs = readIO . head
let t = make (n*2) n
print (check t)

make :: Int - Int - Tree
make i 0 = Node (Leaf 0) i (Leaf 0)
make i d = Node (make (i2-1) d2) i (make i2 d2)
  where i2 = 2*i
d2 = d-1

check :: Tree - Int
check (Leaf _) = 0
check (Node l i r) = i + check l - check r

Running:

$ time ./A 28  
55
./A 28  24.39s user 0.03s system 99% cpu 24.424 total

Ok. Now, parallelise that recursive call in 'check':

check :: Tree - Int
check (Leaf _) = 0
check (Node l i r) = lp `par` (rp `pseq` i + lp - rp) -- --
   where lp = check l
 rp = check r

Super-simple strategy -- will register too many sparks, but what the heh...

$ time ./B 28  +RTS -N2
55
./B 28 +RTS -N2  31.81s user 0.14s system 147% cpu 21.700 total

Pretty good for a naive strategy, and only one branch, on one line had to be 
modified.
Control.Parallel, yay!

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


[Haskell-cafe] Re: Optimizing cellular automata evaluation (round 2)

2007-12-03 Thread Mirko Rahn



 http://hpaste.org/4151#a1


It is interesting, that the naive implementation

import Data.List (tails)

neighbours :: Int - [a] - [[a]]
neighbours w = rotL . take w . map (take 3) . tails . cycle

rotL :: [a] - [a]
rotL xs = last xs : init xs

type Rule a = [a] - a

step :: Int - Rule a - [a] - [a]
step w f = map f . neighbours w

rule110 :: Rule Char
rule110 = ' '
rule110 X   = ' '
rule110 XXX = ' '
rule110 _ = 'X'

main = let f = step 149 rule110
   init = replicate 148 ' ' ++ X
   in mapM_ putStrLn $ take 1 $ iterate f init

is only 3 times slower than your quite complex, hard to follow and hard 
to debug implementation.


As always, I prefer to write most code in Haskell, quick, easy, nice, 
reasonable fast, ... If speed matters, I switch to some lower level 
language, as you did staying inside Haskell.


/BR, Mirko Rahn

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


[Haskell-cafe] Re: Trees

2007-12-03 Thread apfelmus

Thomas Davie wrote:

apfelmus wrote

Well, this problem doesn't make much sense in Haskell.
How do you specify the subtrees u and v in the first place? 


One could alway store a node's depth at each node -- then you must 
search for u and v, creating a list of what nodes you found at each 
depth, and finally, simply compare the lists -- O(n) in the depth of u 
and v.


Huh? I mean, are u and v node labels of type a? Or are they subtrees? In 
any case, they aren't pointers into the tree.


In the case of node labels, a breath first search will take

  O(number of nodes of depth = min (depth u) (depth v))

steps which is

  O(size of the tree)

in the worst case.


Regards,
apfelmus

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


Re: [Haskell-cafe] Re: Trees

2007-12-03 Thread Thomas Davie
One could alway store a node's depth at each node -- then you must  
search for u and v, creating a list of what nodes you found at each  
depth, and finally, simply compare the lists -- O(n) in the depth of u  
and v.


Bob

On 3 Dec 2007, at 08:40, apfelmus wrote:


Adrian Neumann wrote:

 data Tree a = Leaf a | Node a [Tree a]
But now the assignments require more than a simple top-down  
traversal. For example: given a tree t and two nodes u,v, find the  
first common ancestor.


Well, this problem doesn't make much sense in Haskell. How do you  
specify the subtrees u and v in the first place?



Regards,
apfelmus

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


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


[Haskell-cafe] do

2007-12-03 Thread PR Stanley

Hi
I've probably asked about the do construct, if that's the right 
label. Unfortunately I'm still not quite sure of its role and more 
specifically its syntax. Something to do with generators perhaps? A 
description plus some examples would be most gratefully received.

Thanks, Paul

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


Re: [Haskell-cafe] ARM back end?

2007-12-03 Thread John Meacham
On Fri, Nov 02, 2007 at 01:30:44PM -0700, Greg Fitzgerald wrote:
 Anybody know of an ARM back end for any of the Haskell compilers?

jhc can compile to the arm as well. This was tested by compiling a
simple program for the iPhone. :)

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] I'm translating All about Monads to Chinese

2007-12-03 Thread Radosław Grzanka
2007/12/3, Albert Lee [EMAIL PROTECTED]:
 I have been confussed by monad for a long time. and I can't stand for
 it any more. so I start to translate the tutorial All About Monads
 to my mother language Chinese.
 My English is not good enough, so this work is only for my own study~
 I know there are some other Chinese fellow in this list, wish it would
 be helpful.
 I will work for one chapter everyday.

I will hijack somewhat this thread. If anybody is interested in
helping translation of All About Monads into Polish for (slowly)
emerging http://haskell.pl/ *) website then contact me.

Thanks,
 Radek.

*) http://haskell.pl/ is not ready by any means. I'm configuring
drupal and I'm gathering some initial content. If anybody is
interested then dop me a line.

-- 
Codeside: http://codeside.org/
Przedszkole Miejskie nr 86 w Lodzi: http://www.pm86.pl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] I'm translating All about Monads to Chinese

2007-12-03 Thread Albert Lee
I have been confussed by monad for a long time. and I can't stand for
it any more. so I start to translate the tutorial All About Monads
to my mother language Chinese.
My English is not good enough, so this work is only for my own study~
I know there are some other Chinese fellow in this list, wish it would
be helpful.
I will work for one chapter everyday.

the address is: http://www.kamang.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] type class question

2007-12-03 Thread Peter Padawitz
What is wrong here? ghci tries (and fails) to deduce certain types for 
the comp functions that I did not expect.


|type Block   = [Command]
data Command = Skip | Assign String IntE | Cond BoolE Block Block |
  Loop BoolE Block
data IntE= IntE Int | Var String | Sub IntE IntE | Sum [IntE] | Prod 
[IntE]

data BoolE   = BoolE Bool | Greater IntE IntE | Not BoolE

class Java block command intE boolE
  where block_ :: [command] - block
skip :: command
assign :: String - intE - command
cond :: boolE - block - block - command
loop :: boolE - block - command
intE_ :: Int - intE
var :: String - intE
sub :: intE - intE - intE
sum_ :: [intE] - intE
prod :: [intE] - intE
boolE_ :: Bool - boolE
greater :: intE - intE - boolE
not_ :: boolE - boolE

compBlock :: Block - block
compBlock = block_ . map compCommand

compCommand :: Command - command
compCommand Skip   = skip
compCommand (Assign x e)   = assign x (compIntE e)
compCommand (Cond be c c') = cond (compBoolE be) (compCommand c)
 (compCommand c')
compCommand (Loop be c)= loop (compBoolE be) (compCommand c)-}

compIntE :: IntE - intE
compIntE (IntE i)   = intE_ i
compIntE (Var x)= var x
compIntE (Sub e e') = sub (compIntE e) (compIntE e')
compIntE (Sum es)   = sum_ (map compIntE es)
compIntE (Prod es)  = prod (map compIntE es)

compBoolE :: BoolE - boolE

compBoolE (BoolE b)  = boolE_ b
compBoolE (Greater e e') = greater (compIntE e) (compIntE e')
compBoolE (Not be)   = not_ (compBoolE be)
|
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: A tale of three shootout entries

2007-12-03 Thread Simon Marlow

Simon Peyton-Jones wrote:

| There may well have been changes to the strictness analyser that make
| some of the bangs (or most) unnecessary now. Also, its very likely
| I didn't check all combinations of strict and lazy arguments for the
| optimal evaluation strategy :)
|
| If it seems to be running consitently faster (and producing better Core
| code), by all means submit. I don't think this is a ghc bug or anything
| like that though: just overuse of bangs, leading to unnecessary work.

You might think that unnecessary bangs shouldn't lead to unnecessary work -- if 
GHC knows it's strict *and* you bang the argument, it should still only be 
evaluated once. But it can happen.  Consider

f !xs = length xs

Even though 'length' will evaluate its argument, f nevertheless evaluates it too.  Bangs 
say evaluate it now, like seq, because we may be trying to control space 
usage.  In this particular case it's silly, because the *first* thing length does is 
evaluate its argument, but that's not true of every strict function.

That's why I say it'd be good to have well-characterised examples.  It *may* be 
something like what I describe. Or it may be a silly omission somewhere.


A little addition to what Simon mentioned above: while it is definitely 
true that adding unnecessary bangs can cause a slowdown, the slowdown 
should be much less with 6.8.1 because in the common case each evaluation 
will be an inline test rather than an out-of-line indirect jump and return.


So, with 6.8.x, you should feel more free to sprinkle those bangs...

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


[Haskell-cafe] Re: Waiting for thread to finish

2007-12-03 Thread Simon Marlow

Brad Clow wrote:

On Nov 28, 2007 11:30 AM, Matthew Brecknell [EMAIL PROTECTED] wrote:

Even with threads, results are evaluated only when they are needed (or
when forced by a strictness annotation). So the thread that needs a
result (or forces it) first will be the one to evaluate it.


So does GHC implement some sychronisation given that a mutation is
occuring under the covers, ie. the thunk is being replaced by the
result?


Yes, see

http://haskell.org/~simonmar/bib/multiproc05_abstract.html

we use lock-free synchronisation, with a slight possibility that two 
threads might evaluate the same thunk.  But since they'll produce the same 
result, nothing goes wrong.


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


Re: [Haskell-cafe] do

2007-12-03 Thread Denis Bueno
On Dec 3, 2007 6:55 AM, PR Stanley [EMAIL PROTECTED] wrote:
 Hi
 I've probably asked about the do construct, if that's the right
 label. Unfortunately I'm still not quite sure of its role and more
 specifically its syntax. Something to do with generators perhaps? A
 description plus some examples would be most gratefully received.

Probably one should understand how to use monads before worrying about
the do-notation.  Here are some references:

  http://haskell.org/haskellwiki/Books_and_tutorials#Using_monads
  http://en.wikibooks.org/wiki/Haskell/Understanding_monads
  Section 2.5 of http://haskell.org/haskellwiki/Learning_Haskell

Hope this helps.

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


[Haskell-cafe] Re: Array copying

2007-12-03 Thread ChrisK
Reinier Lamers wrote:
 ChrisK wrote:
 
 For GHC 6.6 I created

  

 foreign import ccall unsafe memcpy
memcpy :: MutableByteArray# RealWorld - MutableByteArray#
 RealWorld - Int# - IO ()
   

  

 {-# INLINE copySTU #-}
 copySTU :: (Show i,Ix i,MArray (STUArray s) e (ST s)) = STUArray s i
 e - STUArray s i e - ST s ()
 copySTU (STUArray _ _ msource) (STUArray _ _ mdest) =
 -- do b1 - getBounds s1
 --  b2 - getBounds s2
 --  when (b1/=b2) (error (\n\nWTF copySTU: ++show (b1,b2)))
  ST $ \s1# -
case sizeofMutableByteArray# msourceof { n# -
case unsafeCoerce# memcpy mdest msource n# s1# of { (# s2#, () #) -
(# s2#, () #) }}
   

 To allow efficient copying of STUArrays.
  

 How does this guarantee that it doesn't overflow the buffer of the
 destination array?

As is, the above is a very unsafe operation.  The check is commented out.
You can uncomment the code above that says:

  do b1 - getBounds s1
 b2 - getBounds s2
 when (b1/=b2) (error (\n\nWTF copySTU: ++show (b1,b2)))

Which checks the high-level boundary matches, not just the actual length.

I only have a single size of STUArray haning around, so I use the unsafe and
fast version.

-- 
Chris

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


Re: [Haskell-cafe] Trees

2007-12-03 Thread Yitzchak Gale
Adrian Neumann wrote:
  data Tree a = Leaf a | Node a [Tree a]
 example: given a tree t and two nodes u,v, find the
 first common ancestor. In Java this is really simple,
 because each node has a parent reference...
 In Haskell however the best way I've come up with so
 far is doing a BFS and looking for the last common
 node in the paths to u and v.

Stefan O'Rear wrote:
 the Java solution translates to Haskell:
 data Tree a = Node { idn:: Int, val:: a, parent:: Maybe (Tree a), children:: 
 [Tree a] }
 You can make this efficiently mutable...

That looks like a tying-the-knot approach. It is interesting,
but I don't see how it is similar to the Java. You still
need to search for u and v somehow. And as for making
it mutable, you can forget it; your fingers will quickly
become weary from untying and retying all of those knots.

Perhaps you meant:

data Node a = Node { idn:: Int, val:: a, parent:: Maybe Int, children:: [Int] }
type Tree a = Data.IntMap (Node a)

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


[Haskell-cafe] Re: Array copying

2007-12-03 Thread ChrisK
Andrew Coppin wrote:
 ChrisK wrote:
 For GHC 6.6 I created

  
 foreign import ccall unsafe memcpy
 memcpy :: MutableByteArray# RealWorld - MutableByteArray#
 RealWorld - Int# - IO ()
 

  
 {-# INLINE copySTU #-}
 copySTU :: (Show i,Ix i,MArray (STUArray s) e (ST s)) = STUArray s i
 e - STUArray s i e - ST s ()
 copySTU (STUArray _ _ msource) (STUArray _ _ mdest) =
 -- do b1 - getBounds s1
 --  b2 - getBounds s2
 --  when (b1/=b2) (error (\n\nWTF copySTU: ++show (b1,b2)))
   ST $ \s1# -
 case sizeofMutableByteArray# msourceof { n# -
 case unsafeCoerce# memcpy mdest msource n# s1# of { (# s2#, () #) -
 (# s2#, () #) }}
 

 To allow efficient copying of STUArrays.
   
 
 So... that copies the entire array into another array of the same size?
 (I'm having a lot of trouble understanding the code...)

Yes, that is what it does.  The STUArray data type has the STUArray
constructor which I import and pattern match against.  The imports are:

 import Data.Array.Base(unsafeRead,unsafeWrite,STUArray(..))
 import 
 GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)

in 6.6.1 this is defined as
 data STUArray s i a = STUArray !i !i (MutableByteArray# s)
in 6.8.1 this is defined as
 data STUArray s i a = STUArray !i !i !Int (MutableByteArray# s)

I use sizeofMutableByteArray# to get the source size, n#.

I have lost track of how unsafeCoerce# and s1# are being used...oops.
It is similar to data-dependency tricks used inside Data.Array.Base, though.

-- 
Chris

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


Re: [Haskell-cafe] Trees

2007-12-03 Thread Matthew Brecknell
Adrian Neumann:
  data Tree a = Leaf a | Node a [Tree a]
 example: given a tree t and two nodes u,v, find the
 first common ancestor.

The following solves what I think is a generalisation of this problem.
That is, given a tree and a predicate on its elements, return the
smallest subtree containing all nodes satisfying the predicate, or
Nothing if none satisfy it.

 import Data.Maybe
 
 data Tree a = Node a [Tree a]
 
 lub :: (a - Bool) - Tree a - Maybe (Tree a)
 lub p (Node a s) 
   | p a = Just (Node a s)
   | otherwise = case mapMaybe (lub p) s of
   [] - Nothing
   [t] - Just t
   _ - Just (Node a s)

If I understand the original problem correctly, then the appropriate
predicate would just be (flip elem [u,v]).

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


Re: [Haskell-cafe] ARM back end?

2007-12-03 Thread Mathieu Boespflug
On Nov 2, 2007 10:19 PM, nornagon [EMAIL PROTECTED] wrote:
 On 03/11/2007, Greg Fitzgerald [EMAIL PROTECTED] wrote:
  Anybody know of an ARM back end for any of the Haskell compilers?
 

 If there's an arm-eabi port somewhere, I might be able to get Haskell
 code running on the Nintendo DS...

https://garage.maemo.org/projects/hugs/

Runs on my Nokia N800 which is arm-eabi based.

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


[Haskell-cafe] Nofib modifications

2007-12-03 Thread Neil Mitchell
Hi,

Some of the nofib suite are messed up by Yhc/nhc because of the
monomorphism restriction. Take imaginary/bernouilli as an example:

powers = [2..] : map (zipWith (*) (head powers)) powers

Hugs and GHC both see powers :: [[Integer]] and a CAF.

Yhc (and nhc) both see powers :: (Enum a, Num a) = [[a]] and no CAF.

This completely destroys the performance in Yhc/nhc. Since this is not
so much a performance aspect but a compiler bug, based on a feature
whose future in Haskell' is as yet unclear, perhaps it would be wise
to patch nofib to include an explicit type signature where this
matters. I am happy to send in a patch (or just apply it) - but I have
no idea who maintains the suite. I've CC'd those people who make
substantial use of the nofib suite.

Thanks

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


[Haskell-cafe] foild function for expressions

2007-12-03 Thread Carlo Vivari

Hi! I'm a begginer in haskell and I have a problem with an exercise, I expect
someone could help me:

In one hand I have a declaration of an algebra data, like this:

data AlgExp a = AlgExp
{ litI  :: Int - a,
   litB :: Bool - a,
   add :: a - a - a,
   and :: a - a - a,
   ifte :: a - a - a - a}

(being ifte an 'ifthenelse' expresion...)

What I want to do is to write a fold function for expressions, something
like this:

foldExp :: AlgExp a - Exp - a
foldExp alg (LitI i) = litI alg i
foldExp alg (LitB i) = litB alg i
foldExp alg (add exp1 exp2) = ¿¿¿???
foldExp alg (and exp1 exp2) = ¿¿¿???
foldExp alg (ifte exp1 exp2 exp3) = ¿¿¿???

..ETC


the fact is that I have no idea of what to do with the other expresions
(add, and, and ifte)... I really don' t understand how to do this... It's
clear that a fold function should colapse in one valour, but how can I
espress it in the terms of the exercise?

For further information about the problem after this,  it's suposed that I
have to rewrite some functions for expresions but in terms of foldexp (the
one I should write before)


Thank you very much

-- 
View this message in context: 
http://www.nabble.com/foild-function-for-expressions-tf4932877.html#a14119002
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Trees

2007-12-03 Thread Derek Elkins
On Mon, 2007-12-03 at 16:56 +0200, Yitzchak Gale wrote:
 Adrian Neumann wrote:
   data Tree a = Leaf a | Node a [Tree a]
  example: given a tree t and two nodes u,v, find the
  first common ancestor. In Java this is really simple,
  because each node has a parent reference...
  In Haskell however the best way I've come up with so
  far is doing a BFS and looking for the last common
  node in the paths to u and v.
 
 Stefan O'Rear wrote:
  the Java solution translates to Haskell:
  data Tree a = Node { idn:: Int, val:: a, parent:: Maybe (Tree a), 
  children:: [Tree a] }
  You can make this efficiently mutable...
 
 That looks like a tying-the-knot approach. It is interesting,
 but I don't see how it is similar to the Java. You still
 need to search for u and v somehow. And as for making
 it mutable, you can forget it; your fingers will quickly
 become weary from untying and retying all of those knots.

If made mutable, there's nothing stopping it from being exactly like the
Java approach.  It should be no more finger tiring than Java (but then
we -are- talking about Java...)

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


Re: [Haskell-cafe] Possible Improvements

2007-12-03 Thread Derek Elkins
On Mon, 2007-12-03 at 10:48 +0100, Ketil Malde wrote:
 Johan Tibell [EMAIL PROTECTED] writes:
 
  It would be great if someone could exemplify these rules of thumb,
  e.g. Primitive types such as Int should be strict unless in the three
  canonical examples X, Y and Z. My strictness radar is still quite
  poor and I feel I can't make informed decisions on when I need to make
  something more strict or lazy.
 
 I find that I often need to add strictness when:
 
  left thumb)  parsing [Char] into something more compact, i.e. almost
   all cases.
  right thumb) storing data into maps, especially when the values are produced 
 by
   multiple updates - i.e. doing word frequency counts.

Indeed, this generalizes fairly well.  In general when going from a
large structure (especially recursive types or arrays) to a small
one (especially base types or small non-recursive types e.g. a vector
type) you want strictness.  Cale Gibbard argues that this is the only
case where strictness is desirable.  In the other three cases, small
to large, large to large and small to small either laziness is
preferable or there is not a big difference between them.

http://www.haskell.org/haskellwiki/Stack_overflow gives some advice on
how to choose strictness for avoiding stack overflows.  On that page you
can see the above rule in action in, for example, the difference between
concat :: [[a]] - [a] and sum :: Num a = [a] - a.

The techniques sidebar on the Performance page,
http://www.haskell.org/haskellwiki/Performance also contains some bits
of advice.  For example, the widely known advice about making
accumulating parameters strict.  This is related to Ketil's right rule
of thumb.

Oftentimes the best way to get good behaviour is to use strict (in the
appropriate places) data constructors.  This will often eliminate most
or all of the need for (other) strictness annotations.  For example, one
way of solving the issue with the scanl code on the Stack Overflow wiki
page is by using a head strict list type (which, incidentally, Clean has
native support for.)  In fact, I suspect most of the time a head strict
list type is either comparable or what is desired (though certainly not
all of the time).

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


Re: [Haskell-cafe] foild function for expressions

2007-12-03 Thread Kalman Noel
Carlo Vivari wrote:
 data AlgExp a = AlgExp
 { litI  :: Int - a,
litB :: Bool - a,
add :: a - a - a,
and :: a - a - a,
ifte :: a - a - a - a}

You're confusing sum and product types. That is, you're using a product type,
but you probably need a sum type, like this:

data Exp1 = LitI Int 
| LitB Bool 
| Add Exp1 Exp1 
| And Exp1 Exp1 
| IfThenElse Exp1 Exp1 Exp1

But in this case, using GADTs (beware: not Haskell 98, but a very popular
extension) makes for a more elegant solution. Note the strong types, disallowing
e. g. the addition of a number to a boolean value:

data Exp2 a where
LitI:: Int  - Exp2 Int
LitB:: Bool - Exp2 Bool
Add :: Exp2 Int  - Exp2 Int  - Exp2 Int
And :: Exp2 Bool - Exp2 Bool - Exp2 Bool
IfThenElse  :: Exp2 Bool - Exp2 a - Exp2 a - Exp2 a

Kalman

--
Get a free email address with REAL anti-spam protection.
http://www.bluebottle.com/tag/1

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


RE: [Haskell-cafe] Nofib modifications

2007-12-03 Thread Simon Peyton-Jones
By all means apply a patch, I think.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Neil Mitchell
| Sent: 03 December 2007 17:34
| To: Haskell Cafe
| Cc: Simon Marlow; Malcolm Wallace; Duncan Coutts
| Subject: [Haskell-cafe] Nofib modifications
|
| Hi,
|
| Some of the nofib suite are messed up by Yhc/nhc because of the
| monomorphism restriction. Take imaginary/bernouilli as an example:
|
| powers = [2..] : map (zipWith (*) (head powers)) powers
|
| Hugs and GHC both see powers :: [[Integer]] and a CAF.
|
| Yhc (and nhc) both see powers :: (Enum a, Num a) = [[a]] and no CAF.
|
| This completely destroys the performance in Yhc/nhc. Since this is not
| so much a performance aspect but a compiler bug, based on a feature
| whose future in Haskell' is as yet unclear, perhaps it would be wise
| to patch nofib to include an explicit type signature where this
| matters. I am happy to send in a patch (or just apply it) - but I have
| no idea who maintains the suite. I've CC'd those people who make
| substantial use of the nofib suite.
|
| Thanks
|
| Neil
| ___
| 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] Parsing unstructured data

2007-12-03 Thread Olivier Boudry
On 12/2/07, Steven Fodstad [EMAIL PROTECTED] wrote:

 Sorry for not responding earlier.  The haskell-cafe list is hard to keep
 up with.

 The process of finding geographic (lat/long) coordinates from a text
 address is called geocoding.  Obviously extracting the parts of an
 address is part of that, so you might find better results looking for
 geocoding, rather than the more general and more difficult topic of
 extracting structure from unstructured data.  Unfortunately, I don't
 have any references at hand on that part of geocoding.


Hi Steven,

The idea of using the geocoding approach seems appealing. I already thought
of using geocoding for address validation (after the parsing) but not of
looking at how geocoding tools parse addresses. But I'm not sure geocoding
tools would be suitable to handle my addresses. I used a few geocoding tools
and usually you have to provide the address in a very specific format if you
want it to be recognized. Also most of the time it work quite well for US
addresses but not for other countries addresses.

I need to recognize very specific parts of an address. More than what a
geocoding tools will require. Like dock #, doors, suite #, contact person,
etc...

I'm currently using the ZipFourCE web service from BCCSoftware for
validating my addresses against the USPS address database. This tool is
built for parsing and correcting addresses but I just use it for validation
as it's not smart enough to parse them or maybe they are just too
scrambled for the parsing to be automated using an out of the box tool. ;-)

Thanks for your input,

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


Re: [Haskell-cafe] do

2007-12-03 Thread Tim Newsham

Probably one should understand how to use monads before worrying about
the do-notation.  Here are some references:


I don't totally agree.  You can teach monads to beginners just fine
using the do-notation.  Unsuprisingly its very much like teaching
monads using bind.  You describe a two line do-block as the basic
building block for combining two actions into a single action:

do {
result1 - act1
expr involving result1 building an act
}

show that you can nest them (expr can be another do block)

do {
result1 - act1
do {
result2 - act2
expr involving result1 and result2 building an act
}
}

and how the do-notation doesn't require you to start a new do-block
for nesting of do's and let's

   do {
   result1 - act1
   let val1 - expr resulting in a pure value
   result2 - act2
   expr involving result1 and result2 building an act
   }

Then you can describe pattern matching and fail...

I've had debates about what should be taught, and obviously not
everyone agrees, but at the least, its possible and reasonable
and understandable to teach do-notation first.


 Denis


Tim Newsham
http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: atom 2007.12

2007-12-03 Thread Tom Hawkins
Hello,

Atom is a language embedded in Haskell for describing reactive
software, primarily for realtime control applications.  Based on
conditional term rewriting, an atom
description is composed of a set of state transition rules.  The name
atom comes from the atomic behavior of rules: if a rule is selected
to fire, all its transitions occur or none at all.  A hallmark of the
language, rule atomicity greatly simplifies design reasoning.

This release of atom is a major redirection.  Atom is no longer a
hardware description language (I changed jobs.  I'm now in software.).
 Much of the frontend language and backend generators have changed,
though rule scheduling remains nearly the same.  On the frontend,
atom's Signal datatypes have been replaced with Terms and Vars, which
leverage Haskell's GADTs.  The 4 supported Term and Var types include
Bool, Int, Float, and Double.  At the backend, atom generates C and
Simulink models.  The Verilog and VHDL generators have been dropped,
but they may reappear in the future.

Enjoy!

http://funhdl.org/
darcs get http://funhdl.org/darcs/atom

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


Re: [Haskell-cafe] Possible Improvements

2007-12-03 Thread Andrew Coppin

Johan Tibell wrote:

It would be great if someone could exemplify these rules of thumb,
e.g. Primitive types such as Int should be strict unless in the three
canonical examples X, Y and Z. My strictness radar is still quite
poor and I feel I can't make informed decisions on when I need to make
something more strict or lazy.
  


+1

When I first learned Haskell, lazyness sounded like a great idea, and I 
was somewhat puzzled as to why you would ever want to turn such a thing 
off. Fortunately (?!) after lots of experiments with the lambda calculus 
and other such things, I quickly realised that reducing large 
subexpression can sometimes be a big win. But I couldn't find much on 
the Wiki that explains all this stuff, and it would probably be quite 
useful to have!


Of course, now we need somebody to *write* the thing...

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


Re: [Haskell-cafe] A tale of three shootout entries

2007-12-03 Thread Andrew Coppin

Don Stewart wrote:

Please go ahead and submit. :) and remember to upload also to our wiki,
so we have a permanent record of the attempt,

http://haskell.org/haskellwiki/Shootout

Note down any ideas you have.
  


Now that GHC 6.6 is available, please you it?

Last time I looked at the shootout website, 6 of the GHC entries were 
marked simply as error. Do we know why, or am I missing something 
obvious? (I find the site to be a little unintuitive at times...)


Unfortunately I don't understand what half the benchmarks are supposed 
to be, which makes it rather hard to follow.


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


Re: [Haskell-cafe] A tale of three shootout entries

2007-12-03 Thread Don Stewart
andrewcoppin:
 Don Stewart wrote:
 Please go ahead and submit. :) and remember to upload also to our wiki,
 so we have a permanent record of the attempt,
 
 http://haskell.org/haskellwiki/Shootout
 
 Note down any ideas you have.
   
 
 Now that GHC 6.6 is available, please you it?

Looks like something broke in an edit. Feel free to correct it.
  
 Last time I looked at the shootout website, 6 of the GHC entries were 
 marked simply as error. Do we know why, or am I missing something 
 obvious? (I find the site to be a little unintuitive at times...)

Sounds like you're looking at the wrong thing?


http://shootout.alioth.debian.org/gp4/benchmark.php?test=alllang=ghclang2=ghc

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


Re: [Haskell-cafe] A tale of three shootout entries

2007-12-03 Thread Andrew Coppin

Don Stewart wrote:

andrewcoppin:
  

Now that GHC 6.6 is available, please you it?



Looks like something broke in an edit. Feel free to correct it.
  


Oh well. ;-)

But then, the GHC wiki still says The 6.8 branch is the current STABLE, 
and we are in the 6.8.1 release candidate phase. We aim to release 6.8.1 
around the beginning of October. I guess most people are busy writing 
the real stuff rather than updating documentation.


Last time I looked at the shootout website, 6 of the GHC entries were 
marked simply as error. Do we know why, or am I missing something 
obvious? (I find the site to be a little unintuitive at times...)



Sounds like you're looking at the wrong thing?


http://shootout.alioth.debian.org/gp4/benchmark.php?test=alllang=ghclang2=ghc
  


Mmm, interesting. I was looking at

http://shootout.alioth.debian.org/debian/benchmark.php?test=alllang=ghclang2=ghc

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


Re: [Haskell-cafe] do

2007-12-03 Thread Denis Bueno


On 03 Dec 2007, at 13:25 , Tim Newsham wrote:

Probably one should understand how to use monads before worrying  
about

the do-notation.  Here are some references:


I don't totally agree.  You can teach monads to beginners just fine
using the do-notation.  Unsuprisingly its very much like teaching
monads using bind.  You describe a two line do-block as the basic
building block for combining two actions into a single action:

do {
result1 - act1
expr involving result1 building an act
}


By teaching = and return first in the context of monads, I think it  
encourages seeing 'do' primarily as syntactic sugar, instead of some  
mysterious construct in its own right.  This lets you apply  
everything you know about programming in pure, functional, typed  
programming (e.g. Haskell, SML, etc.) to monads, by seeing the type  
signature of = and return.  This, in turn, lets you conclude that  
monads are not mysterious at all, but simply a few operations whose  
types work in concert.  This doesn't mean you understand them, but it  
removes certain potential confusions.


If you learn 'do' first, there is a tendency to think of using  
monads and using do as synonymous, which they are not; and of  
thinking that 'do' is performing some sort of magic on your types  
(i.e. that you couldn't straightforwardly emulate 'do' with other  
operations).


When you're first learning monads, you're constantly suspicious of  
the mysterious, because of their name, their reputation, and their  
putative generality and power.  (I say 'putative' because when you're  
learning you don't yet know that it's true. =])



I've had debates about what should be taught, and obviously not
everyone agrees, but at the least, its possible and reasonable
and understandable to teach do-notation first.


I don't think I can conclude that there are *no* reasons to teach the  
do-notation first.  I just think that it is more instructive to teach  
it later.


Please understand I'm a relative newbie in Haskell, so I would  
appreciate any comments on what I said above.  I'm still trying to  
learn. =]


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


Re: [Haskell-cafe] ANN: atom 2007.12

2007-12-03 Thread Alex Jacobson
This sounds like a really interesting piece of software.  That being 
another significant use for the name Atom these days is as an identifier 
for a feed format.


  http://en.wikipedia.org/wiki/Atom_(standard)

You may find it easier to advertise and romote this project with a more 
unique name.


-Alex-

Tom Hawkins wrote:

Hello,

Atom is a language embedded in Haskell for describing reactive
software, primarily for realtime control applications.  Based on
conditional term rewriting, an atom
description is composed of a set of state transition rules.  The name
atom comes from the atomic behavior of rules: if a rule is selected
to fire, all its transitions occur or none at all.  A hallmark of the
language, rule atomicity greatly simplifies design reasoning.

This release of atom is a major redirection.  Atom is no longer a
hardware description language (I changed jobs.  I'm now in software.).
 Much of the frontend language and backend generators have changed,
though rule scheduling remains nearly the same.  On the frontend,
atom's Signal datatypes have been replaced with Terms and Vars, which
leverage Haskell's GADTs.  The 4 supported Term and Var types include
Bool, Int, Float, and Double.  At the backend, atom generates C and
Simulink models.  The Verilog and VHDL generators have been dropped,
but they may reappear in the future.

Enjoy!

http://funhdl.org/
darcs get http://funhdl.org/darcs/atom

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


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


Re: [Haskell-cafe] do

2007-12-03 Thread Dan Piponi
On Dec 3, 2007 1:09 PM, Denis Bueno [EMAIL PROTECTED] wrote:

 I don't think I can conclude that there are *no* reasons to teach the
 do-notation first.  I just think that it is more instructive to teach
 it later.

It's standard in mathematics teaching, when introducing a mathematical
structure X, to ensure that students have the knowledge to understand
an example of X before they see the definition of X. So students won't
study groups before they've met the integers, they won't study fields
before they've met the rationals, and they won't study topology until
they're familiar with the real line. Not just met them either, usually
they've usually completely internalised the examples before moving
onto the general structure.

The problem with monads is that students have never knowingly met an
example of a monad before. If you teach them do-notation for IO
without monads, and they get completely familiar with it (which (1) I
claim is easy: 
http://sigfpe.blogspot.com/2007/11/io-monad-for-people-who-simply-dont.html
and (2) is inevitable if they want to see the output of their
programs) then when they come to learning about monads in general
they'll have an example they don't even have to think about. The more
adventurous ones may even discover some of the monad laws for
themselves if they experiment with nested do's like in Tim Newsham's
examples (and think them so obvious they hardly need to be graced with
the name law).
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Waiting for thread to finish

2007-12-03 Thread Ryan Ingram
On 11/27/07, Matthew Brecknell [EMAIL PROTECTED] wrote:

  wait_first :: [Wait a] - IO (a, [Wait a])
  wait_first [] = error wait_first: nothing to wait for
  wait_first ws = atomically (do_wait ws) where
do_wait [] = retry
do_wait (Wait w : ws) = do
  r - readTVar w
  case r of
Nothing - fmap (second (Wait w:)) (do_wait ws)
Just s - return (s,ws)


Interesting, although this seems like a perfect use for orelse:

 wait_stm :: Wait a - STM a
 wait_stm (Wait w) = readTVar w = maybe retry return

 wait :: Wait a - IO a
 wait w = atomically $ wait_stm w

 wait_first :: [Wait a] - IO (a, [Wait a])
 wait_first [] = error wait_first: nothing to wait for
 wait_first ws = atomically (do_wait ws) where
do_wait [] = retry
do_wait (w : ws) = do
r - wait_stm w
return (r, ws)
  `orelse` fmap (second (w:)) (do_wait ws)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problems building and using ghc-6.9

2007-12-03 Thread Daniel Fischer
Hi,
so today I built ghc-6.9.20071124.

First, make died because HsColour version = 1.8 was needed, couldn't 
determine the version. I had HsColour 1.6, got myself 1.8, built and 
installed.
make died again, same problem.
I added (v, Version) to the optionTable in HsColour.hs and it worked :)

Then I tried to build zlib-0.4.0.1:
$ runghc ./Setup.hs configure --user --prefix=$HOME
Configuring zlib-0.4.0.1...
Setup.hs: At least the following dependencies are missing:
base =2.02.2
??? okay, there was something with flag bytestring-in-base, removed that, so 
that build-depends was base  2.0 || = 2.2, bytestring = 0.9, then
$ runghc ./Setup.hs configure --user --prefix=$HOME
Configuring zlib-0.4.0.1...
Setup.hs: At least the following dependencies are missing:
base 2.0||=2.2, bytestring =0.9

but:
$ ghc-pkg list
/home/dafis/lib/ghc-6.9.20071124/package.conf:
ALUT-2.1.0.0, Cabal-1.3, GLUT-2.1.1.1, HUnit-1.2.0.0,
OpenAL-1.3.1.1, OpenGL-2.2.1.1, QuickCheck-1.1.0.0, array-0.1,
base-3.0, bytestring-0.9, cgi-3001.1.5.1, containers-0.1,
directory-1.0, fgl-5.4.1.1, filepath-1.1, (ghc-6.9.20071124),
haskell-src-1.0.1.1, haskell98-1.0.1, hpc-0.5, html-1.0.1.1,
mtl-1.1.0.0, network-2.1.0.0, old-locale-1.0, old-time-1.0,
packedstring-0.1, parallel-1.0.0.0, parsec-2.1.0.0, pretty-1.0,
process-1.0, random-1.0, readline-1.0.1, regex-base-0.72.0.1,
regex-compat-0.71.0.1, regex-posix-0.72.0.2, rts-1.0, stm-2.1.1.0,
template-haskell-2.2, time-1.1.2.0, unix-2.2, xhtml-3000.0.2.1

and in stringsearch-0.2:
$ runghc ./Setup.lhs configure --user --prefix=$HOME
Configuring stringsearch-0.2...
Setup.lhs: At least the following dependencies are missing:
base -any

What's going on??

How can I build packages with ghc-6.9? 
Or do I have to go back to 6.8.1?

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


[Haskell-cafe] Re: Waiting for thread to finish

2007-12-03 Thread Ben Franksen
Belatedly I realized that this answer should have been going to the list:
---
ChrisK wrote:
On Mittwoch, 28. November 2007, you wrote:
 A safer gimmick...

 Ben Franksen wrote:
  tickWhileDoing :: String - IO a - IO a
  tickWhileDoing msg act = do
hPutStr stderr msg  hPutChar stderr ' '  hFlush stderr
start_time - getCPUTime
tickerId - forkIO ticker

 ... an async exception here will leave the ticker runnning

res - act `finally` killThread tickerId

Thanks for spotting this loophole. I keep forgetting people tend to hit 
Ctrl-C whenever they feel like it... ;-) Thinking some more about this, I 
realise that the async exception could also come from somewhere inside the 
Haskell program (e.g. from a killThread like I did myself in the next 
line.) So the fix below makes this whole things more robust indeed.

 The best way to make this safe that I know of is:
res - block $ do
  tickerId - forkIO ticker
  unblock act `finally` killThread tickerId

Yes.

Cheers
Ben

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


Re: [Haskell-cafe] Possible Improvements

2007-12-03 Thread ajb

G'day all.

On Mon, 2007-12-03 at 10:48 +0100, Ketil Malde wrote:


I find that I often need to add strictness when:

 left thumb)  parsing [Char] into something more compact, i.e. almost
  all cases.
 right thumb) storing data into maps, especially when the values   
are produced by

  multiple updates - i.e. doing word frequency counts.


Quoting Derek Elkins [EMAIL PROTECTED]:


Indeed, this generalizes fairly well.  In general when going from a
large structure (especially recursive types or arrays) to a small
one (especially base types or small non-recursive types e.g. a vector
type) you want strictness.


On the right thumb rule, just a quick comment.

In general, it makes sense for the spine of data structures to be
lazy but the content to be strict, if the structure depends on the
content.  So, for example, in a binary search tree, it would make
sense for the pointers-to-nodes to be lazy but the keys to be strict.

However, if the content does _not_ determine the structure (e.g.
lists), then it should not be strict by default.  So, for example, in
a binary search tree, while it makes sense for keys to be strict,
it is wrong for values to be strict by default.

Expressed as rules of thumb:

1. Data structure spines should almost always be lazy.

2. If it's logically a Functor, strictness will break the axioms,
so don't do that.

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


[Haskell-cafe] Re: Monads

2007-12-03 Thread Ben Franksen
PR Stanley wrote:
 Does the list consider

http://en.wikibooks.org/w/index.php?title=Haskell/Understanding_monadsoldid=933545
 a reliable tutorial on monads and, if not, could you recommend an
 onlien alternative please?

I strongly recommend the original papers by Philip Wadler, especially this
one:

http://citeseer.ist.psu.edu/wadler95monads.html

IMHO it still beats almost everything that's been written lately, including
the wikibook chapter you asked about (which I personally don't like at
all).

My other standard recommendation is
http://sigfpe.blogspot.com/2006/08/you-could-have-invented-monads-and.html
but I'd read the above paper first.

Cheers
Ben

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


[Haskell-cafe] doing builds using cygwin on Windows

2007-12-03 Thread Galchin Vasili
To Nanonthief ..



VasiliIGalchin wrote:


  .. however, I don't see in which file PATH can be set. Any help? I
 really
 want to get my Haskell build environment set up and cranking away.

Unless I misunderstood what you want, you can add a path to the PATH
variable by adding the line:
export PATH=$PATH:/path/to/folder
to the ~/.bashrc file (and also possibly the ~/.bash_profile file).

I've also tried to build haskell with cygwin, but didn't have any luck.
Could you describe how you managed to do it?

--

nanothief ... here is what I decided to add to unix.cabal .. and I am
getting farther ...

build-depends:base, directory
extensions:CPP, ForeignFunctionInterface
include-dirs: include c:/cygwin/usr/include  added
cygwin include path
includes:   HsUnix.h execvpe.h
install-includes:
HsUnix.h HsUnixConfig.h execvpe.h
c-sources:cbits/HsUnix.c cbits/execvpe.c
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: do

2007-12-03 Thread Ben Franksen
Dan Piponi wrote:
 On Dec 3, 2007 1:09 PM, Denis Bueno [EMAIL PROTECTED] wrote:
 
 I don't think I can conclude that there are *no* reasons to teach the
 do-notation first.  I just think that it is more instructive to teach
 it later.
 
 It's standard in mathematics teaching, when introducing a mathematical
 structure X, to ensure that students have the knowledge to understand
 an example of X before they see the definition of X. So students won't
 study groups before they've met the integers, they won't study fields
 before they've met the rationals, and they won't study topology until
 they're familiar with the real line. Not just met them either, usually
 they've usually completely internalised the examples before moving
 onto the general structure.

Right.

 The problem with monads is that students have never knowingly met an
 example of a monad before.

When one learns about Groups one hasn't met them /knowingly/ before, either.
It may be that one has learned the laws that govern arithmetic; but it is
not at all clear why one would want to look at one of the operations in
separation, i.e. what the generality of the concept might be good for. This
becomes clear only after having seen examples of a group whose elements
are /not/ integers.

 If you teach them do-notation for IO 
 without monads, and they get completely familiar with it (which (1) I
 claim is easy:

http://sigfpe.blogspot.com/2007/11/io-monad-for-people-who-simply-dont.html
 and (2) is inevitable if they want to see the output of their programs)
 then when they come to learning about monads in general they'll have an
 example they don't even have to think about. 

I don't buy this. As has been noted by others before, IO is a very special
case, in that it can't be defined in Haskell itself, and there is no
evaluation function runIO :: IO a - a.

I'd rather use a simple example like Maybe (modeling failure as an effect).
It can be completely understood even as a beginner, and is non-trivial
enough to demonstrate the utility of the concept 'monad'.

Cheers
Ben

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


Re: [Haskell-cafe] foild function for expressions

2007-12-03 Thread Brent Yorgey

 foldExp :: AlgExp a - Exp - a
 foldExp alg (LitI i) = litI alg i
 foldExp alg (LitB i) = litB alg i
 foldExp alg (add exp1 exp2) = ¿¿¿???
 foldExp alg (and exp1 exp2) = ¿¿¿???
 foldExp alg (ifte exp1 exp2 exp3) = ¿¿¿???


One comment: it looks like (add exp1 exp2), (and exp1 exp2) and so on above
are not correct.  The second argument of foldExp is a value of type Exp, so
you are pattern-matching on the constructors of Exp, and constructors are
always uppercase.  Perhaps Exp has constructors named Add, And, and so on?
Then you would want to do something like

foldExp alg (Add exp1 exp2) = ???

and so on.  For the ??? part, you want to pull out an appropriate function
from your alg record and apply it to exp1 and exp2.

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


Re: [Haskell-cafe] Possible Improvements

2007-12-03 Thread Felipe Lessa
On Dec 3, 2007 9:23 PM,  [EMAIL PROTECTED] wrote:
 2. If it's logically a Functor, strictness will break the axioms,
 so don't do that.

What do you mean by breaking the axioms? If I define

 data List a = Nil | Cons !a !(List a)

 instance Functor List where
   fmap f Nil = Nil
   fmap f (Cons x xs) = Cons (f x) (fmap f xs)

Then the laws

1) fmap id == id
2) fmap f . fmap g == fmap (f . g)

won't hold? What am I missing here? Are there some bottoms hiding out?

...

Oh, I think I saw one! Let

 f x = 1
 g x = _|_
 l = Cons 2 Nil

Then

 fmap f (fmap g l) == fmap f (Cons _|_ Nil) == fmap f _|_ == _|_

but

 fmap (f . g) l == Cons (f (g 2)) Nil == Cons (f _|_) Nil == Cons 1 Nil

right? Very interesting. Is this written somewhere on the wiki?

Cheers,

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


Re: [Haskell-cafe] foild function for expressions

2007-12-03 Thread Ryan Ingram
On 12/3/07, Kalman Noel [EMAIL PROTECTED] wrote:

 You're confusing sum and product types. That is, you're using a product
 type,
 but you probably need a sum type, like this:


I'm not so sure; it looks like they already have that type (Exp) and wants
to use AlgExp to hold the folding functions used.

Carlo, I think you're on the right track. Think of it this way: you have
some Exps and you want to get some things of type a to pass to the
functions in alg.  How could you get those things with what you have so far?

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


Re: [Haskell-cafe] Re: do

2007-12-03 Thread Dan Piponi
On Dec 3, 2007 3:54 PM, Ben Franksen [EMAIL PROTECTED] wrote:

 I don't buy this. As has been noted by others before, IO is a very special
 case, in that it can't be defined in Haskell itself, and there is no
 evaluation function runIO :: IO a - a.

I'm not sure what a function of type m a - a has to do with the
concept of a monad. And I don't really see what the problem is with
the IO monad not being definable in (pure) Haskell. IO exposes the
same interface as every other Monad, and you need to use that
interface to get visible results. So people have to learn it whatever.
And the whole point of the Monad is that it's an interface, not a
specific implementation.

 I'd rather use a simple example like Maybe (modeling failure as an effect).

And I'd like to see more people getting off the ground doing
interesting stuff with Haskell before their attention spans for
pointless-seeming new stuff run out. I'm not talking about the
smartest people in computer science courses here. I'm talking about
the millions of people writing everyday Python and Ruby scripts, say,
who might benefit from a more expressive, type-safe, well-thought out,
fast and compiled language.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] An interesting monad: Prompt

2007-12-03 Thread Thomas Hartman
I've been playing with MonadPrompt for about ten days now, trying to get 
it to do something useful for me.

Specifically, I'm trying to implement guess a number since that's the 
hello world of haskell state programs, or so it seems to me. I want to 
have this with scripting / replay / undo and the other goodies claimed 
possible

http://thomashartman-learning.googlecode.com/svn/trunk/haskell/guessANumber

It's been slow going due to still getting to grips with GADTs and other 
more advanced features of the typing system.

If Ryan (or anyone) would care to share any working code for a simple game 
that uses MonadPrompt, ideally with scripting / replay / undo that would 
be extremely helpful.

Otherwise I'll be back with more specific questions about my attempts to 
use this stuff soon enough :)

(At present, that;'s just trying to get some of the more interesting code 
you posted as untested to compile.)

For what it's worth, my game currently saves high some (but not all) 
state-y information in a serialized form to track high scores. If I can 
get this working with MonadPrompt, my next quest will be to use MACID to 
do the serialization instead, and then *all* state will be saved if I 
understand correctly.

t.




Ryan Ingram [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
11/18/2007 07:22 PM

To
haskell haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] An interesting monad: Prompt






(This message is a literate haskell file.  Code for the Prompt monad is
preceded by ; code for my examples is preceded by ] and isn't 
complete, 
but intended for illustration.)

I've been trying to implement a few rules-driven board/card games in 
Haskell
and I always run into the ugly problem of how do I get user input?

The usual technique is to embed the game in the IO Monad: 

] type Game = IO
] -- or
] type Game = StateT GameState IO

The problem with this approach is that now arbitrary IO computations are
expressible as part of a game action, which makes it much harder to 
implement 
things like replay, undo, and especially testing!

The goal was to be able to write code like this:

] takeTurn :: Player - Game ()
] takeTurn player = do
] piece  - action (ChoosePiece player) 
] attack - action (ChooseAttack player piece)
] bonusTurn - executeAttack piece attack
] when bonusTurn $ takeTurn player

but be able to script the code for testing, allow undo, automatically 
be able to save replays, etc.

While thinking about this problem earlier this week, I came up with the
following solution:

 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances  #-}
 -- undecidable instances is only needed for the MonadTrans instance 
below 

 module Prompt where
 import Control.Monad.Trans
 import Control.Monad.Identity

 class Monad m = MonadPrompt p m | m - p where
prompt :: p a - m a

prompt is an action that takes a prompt type and gives you a result. 

A simple example:
] prompt [1,3,5] :: MonadPrompt [] m = m Int

This prompt would ask for someone to pick a value from the list and return 
it.
This would be somewhat useful on its own; you could implement a choose 
function that picked randomly from a list of options and gave
non-deterministic (or even exhaustive) testing, but on its own this 
wouldn't
be much better than the list monad.

What really made this click for me was that the prompt type could be built 

on a GADT:

] newtype GamePrompt a = GP (GameState, GameChoice a)
] data GameChoice a where
]-- pick a piece to act with
]ChoosePiece :: Player - GameChoice GamePiece
]-- pick how they should attack 
]ChooseAttack :: Player - GamePiece - GameChoice AttackType
]-- etc.

Now you can use this type information as part of a handler function:
] gameIO :: GamePrompt a - IO a
] gameIO (GP (state, ChoosePiece player)) = getPiece state player
] gameIO (GP (state, ChooseAttack player piece)) = attackMenu player piece
] -- ...

The neat thing here is that the GADT specializes the type of IO a on the 

right hand side.  So, getPiece state player has the type IO GamePiece, 
not
the general IO a.  So the GADT is serving as a witness of the type of
response wanted by the game.

Another neat things is that, you don't need to embed this in the IO monad 
at
all; you could instead run a pure computation to do AI, or even use it for
unit testing!

 -- unit testing example
 data ScriptElem p where SE :: p a - a - ScriptElem p 
 type Script p = [ScriptElem p]

 infix 1 --
 (--) = SE


] gameScript :: ScriptElem GameChoice - GameChoice a - Maybe a
] gameScript (SE (ChoosePiece _)piece)  (ChoosePiece _)= Just 
piece 
] gameScript (SE (ChooseAttack _ _) attack) (ChooseAttack _ _) = Just 
attack
] gameScript _  _  = Nothing
]
] testGame :: Script GameChoice
] testGame =
]   [ ChoosePiece  P1-- Knight 
]   , ChooseAttack P1 Knight -- Charge
]   , ChoosePiece  P2-- FootSoldier
]   , ...
]   ]

So, how to implement all of this?

 

Fw: [Haskell-cafe] Re: do

2007-12-03 Thread Thomas Hartman
It took me forever to get comfortable with monads.

I think it helps if you've seen continuations, or done FP before, or a 
variety of things that build familiarity.

But probably the only thing that I think will work for the masses of 
plodders (there are always a few stars to crash the curve) is a desire to 
learn and tons of practice.

I wouldn't worry so much about the ideal way to introduce the material.

Oh, one other thing. You learn monads when you need them. You need IO 
right away... well, after you tired of playing with pure functions in the 
ghci sandbox.

my 2c.

t.






Dan Piponi [EMAIL PROTECTED] 
Sent by: [EMAIL PROTECTED]
12/03/2007 07:19 PM

To
haskell-cafe@haskell.org
cc

Subject
Re: [Haskell-cafe] Re: do






On Dec 3, 2007 3:54 PM, Ben Franksen [EMAIL PROTECTED] wrote:

 I don't buy this. As has been noted by others before, IO is a very 
special
 case, in that it can't be defined in Haskell itself, and there is no
 evaluation function runIO :: IO a - a.

I'm not sure what a function of type m a - a has to do with the
concept of a monad. And I don't really see what the problem is with
the IO monad not being definable in (pure) Haskell. IO exposes the
same interface as every other Monad, and you need to use that
interface to get visible results. So people have to learn it whatever.
And the whole point of the Monad is that it's an interface, not a
specific implementation.

 I'd rather use a simple example like Maybe (modeling failure as an 
effect).

And I'd like to see more people getting off the ground doing
interesting stuff with Haskell before their attention spans for
pointless-seeming new stuff run out. I'm not talking about the
smartest people in computer science courses here. I'm talking about
the millions of people writing everyday Python and Ruby scripts, say,
who might benefit from a more expressive, type-safe, well-thought out,
fast and compiled language.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: do

2007-12-03 Thread Jonathan Cast

On 3 Dec 2007, at 4:19 PM, Dan Piponi wrote:


On Dec 3, 2007 3:54 PM, Ben Franksen [EMAIL PROTECTED] wrote:

I don't buy this. As has been noted by others before, IO is a very  
special

case, in that it can't be defined in Haskell itself, and there is no
evaluation function runIO :: IO a - a.


I'm not sure what a function of type m a - a has to do with the
concept of a monad.


Nothing.  But there are plenty of legal, safe functions of type m a - 
 a for almost all monads m.  Except those based on IO.


So leading off with IO can lead to the impression that (a) monads are  
impossible to break out of / can't be used in purely functional code  
or (b) the main point of monads is to let you write imperative code  
in Haskell.  The main point of monads is that they're so common in  
Haskell we'd be crazy not to call them /something/, just so we have  
something to say when we realize, hey, this is another of those  
thingies with a return and a bind!  IO is quite atypical as far as  
the class of monads we use every day in Haskell goes; the absence of  
any useful, safe, pure function of type IO a - a is a (small)  
instance of that atypicality.


IMHO, teaching IO first and then saying, monads are things that are  
like IO, is very counter-productive.  In particular, I think it's why  
so few people understand the list monad (which is of course one of  
the pardigmatic examples).


Just my 2c, of course.

jcc

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


[Haskell-cafe] ANN: Shu-thing 1.0 and Monadius 0.9

2007-12-03 Thread gwern0
Hi everyone. With the permission of the authors, I'd like to announce the 
release  upload to Hackage of two games written in Haskell (you may've seen 
them mentioned here once or twice before):

*Monadius
*Shu-thing

They are both scrolling 2 dimensional arcade shooting games which use 3D vector 
graphics. Shu-thing is a fairly simpler upwards scrolling shooter with one 
level and geometric objects; Monadius is a sort of clone/homage to the classic 
arcade game Gradius, and I find it quite fun (although I have yet to beat it).

You can find screenshots and original here:
*http://www.geocities.jp/takascience/index_en.html#haskell

The Hackage pages:
*http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Monadius-0.9.20071203
*http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Shu-thing-1.0.20071203

--

They both have dependencies on GLUT, and it's definitely advisable to have 3D 
acceleration enabled on your system. I've only tested them with GHC 6.8.1 and 
up (where they work fine) on my Gentoo Linux box.

You should be able to 'cabal install' Shu-thing, but Monadius doesn't compile 
successfully for reasons I don't understand.

--

My changes to the programs in question are not terribly major - largely 
Cabalizing them, formatting and making stylistic changes, stomping most -Wall 
messages, and occasionally changing algorithms or attempting to optimize them. 
In the case of Monadius, I removed all the Windows-specific material (the audio 
files were apparently copyright violations, so no big loss) and improved 
storage of replay files.

I'd like to thank Takayuki Muranushi for answering my questions about the code 
and giving permission to update them. I hereby release all my changes into the 
public domain.

--
gwern


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


[Haskell-cafe] IO is a bad example for Monads [was: do]

2007-12-03 Thread Ben Franksen
Dan Piponi wrote:
 On Dec 3, 2007 3:54 PM, Ben Franksen [EMAIL PROTECTED] wrote:
 
 I don't buy this. As has been noted by others before, IO is a very
 special case, in that it can't be defined in Haskell itself, and there is
 no evaluation function runIO :: IO a - a.
 
 I'm not sure what a function of type m a - a has to do with the
 concept of a monad. And I don't really see what the problem is with 
 the IO monad not being definable in (pure) Haskell. 

Funny you say that because this is exactly my point! Both have nothing to do
with monads per se.

But if IO is not only the first monad one learns about, but also used as the
first example to explain monads in general, then the special features of IO
will remain associated with monads in general, leading to a whole jumble of
completely wrong ideas about them.

For example, since IO can't be defined in Haskell, Monads get associated
with the idea that there is some 'magic' to make them work going on. (The
OP's question about 'the do construct' nicely illustrates this.)

Another common fallacy is to think of monads as 'sequencing effects', when
in fact this is not necessarily the case. Again, IO is a bad example,
because it is too special to generalize from, its effect base too complex
to study comprehensively, and its implementation not accessible and
therefore obscure. With a simple monad it is easy to see that, if any
sequencing of effects happens at all, then this is due to data dependencies
alone, period.

(I fell afoul of both of the above mistakes and it wasn't easy to get them
out of my head.)

 IO exposes the 
 same interface as every other Monad, and you need to use that
 interface to get visible results. So people have to learn it whatever.
 And the whole point of the Monad is that it's an interface, not a
 specific implementation.

Indeed, it is an interface, and a /very/ general one. It is in fact so
general that in itself alone it is completely useless. You always need an
effect base to get useful things done.

This is yet another problem with IO as the standard example for monads: its
effect base is huge and poorly structured. This again makes it difficult to
see exactly which intuitions about IO can be generalized to arbitrary
monads and which not.

People (and especially those who start learning Haskell, coming form
imperative languages) keep asking the question: all very nice, but what
exactly /is/ a monad? As with the concept of a group in algebra ('a set
with an operation bla bla satisfying the laws ...)', you can of course
say 'a type constructor of kind bla bla with functions bla bla satisfying
the laws...'. However this won't really help the newcomer. What helps is
examples. And looking into the implementation of a simple monad greatly
helps to dispell many kinds of wrong ideas one might have (due to exclusive
exposure to IO as the prime example for a Monad).

 I'd rather use a simple example like Maybe (modeling failure as an
 effect).
 
 And I'd like to see more people getting off the ground doing
 interesting stuff with Haskell before their attention spans for
 pointless-seeming new stuff run out. I'm not talking about the
 smartest people in computer science courses here. I'm talking about
 the millions of people writing everyday Python and Ruby scripts, say,
 who might benefit from a more expressive, type-safe, well-thought out,
 fast and compiled language.

What is pointless about failure and how to handle it? IMO this is the /most/
immediate practical problem one encounters whenever the Python or Ruby (or,
for that matter, Haskell) script starts to exceed a few lines.

Cheers
Ben

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


[Haskell-cafe] Advice for clean code.

2007-12-03 Thread David McBride
I am still in the early stages learning haskell, which is my first foray 
into functional programming.  Well there's no better way to learn than 
to write something, so I started writing a game.


Mostly the thing looks good so far, far better than the C version did.  
However, my problem is that code like the following is showing up more 
often and it is becoming unwieldy.


gameLoop :: World - IO ()
gameLoop w = do
  drawScreen w

  action - processInput

  let (result, w') = processAction action w

  case result of
MoveOutOfBounds - putStrLn Sorry you can't move in that direction.
MoveBadTerrain a - case a of
  Wall - putStrLn You walk into a wall.
  Tree - putStrLn There is a tree in the way.
  otherwise - putStrLn You can't move there.
otherwise - return ()

  let w'' = w' { window = updateWindowLocation (window w') (location $ 
player w')}


  unless (action == Quit) (gameLoop w'')

Where world contains the entire game's state and so I end up with w's 
with multiple apostrophes at the end.  But at the same time I can't 
really break these functions apart easily.  This is error prone and 
seems pointless.


I have been reading about control.monad.state and I have seen that I 
could run execstate over this and use modify but only if each function 
took a world and returned a world.  That seems really limiting.  I'm not 
even sure if this is what I should be looking at.


I am probably just stuck in an imperative mindset, but I have no idea 
what to try to get rid of the mess and it is only going to get worse 
over time.  Any suggestions on what I can do about it?

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


Re: [Haskell-cafe] Re: Waiting for thread to finish

2007-12-03 Thread Matthew Brecknell
Ryan Ingram said:
 Interesting, although this seems like a perfect use for orelse:
 
  wait_stm :: Wait a - STM a
  wait_stm (Wait w) = readTVar w = maybe retry return
 
  wait :: Wait a - IO a
  wait w = atomically $ wait_stm w
 
  wait_first :: [Wait a] - IO (a, [Wait a])
  wait_first [] = error wait_first: nothing to wait for
  wait_first ws = atomically (do_wait ws) where
 do_wait [] = retry
 do_wait (w : ws) = do
 r - wait_stm w
 return (r, ws)
   `orelse` fmap (second (w:)) (do_wait ws)

Indeed, that is very nice. I see now that orElse allows wait_stm to
compose easily, so you don't need to keep opening up the insides of the
Wait variable.

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


Re: [Haskell-cafe] Advice for clean code.

2007-12-03 Thread Don Stewart
stefanor:
 On Mon, Dec 03, 2007 at 08:47:48PM -0600, David McBride wrote:
  I am still in the early stages learning haskell, which is my first foray 
  into functional programming.  Well there's no better way to learn than to 
  write something, so I started writing a game.
 
  Mostly the thing looks good so far, far better than the C version did.  
  However, my problem is that code like the following is showing up more 
  often and it is becoming unwieldy.
 
  gameLoop :: World - IO ()
  gameLoop w = do
drawScreen w
 
action - processInput
 
let (result, w') = processAction action w
 
case result of
  MoveOutOfBounds - putStrLn Sorry you can't move in that direction.
  MoveBadTerrain a - case a of
Wall - putStrLn You walk into a wall.
Tree - putStrLn There is a tree in the way.
otherwise - putStrLn You can't move there.
  otherwise - return ()
 
let w'' = w' { window = updateWindowLocation (window w') (location $ 
  player w')}
 
unless (action == Quit) (gameLoop w'')
 
  Where world contains the entire game's state and so I end up with w's with 
  multiple apostrophes at the end.  But at the same time I can't really break 
  these functions apart easily.  This is error prone and seems pointless.
 
  I have been reading about control.monad.state and I have seen that I could 
  run execstate over this and use modify but only if each function took a 
  world and returned a world.  That seems really limiting.  I'm not even sure 
  if this is what I should be looking at.
 
  I am probably just stuck in an imperative mindset, but I have no idea what 
  to try to get rid of the mess and it is only going to get worse over time.  
  Any suggestions on what I can do about it?
 
 I'd recommend using StateT World IO.  You can always run other functions
 using 'lift'; for instance lift can be :: IO () - StateT World IO ().

The fact your passing state explicitly, which is error prone, pretty much
demands a State monad., And the IO in the main loop seems needless -- the game 
is really just a function from :: World - [Event] - [(World',Action)]

So strongly consider lifting the IO out of the main loop, and just have your
game be a function from input events, to output game states, Which you draw as
they're received.

The game would run in an environment something like:

newtype Game a = Game (StateT World IO) a
deriving (Functor, Monad, MonadState World)

The inner loop would be something like:

game :: Event - Game Action
game Quit   = exitWith ExitSuccess
game Left   = ...  return MoveOK
game Right  = ...  return MoveOK
game Up = return MoveOutOfBounds
game Down   = return (MoveBadTerrain Tree)

Running the game over the input events, producing a sequence of screens
to print:

runGame :: [Event] - [(Board,Action)]
runGame es = evalState (mapM game es) 0

Use show for the result action, to avoid ugly print statements,

data Action
= MoveOutOfBounds
| MoveBadTerrain Object
| MoveOK

-- How to display results
instance Show Action where
show MoveOutOfBounds= Sorry you can't move in that direction.
show (MoveBadTerrain a) = case a of
  Wall  - You walk into a wall.
  Tree  - There is a tree in the way.
  otherwise - You can't move there.
show MoveOk = Good move.

And at  the top level,

main = do
events  - map processInput $ getContents
mapM_ print (runGame events)

This isn't real code, just a sketch.

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


Re: [Haskell-cafe] foild function for expressions

2007-12-03 Thread Stefan O'Rear
On Mon, Dec 03, 2007 at 09:27:45PM -0600, Derek Elkins wrote:
 On Mon, 2007-12-03 at 19:13 -0800, Stefan O'Rear wrote:
  On Mon, Dec 03, 2007 at 09:18:18AM -0800, Carlo Vivari wrote:
   
   Hi! I'm a begginer in haskell and I have a problem with an exercise, I 
   expect
   someone could help me:
   
   In one hand I have a declaration of an algebra data, like this:
   
   data AlgExp a = AlgExp
   { litI  :: Int - a,
  litB :: Bool - a,
  add :: a - a - a,
  and :: a - a - a,
  ifte :: a - a - a - a}
   
   (being ifte an 'ifthenelse' expresion...)
   
   What I want to do is to write a fold function for expressions, something
   like this:
   
   foldExp :: AlgExp a - Exp - a
   foldExp alg (LitI i) = litI alg i
   foldExp alg (LitB i) = litB alg i
   foldExp alg (add exp1 exp2) = ¿¿¿???
   foldExp alg (and exp1 exp2) = ¿¿¿???
   foldExp alg (ifte exp1 exp2 exp3) = ¿¿¿???
   
   ..ETC
   
   
   the fact is that I have no idea of what to do with the other expresions
   (add, and, and ifte)... I really don' t understand how to do this... It's
   clear that a fold function should colapse in one valour, but how can I
   espress it in the terms of the exercise?
   
   For further information about the problem after this,  it's suposed that I
   have to rewrite some functions for expresions but in terms of foldexp (the
   one I should write before)
  
  The problem is that AlgExp defines an arbitrary algebra, but in order to
  fold you need a universal algebra.  So it makes the most sense to add
  foldExp to the reccord.
 
 This is an unusually poor post for you.  Presuming you mean initial or
 free or term for universal then it does (presumably) have it with
 Exp.  Assuming Exp is the expected thing (an AST) it is (combined with
 the constructors) the initial algebra.  foldExp should quite definitely
 be the type it is and not be part of the record and the its
 implementation is so far correct (modulo syntactical errors that are
 potentially indicative of a deeper confusion).

Oh right, I misread the foldExp sketch.  I thought he was trying to go
*from* a member of his algebra *to* Exp.  Sorry.

Stefan


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


Re: [Haskell-cafe] foild function for expressions

2007-12-03 Thread Stefan O'Rear
On Mon, Dec 03, 2007 at 09:18:18AM -0800, Carlo Vivari wrote:
 
 Hi! I'm a begginer in haskell and I have a problem with an exercise, I expect
 someone could help me:
 
 In one hand I have a declaration of an algebra data, like this:
 
 data AlgExp a = AlgExp
 { litI  :: Int - a,
litB :: Bool - a,
add :: a - a - a,
and :: a - a - a,
ifte :: a - a - a - a}
 
 (being ifte an 'ifthenelse' expresion...)
 
 What I want to do is to write a fold function for expressions, something
 like this:
 
 foldExp :: AlgExp a - Exp - a
 foldExp alg (LitI i) = litI alg i
 foldExp alg (LitB i) = litB alg i
 foldExp alg (add exp1 exp2) = ¿¿¿???
 foldExp alg (and exp1 exp2) = ¿¿¿???
 foldExp alg (ifte exp1 exp2 exp3) = ¿¿¿???
 
 ..ETC
 
 
 the fact is that I have no idea of what to do with the other expresions
 (add, and, and ifte)... I really don' t understand how to do this... It's
 clear that a fold function should colapse in one valour, but how can I
 espress it in the terms of the exercise?
 
 For further information about the problem after this,  it's suposed that I
 have to rewrite some functions for expresions but in terms of foldexp (the
 one I should write before)

The problem is that AlgExp defines an arbitrary algebra, but in order to
fold you need a universal algebra.  So it makes the most sense to add
foldExp to the reccord.

Stefan


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


Re: [Haskell-cafe] Advice for clean code.

2007-12-03 Thread Stefan O'Rear
On Mon, Dec 03, 2007 at 08:47:48PM -0600, David McBride wrote:
 I am still in the early stages learning haskell, which is my first foray 
 into functional programming.  Well there's no better way to learn than to 
 write something, so I started writing a game.

 Mostly the thing looks good so far, far better than the C version did.  
 However, my problem is that code like the following is showing up more 
 often and it is becoming unwieldy.

 gameLoop :: World - IO ()
 gameLoop w = do
   drawScreen w

   action - processInput

   let (result, w') = processAction action w

   case result of
 MoveOutOfBounds - putStrLn Sorry you can't move in that direction.
 MoveBadTerrain a - case a of
   Wall - putStrLn You walk into a wall.
   Tree - putStrLn There is a tree in the way.
   otherwise - putStrLn You can't move there.
 otherwise - return ()

   let w'' = w' { window = updateWindowLocation (window w') (location $ 
 player w')}

   unless (action == Quit) (gameLoop w'')

 Where world contains the entire game's state and so I end up with w's with 
 multiple apostrophes at the end.  But at the same time I can't really break 
 these functions apart easily.  This is error prone and seems pointless.

 I have been reading about control.monad.state and I have seen that I could 
 run execstate over this and use modify but only if each function took a 
 world and returned a world.  That seems really limiting.  I'm not even sure 
 if this is what I should be looking at.

 I am probably just stuck in an imperative mindset, but I have no idea what 
 to try to get rid of the mess and it is only going to get worse over time.  
 Any suggestions on what I can do about it?

I'd recommend using StateT World IO.  You can always run other functions
using 'lift'; for instance lift can be :: IO () - StateT World IO ().

Stefan


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


Re: [Haskell-cafe] foild function for expressions

2007-12-03 Thread Derek Elkins
On Mon, 2007-12-03 at 19:13 -0800, Stefan O'Rear wrote:
 On Mon, Dec 03, 2007 at 09:18:18AM -0800, Carlo Vivari wrote:
  
  Hi! I'm a begginer in haskell and I have a problem with an exercise, I 
  expect
  someone could help me:
  
  In one hand I have a declaration of an algebra data, like this:
  
  data AlgExp a = AlgExp
  { litI  :: Int - a,
 litB :: Bool - a,
 add :: a - a - a,
 and :: a - a - a,
 ifte :: a - a - a - a}
  
  (being ifte an 'ifthenelse' expresion...)
  
  What I want to do is to write a fold function for expressions, something
  like this:
  
  foldExp :: AlgExp a - Exp - a
  foldExp alg (LitI i) = litI alg i
  foldExp alg (LitB i) = litB alg i
  foldExp alg (add exp1 exp2) = ¿¿¿???
  foldExp alg (and exp1 exp2) = ¿¿¿???
  foldExp alg (ifte exp1 exp2 exp3) = ¿¿¿???
  
  ..ETC
  
  
  the fact is that I have no idea of what to do with the other expresions
  (add, and, and ifte)... I really don' t understand how to do this... It's
  clear that a fold function should colapse in one valour, but how can I
  espress it in the terms of the exercise?
  
  For further information about the problem after this,  it's suposed that I
  have to rewrite some functions for expresions but in terms of foldexp (the
  one I should write before)
 
 The problem is that AlgExp defines an arbitrary algebra, but in order to
 fold you need a universal algebra.  So it makes the most sense to add
 foldExp to the reccord.

This is an unusually poor post for you.  Presuming you mean initial or
free or term for universal then it does (presumably) have it with
Exp.  Assuming Exp is the expected thing (an AST) it is (combined with
the constructors) the initial algebra.  foldExp should quite definitely
be the type it is and not be part of the record and the its
implementation is so far correct (modulo syntactical errors that are
potentially indicative of a deeper confusion).

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


[Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-03 Thread Dan Piponi
Is there anything in any of the interfaces to Integer that will allow
me to quickly find the highest bit set in an Integer? If not, does
anyone have any recommendations for how to do it efficiently. There
are some obvious things that come to mind but which might involve
quite a bit of useless copying of data internally by the
implementation of Integer.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-03 Thread Brandon S. Allbery KF8NH


On Dec 3, 2007, at 23:36 , Dan Piponi wrote:


Is there anything in any of the interfaces to Integer that will allow
me to quickly find the highest bit set in an Integer? If not, does


Isn't Integer unlimited (well, limited by RAM)?

--
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] Advice for clean code.

2007-12-03 Thread Andrew Wagner
Don's code intrigued me, so I fired up my trusty emacs and ghci, and
turned it into actual code, which type-checks. Well, ok, I kind of
randomly poked at it, while begging for help, which I received in
abundance from #haskell, particularly oerjan, and Don himself. Anyway,
here's the code:

{-# OPTIONS -fglasgow-exts #-}

module Game
where

import Control.Applicative
import Control.Monad.State
import System

newtype Game a = Game (StateT World IO a)
deriving (Functor, Monad, MonadState World, MonadIO)

data Event = Quit | LeftE | RightE | Up | Down
data Board = Board [Int] deriving (Show)
data World = World [Int]

game :: Event - Game Action
game Quit   =  liftIO $ exitWith ExitSuccess
game LeftE   = return MoveOK
game RightE  = return MoveOK
game Up = return MoveOutOfBounds
game Down   = return (MoveBadTerrain Tree)

runGame :: [Event] - IO [Action]
runGame es = evalStateT s (World [0])
where Game s = mapM game es

data Action = MoveOutOfBounds | MoveBadTerrain String | MoveOK

   -- How to display results
instance Show Action where
show MoveOutOfBounds= Sorry you can't move in that direction.
show (MoveBadTerrain a) = case a of
Wall  - You walk into a wall.
Tree  - There is a tree in the way.
otherwise - You can't move there.
show MoveOK = Good move.

main = do
  events  - map processInput $ getContents
  mapM_ print = runGame events

processInput :: Char - Event
processInput = undefined


On Dec 3, 2007 10:28 PM, Don Stewart [EMAIL PROTECTED] wrote:
 stefanor:
  On Mon, Dec 03, 2007 at 08:47:48PM -0600, David McBride wrote:
   I am still in the early stages learning haskell, which is my first foray
   into functional programming.  Well there's no better way to learn than to
   write something, so I started writing a game.
  
   Mostly the thing looks good so far, far better than the C version did.
   However, my problem is that code like the following is showing up more
   often and it is becoming unwieldy.
  
   gameLoop :: World - IO ()
   gameLoop w = do
 drawScreen w
  
 action - processInput
  
 let (result, w') = processAction action w
  
 case result of
   MoveOutOfBounds - putStrLn Sorry you can't move in that direction.
   MoveBadTerrain a - case a of
 Wall - putStrLn You walk into a wall.
 Tree - putStrLn There is a tree in the way.
 otherwise - putStrLn You can't move there.
   otherwise - return ()
  
 let w'' = w' { window = updateWindowLocation (window w') (location $
   player w')}
  
 unless (action == Quit) (gameLoop w'')
  
   Where world contains the entire game's state and so I end up with w's with
   multiple apostrophes at the end.  But at the same time I can't really 
   break
   these functions apart easily.  This is error prone and seems pointless.
  
   I have been reading about control.monad.state and I have seen that I could
   run execstate over this and use modify but only if each function took a
   world and returned a world.  That seems really limiting.  I'm not even 
   sure
   if this is what I should be looking at.
  
   I am probably just stuck in an imperative mindset, but I have no idea what
   to try to get rid of the mess and it is only going to get worse over time.
   Any suggestions on what I can do about it?
 
  I'd recommend using StateT World IO.  You can always run other functions
  using 'lift'; for instance lift can be :: IO () - StateT World IO ().

 The fact your passing state explicitly, which is error prone, pretty much
 demands a State monad., And the IO in the main loop seems needless -- the game
 is really just a function from :: World - [Event] - [(World',Action)]

 So strongly consider lifting the IO out of the main loop, and just have your
 game be a function from input events, to output game states, Which you draw as
 they're received.

 The game would run in an environment something like:

 newtype Game a = Game (StateT World IO) a
 deriving (Functor, Monad, MonadState World)

 The inner loop would be something like:

 game :: Event - Game Action
 game Quit   = exitWith ExitSuccess
 game Left   = ...  return MoveOK
 game Right  = ...  return MoveOK
 game Up = return MoveOutOfBounds
 game Down   = return (MoveBadTerrain Tree)

 Running the game over the input events, producing a sequence of screens
 to print:

 runGame :: [Event] - [(Board,Action)]
 runGame es = evalState (mapM game es) 0

 Use show for the result action, to avoid ugly print statements,

 data Action
 = MoveOutOfBounds
 | MoveBadTerrain Object
 | MoveOK

 -- How to display results
 instance Show Action where
 show MoveOutOfBounds= Sorry you can't move in that direction.
 show (MoveBadTerrain a) = case a of
   Wall  - You walk into a wall.
   

Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-03 Thread Stefan O'Rear
On Mon, Dec 03, 2007 at 11:40:14PM -0500, Brandon S. Allbery KF8NH wrote:

 On Dec 3, 2007, at 23:36 , Dan Piponi wrote:

 Is there anything in any of the interfaces to Integer that will allow
 me to quickly find the highest bit set in an Integer? If not, does

 Isn't Integer unlimited (well, limited by RAM)?

Any *specific* integer has a finite number of 1-bits.

Stefan


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


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-03 Thread Don Stewart
dpiponi:
 On Dec 3, 2007 9:10 PM, Don Stewart [EMAIL PROTECTED] wrote:
   Is there anything in any of the interfaces to Integer that will allow
   me to quickly find the highest bit set in an Integer?
  Well, you could use testBit, which is pretty efficient,
 
 But testBit tests only one bit at a time. To prove that i is the
 highest bit of n I need to prove that all higher bits are set to zero,
 and I can't do that with testBit. The obvious thing is shiftR n i ==
 0 but I'm worried that that entails the wasteful operation of
 shifting all of the bits above bit i. Internally the implementation of
 Integer must know a good upper bound on where the highest bit is.
 Maybe I need to delve into GHC.Prim.

Yes, perhaps look into what GMP provides, then bind to it, and call it
on the underlying ByteArray#

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


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-03 Thread Sterling Clover
Actually, I suspect GHC's strictness analyzer will give you  
reasonable performance with even the naive version, but fancier ideas  
are at http://graphics.stanford.edu/~seander/bithacks.html#IntegerLog


The problem with all those, however, is since they do bit-twiddling  
and use shifts and masks, they're designed to, as far as I can tell,  
only work on integers of defined sizes (the names given to the  
functions to the contrary). You could, of course, dynamically choose  
how many masks to apply based on the length of the Integer in  
question, which can, if all else fails, be determined by unpacking it  
into the primitives, which are (# Int#, ByteArr# #) with the Int# as  
the number of limbs of the integer, as well as its sign. As far as  
I understand it, each limb is generally 32 bits.


Unless this is a real performance hotspot, you're probably fine  
sticking with a relatively naive version. For example, in my  
translation of the clean version of the meteor-contest shootout  
entry, I used the following function (which, I'll grant, does  
something slightly different):


first0 :: Mask - Int
first0 i
| i .. 1 == 0 = 0
| otherwise = 1 + first0 (i `shiftR` 1)

and it worked out fine for my purposes.

--s.

On Dec 3, 2007, at 11:36 PM, Dan Piponi wrote:


Is there anything in any of the interfaces to Integer that will allow
me to quickly find the highest bit set in an Integer? If not, does
anyone have any recommendations for how to do it efficiently. There
are some obvious things that come to mind but which might involve
quite a bit of useless copying of data internally by the
implementation of Integer.
--
Dan
___
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] Looking for smallest power of 2 = Integer

2007-12-03 Thread Don Stewart
dpiponi:
 Is there anything in any of the interfaces to Integer that will allow
 me to quickly find the highest bit set in an Integer? If not, does
 anyone have any recommendations for how to do it efficiently. There
 are some obvious things that come to mind but which might involve
 quite a bit of useless copying of data internally by the
 implementation of Integer.

Well, you could use testBit, which is pretty efficient,

x `testBit` i   = (x .. bit i) /= 0
(J# s1 d1) .. (J# s2 d2) = 
case andInteger# s1 d1 s2 d2 of
  (# s, d #) - J# s d

Of course, working out which bit to test is the puzzle :)

Just for fun, I tried to see how large gmp could go,

import Data.Bits
import Text.Printf

main = mapM_ test [0,1 ..]
  where
test n = printf 2 ^ %d has bit %d set: %s\n n n (show t)
where
t = (2 ^ n :: Integer) `testBit` n

gmp is quite remarkable.

$ ghc  -O2 A.hs -o A
$ time ./A  
2 ^ 0 has bit 0 set: True
2 ^ 1 has bit 1 set: True
2 ^ 2 has bit 2 set: True
2 ^ 3 has bit 3 set: True
2 ^ 4 has bit 4 set: True
2 ^ 5 has bit 5 set: True
2 ^ 6 has bit 6 set: True
A: out of memory (requested 202375168 bytes)
./A  504.00s user 1.73s system 99% cpu 8:26.71 total

and I ran out of ram.

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


Re: [Haskell-cafe] IO is a bad example for Monads [was: do]

2007-12-03 Thread Dan Piponi
On Dec 3, 2007 6:36 PM, Ben Franksen [EMAIL PROTECTED] wrote:
 then the special features of IO
 will remain associated with monads in general, leading to a whole jumble of
 completely wrong ideas about them.

As I only learnt about monads a couple of years ago, the process is
still fresh in my mind. I wasted quite a bit of time labouring under
the impression that monads were primarily about sequencing. But that
wasn't because I incorrectly generalised from IO. It was because
countless people out there explicitly said they were about sequencing.
I suspect that if courses started with the List monad there'd be
countless blogs telling people that monads are a way to eliminate
loops from your code like the way list comprehensions are used in
Python.

 This is yet another problem with IO as the standard example for monads: its
 effect base is huge and poorly structured.

You don't teach *all* of IO to students in one go!

 This again makes it difficult to
 see exactly which intuitions about IO can be generalized to arbitrary
 monads and which not.

That's true of any monad. IO is unique. [] is unique. Cont is unique.
All of them can lead you down the garden path. You need to see
multiple monads, and it helps if you can sneak an example under a
student's nose so they can already reason about monads before they
even know what a monad is.

 What is pointless about failure and how to handle it?

It's pointless when you're still trying to make your first tweaks to
Hello, World! work.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-03 Thread Dan Piponi
On Dec 3, 2007 9:10 PM, Don Stewart [EMAIL PROTECTED] wrote:
  Is there anything in any of the interfaces to Integer that will allow
  me to quickly find the highest bit set in an Integer?
 Well, you could use testBit, which is pretty efficient,

But testBit tests only one bit at a time. To prove that i is the
highest bit of n I need to prove that all higher bits are set to zero,
and I can't do that with testBit. The obvious thing is shiftR n i ==
0 but I'm worried that that entails the wasteful operation of
shifting all of the bits above bit i. Internally the implementation of
Integer must know a good upper bound on where the highest bit is.
Maybe I need to delve into GHC.Prim.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-03 Thread Dan Piponi
On Dec 3, 2007 9:32 PM, Sterling Clover [EMAIL PROTECTED] wrote:
 if all else fails, be determined by unpacking it
 into the primitives, which are (# Int#, ByteArr# #) with the Int# as
 the number of limbs of the integer, as well as its sign.

That's the answer I'm looking for, thanks.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-03 Thread David Benbennick
On 12/3/07, Dan Piponi [EMAIL PROTECTED] wrote:
 On Dec 3, 2007 9:32 PM, Sterling Clover [EMAIL PROTECTED] wrote:
  if all else fails, be determined by unpacking it
  into the primitives, which are (# Int#, ByteArr# #) with the Int# as
  the number of limbs of the integer, as well as its sign.

 That's the answer I'm looking for, thanks.

Could you please post your code here when you're done?  I'd be
interested to see the final result.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] The Opposite of $

2007-12-03 Thread PR Stanley

Hi
According to the Haskell Wikibook the € is the 
opposite of $. The text also oints out that the 
| can be used as a substitute. I tried using 
| but to no avail. Is the list au fait with the | operator?

Thanks,
Paul

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