[Haskell-cafe] #haskell irc channel reaches 400 users

2007-08-20 Thread Donald Bruce Stewart

A small announcement :)

5 1/2  years after its inception, under the guiding hand of Shae Erisson
(aka shapr), the #haskell IRC channel[1] on freenode has finally reached
400 users!

To chart the growth, we can note that the channel was founded 
in late 2001, and had slow growth till 2006, reaching 200 users in
January of that year. Since then growth in the user base has been far
more rapid, reaching 300 users in Dec 2006, and 400 users now, in August
2007.

This puts the channel at around the 13th largest community of the 5500
freenode channels. For comparision, a sample of the state of the other
language communities:

#php 485
#perl472
##c++457
##c  445
#python  430
#ruby-lang   420
 
   #haskell 411

#lisp246
##java   236
##javascript 226
#perl6   144
#scheme  139
#erlang  118
#lua 105
#ocaml58

You can see the growth of the channel over here: 
http://www.cse.unsw.edu.au/~dons/irc

If you've not dropped by the channel yet, feel free to come and chat,
and toss around some lambdas! :)

Cheers,
  Don

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


Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Donald Bruce Stewart
ryani.spam:
 
 Your code is broken in a most evil and insidious way.
 
 
 
Interesting.  This is for a toy project, so I'm not too
worried, but lets say I wanted to do this correctly and I
was set on using IOUArray for some reason. (The Haskell wiki
claims that StorableArray is slower; is that actually the
case?)
 
 
 
Which of the following fixes would work now?  Which has the
lowest probability of not working in the future?
 
 
 
1) Declare f to take Addr# and don't construct a Ptr Word32
 
I suspect this would be enough unless the GC changed to
some sort of continous GC which can happen even without an
allocation
 
 
 
2) Declare f to take MutableByteArray#
 
Is this good enough to make the collector happy?
 
 
 
3) Something else I haven't thought of?
 
If there was no other option, and StorableArray wasn't
slower, and I was working on a real project, I'd probably
wrap my own around ForeignPtr like Data.ByteString.

Yeah, we have ForeignPtr arrays and Foreign.Array /exactly/ for calling
to C safely. I don't know why people suggest all these other dodgy
solutions, when there's one that's guaranteed by the FFI spec to work.

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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Donald Bruce Stewart
phil:
 On Mon, Aug 20, 2007 at 09:57:38PM +0100, Simon Peyton-Jones wrote:
 GHC does some constant folding, but little by way of strength
 reduction, or using shifts instead of multiplication.  It's pretty
 easy to add more: it's all done in a single module.  Look at
 primOpRules in the module PrelRules.
 
 Patches welcome!  But please also supply test-suite tests that check
 the correctness of the rules.
 
 Sucking another example out of comp.lang.functional:
 
 This:
 
   import System
 
   f :: Int - Int - Int
   f s n = if n  0 then f (s+n) (n-1) else s
 
   main = do
 [n] - getArgs
 putStrLn $ show $ f 0 (read n) 
 
 is 3-4x slower than this:
 
   #include stdio.h
   #include stdlib.h
   #include assert.h
 
   int f(int s, int n) { 
 return n  0 ? f(s+n, n-1) : s;
   }
 
   int main(int argc, char *argv[]) { 
 assert(argc == 2);
 printf(%d\n, f(0, strtol(argv[1],0,0)));
   }
 
 The generated assembler suggests (if I've read it correctly) that gcc
 is spotting that it can replace the tail call with a jump in the C
 version, but for some reason it can't spot it for the Haskell version
 when compiling with -fvia-C (and neither does ghc itself using
 -fasm). So the haskell version ends up pushing and popping values on
 and off the stack for every call to f, which is a bit sad.
 

That doesn't sound quite right. The C version should get a tail call ,
with gcc -O2, the Haskell version should be a tail call anyway.

Let's see:

C
$ gcc -O t.c -o t 
$ time ./t 10
zsh: segmentation fault (core dumped)  ./t 10
./t 10  0.02s user 0.22s system 5% cpu 4.640 total

Turning on -O2

$ time ./t 10
-243309312
./t 10  1.89s user 0.00s system 97% cpu 1.940 total


And GHC:

$ ghc -O2 A.hs -o A
$ time ./A 10   
   
-243309312
./A 10  3.21s user 0.01s system 97% cpu 3.289 total

So, what, 1.6x slower than gcc -O2
Seems ok without any tuning.

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


Re: [Haskell-cafe] Parsing binary data.

2007-08-21 Thread Donald Bruce Stewart
dot:
 On Sun, 19 Aug 2007, Peter Cai wrote:
 
  My duty is writing a network server which talks to another server through a
  binary based private protocol.
 
 Haskell needs something like Erlang's bit syntax.
 
 http://erlang.org/doc/reference_manual/expressions.html#6.16
 http://erlang.org/doc/programming_examples/bit_syntax.html#4
 The IP header example in the latter is a brilliant real-world example.
 
 It has recently been upgraded to support arbitrary bit streams.
 See http://www.it.uu.se/research/group/hipe/papers/padl07.pdf
 

Yes, we've looked at this in the context of Data.Binary. Rather than
extending the core syntax, on option is to use Template Haskell,

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/BitSyntax-0.3

Another is to just use monad and pattern guards, which give quite
reasonable syntax.

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


Re: [Haskell-cafe] Norvig's Sudoku Solver in Haskell

2007-08-28 Thread Donald Bruce Stewart
chaddai.fouche:
 For the translation of the above OCaml code, there is not much to do,
 in fact it is mostly functional, and so easily translated in Haskell
 code, note that I add a code to handle input of the form
 4.8.5.3..7..2.6.8.4..1...6.3.7.5..2.1.4..,
 to resolve it and print a solution :

Spencer Janssen also wrote a rather elegant translation, which you can
find on hpaste.org

import Data.List
import Data.Ord

n = 3 :: Int

invalid (i, j) (i', j') = i == i' || j == j' ||
  i `div` n == i' `div` n  j `div` n == j' `div` n

select p n p' ns | invalid p p' = filter (/= n) ns
 | otherwise= ns
  
add p n sols = sortBy (comparing (length . snd)) $ map f sols
  where f (p', ns) = (p', select p n p' ns)

search [] = [[]]
search ((p, ns):sols) = [(p, n):ss | n - ns, ss - search $ add p n sols]

You can see the development here,

http://hpaste.org/2348  

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


Re: [Haskell-cafe] Hawiki articles

2007-09-03 Thread Donald Bruce Stewart
lemming:
 
 On Mon, 3 Sep 2007, Derek Elkins wrote:
 
  On Mon, 2007-09-03 at 14:57 +0200, Henning Thielemann wrote:
   In the current Haskell Wiki (haskell.org/haskellwiki) I found references
   to articles of the old Hawiki (haskell.org/hawiki), like OnceAndOnlyOnce
   and SeparationOfConcerns. Are the files still available somewhere?
 
  HaWiki was taken down for the not unreasonable reason that, since it is
  no longer being updated, there is a decent chunk of out-dated and thus
  misleading information on it.  Unfortunately there is a ridiculously
  large amount extremely good information on it that never got ported and
  frankly never is going to be ported (for good and bad reasons).
 
 ... and there was unfortunately no support in porting the stuff. I guess
 some simple program (perl -p -e 's/{{{/hask/g' :-) could have simplified
 a lot. Its however more difficult for me to do this via the web interface,
 than for the people who have access to the bare files.

The problem was the licensing. Only pages whose authors were known, and
who gave permission to license the work freely, were ported. And only
some of those pages actually got moved.

  Clearly making HaWiki live again would be a bad idea; haskellwiki is
  being used now for a reason.  However, having it up in stasis as it
  was with some prominent indication on each page that it is out of
  date/no longer updated/obsolete or whichever term suits you fancy should
  effectively solve the problem.  It should be possible and probably even
  desirable to distill the pages into static HTML documents so that
  MoinMoin would not be needed, if that is an issue.
 
 Since it is easier to port Wiki code than HTML code, I propose copying all
 hawiki pages as they are to haskellwiki in a directory like DEPRECATED.
 From there people can go on moving pages into the space of current pages.
 This would also allow to track where pages came from Hawiki.

We can't do that, due to the licensing issues. Details here:

http://haskell.org/haskellwiki/HaWiki_migration

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


Re: [Haskell-cafe] Serial Communications in Haskell

2007-09-03 Thread Donald Bruce Stewart
mmitar:
 Hi!
 
  Of course, I don't know how to call Windows API functions from Haskell,
  and I have no idea how to hook things to the IO library so that I can
  use a Handle for a serial port.  I'm looking for some advice on how to
  proceed.
 
 You can check how I did this in my Lego Mindstorms NXT interface,
 pre-beta version:
 
 http://www.forzanka.si/files/NXT.tgz
 
 It is for UNIX (POSIX?) systems but I had similar problems so I had to
 use FFI (foreign function interface) to setup a link. You will
 probably just have to replace that with Windows API calls. I hope.
 

That's really cool! I hope you can upload this to hackage soon.

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


[Haskell-cafe] ANNOUNCE: xmonad 0.3

2007-09-04 Thread Donald Bruce Stewart

The xmonad dev team is pleased to announce the 0.3 release of xmonad. 

xmonad: a tiling window manager
   http://xmonad.org

About:

xmonad is a tiling window manager for X. Windows are arranged
automatically to tile the screen without gaps or overlap, maximising
screen use. All features of the window manager are accessible from the
keyboard: a mouse is strictly optional. xmonad is written and extensible
in Haskell. Custom layout algorithms, and other extensions, may be
written by the user in config files. Layouts are applied dynamically,
and different layouts may be used on each workspace. Xinerama is fully
supported, allowing windows to be tiled on several screens.

Features:

* Very stable, fast, small and simple.
* Automatic window tiling and management
* First class keyboard support: a mouse is unnecessary
* Full support for tiling windows on multi-head displays
* Full support for floating windows
* XRandR support to rotate, add or remove monitors
* Per-workspace layout algorithms
* Per-screens custom status bars
* Easy, powerful customisation and reconfiguration
* Large extension library
* Extensive documentation and support for hacking

Since xmonad 0.2, the following notable features and bug fixes have appeared:

New features:

  * floating layer support: transients windows are not tiled by default,
and windows may be dragged to and from a traditional floating layer
(which allows mouse-resizing, and overlapping windows).

  * improved Xinerama support: workspace switching reuses multiple
displays more effectively.

  * huge new extension library. Over 50 extensions to xmonad have been
contributed by users, and are available all in a standard library,
with documentation.

More information, screenshots, documentation and community resources are
available from:

http://xmonad.org

Xmonad is available from hackage, and via darcs. Happy hacking!

The Xmonad Team:

Spencer Janssen
Don Stewart
Jason Creighton

Xmonad has also received contributions from at least:

Alec Berryman Andrea Rossato Chris Mears
Daniel Wagner David Glasser David Lazar
David Roundy Hans Philipp Annen Joachim Fasting
Joe Thornber Kai Grossjohann Karsten Schoelzel
Michael Sloan Miikka Koskinen Neil Mitchell
Nelson Elhage Nick Burlett Peter De Wachter
Robert Marlow Sam Hughes Shachaf Ben-Kiki
Shae Erisson Simon Peyton Jones Stefan O'Rear

as well as many others on the IRC channel and mailing list. Thanks to everyone!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient way to edit a file

2006-06-01 Thread Donald Bruce Stewart
briqueabraque:
   Hi,
 
   I need to edit big text files (5 to 500 Mb). But I just need to 
 change one or two small lines, and save it. What is the best way to do 
 that in Haskell, without creating copies of the whole files?
 

I'd think maybe a lazy bytestring would be ok.

Something like:
  import Data.ByteString.Lazy.Char8
  B.putStr . B.unlines . B.map edit . B.lines = B.getContents

in the darcs version of Data.ByteString, here, 
http://www.cse.unsw.edu.au/~dons/fps.html
Let me know how you go, it would make a good benchmark.

-- Don

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


Re: [Haskell-cafe] Efficient way to edit a file

2006-06-01 Thread Donald Bruce Stewart
dons:
 briqueabraque:
Hi,
  
I need to edit big text files (5 to 500 Mb). But I just need to 
  change one or two small lines, and save it. What is the best way to do 
  that in Haskell, without creating copies of the whole files?
  
 
 I'd think maybe a lazy bytestring would be ok.
 
 Something like:
   import Data.ByteString.Lazy.Char8
   B.putStr . B.unlines . B.map edit . B.lines = B.getContents
 
 in the darcs version of Data.ByteString, here, 
 http://www.cse.unsw.edu.au/~dons/fps.html
 Let me know how you go, it would make a good benchmark.

Oh, of course, if you actually don't want to copy the file, you'll need
to strictly read the input file, in order to write over it safely.

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


Re: [Haskell-cafe] Efficient way to edit a file

2006-06-01 Thread Donald Bruce Stewart
dons:
 briqueabraque:
Hi,
  
I need to edit big text files (5 to 500 Mb). But I just need to 
  change one or two small lines, and save it. What is the best way to do 
  that in Haskell, without creating copies of the whole files?
  

Thinking further, since you want to avoid copying on the disk, you need
to be able to keep the edited version in memory. So the strict
bytestring would be best, for example:

import System.Environment
import qualified Data.ByteString.Char8 as B

main = do
[f] - getArgs
B.writeFile f . B.unlines . map edit . B.lines = B.readFile f

where
edit :: B.ByteString - B.ByteString
edit s | (B.pack Instances) `B.isPrefixOf` s = B.pack EDIT
   | otherwise = s

Edits a 100M file in

$ ghc -O -funbox-strict-fields A.hs -package fps 
$ time ./a.out /home/dons/data/100M
./a.out /home/dons/data/100M  1.54s user 0.76s system 13% cpu 17.371 total

You could probably tune this further.

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


Re: [Haskell-cafe] Newbie request

2006-06-09 Thread Donald Bruce Stewart
gphilip.newsgroups:
 I am trying to learn Haskell. As an exercise, I wrote a
 function to create a binary tree in level-order. I am attaching
 the code. I am sure there are a number of places where
 the code could be improved. Could you please point these out?

There's a highly efficient example here, not exactly a beginner's
example, but perhaps useful:


http://shootout.alioth.debian.org/gp4/benchmark.php?test=binarytreeslang=ghcid=2
 
 --
 BinTree.lhs : Implementation of a binary tree. createTree 
 accepts a sequence and builds a binary tree in level-order.
 --
 
 module BinTree where
 
 --
 A binary tree either 
 1. is empty, or
 2. consists of three distinct binary trees : a root node, a left 
 subtree, and a right subtree.
 --
 
 data Tree a = Empty | Tree {rootNode::a, left::(Tree a), 
   right::(Tree a)} deriving (Eq, Show)

Too many parens, perhaps? Those (Tree a)'s look unnecessary.

 --
 Count the number of nodes in a binary tree, using the simple 
 recursive definition of the count.
 --
 
 countNodes :: Tree a - Integer
 countNodes Empty = 0
 countNodes (Tree rootNode left right) = 1 + countNodes left 
   + countNodes right
 
 --
 Insert a single element into the proper place in the tree, as 
 per level-order.
 --
 
 insert :: Eq a = Tree a - a - Tree a
 insert tree x = if tree == Empty
then Tree x Empty Empty
else if (left tree) == Empty
then Tree (rootNode tree) (Tree x Empty 
  Empty) (right tree)
else if (right tree) == Empty 
then Tree (rootNode tree) (left tree) 
  (Tree x Empty Empty) 
else if countNodes (left tree) = 
  countNodes (right tree)
then Tree (rootNode tree) 
  (insert (left tree) x) (right tree)
else Tree (rootNode tree) 
  (left tree) (insert (right tree) x)

Logic looks too convoluted. Perhaps use guards and pattern matching:

insert Empty x   = Tree x Empty Empty
insert (Tree root Empty r) x = Tree root (Tree x Empty Empty) r
insert (Tree root l Empty) x = Tree root l (Tree x Empty Empty)
insert (Tree root l r) x
| countNodes l = countNodes r = Tree root (insert l x) r   
| otherwise= Tree root l (insert r x)

Seems inefficent to recalculate countNodes each time though.
  
 --
 Use insert to create a tree from a sequence.
 --
 
 createTree :: Eq a = [a] - Tree a
 createTree [] = Empty
 createTree (x:xs) = foldl insert (insert Empty x) xs

Pretty good.

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


Re: [Haskell-cafe] HCAR

2006-06-12 Thread Donald Bruce Stewart
stefan:
 Tashdid,
 
 does anyone know what happened to HCAR?
 or HWN?
 
 I guess the May ;) 2006 edition of HCAR will appear soon. I'm not  
 sure about what happened to HWN the last couple of weeks, though, but  
 I think that Donald is just quite busy these days.

Yep, that's the case. Expect an issue tomorrow though.

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


Re: [Haskell-cafe] what do you think of haskell ? (yes, it's a bit general ...:)

2006-06-16 Thread Donald Bruce Stewart
noteed:
 
 i want to process 4k pictures (and not just one pixel fater one)...
 for example.  if there is a better solution than array, i'm eager to
 know it!

Try Data.ByteString. 4G can be feasible :) 

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


Re: [Haskell-cafe] Binary IO

2006-06-24 Thread Donald Bruce Stewart
m4d.skills:
 
Greetings,
I am considering writing -in Haskell of course - a small
program to translate binary files to human readable text.
The trouble is that I can find no easily digestible tutorial
style info on how to do binary IO in Haskell.
I have read about some of the libraries that people have
created to do binary IO, but the documentation wasn't
sufficient to get me started (perhaps because I'm a bit
dense, and also relatively new to Haskell).
What I would like is to see a short example showing some
code that reads from a binary file.  I would also
like to know what the most widely used library for doing
binary IO in Haskell is.
I would greatly appreciate it if someone could post a small
example or two illustrating how to do
binary IO in Haskell using the most widely used binary IO
lib (if there is such a thing).  Failing that, I would
appreciate a link to some Haskell code that does binary IO
that I could study.
Lastly, if there is a good tutorial on doing binary IO in
Haskell then I would appreciate a link to that as well.
Thanks in advance,
Jeff Lasslett

Here's a howto:
http://www.haskell.org/hawiki/BinaryIo

Look for the instance Binary  code. That's where you set up your binary
parsers for each Haskell type. lso, these day,s you can do a fair bit of
binary hacking with Data.ByteString, without the Binary class layer over
the top.  Hope that helps.

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


Re: [Haskell-cafe] A question about stack overflow

2006-06-27 Thread Donald Bruce Stewart
hankgong:
 
Hi, all
 
I'm just a newbie for Haskell and functional programming
world. The idea I currently read is quite different and
interesting.
 
I have one general question about the recursively looping
style. For example:
 
myMax [ ] = error empty list
 
myMax [x] = x
 
myMax [x:xs] = if x= (myMax xs) then x else (myMax xs)
 
 
I just list out this kind of very simple program. However,
if the list size if a big number such as 1000, the
Does it mean that the functional programming is lacking of
scalability? I do know that we can manually change the stack
size for it. But that's not a good solution according to my
opinion.
 

No, your code is just really inefficient (think about how many times its
traversing the list). Try rewriting it as a simple accumulating pass over the
list, carrying the largest element you've seen so far.

mymax [] = undefined
mymax (x:xs) = f x xs
where
  f x [] = x
  f x (y:ys) | y  x = f y ys
 | otherwise = f x ys

However, 'f' is just a foldl inlined:

import Data.List
mymax [] = undefined
mymax (x:xs) = foldl' (\a b - if b  a then b else a) x xs

And the lambda is just 'max':

import Data.List
mymax [] = undefined
mymax (x:xs) = foldl' max x xs

Now, we already check for the empty list, so avoid checking again:

import Data.List
mymax [] = undefined
mymax xs = foldl1' max xs

And that'll do.

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


Re: [Haskell-cafe] New Benchmark Under Review: Magic Squares

2006-07-03 Thread Donald Bruce Stewart
Perhaps you could post a new entry page on our shootout wiki?

http://www.haskell.org/hawiki/ShootoutEntry

This makes it easier for people to keep contributing.

Cheers,
  Don

daniel.is.fischer:
 Am Sonntag, 2. Juli 2006 01:58 schrieb Brent Fulgham:
  We recently began considering another benchmark for the shootout,
  namely a Magic Square via best-first search.  This is fairly
  inefficient, and we may need to shift to another approach due to the
  extremely large times required to find a solution for larger squares.
 
 A slightly less naive approach to determining the possible moves dramatically 
 reduces the effort, while Josh Goldfoot's code did not finish within 4 1/2 
 hours on my machine, a simple modification (see below) reduced runtime for 
 N = 5 to 4.3 s, for N = 6 to 86.5 s. 
 Unfortunately, the squares are now delivered in a different order, so my 
 programme would probably be rejected :-(
 
 
  I thought the Haskell community might be interested in the
  performance we have measured so far (see http://
  shootout.alioth.debian.org/sandbox/fulldata.php?
  test=magicsquaresp1=java-0p2=javaclient-0p3=ghc-0p4=psyco-0
 
  Interestingly, Java actually beats the tar out of GHC and Python for
  N=5x5 (and I assume higher, though this already takes on the order of
  2 hours to solve on the benchmark machine).  Memory use in GHC stays
  nice and low, but the time to find the result rapidly grows.
 
  I was hoping for an order of magnitude increase with each increase in
  N, but discovered that it is more like an exponential...
 
  Thanks,
 
  -Brent
 
 Modified code, still best-first search:
 
 import Data.Array.Unboxed
 import Data.List
 import System.Environment (getArgs)
 
 main :: IO ()
 main = getArgs = return . read . head = msquare
 
 msquare :: Int - IO ()
 msquare n = let mn = (n*(n*n+1)) `quot` 2
 grd = listArray ((1,1),(n,n)) (repeat 0)
 unus = [1 .. n*n]
 ff  = findFewestMoves n mn grd unus
 ini = Square grd unus ff (2*n*n)
 allSquares = bestFirst (successorNodes n mn) [ini]
 in  putStrLn $ showGrid n . grid $ head allSquares
 
 data Square = Square { grid :: UArray (Int,Int) Int
  , unused :: [Int]
  , ffm :: ([Int], Int, Int, Int)
  , priority :: !Int
  } deriving Eq
 
 instance Ord Square where
 compare (Square g1 _ _ p1) (Square g2 _ _ p2)
 = case compare p1 p2 of
 EQ - compare g1 g2
 ot - ot
 
 showMat :: [[Int]] - ShowS
 showMat lns = foldr1 ((.) . (. showChar '\n')) $ showLns
   where
 showLns = map (foldr1 ((.) . (. showChar ' ')) . map shows) 
 lns
 
 showGrid :: Int - UArray (Int,Int) Int - String
 showGrid n g = showMat [[g ! (r,c) | c - [1 .. n]] | r - [1 .. n]] 
 
 bestFirst :: (Square - [Square]) - [Square] - [Square]
 bestFirst _ [] = []
 bestFirst successors (front:queue)
 | priority front == 0 = front : bestFirst successors queue
 | otherwise = bestFirst successors $ foldr insert queue (successors front)
 
 successorNodes n mn sq
 = map (place sq n mn (r,c)) possibilities
   where
 (possibilities,_,r,c) = ffm sq
 
 place :: Square - Int - Int - (Int,Int) - Int - Square
 place (Square grd unus _ _) n mn (r,c) k
 = Square grd' uns moveChoices p
   where
 grd' = grd//[((r,c),k)]
 moveChoices@(_,len,_,_) = findFewestMoves n mn grd' uns
 uns = delete k unus
 p = length uns + len
 
 findFewestMoves n mn grid unus
 | null unus = ([],0,0,0)
 | otherwise = (movelist, length movelist, mr, mc)
   where
 openSquares = [(r,c) | r - [1 .. n], c - [1 .. n], grid ! (r,c) == 
 0]
 pm = possibleMoves n mn grid unus
 openMap = map (\(x,y) - (pm x y,x,y)) openSquares
 mycompare (a,_,_) (b,_,_) = compare (length a) (length b)
 (movelist,mr,mc) = minimumBy mycompare openMap
 
 possibleMoves n mn grid unus r c
 | grid ! (r,c) /= 0 = []
 | otherwise = intersect [mi .. ma] unus -- this is the difference that
   -- does it: better bounds
   where
 cellGroups
 | r == c  r + c == n + 1 = [d1, d2, theRow, theCol]
 | r == c = [d1, theRow, theCol]
 | r + c == n + 1 = [d2, theRow, theCol]
 | otherwise = [theRow, theCol]
 d1 = diag1 grid n
 d2 = diag2 grid n
 theRow = gridRow grid n r
 theCol = gridCol grid n c
 lows = scanl (+) 0 unus
 higs = scanl (+) 0 $ reverse unus
 rge cg = let k = count0s cg - 1
  lft = mn - sum cg
  in (lft - (higs!!k),lft - (lows!!k))
 (mi,ma) = foldr1 mima $ map rge cellGroups
 mima (a,b) (c,d) = (max a c, min b d)
 
 gridRow grid n r = [grid ! (r,i) | i - [1 .. n]]
 gridCol grid n c = [grid ! (i,c) | i - [1 .. n]]
 diag1 grid n = [grid ! (i,i) | 

Re: [Haskell-cafe] Clever generic ByteString hack?

2006-07-05 Thread Donald Bruce Stewart
duncan.coutts:
 On Wed, 2006-07-05 at 05:58 -0500, John Goerzen wrote: 
  Hi,
  
  In MissingH, I have a bunch of little functions that operate on lists.
  Some, like uniq (which eliminates duplicate elements in a list), operate
  on (Eq a = [a]) lists.  Others, like strip (which eliminates whitespace
  at the start and end), operate on Strings only.
  
  Most functions of both types would be useful on ByteStrings and lazy
  ByteStrings.  Most of these functions are written in terms of Data.List
  functions or list primitives that have equivolents in Data.ByteString.
  
  So, my question is: is there a clever hack available to me so that I
  could have 1 version of each function, and have it work on all three
  different types of input?  I'd rather avoid having 3 versions, that are
  exactly the same except for imports.
 
 People sometimes talk about doing a type class to cover string like
 modules.
 
 What functions are you thinking of btw? We may want to include them in
 the ByteString modules anyway (possibly directly rather than in terms of
 other functions, to take advantage of tricks with the representation).

Spencer Janssen is actually working on such a class (String) to deal
with this, initially to support [a] and Word8 and Unicode bytestrings, 
as part of his Summer of Code project.

Note also that we have the Foldable and Monoid classes, which support parts of
a String interface.

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


Re: [Haskell-cafe] Re[2]: Haskell performance in heavy numerical computations

2006-07-10 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello Simon,
 
 Monday, July 10, 2006, 1:12:13 PM, you wrote:
 
  numerical speed is poor in ghc 6.4, according to my tests. it's 10-20
  times worse than of gcc. afair, the mandelbrot benchmark of Great
  Language Shootout proves this - despite all optimization attempts,
  GHC entry is still 5-10 times slower than gcc/ocaml/clean ones
 
  We average 1.3x slower than C in the shootout. Thanks to Don Stewart for
  the following stats...
 
 as i once wrote, most of shootout benchmarks depends on the libs. for
 example, multi-threading benchmark is much faster on GHC than on GCC
 because former has user-level threads support pre-included and for
 later the external libs should be used (testing policy prohibits using
 of additional libs)
 
  The numerical floating-point-intensive benchmarks:
 
   mandelbrot  2.7x C(Clean 1.7x, OCaml 2.4x, C++ 2.6x)
   n-body  2.1x C(Clean 0.9x, OCaml 1.3x, C++ 1.4x)
 
 that is the benchmarks that i had in mind
 
  http://shootout.alioth.debian.org/gp4/benchmark.php?test=mandelbrotlang=all
 
 the same benchmark with N=600 and Sempron processor:
 
 http://shootout.alioth.debian.org/debian/benchmark.php?test=mandelbrotlang=all
 
 here GHC is 10x slower than GCC and more than 5 times compared to
 Clean and Ocaml. i think that this is the real computing speed
 difference while with N=2000 C/Ocaml/Clean programs was really limited
 by memory speed.

Ah! In this case, on the debian, the benchmark has been compiled
_without_ -fexcess-precision, that's what's causing the big slow down.
We had to turn it on, on the gp4, but it seems the flag wasn't
propagated to the debian/sempron builds for some reason.

Looks like the ghc/mandelbrot benchmarks just needs to be rerun with
-fexcess-precision in this case.

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


Re: [Haskell-cafe] Defining show for a function type.

2006-07-10 Thread Donald Bruce Stewart
johan.gronqvist:
 I am a haskell-beginner and I wish to write a Forth-like interpreter. 
 (Only for practice, no usefulness.)
 
 I would like use a list (as stack) that can contain several kinds of values.
 
 data Element = Int Int | Float Float | Func : Machine - Machine  | ...
 
 Now I would like to have this type be an instance of the class Show, so 
 that I can see what the stack contains in ghci.

Here's an interesting, I think, show for functions that we use in
lambdabot's Haskell interpreter environment:

module ShowQ where

import Language.Haskell.TH
import System.IO.Unsafe
import Data.Dynamic

instance (Typeable a, Typeable b) = Show (a - b) where
show e = '' : (show . typeOf) e ++ 

instance Ppr a = Show (Q a) where
show e = unsafePerformIO $ runQ e = return . pprint

which generates results like:

 dons::  toUpper
 lambdabot::  Char - Char

 dons::  \x - x+1::Int
 lambdabot::  Int - Int

 dons::  map
 lambdabot::  Add a type signature

Note that also the standard libraries come with Text.Show.Functions

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


Re: [Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-12 Thread Donald Bruce Stewart
simonmarhaskell:
 I guess the problem with the splitWith thing is that it's a slippery
 path that leads right up to full-on parsers.
 
 Exactly, and this is why we didn't reach a concensus last time.
 
 Would someone like to make a concrete proposal (with code!) for 2-3 
 functions we could reasonably add to Data.List?

No parsers!

I vote for this, currently implemented in Data.ByteString:

-- | split on characters
split:: Char - String - [String]

-- | split on predicate *
splitBy  :: (Char - Bool) - String - [String]

and
-- | split on a string
tokens   :: String - String - [String]

Question over whether it should be:
splitBy (=='a') aabbaca == [,,bb,c,]
  or
splitBy (=='a') aabbaca == [bb,c]

I argue the second form is what people usually want.

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


Re: [Haskell-cafe] Re: Type-Level Naturals Like Prolog?

2006-07-17 Thread Donald Bruce Stewart
jawarren:
 Thank you to everyone for the responses. I guess what I should have
 clarified is that I know how Peano numbers are *normally* encoded in
 the type language (I am very familiar with the HList library), but I
 would like to know why the type language appears to require data
 structures to do so while [Idealised] Prolog has none.
 
 Niklas Broberg helpfully corrected my Prolog:
 
 That is not a valid encoding of peano numbers in prolog, so I think
 that's where your problems stem from. :-)
 
 % defining natural numbers
 natural(zero).
 natural(s(X)) :- natural(X).
 
 % translate to integers
 toInt(zero, 0).
 toInt(s(X), N) :- toInt(X, Y), N is Y + 1.
 
 Thank you. I can now more precisely state that what I'm trying to
 figure out is: what is 's', a predicate or a data structure? If it's a
 predicate, where are its instances? If not, what is the difference
 between the type language and Prolog such that the type language
 requires data structures?

It shouldn't actually require new data structures, just new types (with
no inhabiting values).

such as,
data Zero
data Succ a

So there are no values of this type (other than bottom).
That is, you can just see 'data' here as a way of producing new types to
play with in the type checker.

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


[Haskell-cafe] irc channel stats

2006-07-20 Thread Donald Bruce Stewart
While we're in a period of reflection, pondering the history of haskell,
I've prepared some graphs of activity on the IRC channel.

Summary: its growing much as the mailing lists are, with more than 5000
users over the past 5 years.

Full details here,
http://www.cse.unsw.edu.au/~dons/irc/

Another interesting note is that lambdabot's get more and more verbose
over time, as it provides further features. It's turning into an ide of
sorts.

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


Re: [Haskell-cafe] Why Haskell?

2006-07-24 Thread Donald Bruce Stewart
marco-oweber:
  2) Recompiling binaries (necessary in order to link in foreign object 
  code into GHCi) is slow using GHC.  Moreover I have to restart GHCi if I 
  want to reload a changed DLL (unless there is a way to unload a DLL in 
  GHCi).  It also requires jumping around between several console windows 
  to get the job done.  (I'm not using an IDE does one exist?)
 There are several. (I know of one using visual studio and eclipsefp)..
 It should|nt be a problem to find them.. But I still prefer vim :)
 
 Concerning switching between several console windows... Perhaps try
 something like mrxvt which has several tabs to run more than one shell.
 You can then use key combinations to switch.. (I haven't used mrxvt on
 cygwin yet but I've read that it runs there)
 
 Marc

Or use a more efficient window manager, i.e. ion or wmii let you
navigate entirely from the keyboard, as if you were inside an editor.

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


[Haskell-cafe] Universal machines in Haskell

2006-07-26 Thread Donald Bruce Stewart
Now the ICFP contest is now over, several of the entrants have been
interested in seeing if we can't write a decent universal machine (the
'hardware' of this year's contest), in Haskell.

This is an interesting problem for Haskell, since the spec encourages
the use of mutable variables and mutable arrays, as well as a bit of IO.
Getting C-like performance from Haskell, for this problem, is a bit of a
challenge, and highlights some corners in our libraries.

So, we're collecting any UMs in Haskell, with the goal to breed some
good solutions, and learn a bit about writing low level machines in
Haskell.

The website is here,
http://www.cse.unsw.edu.au/~dons/um.html

If you wrote a Haskell UM, or a faster C UM, free to submit it! Just
mail me a darcs repo url, a source module url, or the source itself.

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


Re: [Haskell-cafe] Monad Imparative Usage Example

2006-08-02 Thread Donald Bruce Stewart
kaveh.shahbazian:
 Haskell is the most powerfull and interesting thing I'v ever
 encountered in IT world. But with an imparative background and lack of
 understanding (because of any thing include that maybe I am not that
 smart) has brought me problems. I know this is an old issue. But
 please help it.
 Question : Could anyone show me a sample of using a monad as a
 statefull variable?
 For example see this code in C# :
 //
 public class Test
 {
int var;
static void Fun1() { var = 0; Console.Write(var); }
static void Fun2() { var = var + 4; Console.Write(var); }
static void Main() { Fun1(); Fun2(); var = 10; Console.Write(var
 =  + var.ToString()); }
 }
 //
 I want to see this code in haskell.

Ok, here you go. A state monad on top of IO, storing just your variable. Its
even 'initialised' to undefined at the start :)

import Control.Monad.State

main = execStateT (do f1; f2; put 10) undefined

f1 = do 
let v = 0
put v
liftIO $ print v

f2 = do
v - get
let v' = v + 4
put v'
liftIO $ print v'

Running:
$ runhaskell A.hs
0
4
10

Of course, there are many other ways to do this, too.

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


Re: [Haskell-cafe] Monad Imparative Usage Example

2006-08-02 Thread Donald Bruce Stewart
kaveh.shahbazian:
 Monad Imparative Usage Example
 
 Thanks for your replies. I have not haskell on this computer and I
 will try this solutions tonight.
 I must notice that IO computations is not the point here. My target is
 to have this code for mutable variable 'var'.

Still not entirely clear what your goal in the translation is.
The most Haskell way would be to emulate a mutable variable with a state
monad, but you seem to want an actual named mutable variable?

So here's an example, like Seb's, where we create a mutable variable (in
the IO monad) and mutate it all over the place. This uses similar
scoping to your original code. For fun we use MVars instead of IORefs.

import Control.Concurrent.MVar
  
main = do
var - newEmptyMVar
let write = withMVar var print

f1 = do putMVar var 0
write

f2 = do modifyMVar_ var (return.(+4))
write
f1
f2
swapMVar var 10
write

Produces:
$ runhaskell A.hs
0
4
10

Of course, if you're learning Haskell, you should probably try to
/avoid/ mutable variables for a while.

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


Re: [Haskell-cafe] fast image processing in haskell?

2006-08-05 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello Chris,
 
 Saturday, August 5, 2006, 3:47:19 AM, you wrote:
 
  in Haskell before blitting the data (whilst also retaining some
  semblance of functional programming...)
 
 the best way to optimize Haskell program (with current technologies)
 is to rewrite it in strict  imperative manner:

Strict, very often, since we get unboxed types out of ghc. Imperative,
not always (and will be less so with Data.ByteString -- since we don't
need to drop into IO to get peek/poke).

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


Re: [Haskell-cafe] A problem with Show

2006-08-06 Thread Donald Bruce Stewart
zdenes:
 Hello,
 
 I made a simple datatype called Pair and I'd like to make it an instance of 
 Show class. But when I try to do that I run into troubles:
 
 
 data Pair a b = Pair a b
 instance Show a b = Show (Pair a b) where show (Pair a b) = show a ++ _ ++ 
 show b
 
 
 In Hugs I get this error: Haskell does not support multiple parameter 
 classes When I run it in ghci I get a kind error Show is applied to too 
 many type arguments in the instance declaration for Show (Pair a b)
 
 Am I jsut using wrong syntax or is it not possible to do?
 

Missing some parens and a comma:

 data Pair a b = Pair a b

 instance (Show a, Show b) = Show (Pair a b) where
 show (Pair a b) = show a ++ _ ++ show b

$ hugs A.hs
Main show (Pair 'x' ())
'x'_()

Alternately:

 data Pair a b = Pair a b
   deriving Show

-- Don

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


Re: [Haskell-cafe] Need a good book on Haskell

2006-08-07 Thread Donald Bruce Stewart
Also, we have a large library of research papers here:
http://www.haskell.org/haskellwiki/Research_papers

mvanier:
 A good follow-up is The Haskell School of Expression by Paul Hudak. 
 Eventually, though, you're going to have to start reading research papers, 
 which is where most of the cutting-edge stuff is.  Phil Wadler's papers 
 (available from his web site, just google it) are a good place to start, as 
 are Simon Peyton-Jones' papers.
 
 Mike
 
 Johan Tibell wrote:
 I've read Haskell: The Craft of Functional Programming on a course on
 functional programming at Chalmers (I also took the advanced course)
 and now I'm looking for some more reading material. Are there any
 other good Haskell books? Is there a Pick Axe, Camel or Dragon Book
 for Haskell?
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How can we detect and fix memory leak due to lazyness?

2006-08-07 Thread Donald Bruce Stewart
kyagrd:
 On 8/7/06, Spencer Janssen [EMAIL PROTECTED] wrote:
 
 Forcing evaluation using (==) is a bit of a hack.  Luckily, we have a
 better function to force evaluation: seq (which has type a - b - b).
  seq x y evaluates x to weak head normal form before returning
 y.
 
 Let's try another feature of Haskell to force evaluation: strict data
 fields.  A ! in front of a field in a data declaration signifies
 strictness.  In the example below, whenever we construct a value with
 TT, the second argument is evaluated.
 
 \begin{code}
 data TT a b = TT a !b
 \end{code}
 
 Perhaps your instances will work correctly with this data declaration?
 
 Surely I've tried that.
 
 Unfortunately seq and the strict data declaration is not helpful in general.
 They are only helpful on base values such as Int or Bool.
 What they do is just making sure that it is not a thunk.
 That is if it was a list it would just evaluate to see the cons cell
 but no further.
 
 Someone wrote a deepSeq module for forcing deep evaluation, which is
 like doing self equality strictness hack like x==x.
 However, we should be able to locate what is the source of the memory
 leak to apply such strictness tricks.


The key is to profile. Compile the code, with optimisations on, with
-prof -auto-all, then run the resulting program with +RTS -p -RTS.
This will identify costly and timely functions.

You can then refine the search further with {-# SCC line1 #-} pragmas,
next to expressoins you want to check the cost of.

-- Don

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


Re: [Haskell-cafe] Re:Re: Why Haskell

2006-08-07 Thread Donald Bruce Stewart
hthiel.char:
 And just from a PR point of view, Haskell does project a cutting edge
 image. Anyway...

Maybe this is our brand!

Be on the cutting edge of programming language development -- use Haskell

Bored of your language? Try something new. Try Haskell!

Same old syntax? Same old bugs? Think different. Think Haskell

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


Re: [Haskell-cafe] beginner's haskell question

2006-08-08 Thread Donald Bruce Stewart
jens-theisen-tmp01:
 Hello,
 
 as a haskell newbie I'm wondering about the following question.
 
 Are there options to popular haskell implementations or other means 
 (haskell lint?) to check for incomplete patterns at compile time for 
 some? I can't see a reason why this shouldn't be possible or even a 
 relatively simple thing to implement.
 
 Cheers,
 
 Jens

You might just want to always use:
-Wall -Werror

to get the full range of extended warnings and checks.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Not Haskell?

2006-08-09 Thread Donald Bruce Stewart
robdockins:
 On Aug 8, 2006, at 5:36 PM, Albert Lai wrote:
 
 Brian Hulley [EMAIL PROTECTED] writes:
 
 Also, the bottom line imho is that Haskell is a difficult language to
 understand, and this is compounded by the apparent cleverness of
 unreadable code like:
 
  c = (.) . (.)
 
 when a normal person would just write:
 
  c f g a b = f (g a b)
 
 All mainstream languages are also difficult to understand, with
 similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
 mainstream languages in question:
 
 [snip]
 
 2. What language allows you to test primality in constant runtime?
That is, move all the work to compile time, using its polymorphism.
 
 GHC-Haskell (with enough extensions enabled)?  We're most of the way  
 there already with type arithmetic.  I bet putting together a nieve  
 primality test would be pretty doable.  In fact, I suspect that GHC's  
 type-checker is turing-complete with MPTCs, fundeps, and undecidable  
 instances.  I've been contemplating the possibility of embedding the  
 lambda calculus for some time (anybody done this already?)

http://haskell.org/haskellwiki/Type_arithmetic#A_Really_Advanced_Example_:_Type-Level_Lambda_Calculus

also

http://haskell.org/haskellwiki/Type_arithmetic#An_Advanced_Example_:_Type-Level_Quicksort

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


Re: [Haskell-cafe] Flags

2006-08-10 Thread Donald Bruce Stewart
Maduser:
 
 I have started to program in Haskell.  Now I want programm something like
 flags.  It's a set of flags. It sould be possible to convert the Flag as
 Int/String (the bit combination). I have written this:
 
 import Data.Set as Set
 
 type Flags = Set Flag
 data Flag = Flag1 | Flag2 | Flag3
   deriving(Eq, Ord, Enum, Show)
   
 flagToInt :: Flags - Int
 flagToInt flags = flag1 + flag2 + flag3
   where
   flag1 = if member Flag1 flags then 1 else 0
   flag2 = if member Flag2 flags then 2 else 0
   flag3 = if member Flag3 flags then 4 else 0
 
 but this seems to me to be inelegant. Can somebody help me making it better,
 please.

Something like:

type Flags = [Flag]

data Flag = Flag1 | Flag2 | Flag3
deriving (Eq, Ord, Enum, Show)

flagToInt :: Flags - Int
flagToInt = sum . map ((2 ^) . fromEnum)

Perhaps?

-- Don

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


Re: [Haskell-cafe] A restricted subset of CPP included in a revision of Haskell 98

2006-08-17 Thread Donald Bruce Stewart
brianlsmith:
 
Hi,
I find it strange that right now almost every Haskell
program directly or indirectly (through FPTOOLS) depends on
CPP, yet there is no effort to replace CPP with something
better or standardize its usage in Haskell. According to the

Note also cpphs,
http://www.cs.york.ac.uk/fp/cpphs/

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


Re: [Haskell-cafe] Description of Haskell extensions used by FPTOOLS

2006-08-17 Thread Donald Bruce Stewart
brianlsmith:
 
Is there any design document for the FPTOOLS libraries or
some description of language features that are (allowed to
be) used in them?

There's a list of extensions used at the bottom of this page:
http://hackage.haskell.org/trac/haskell-prime/wiki/HaskellExtensions

I am going to be taking some significant time off from my
normal jobs in the upcoming months. During part of that
time, I would like to do some work to improve the Haskell
toolchain. This involves creating or improving tools that
parse and analyze Haskell code. My goal is to have these
tools support enough of Haskell to be able to handle at
least the most important libraries used by Haskell
programmers. In particular, this includes all or most of the
libraries in FPTOOLS. Plus, I want these tools to operate on
Darcs as it is an obvious poster-child for Haskell. Thus, I
need to support Haskell 98 plus all the extensions being
used in Darcs and FPTOOLS as of approx. March, 2007 (as I
intened to start working again at that time).

Cool!

It would be very nice if there was some document that
described Haskell 98 plus all the extensions being used in
Darcs and FPTOOLS as of March, 2007. Besides being useful
to me, it would be a useful guide for potential contributors
to FPTOOLS.

Darcs may also use GADTs then (not in the standard libs). Better check
with the darcs src.

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


Re: [Haskell-cafe] Re: Useful: putCharLn {inspire by the Int-[Char] thread

2006-08-21 Thread Donald Bruce Stewart
yumagene:
 On 8/19/06, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote:
 
 Or you could use:
putStrLn [head This and that]
 
 
 Gotta say I really like this ... running the head function inside of the 
 list...
 Okay so I can really learn something here... what would that look like
 in raw monadic notation?
 using bind and such notation... =  etc..
 hey, mention was made of lists being monads.. so 

Perhaps:
putStrLn . return . head $ This and that

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


Re: Re[2]: class [] proposal Re: [Haskell-cafe] One thought: Num to 0as ? to list?

2006-08-23 Thread Donald Bruce Stewart
tomasz.zielonka:
 On Wed, Aug 23, 2006 at 01:28:57PM +0100, Malcolm Wallace wrote:
  The lengths people will go to in making things difficult for the reader,
  just to save a few characters is truly amazing.  Remember, the code will
  be read many more times than it is written.  IMHO, the various proposed
  sugar adds nothing helpful, and just muddies understanding.
 
 Seconded. If someone just wants to type less characters, the he/she
 can omit most of type signatures.
 
 I haven't used any IDE for Haskell (like VisualHaskell), but it would be
 nice if it could fill the missing type signatures automatically. In
 cases when monomorphism restriction kicks in, it could also present the
 type that would be inferred with MR turned off.

I use the following script from vim to infer top level type declarations
for me. I've found it particularly useful for understanding others' code:

#!/bin/sh
# input is a top level .hs decls

FILE=$*
DECL=`cat`
ID=`echo $DECL | sed 's/^\([^ ]*\).*/\1/'`
echo :t $ID | ghci -v0 -cpp -fglasgow-exts -w $FILE
echo $DECL

Saved to 'typeOf', you can bind it from vim with:
:map ty :.!typeOf %^M

in your .vimrc
So, from vim the following source:

f (x,y,z) a b = y + a + b

hit, 'ty' and its replaced with:

f :: forall b c a. (Num b) = (a, b, c) - b - b - b
f (x,y,z) a b = y + a + b

I imagine it would be possible to bind from emacs with little effort.

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


Re: [Haskell-cafe] question on traversing syntax tree

2006-08-24 Thread Donald Bruce Stewart
xiongyf04:
 I am writing a compiler using Haskell. After the compiler parses program, the 
 program is stored into an syntax tree stucture defined blew:
 
 ..
 data Exp 
   = Plus Exp Term 
   | Minus Exp Term 
   | Term Term
   deriving Show
 
 data Term 
   = Times Term Factor 
   | Div Term Factor 
   | Factor Factor
   deriving Show
 ..
 
 This is just part of the definition. The full tree contains much more 
 definition than this. Now I want to adjust the syntax-tree. However, I don't 
 need to adjust all the data types, but a small subset of the syntax tree. 
 e.g. I might adjust the Times data like the following, but not modify the 
 rest of the syntax tree:
 transformTerm (Times t f) = Times t (FactorInt 100)
 
 However, in order to apply the modification like this, I have to write a 
 series of function to traverse the tree until I get to the Term data type. 
 e.g. I have to define:
 transformExp (Plus e t) = Plus (transformExp e) (transformTerm t)
 transformExp (Minus e t) = Minus (transformExp e)(transformTerm t)
 transformTerm (Term t) = ...
 
 This is tedious and error-prone. I want to know if there some means in 
 Haskell to write a single generic function to traverse the syntax tree and 
 only stop on the Term data type. Can anyone tell me something about it? 
 Thanks a lot.
 

The Scrap Your Boilerplate series covers this, as does several other
works on generics in Haskell. Here's a good place to start:

http://www.cs.vu.nl/boilerplate/

also,
http://www.informatik.uni-bonn.de/~loeh/SYB0.html
http://www.informatik.uni-bonn.de/~loeh/SYB1.html

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


Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Donald Bruce Stewart
haskell:
 Hello,
 
 I was just doing Exercise 7.1 of Hal Daum?'s very good Yet Another 
 Haskell Tutorial. It consists of 5 short functions which are to be 
 converted into point-free style (if possible).
 
 It's insightful and after some thinking I've been able to come up with 
 solutions that make me understand things better.
 
 But I'm having problems with one of the functions:
 
 func3 f l = l ++ map f l
 
 Looks pretty clear and simple. However, I can't come up with a solution. 
 Is it even possible to remove one of the variables, f or l? If so, how?

The solution is to install lambdabot ;)

Point free refactoring:
lambdabot pl func3 f l = l ++ map f l
func3 = ap (++) . map

Find the type:
lambdabot type ap (++) . map
forall b. (b - b) - [b] - [b]

Get some free theorems:
lambdabot free f :: (b - b) - [b] - [b]
f . g = h . f = map f . f g = f h . map f

:)

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


Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Donald Bruce Stewart
haskell:
 Julien Oster wrote:
 
 But I'm having problems with one of the functions:
 
 func3 f l = l ++ map f l
 
 While we're at it: The best thing I could come up for
 
 func2 f g l = filter f (map g l)
 
 is
 
 func2p f g = (filter f) . (map g)
 
 Which isn't exactly point-_free_. Is it possible to reduce that further?

Similarly:

lambdabot pl func2 f g l = filter f (map g l)
func2 = (. map) . (.) . filter

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


Re: [Haskell-cafe] Why does this program eat RAM?

2006-09-04 Thread Donald Bruce Stewart
jeremy.shaw:
 At Tue, 5 Sep 2006 03:03:51 + (UTC),
 John Goerzen wrote:
  
  I have the below program, and I'm trying to run it on an input of about
  90MB.  It eats RAM like crazy, and I can't figure out why.
 
 I have not looked in detail at your code -- but it could simply be the
 fact that String requires gobs of memory to store a string. If you
 forced all 90MB into memory at once, I would expect it to take almost
 of gig of RAM. (Around a 10-11 fold increase in size).
 
 I suspect this line could be forcing the whole thing into memory:
 
  wordfreq = map (\x - (head x, length x)) . group . sort
 
 because sort can not return the first element until it has looked at
 all the elements in the list to determine which one should be first.
 
 If you fold a Data.Map or associative list over the word-list, then
 you could probably get the lazy behaviour you expect.

A quick hack up to use Data.ByteString uses a lot less ram, though
profiling still shows 95% of time spent in the building the Map.

import System.Environment
import Data.Char
import Data.List
import qualified Data.Map as Map

import qualified Data.ByteString.Char8 as B
import Data.ByteString (ByteString)

wordfreq inp = Map.toList $ foldl' k m inp
where
  m = Map.empty :: Map.Map ByteString Int
  k n w = Map.insertWith f w 1 n
  f _ x = let y = x + 1 in y `seq` y

freqsort (w1, c1) (w2, c2) | c1 == c2  = compare w1 w2
   | otherwise = compare c2 c1

showit (w, c) = B.join (B.singleton ' ') [B.pack(show c), w]

main :: IO ()
main = do args - getArgs
  B.interact $ B.unlines . map showit . take (read . head $ args)
 . sortBy freqsort . wordfreq . B.words

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


Re: [Haskell-cafe] User data type with operator contructors only

2006-09-05 Thread Donald Bruce Stewart
kolar:
 Hello all,
 
  my question probably comes from not reading manual properly. But, why 
 is it not possible to have something like:
 
 infixr 5 :
 
 data Stack a
  = a : (Stack a)
  | :||
 
 And if yes, how can I do that? I know that lists are a hack in Haskell, 

infixr 5 :

data Stack a = a : (Stack a) | (:||)

test = 7 : 8 : 2 : (:||)

Not ideal, though, I suppose.

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


Re: [Haskell-cafe] how do you debug programs?

2006-09-06 Thread Donald Bruce Stewart
mnislaih:
 Hi Tamas
 
 There are several ways to debug a Haskell program.
 
 The most advanced ones are based in offline analysis of traces, I
 think Hat [1] is the most up-to-date tool for this. There is a Windows
 port of Hat at [5].
 
 Another approach is to simply use Debug.Trace. A more powerful
 alternative for this approach is Hood [2]. Even if it hasn't been
 updated in some time, Hood works perfectly with the current ghc
 distribution. Even more, Hugs has it already integrated [3]. You can
 simply import Observe and use observations directly in your program.
 For instance:
 
 import Observe
 
 f' = observe f f
 f a b = 
 
 And then in hugs the expression:
 f' 1 2
 
 would output what you want.
 
 Finally, the GHCi debugger project [4] aims to bring dynamic
 breakpoints and intermediate values observation to GHCi in a near
 future. Right now the tool is only available from the site as a
 modified version of GHC, so unfortunately you will have to compile it
 yourself if you want to try it.

Pepe, would you like to put up a page on the haskell.org wiki about
debugging in Haskell? You could use the above mail as a start :)

-- Don



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


Re: [Haskell-cafe] does the compiler optimize repeated calls?

2006-09-06 Thread Donald Bruce Stewart
tpapp:
 Hi,
 
 I have a question about coding and compilers.  Suppose that a function
 is invoked with the same parameters inside another function declaration, eg
 
 -- this example does nothing particularly meaningless
 g a b c = let something1 = f a b
 something2 = externalsomething (f a b) 42
 something3 = externalsomething2 (137 * (f a b)) in
 ...
 
 Does it help (performancewise) to have
 
 g a b c = let resultoff = f a b
 something2 = externalsomething resultoff 42
 something3 = externalsomething2 (137 * resultoff) in
 ...
 
 or does the compiler perform this optimization?  More generally, if a
 function is invoked with the same parameters again (and it doesn't
 involve anything like monads), does does it makes sense
 (performancewise) to store the result somewhere?
 

on the wiki,
http://www.haskell.org/haskellwiki/Performance/GHC#Common_subexpressions

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


Re: [Haskell-cafe] Heap profiling

2006-09-11 Thread Donald Bruce Stewart
bitshifter:
 Does anyone know if there is a way around the 20 charachter identifier
 limitation when heap profiling?  I have a number of identifiers that
 indistinguishably break that limit.
 

Add custom {-# SCC mybetteridentifier #-} pragmas next to the places
with overly long names?

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


Re: [Haskell-cafe] Slow IO

2006-09-12 Thread Donald Bruce Stewart
daniel.is.fischer:
 Am Dienstag, 12. September 2006 22:26 schrieben Sie:
  Daniel Fischer wrote:
   The programme consumed more and more memory (according to top),
   kswapd started to have a higher CPU-percentage than my programme,
   programme died, system yelling 'Speicherzugriffsfehler', top displays
   'kswapddefunct'.
   I believe that means my programme demanded more memory than I have
   available (only 256MB RAM + 800MB swap). Is that a segfault or what is
   the correct term?
  
   That is probably due to (apart from the stupidity of my IO-code) the
   large overhead of Haskell lists.
 
  Most certainly not.  I'm pretty sure this is to a bug in your code.
  Something retains a data structure which is actually unneeded.  Probably
 
 Apparently. And my money is on a load of lines from the file (of which I need 
 only the first and last Char).
 
  a case of foldl where foldl' should be used or a try in Parsec
  code where it should be left out or a lot of updateWiths to a Map,
  etc.  Or it could be a bad choice of data structure.  I bet, it's the
  map you're using to represent the graph (which you don't even need to
  represent at all, btw).
 
 No foldl nor parsec around. I represent the graph as a
 
 UArray (Char,Char) Int 
 
 (I've switched to Int for the index type, too, when tuning the code), so that 
 shouldn't use much memory (array size is 676).
 The array is built via accumArray, I hope that's sufficiently efficient
 (though now I use unsafeAccumArrayUArray, that's faster).
 
 How could I solve the problem without representing the graph in some way?
 Possibly that could be done more efficiently than I do it, but I can't 
 imagine 
 how to do it without representing the graph in some data structure.
 
   So the chunk of the file which easily fits into my
   RAM in ByteString form is too large as a list of ordinary Strings.
 
  The chunk of file should never need to fit into RAM.  If that's a
  problem, you also forgot to prime a crucial foldl.
 
 
 Forgive the stupid question, but where if not RAM would the chunk currently 
 processed reside?

I agree. Some problems simply require you to hold large strings in
memory. And for those, [Char] conks out around 5-10M (try reversing a
10M [Char]).

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


Re: [Haskell-cafe] foreach

2006-09-12 Thread Donald Bruce Stewart
lemmih:
 On 9/13/06, Tim Newsham [EMAIL PROTECTED] wrote:
 I was rewriting some non-haskell code in haskell and came up with this
 construct:
 
foreach l f = mapM_ f l
 
main = do
args - getArgs
foreach args (\arg - do
foreach [1..3] (\n - do
putStrLn ((show n) ++ )  ++ arg)
 )
 )
 
 which is reminiscent of foreach in other languages.  Seems fairly
 useful and I was wondering how hard it would be to add some syntactic
 sugar to the do construct to make it a little prettier (ie.
 not require the parenthesis, binding and nested do, as:
 
main = do
args - getArgs
foreach args arg
foreach [1..3] n
putStrLn ((show n) ++ )  ++ arg)
 
 would this type of transformation be possible with template haskell
 or does this need stronger support from the parser to pull off?
 
 How about:
 
  main = do
args - getArgs
flip mapM_ args $ \arg -
  flip mapM_ [1..3] $ \n -
putStrLn $ show n ++ )  ++ arg
 

Which is, with current Control.Monad:

   main = do
 args - getArgs
 forM_ args $ \arg -
   forM_ [1..3] $ \n -
 putStrLn $ show n ++ )  ++ arg

I think Tim is looking for an if-then-else real syntax feel to his
`foreach' though. I.e. TH or some small preprocessor.
  
-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bit string

2006-09-15 Thread Donald Bruce Stewart
tomasz.zielonka:
 On Fri, Sep 15, 2006 at 11:35:45AM +1000, Thomas Conway wrote:
  My question for all present is: Have I missed either a problem with
  using Integer, or have I overlooked a better representation?
 
 Consider also (UArray Int Bool). In GHC it has an efficient
 implementation.

A _very_ efficient implementation:
http://shootout.alioth.debian.org/gp4/benchmark.php?test=nsievelang=all

:)

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


Re: [Haskell-cafe] Microsoftish Haskell

2006-09-17 Thread Donald Bruce Stewart
kaveh.shahbazian:
 Will Haskell become another pet for Microsoft? 

No. This question doesn't even make sense.

 are many issues around licensing GHC as you'v seen in this mailing
 list and I think Haskell already HAS some big problems that prevent
 others to use it confidently.)

Haskell is in wide academic, and commerical use. Just use it, and quit with the 
FUD.

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


Re: [Haskell-cafe] Microsoftish Haskell

2006-09-17 Thread Donald Bruce Stewart
kaveh.shahbazian:
 Thanks Don
 I sense the truth in your words. But I expect a more technical view of
 point. I need it for presenting to other peoples i.e. to whom wanted
 fom me an overview of Haskell/Using It/Licensing/Libraries/Communities
 to be provided (BOSS!).

Ok.

Overview,
http://haskell.org/haskellwiki/Introduction

Using it,
http://haskell.org/haskellwiki/Learning_Haskell

Licensing,
Compilers and libraries are generally BSD licensed

Libraries,
http://haskell.org/ghc/docs/latest/html/libraries/
http://haskell.org/haskellwiki/Libraries_and_tools

Communities,
http://haskell.org/communities/
http://planet.haskell.org/
http://haskell.org/haskellwiki/Mailing_lists
http://haskell.org/haskellwiki/IRC_channel

All this and more at http://haskell.org

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


Re: [Haskell-cafe] Re: Optimization problem

2006-09-17 Thread Donald Bruce Stewart
ross:
 On Thu, Sep 14, 2006 at 07:51:59PM +0200, Bertram Felgenhauer wrote:
  It's a result of thinking about lazy evaluation, and
  especially lazy patterns (and let bindings) for some time. A wiki article
  that helped me a lot to understand these is
  
http://www.haskell.org/hawiki/TyingTheKnot
  
  I'd like to point out the trustList function there which uses the idea
  of encoding the structure of a term and its actual values in different
  arguments, i.e. a blueprint.
 
 One view of your device is as separating the shape (blueprint) from the
 contents, e.g. one can split a finite map type
 
   data Map k a  = Node !Int k a (Map k a) (Map k a) | Leaf
 
 into a pair of types
 
   data MapShape k = SNode !Int k (MapShape k) (MapShape k) | SLeaf
   data MapData a = DNode a (MapData a) (MapData a) | DLeaf

...

Nice description.

Ross, I added a wiki page for this technique. Would you like to
either elaborate on the wiki, or include the text of your email to it?

http://haskell.org/haskellwiki/Separating_shape_and_content

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Donald Bruce Stewart
crespi.albert:
 
 I'm trying to write in Haskell a function that in Java would be something
 like this:
 
 char find_match (char[] l1, char[] l2, char e){
   //l1 and l2 are not empty
   int i = 0;
   while (l2){
   char aux = l2[i];
   char[n] laux = l2;
   while(laux){
   int j = 0;
   if(laux[j] = aux) laux[j] = e;
   j++;
   }
   if compare (l1, laux) return aux;
   else i++;
   }
 return '';
 }

Yikes!

 
 compare function just compares the two lists and return true if they are
 equal, or false if they are not.
 it is really a simple function, but I've been thinking about it a lot of
 time and I can't get the goal. It works like this:
 
 find_match 4*ha 4*5a 'h'  returns '5' (5 matches with the h)
 find_match 4*ns 4dhnn k  returns ''  (no match at all - lists
 are different anyway)

That's almost a spec there :)

How about:

  import Data.List
 
  findMatch s t c
  | Just n - elemIndex c s = Just (t !! n)
  | otherwise   = Nothing

Using it in GHCi:

 findMatch 4*ha 4*5a 'h'
Just '5'

 findMatch 4*ns 4dhnn 'k'
Nothing

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Donald Bruce Stewart
dons:
 crespi.albert:
  
  I'm trying to write in Haskell a function that in Java would be something
  like this:
  
  char find_match (char[] l1, char[] l2, char e){
  //l1 and l2 are not empty
  int i = 0;
  while (l2){
  char aux = l2[i];
  char[n] laux = l2;
  while(laux){
  int j = 0;
  if(laux[j] = aux) laux[j] = e;
  j++;
  }
  if compare (l1, laux) return aux;
  else i++;
  }
  return '';
  }
 
 Yikes!
 
  
  compare function just compares the two lists and return true if they are
  equal, or false if they are not.
  it is really a simple function, but I've been thinking about it a lot of
  time and I can't get the goal. It works like this:
  
  find_match 4*ha 4*5a 'h'  returns '5' (5 matches with the h)
  find_match 4*ns 4dhnn k  returns ''  (no match at all - lists
  are different anyway)
 
 That's almost a spec there :)

Ah, I see I misread the spec :) Time for some tea.

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


Re: [Haskell-cafe] Java or C to Haskell

2006-09-20 Thread Donald Bruce Stewart
mailing_list:
 On Wed, Sep 20, 2006 at 01:31:22AM -0700, Carajillu wrote:
  compare function just compares the two lists and return true if they are
  equal, or false if they are not.
  it is really a simple function, but I've been thinking about it a lot of
  time and I can't get the goal. 
 
 I forgot, obviously, that lists are an instance of the Eq class...
 so, this is enough:
 comp l1 l2 = if l1 == l2 then True else False
 
 You never stop learning!
 andrea

which you would just write as:
comp = (==)

and then you'd just use == anyway :)

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


[Haskell-cafe] ICFP programming contest 2006 results: video stream

2006-09-20 Thread Donald Bruce Stewart
Malcolm Wallace has recorded the ICFP programming contest results
announcement as video, straight from the ICFP conference in Portland.

He's posted it to Google Video, and it's available to download (120M) or
stream from Google video, here:

http://video.google.com/videoplay?docid=6419094369756184531

Thanks Malcolm!

-- Don

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


Re: [Haskell-cafe] [newbie] How to test this function?

2006-09-20 Thread Donald Bruce Stewart
br1:
 I've written a function that looks similar to this one
  
 getList = find 5 where
 find 0 = return []
 find n = do
   ch - getChar
   if ch `elem` ['a'..'e'] then do
 tl - find (n-1)
 return (ch : tl) else
   find n
  
 First, how do I fix the identation of the if then else?
  
getList = find 5
where find 0 = return []
  find n = do
ch - getChar
if ch `elem` ['a'..'e'] 
then do tl - find (n-1)
return (ch : tl) 
else find n
  
 Second, I want to test this function, without hitting the filesystem.  In  
 C++ I would use a istringstream.  I couldn't find a function that returns  
 a Handle from a String.  The closer thing that may work that I could find  
 was making a pipe and convertind the file descriptor.  Can I simplify that  
 function to take it out of the IO monad?  How?  I thought about  
 getContents, but that eats all input.

Refactor! 
The reason your getList is hard to test, is that you're mixing side
effecting monadic code with pure computations. Let's untangle that, and
then test the the referentially transparent parts simply with
QuickCheck. And remember that since getContents uses lazy IO, it only
eats as much input as you ask it to.

So let's refactor this, partitioning off the side effecting IO code:

getList :: IO [Char]
getList = take5 `fmap` getContents -- a thin IO skin

take5 :: [Char] - [Char]
take5 = take 5 . filter (`elem` ['a'..'e']) -- the actual worker

Now we can test the 'guts' of the algorithm, the take5 function, in
isolation. Let's use QuickCheck. First we need an Arbitrary instance for
the Char type -- this takes care of generating random Chars for us to
test with. I'll restrict it to a range of nice chars just for simplicity:

import Data.Char
import Test.QuickCheck

instance Arbitrary Char where
arbitrary = choose ('\32', '\128')
coarbitrary c = variant (ord c `rem` 4)

So now we can write some simple tests. 
An easy one, a [Char] is equal to itself:

*A quickCheck ((\s - s == s) :: [Char] - Bool)
OK, passed 100 tests.

Reversing twice is the identity:
*A quickCheck ((\s - (reverse.reverse) s == s) :: [Char] - Bool)
OK, passed 100 tests.

Ok, so what properties does take5 have? Well, for one, the length of the
string returned by take5 should be 5, no?

*A quickCheck (\s - length (take5 s) == 5)
Falsifiable, after 0 tests:


Ah, but what if the input file is small :) Thanks quickCheck. 

Let's modify that then:
*A quickCheck (\s - length (take5 s) = 5)
OK, passed 100 tests.

Ok good.  You can probably come up with some more things to check for now.

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


Re: [Haskell-cafe] [newbie] How to test this function?

2006-09-20 Thread Donald Bruce Stewart
dons:
 br1:
  Second, I want to test this function, without hitting the filesystem.  In  
  C++ I would use a istringstream.  I couldn't find a function that returns  
  a Handle from a String.  The closer thing that may work that I could find  
  was making a pipe and convertind the file descriptor.  Can I simplify that  
  function to take it out of the IO monad?  How?  I thought about  
  getContents, but that eats all input.

Oh, another thing to check would be that the correct characters are
returned, such as:
*A quickCheck (\s - all (`elem` ['a'..'e']) (take5 s))
OK, passed 100 tests.

So for all strings QuickCheck produced, all Chars in the string returned
by take5 where elements of ['a'..'e'].

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


Re: [Haskell-cafe] [newbie] How to test this function?

2006-09-20 Thread Donald Bruce Stewart
dons:
 br1:
  Second, I want to test this function, without hitting the filesystem.  In  
  C++ I would use a istringstream.  I couldn't find a function that returns  
  a Handle from a String.  The closer thing that may work that I could find  
  was making a pipe and convertind the file descriptor.  Can I simplify that  
  function to take it out of the IO monad?  How?  I thought about  
  getContents, but that eats all input.

I've summarised  this little introduction to QuickCheck on the
haskell.org wiki here,
http://haskell.org/haskellwiki/Introduction_to_QuickCheck

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


[Haskell-cafe] Haskell.org down

2006-09-23 Thread Donald Bruce Stewart

Just in case it has gone unnoticed, haskell.org seems to have been down
for a few hours now.

Do we have an admin looking into this?

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


Re: [Haskell-cafe] Unable to profile program using Data.ByteString.Lazy

2006-09-23 Thread Donald Bruce Stewart
lists:
 Hi folks,
 
 I wrote a program that uses some of the Data.ByteString libraries. I'm 
 using GHC 6.4.1 and FPS 0.7.
 
 The program compiles and works just fine. But when I try to profile it, 
 by compiling with -prof, I get:
 
Failed to load interface for `Data.ByteString.Lazy':
Could not find module `Data.ByteString.Lazy':
  locations searched:
Data/ByteString/Lazy.hi
Data/ByteString/Lazy.hi-boot
/f/g/lib/fps-0.7/Data/ByteString/Lazy.p_hi
 
 Why can it find the module when it's compiling without -prof, but not 
 when it's compiling with it? I would really like to get profiling to work.

Probably you didn't build fps with profiling as well? You can rebuild
fps with:
runhaskell Setup.hs configure -p 
as the first step.

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


Re: [Haskell-cafe] Haskell.org down

2006-09-23 Thread Donald Bruce Stewart
paul.hudak:
 Thanks Don.  I alerted our IT staff this morning, and they seem to have 
 things working again, although here is their final response:
 
The web server had over 150 client connections which exceeded
its limit. I restarted the web server and all is well.
 
I'll keep and eye on it and see if someone is trying a denial of
server attack, or it could be you need a newer faster machine. :-)
 
 So either Haskell is getting really popular (on a Friday night?) or 
 there's something fishy going on.

Hmm. Looks like its gone down again?

Seems fishy...

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


Re: [Haskell-cafe] Unable to profile program using Data.ByteString.Lazy

2006-09-24 Thread Donald Bruce Stewart
lists:
 Donald Bruce Stewart wrote:
 Probably you didn't build fps with profiling as well? You can rebuild
 fps with:
 runhaskell Setup.hs configure -p 
 as the first step.
 
 -- Don
   
 
 Thanks, I'll try it. Does that mean when I want to optimize my program, 
 I'll need to rebuild fps without profiling?
 
 - Lyle

If you build a cabalised project with the -p flag to configure, you get
both the profiled and normal versions. You won't need to rebuild after
that.

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


[Haskell-cafe] Haskell.org down (again)

2006-09-26 Thread Donald Bruce Stewart
Something's going on. Haskell.org seems to be down again.
That's the 3rd time in 4 days.

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


Re: [Haskell-cafe] Unable to profile program using Data.ByteString.Lazy

2006-09-26 Thread Donald Bruce Stewart
lists:
 Donald Bruce Stewart wrote:
 Probably you didn't build fps with profiling as well? You can rebuild
 fps with:
 runhaskell Setup.hs configure -p 
 as the first step.
   
 That worked on my Windows box at home, but on my Linux box at work, I 
 got unrecognized flag -p.

You're cabal version is too old then. Try updating either Cabal or GHC.

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


Re: [Haskell-cafe] Haskell.org down (again)

2006-09-26 Thread Donald Bruce Stewart
dons:
 Something's going on. Haskell.org seems to be down again.
 That's the 3rd time in 4 days.

And of course sending this message when the server _was_ down is guaranteed
to lead to confusion when it is finally delivered, and the server is _up_.

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


Re: [Haskell-cafe] Is Haskell a 5GL?

2006-09-28 Thread Donald Bruce Stewart
david.curran:
 Where are compute languages going?
 I think multi core, distributed, fault tolerant.
 So you would end up with a computer of the sort envisioned by Hillis
 in the 80s with his data parallel programs. The only language that
 seems even close to this model is Erlang. What am I missing about the
 ability of Haskell to distribute across processors or a network?

Data parallel Haskell is a very active area at the moment,
http://www.cse.unsw.edu.au/~chak/project/dph/

Just last week Roman Leshchinskiy was able to get parallel arrays
running SMP GHC on a shared memory 40 cpu Sun sparc server :)

Also, GPH and its ilk have a long history:

http://www.haskell.org/haskellwiki/Research_papers/Parallelism_and_concurrency

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


[Haskell-cafe] Porting content from the old wiki

2006-10-08 Thread Donald Bruce Stewart
The main thing holding up porting of content from the old wiki is
licensing. In order to help this, could people who've written for the
old wiki, and are happy to have that work moved to the new wiki and
relicensed, add their names to the list here:

http://haskell.org/haskellwiki/HaWiki_migration

Or email me and I'll add the name.
Then anyone can move your work over, which should really speed things up.

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


Re: [Haskell-cafe] Haskell performance (again)!

2006-10-08 Thread Donald Bruce Stewart
duncan.coutts:
 On Sun, 2006-10-08 at 15:25 -0700, Jason Dagit wrote:
 
  Another good idea when you have a pretty version which is easy to
  verify for correctness and an ugly version that is harder to verify is
  to use QuickCheck or SmallCheck and define a property that says both
  versions are equal for all inputs.  Ugly code is notorious for holding
  bugs, but doing this would help test the ugly code.
 
 This is exactly how we tested Data.ByteString and to great effect I
 think. We uncovered loads of bugs during testing. The few bugs uncovered
 by our users since it has been released have invariably been in things
 we didn't have QC properties for.

Yes, I agree with this. By checking fast-bug-ugly code against
slow-but-obvious code, we were able to catch bugs before Data.ByteString
was deployed in the outside world, and before the bugs could hurt
anyone. These days, Data.ByteString has some 2000 lines of QC
properties, which are run on ever darcs commit.

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


Re: [Haskell-cafe] Re: What's going on in our courses?

2006-10-14 Thread Donald Bruce Stewart
monnier:
  Last Spring my Functional Programming class implemented a Genetic  Algorithm
  with Neural Networks that learned to play Nim. The students  had a really
  good time--they also learned lots about Functional  Programming
  with Haskell.
  Part of the final exam was a tournament.
 
  This Fall in AI we'll be  doing GA's again and Genetic Programming.
 
  Is there a list or forum that talks about teaching our students
  about  Haskell?
 
 Indeed, I'd be interested as well.
 I'm actually looking for a good textbook for a concepts of programming
 language course.  All the books I can find tend to emphasize OO or
 imperative programming too much for my taste.

You might want to look at :
http://cgi.cse.unsw.edu.au/~cs3161/docs/references.php

We use:
Bob Harper's book, Programming Languages: Theory and Practice
http://www-2.cs.cmu.edu/~rwh/plbook/
and
Types and Programming Languages, Benjamin Pierce

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


Re: [Haskell-cafe] Re: What's going on in our courses?

2006-10-14 Thread Donald Bruce Stewart
dons:
 monnier:
   Last Spring my Functional Programming class implemented a Genetic  
   Algorithm
   with Neural Networks that learned to play Nim. The students  had a really
   good time--they also learned lots about Functional  Programming
   with Haskell.
   Part of the final exam was a tournament.
  
   This Fall in AI we'll be  doing GA's again and Genetic Programming.
  
   Is there a list or forum that talks about teaching our students
   about  Haskell?

Also, 
http://haskell.org/haskellwiki/Haskell_in_education

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


Re: [Haskell-cafe] List comparisons and permutation group code

2006-10-21 Thread Donald Bruce Stewart
dmhouse:
 On 21/10/06, Tomasz Zielonka [EMAIL PROTECTED] wrote:
 Do you also have this experience with Haskell?: when you feel that
 some code is not ideal, almost always it can be improved.
 
 One of the recurring features of the #haskell IRC conversations is
 something called 'Algorithm Golf' (which is a misnomer and should
 really be 'Algorithm Tennis'): one person will request an algorithm
 and anyone interested sets about building their own. The results are
 then shared using lambdabot's Haskell evaluation feature and
 collaboratively improved.

I also like how when doing true 'golf', with @pl, we find new
combinators:

http://haskell.org/haskellwiki/Pointfree#Combinator_discoveries

Like the owl:

((.)$(.)) 

 I'd recommend hanging out in the channel to anyone. :)

I agree, if you're not on #haskell, you're missing out!
http://haskell.org/haskellwiki/IRC_channel :)

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


Re: [Haskell-cafe] Read a single char

2006-10-23 Thread Donald Bruce Stewart
briqueabraque:
   Hi,
 
   How can I read a single character from standard output? I would like 
 the user to press a single key and the reading function return 
 imediately after that key is pressed.

so you want a function of type:
IO Char

asking Hoogle (http://haskell.org/hoogle) we get:
Prelude.  getChar:: IO Char
IO.   hGetChar   :: Handle - IO Char

-- Don

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


[Haskell-cafe] Haskell custom search engine

2006-10-24 Thread Donald Bruce Stewart
Google now lets us create our own custom search engine pages, so I
whipped one up for Haskell,

http://www.google.com/coop/cse?cx=015832023690232952875%3Acunmubfghzq

also, as a demo, embedded

http://www.cse.unsw.edu.au/~dons/search.html

Seems to do a reasonable job of targetting just Haskell sites. Feel free
to add more Haskell material, or refine the search. In fact, search for
mailing list items seems rather easy this way.

Neil, I wonder if we could integrate this with Hoogle somehow?

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


Re: [Haskell-cafe] Haskell custom search engine

2006-10-25 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello Donald,
 
 Wednesday, October 25, 2006, 8:44:48 AM, you wrote:
 
  Google now lets us create our own custom search engine pages, so I
  whipped one up for Haskell,
 
 great. and it search mail archives too
 
 how about adding it to haskell site, or at least a LARGE link so that
 everyone will see it. it will be very helpful for strangers/novices

My plan was to have the community play with it for a week or so, and
tune the results (i.e. volunteer and help refine the searches), and then
we can embed it in haskell.org

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


Re: Fwd: [Haskell-cafe] Haskell custom search engine

2006-10-25 Thread Donald Bruce Stewart
dnavarro:
 Google now lets us create our own custom search engine pages, so I
 whipped one up for Haskell,
 
 I volunteered.

Accepted.
  
 Are you planning to add just sites for Haskell-related software, or
 are research papers included in the scope of this?
 
 (Dude, where's my english grammar.)

Yes, Haskell research sites would be good, as would working out the
'Refinement' stuff, to give more detailed searches (i.e. search only the
research papers)

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


Re: [Haskell-cafe] Haskell custom search engine

2006-10-25 Thread Donald Bruce Stewart
ndmitchell:
 Hi
 
 Neil, I wonder if we could integrate this with Hoogle somehow?
 
 If I provide an Ajax'y style API and we put the results in a frame,
 I'm sure we can give something like top 3 results from hoogle (if
 they make any sense). That sound a reasonable idea?

You should be able to do just that, yes. The code for embedding the
search engine on my example page might be a good place to start.

I think augmenting hoogle is a in general better than forking two search
engines for slightly different problems.

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


[Haskell-cafe] Ruby quiz, Haskell wiki

2006-10-25 Thread Donald Bruce Stewart
I've created a page to document haskell solutions to the ruby quiz
puzzle series.

http://haskell.org/haskellwiki/Haskell_Quiz

Those of you working on them, please upload your solutions, and create
sub pages for new puzzles as they appear.

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


[Haskell-cafe] More documentation: how to create a Haskell project

2006-10-29 Thread Donald Bruce Stewart
There's been a bit of discussion on irc, lists and privately about 
about documenting publically the best practice for creating a new
Haskell project -- be that a library or an application.

Some advice is now available here:
http://haskell.org/haskellwiki/How_to_write_a_Haskell_program

Suggestions include:
* use darcs
* use cabal

But we could do with more information on:
* where to host a haskell project 
* integration of testsuites
* anything about Hackage?
* portability issues?

So have a look at the page and make some suggestions, so it will be
easier for newcomers in the future to create and contribute new
projects, that will be readily accesible, useable and adopted by the
community.

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


[Haskell-cafe] Documenting subcommunities

2006-10-29 Thread Donald Bruce Stewart
As the Haskell community grows and spreads its lambda-tipped tentacles
into new domains, I've noticed that some distinct sub-communities are
emerging.

To try to document and collect information relevant to these groups,
some new wiki pages have been created.

Alongside the 'traditional' areas of: 

http://haskell.org/haskellwiki/Haskell_in_research
http://haskell.org/haskellwiki/Haskell_in_education

There is also a growing number of users of Haskell:

http://haskell.org/haskellwiki/Haskell_in_industry
http://haskell.org/haskellwiki/Haskell_and_mathematics

If you're using Haskell for maths or in industry, and know of some
relevant resources, please feel free to add the material to the above
pages.

Alternatively, if there are subcommunities that are missing a page (hmm,
the open source community, perhaps?), then dive in and create a page
documenting this.

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


[Haskell-cafe] More documentation: languages written in Haskell

2006-10-29 Thread Donald Bruce Stewart
I noticed today that although we have a list of most applications
written in Haskell, nowhere was there collected a page of perhaps our
best use case for Haskell: for implementing compilers and interpreters!

So here's a new 'libraries and tools' category page:

http://haskell.org/haskellwiki/Libraries_and_tools/Compilers_and_interpreters

If you know of a compiler or interpreter written in Haskell, (I think at
least a few people on this list have written one or two themselves ... ;)
please add it to the list.

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


[Haskell-cafe] Tutorial: Writing a Lisp Interpreter In Haskell

2006-10-31 Thread Donald Bruce Stewart
People might be interested in a new tutorial that's just appeared in
blogspace, by coffeemug (of #haskell):

http://www.defmacro.org/ramblings/lisp-in-haskell.html

Also, its on reddit, http://programming.reddit.com/info/oj1w/details 

An enthusiastic view of the language from a newcomer's perspective.

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


Re: [Haskell-cafe] How to improve speed? (MersenneTwister is several times slower than C version)

2006-11-01 Thread Donald Bruce Stewart
Now, this will be hard to get close the the highly tuned C. Possibly its
doable.

The main tricks are documented here:
http://haskell.org/haskellwiki/Performance/GHC#Unboxed_types

Inspecting the Core to ensure the math is being inlined and unboxed will
be the most crucial issue, I'd imagine.

Then again, an FFI binding to mersenne.c is also a good idea :)

-- Don


isto.aho:
 Hi all,
 
 On HaWiki was an announcement of MersenneTwister made by Lennart
 Augustsson.  On a typical run to find out 1000th rnd num the output
 is (code shown below):
 
 $ time ./testMTla
 Testing Mersenne Twister.
 Result is [3063349438]
 
 real0m4.925s
 user0m4.856s
 
 
 I was exercising with the very same algorithm and tried to make it
 efficient (by using IOUArray): now a typical run looks like (code shown
 below):
 
 $ time ./testMT
 Testing Mersenne Twister.
 3063349438
 
 real0m3.032s
 user0m3.004s
 
 
 The original C-version (modified so that only the last number is
 shown) gives typically
 
 $ time ./mt19937ar
 outputs of genrand_int32()
 3063349438
 
 real0m0.624s
 user0m0.616s
 
 Results are similar with 64 bit IOUArray against 64 bit C variant.
 C seems to work about 5 to 10 times faster in this case.
 
 I have tried to do different things but now I'm stuck.  unsafeRead
 and unsafeWrite improved a bit the lazy (STUArray-version) and
 IOUArray-versions but not very much.  I took a look of Core file but
 then, I'm not sure where the boxed values are ok. E.g. should  IOUArray
 Int Word64  be replaced with something else?
 
 Any hints and comments on how to improve the efficiency and make
 everything better will be appreciated a lot!  
 
 br, Isto
 
 - testMTla.hs (MersenneTwister, see HaWiki)
 module Main where
 
 -- ghc -O3 -optc-O3 -optc-ffast-math -fexcess-precision --make testMTla
 
 import MersenneTwister
 
 main = do
   putStrLn Testing Mersenne Twister.
   let mt = mersenneTwister 100
   w = take 1 (drop 999 mt)
   -- w = take 1 (drop 99 mt)
   putStrLn $ Result is  ++ (show w)
 -
 
 - testMT.hs
 module Main where
 
 -- Compile eg with
 --   ghc -O3 -optc-O3 -optc-ffast-math -fexcess-precision --make testMT
 
 import Mersenne
 
 genRNums32 :: MT32 - Int - IO (MT32)
 genRNums32 mt nCnt = gRN mt nCnt 
   where gRN :: MT32 - Int - IO (MT32)
 gRN mt nCnt | mt `seq` nCnt `seq` False = undefined
 gRN mt 1= do 
   (r,mt') - next32 mt
   putStrLn $ (show r)
   return mt'
 gRN mt nCnt = do
   (r,mt') - next32 mt
   gRN mt' $! (nCnt-1) 
 
 
 main = do
   putStrLn Testing Mersenne Twister.
   mt32 - initialiseGenerator32 100
   genRNums32 mt32 1000
 -
 
 - Mersenne.hs (sorry for linewraps)
 module Mersenne where
 
 import Data.Bits
 import Data.Word
 import Data.Array.Base
 import Data.Array.MArray
 import Data.Array.IO
 -- import System.Random
 
 
 data MT32 = MT32 (IOUArray Int Word32) Int
 data MT64 = MT64 (IOUArray Int Word64) Int
 
 
 last32bitsof :: Word32 - Word32 
 last32bitsof a = a .. 0x -- == (2^32-1)  
 
 lm32 = 0x7fff :: Word32
 um32 = 0x8000 :: Word32
 mA32 = 0x9908b0df :: Word32 -- == 2567483615
 
 -- Array of length 624.
 initialiseGenerator32 :: Int - IO MT32 
 initialiseGenerator32 seed = do
   let s = last32bitsof (fromIntegral seed)::Word32
   mt - newArray (0,623) (0::Word32)
   unsafeWrite mt 0 s
   iG mt s 1
   mt' - generateNumbers32 mt
   return (MT32 mt' 0)
   where
   iG :: (IOUArray Int Word32) - Word32 - Int - IO (IOUArray Int
 Word32)
   iG mt lastNro n  
   | n == 624= return mt
   | otherwise = do let n1 = lastNro `xor` (shiftR lastNro 
 30)
new = (1812433253 * n1 + 
 (fromIntegral n)::Word32) 
unsafeWrite mt n new
iG mt new (n+1)
 
 
 generateNumbers32 :: (IOUArray Int Word32) - IO (IOUArray Int Word32)
 generateNumbers32 mt = gLoop 0 mt
   where
   gLoop :: Int - (IOUArray Int Word32) - IO (IOUArray Int 
 Word32)
   gLoop i mt 
   | i==623  = do 
   wL - unsafeRead mt 623
   w0 - unsafeRead mt 0
   w396 - unsafeRead mt 396
   let y = (wL .. um32) .|. (w0 .. lm32) :: 
 Word32
   if even y 
  then unsafeWrite mt 623 (w396 `xor` (shiftR 
 y 1))
  else unsafeWrite mt 623 (w396 `xor` (shiftR 
 y 1) `xor` mA32)
   return mt

Re: [Haskell-cafe] Basic Binary IO

2006-11-01 Thread Donald Bruce Stewart
nuno:
 
Hi all!
 
Today i was reading System.IO and didn't manage to
understand how it works just by reading it.
I looked the internet for some help on this, but only
advanced information is available.
Can anyone show me how to use openBinaryFile ?
Just an example, like opening file somefile and separating
it into something that can be edited in the code (like 8 bit
words) then go to word nr12 and edit the last bit?

http://haskell.org/haskellwiki/Binary_IO

For flat lists of bytes, use Data.ByteString, for structured data, try
NewBinary.

There are other options too, documented above.

openBinaryFile just sets the line ending handling on windows. I don't
think it does what you think it does.

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


Re: [Haskell-cafe] How to improve speed? (MersenneTwister is several times slower than C version)

2006-11-01 Thread Donald Bruce Stewart
lemmih:
 On 11/1/06, isto [EMAIL PROTECTED] wrote:
 Hi all,
 
 On HaWiki was an announcement of MersenneTwister made by Lennart
 Augustsson.  On a typical run to find out 1000th rnd num the output
 is (code shown below):
 
 $ time ./testMTla
 Testing Mersenne Twister.
 Result is [3063349438]
 
 real0m4.925s
 user0m4.856s
 
 
 I was exercising with the very same algorithm and tried to make it
 efficient (by using IOUArray): now a typical run looks like (code shown
 below):
 
 $ time ./testMT
 Testing Mersenne Twister.
 3063349438
 
 real0m3.032s
 user0m3.004s
 
 
 The original C-version (modified so that only the last number is
 shown) gives typically
 
 $ time ./mt19937ar
 outputs of genrand_int32()
 3063349438
 
 real0m0.624s
 user0m0.616s
 
 Results are similar with 64 bit IOUArray against 64 bit C variant.
 C seems to work about 5 to 10 times faster in this case.
 
 I have tried to do different things but now I'm stuck.  unsafeRead
 and unsafeWrite improved a bit the lazy (STUArray-version) and
 IOUArray-versions but not very much.  I took a look of Core file but
 then, I'm not sure where the boxed values are ok. E.g. should  IOUArray
 Int Word64  be replaced with something else?
 
 Any hints and comments on how to improve the efficiency and make
 everything better will be appreciated a lot!
 
 br, Isto
 
 Greetings,
 
 Applying a few optimations can make it about 3x faster.
 
 1. Hoist the array out of your loops. (See generateNumbers32,
 initialiseGenerator32 and genRNums).
 2. Don't create too many new MT32 boxes. Most of the time is spent in
 'next32' and changing its type to 'IOUArray Int Word32 - Int - IO
 (Word32, Int)' makes it much faster.
 3. Demand more inlining. If you're using GHC,
 -funfolding-use-threshold=16 will substantially improve the
 performance.
 
 Using 'seq' is generally a bad idea. It can worsen the performance if
 not used carefully and GHCs strictness analyser is usually good
 enough.
 I used the profiler and -ddump-simpl to analyse this program.
 
 Donald suggested manual unboxing. However, in this case it won't help
 much (if at all) since GHC is doing such an excellent job on its own.

I wasn't suggesting manual unboxing, more that you should carefully
inspect the Core, and tune with bang patterns where necessary. 

-funfolding-use-threshold=16 is a good idea though. or =100 ;)

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


Re: [Haskell-cafe] How to improve speed? (MersenneTwister is several times slower than C version)

2006-11-02 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello isto,
 
 Thursday, November 2, 2006, 1:16:55 AM, you wrote:
 
  I have tried to do different things but now I'm stuck.  unsafeRead
  and unsafeWrite improved a bit the lazy (STUArray-version) and
 
 why you think it's a lazy? :)  ST monad is just the same as IO monad
 internally, only types are different (there is also Lazy.ST monad -
 this is really lazy)
 
 10-20 times difference is typical for GHC programs.

!

It's really more like 2-4x. Sometimes better than C.

Where's this huge figure coming from Bulat? If you have code that
behaves like this, you should report it.

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


Re: [Haskell-cafe] Finding Memory Leaks

2006-11-02 Thread Donald Bruce Stewart
mattcbro:
 
 
 
 Jason Dagit-2 wrote:
  
  
  
  Do any memory leaks show up if you compile with -caf-all when you profile?
  
  Jason
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
  
  
 
 It doesn't seem to make any difference, although I do not know what this
 flag does.
 I compiled the code using
 ghc -fglasgow-exts -fffi -prof -auto -caf-all -I. --make  leaky.hs cleaky.o
 
 and did not see the steady ramp up in memory that one sees with the windows
 xp performance tool.

Hmm, are you missing a -O ? Does that help at all?

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


Re: [Haskell-cafe] RFC and Announcement: HLADSPA, LADSPA for Haskell

2006-11-06 Thread Donald Bruce Stewart
lemming:
 
 On Sun, 5 Nov 2006, Alfonso Acosta wrote:
 
  PS1: Big thanks and claps for the people at [EMAIL PROTECTED] . They
  helped a lot to make this initial release possible.
  PS2: I would like to get the project hosted at the darcs repository at
  haskell.org. Do you consider it interesting enough for it?
 
 Yes, definitely. Could you also please add some note to
   http://www.haskell.org/haskellwiki/Libraries_and_tools/Music_and_sound

I agree, and would remark for anyone reading:

Please add your projects, whether they are applications, libraries,
tools, darcs repos, to :

http://haskell.org/haskellwiki/Libraries_and_tools

*All* Haskell code that's available, and fit to compile should be
findable from that page.

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


[Haskell-cafe] Livecoding music in Haskell

2006-11-06 Thread Donald Bruce Stewart
Alex McLean has kindly put up a screencast of him creating 
*music via live coding in Haskell* !

http://doc.gold.ac.uk/~ma503am/alex/haskellmusic

And a .avi version of the screencast, playable in mplayer (for those not
flash inclined).

http://yaxu.org/20/hs.avi

The code is running in hs-plugins, and being reloaded on the fly as he
edits the source, changing the rhythms that are produced. More on this
on Alex's blog:

http://doc.gold.ac.uk/~ma503am/alex/ 

Cool stuff!

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


[Haskell-cafe] don't: a 'do' for comonads?

2006-11-08 Thread Donald Bruce Stewart
As seen on #haskell, from an idea by Malcolm,

14:42  ?let top'n'tail = (pre++) . (++/pre) 
14:42  lambdabot Defined.
14:43  dons  L.top'n'tail foo me now
14:43  lambdabot  prefoo me now/pre
14:43  mauke that reminds me, haskell needs don't
14:43  dons yes!
14:44  pkhuong- mm. the opposite of do, eh? do for comonads? :)

So now a prize to the person who comes up with the best use for the
identifier:

don't :: ?

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


Re: [Haskell-cafe] Sistema de Ecuaciones NO lineales

2006-11-09 Thread Donald Bruce Stewart
bonobo:
 On Thu, 9 Nov 2006 02:52 pm, Sebastian Gaviria wrote:
  hola como estan
 
  Quiero preguntar quien puede resolver el sistemas de ecuaciones NO lineales
  de Newton y el codigo de Jacobi  en Haskell
 
  me ayudarian mucho al poder implementar ese codigo
 
  por Favor es con urgencia tener estos codigos!!
 
 
  muchas gracias !!!
 
 Hola Sebastian,
 
 Lo siento por mi espa?ol mal.
 
 Si esa es una pregunta sobre tarea, por favor lee 
 http://www.haskell.org/haskellwiki/Homework_help
 
 Y escribo Haskell como escribo espa?ol :-), as? lo siento, no puedo 
 ayudar. :-(
 

You might try:
#haskell.es irc channel

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

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


[Haskell-cafe] Great language shootout: reloaded

2006-11-09 Thread Donald Bruce Stewart
So back in January we had lots of fun tuning up Haskell code for the
Great Language Shootout[1]. We did quite well at the time, at one point
ranking overall first[2]. After doing all we could with ghc 6.4.2, the
Haskell entries have been left for the last 10 months, while we worked
on new libraries (bytestring, regex-*).

1. http://shootout.alioth.debian.org/
2. http://www.cse.unsw.edu.au/~dons/data/haskell_1.html

Now the time has come to reload the shootout for another round!
GHC 6.6 is on the 'sandbox' debian machine, and will soon be on the
other shootout boxes[3], which means we can use:

  * Data.ByteString
  * regex-* libraries

3. 
http://shootout.alioth.debian.org/sandbox/benchmark.php?test=alllang=ghclang2=javaxint#about

And thus greatly improve:
  fannkuch
  fasta
  k-nucleotide
  regex-dna
  reverse-complement
  sum-file

While we're here we should fix:
  chameneos 
And anything else you want to take a look at.

A community page has been set up to which you can submit improved entries:
http://www.haskell.org/haskellwiki/Great_language_shootout

So, install GHC 6.6, read up on Data.ByteString and the new regex libs,
and submit faster code to the wiki! Our shootout-interface officer,
musasabi, can then commit them to shootout cvs, once consensus is
reached on the best code to submit.

Let's take back first place! :)

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


Re: [Haskell-cafe] Re: don't: a 'do' for comonads?

2006-11-09 Thread Donald Bruce Stewart
apfelmus:
 Donald Bruce Stewart wrote:
  As seen on #haskell, from an idea by Malcolm,
  
  14:42  ?let top'n'tail = (pre++) . (++/pre) 
  14:42  lambdabot Defined.
  14:43  dons  L.top'n'tail foo me now
  14:43  lambdabot  prefoo me now/pre
  14:43  mauke that reminds me, haskell needs don't
  14:43  dons yes!
  14:44  pkhuong- mm. the opposite of do, eh? do for comonads? :)
  
  So now a prize to the person who comes up with the best use for the
  identifier:
  
  don't :: ?
  
  -- Don
 
 don't :: IO a - a
 
 example :: ()
 example = don't (do erase /dev/hda)

I like it!

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


Re: [Haskell-cafe] don't: a 'do' for comonads?

2006-11-09 Thread Donald Bruce Stewart
hjgtuyl:
 
 don't :: whatever -
 
 (whatever goes in, nothing comes out)

So its:

don't :: a - Void 

?

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


Re: [Haskell-cafe] Great language shootout: reloaded

2006-11-10 Thread Donald Bruce Stewart
igouy2:
  On 11/10/06, Henk-Jan van Tuyl hjgtuyl at chello.nl wrote:
 
  Haskell suddenly dropped several places in the overall socre, when
 the
  size measurement changed from line-count to number-of-bytes after
  gzipping. Maybe it's worth it, to study why this is; Haskell
 programs 
  are
  often much more compact then programs in other languages, but after
  gzipping, other languages do much better. One reason I can think of,
 is
  that for very short programs, the import statements weigh heavily.
 
 
 Before this gets out-of-hand, my memory is certainly fallible but as I
 recall Haskell /did not/ drop several places because size measurement
 changed from line-count to gzip byte-count.
 
 
 1) Check the webpage that Don Stewart cached and note the values for
 the memory use and code-lines multipliers, and note the values for the
 benchmark weights
http://www.cse.unsw.edu.au/~dons/data/haskell_1.html
  
 Now go to the computer language shootout website and note the
 multipliers and benchmark weights.
 
 
 2) Some Haskell programs were pushed into 'interesting alternative
 implementations' because they'd strayed so far from the spirit of the
 benchmark. (It takes a while for people to notice and complain, but
 eventually they do.)

I agree. Breaking the rules was mainly the reason for the drop. Entries
like chameneos and fasta. Also, the other language teams kept improving
things.  

Other language (perl, iirc) were affected far worse by the gzipping.
gzip is an interesting measurement, and it doesn't hurt Haskell too much
either way -- short Haskell programs stay short when compressed.

As a result, rewriting verbose entries to ByteString will probably be
much more useful :)

Btw, Isaac, are we going to have any new parallelism benchmarks? I'd
love to try out the SMP runtime ;)

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


Re: [Haskell-cafe] best Linux for GHC?

2006-11-12 Thread Donald Bruce Stewart
bulat.ziganshin:
 Hello haskell-cafe,
 
 Now i'm consider installation of some Linux version at my box. My
 friend offered me 3 variants: SuSe, Fedora Core 5, free variant of
 RedHat (i can't remember its name, may be Ubuntu?)
 
 what may be best for GHC-based development? in particular, i want to
 compile Haskell itself
 
 i suspect that it is a really dumb question, and GHC will work great
 just with any linux i can find :)
 
 -- 

Gentoo or Debian, I suspect, since then you get the #haskell-gentoo
team, and Igloo, keeping things up to date :)

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


Re: [Haskell-cafe] ByteString FFI

2006-11-12 Thread Donald Bruce Stewart
donn:
 How do people like to set up their foreign I/O functions to return
 ByteStrings?  I was a little stumped over this yesterday evening,
 while trying to write ` recv :: Socket - Int - Int - ByteString '
 
 Doc says `Byte vectors are encoded as strict Word8 arrays of bytes,
 held in a ForeignPtr, and can be passed between C and Haskell with
 little effort.'  Which sounds perfect - I'm always up for `little effort'!
 
 CString doesn't seem like the right thing for socket results, because
 the data shouldn't be NUL-terminated, and I might want to realloc when
 the returned data doesn't fill the buffer.  I don't see any other
 Ptr-related function or constructor in the documentation - am I missing
 something there?

And for custom data (not just C strings), if the withCString* functions
don't quite fit, you can always pack the foreign Ptr into a ByteString
by stepping inside the ByteString constructor:

http://www.haskell.org/haskellwiki/Wc#Going_via_C

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


Re: [Haskell-cafe] ByteString FFI

2006-11-12 Thread Donald Bruce Stewart
donn:
 On Mon, 13 Nov 2006, Donald Bruce Stewart wrote:
 
  And for custom data (not just C strings), if the withCString* functions
  don't quite fit, you can always pack the foreign Ptr into a ByteString
  by stepping inside the ByteString constructor:
  
  http://www.haskell.org/haskellwiki/Wc#Going_via_C
 
 That's actually what I tried first, but in this particular situation
 (ghc-6.4.1 / fps-0.7), PS apparently isn't exported?

Right, you'll want to grab the soon-to-be-tagged fps 0.8, which matches
that provided with ghc 6.6. It's in the darcs repo.

 The CStringLen approach works, except that the allocated data doesn't
 get garbage-collected.  Just for the sake of experiment I tried a regular
 CString with packMallocCString, and that didn't leak nearly as much memory -
 but still some, in a simple loop where pack doesn't leak anything.

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


Re: [Haskell-cafe] Great language shootout: reloaded

2006-11-13 Thread Donald Bruce Stewart
tpledger:
 Donald Bruce Stewart wrote:
 [...]
  While we're here we should fix:
chameneos
  And anything else you want to take a
  look at.
 
  A community page has been set up to
  which you can submit improved entries:
 
 http://www.haskell.org/haskellwiki/Great_language_shootout
 [...]
 
 
 Well, then!
 
 I've put a new chameneos solution up on the wiki, and will
 wait the recommended couple of days for Community Feedback.

Great!

One issue is that the pragma is unnecessary (all the good flags are
set in the Makefile, so that saves a few gzipped bytes ;)

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


  1   2   3   4   5   6   >