[Haskell-cafe] Re: MD5?

2007-11-10 Thread Dominic Steinitz
Neil Mitchell ndmitchell at gmail.com writes:

 
 Hi
 
  The final alternative is that I just call MD5SUM.EXE from my Haskell
  program and try to parse the output. But that strikes me as rather messy.
 
 Messy, but I don't see any disadvantage to doing it this way - if you
 can control that the MD5SUM program is installed alongside your code.
 
 Of course, there is the standard Crypto library for Haskell,
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Crypto-3.0.3
 - either:
 
 1) it goes fast enough
 2) it goes too slow and someone should make it go faster
 
 Either way, it should go fast enough as soon as someone needs it to go faster.
 
 Thanks
 
 Neil
 

Of course the code in the Crypto library isn't fast enough.

I maintain the package but at the moment I don't have any time to do anything
with it. If anyone wants to send me patches, I will happily apply them. I did
have a quick look a Thomas DuBuisson's code and it looks like a change to the
API. If there is going to be change to this then I think it ought to go via the
libraries change process.

I recall that someone improved the performance of SHA-1 as well but again I
haven't had time to do anything with it.

If anyone wants to take over the care and nurture of the Crypto library then
they are most welcome and I would be very grateful.

Dominic.


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


Re: [Haskell-cafe] WideFinder

2007-11-10 Thread Berlin Brown

Sterling Clover wrote:
Um... you do realize that the code is only supposed to match against 
very specific lines in sample data sets that Bray provides, right? If 
your access log doesn't have lines exactly like those (and why would 
it?) then there's no reason to expect a result.


--S

On Nov 9, 2007, at 11:19 PM, Berlin Brown wrote:


Sterling Clover wrote:
I hacked together a version that I'm pretty happy with today. 
Started off trying an algorithm with channels and forking, then 
realized that in Haskell thanks to referential transparency we can 
get parallelism almost for free, and redid it all in 
Control.Parallel (below). Unfortunately, I don't have a multicore 
processor so I can't put this through any special paces. However, 
its compactness and expressively match or beat the simple Ruby, etc. 
scripts while it gets (theoretically) most of the parallel benefits 
of the enormous and unwieldy Erlang and JOcaml ones.


--S

module Main where
import qualified Data.ByteString.Lazy.Char8 as LB
import Data.List (foldl', unfoldr, insertBy)
import qualified Data.Map as M
import System.Environment (getArgs)
import Control.Parallel (par)
import Control.Parallel.Strategies (parMap, rwhnf)

count :: M.Map LB.ByteString Int - LB.ByteString - M.Map 
LB.ByteString Int
count m line = if LB.pack /ongoing/When `LB.isPrefixOf` myLn then 
M.insertWith' (+) (LB.drop 14 myLn) 1 m else m
where myLn = (LB.takeWhile (/=' ') . LB.dropWhile (/='/') . 
LB.dropWhile (/='\')) line


mapUnionPar :: (Ord k, Num a) = [M.Map k a] - M.Map k a
mapUnionPar m = head $ until (null . tail) mapUnionPar' m
where a |:| b = par a . par b $ a : b
mapUnionPar' (x:x':xs) = (M.unionWith (+) x x' |:| mapUnionPar' xs)
mapUnionPar' x = x

newPar :: FilePath - IO (M.Map LB.ByteString Int)
newPar = ((mapUnionPar . parMap rwhnf (foldl' count M.empty) . 
chunkify . LB.lines) `fmap`) . LB.readFile
where chunkify = unfoldr (\x - if null x then Nothing else Just 
(splitAt 512 x))


main = mapM_ ((print . fst . foldl' takeTop ([],[]) . M.toList =) 
. newPar) = getArgs
where takeTop ac@(bs,low) a = if null low || (snd . head) low  snd 
a then (splitAt 10 . insertBy ((. snd) . flip compare . snd) a) bs 
else ac



On Nov 7, 2007, at 9:06 AM, Bayley, Alistair wrote:


From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of manu

Haskell is conspicuously absent from the languages used to tackle Tim



Bray's Wide Finder problem

(http://www.tbray.org/ongoing/When/200x/2007/10/30/WF-Results?updated). 


So far we have Ocaml, Erlang, Python, Ruby, etc...


Tim Bray mentions that GHC won't build on Solaris, so presumably that
problem would need to be solved before Haskell appears in his table. I
see that there are Solaris binary packages:
http://www.haskell.org/ghc/download_ghc_661.html#sparcsolaris

so perhaps he just needs to be pointed to them?

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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
You didn't do a whole lot when I tried to run it. I know I am being 
mean, but that seems to be what Tim Bray is doing. He takes code and 
if it doesnt work, he isn't spending 3 weeks to figure it out.


So, I would just like to comment. I ran your code against an 
access.log file and it gave me this:


[]

./a.out access.log





Which data set did you test it on?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Disable echo in POSIX terminal

2007-11-10 Thread Henning Thielemann

On Fri, 9 Nov 2007, Derek Elkins wrote:

 Pointless frobbing but is there any issue with setting the echo to False
 when it is already False?  Otherwise not checking seems to both simpler
 and quicker (not that performance matters), i.e.
 getpasswd h = do
 wasEnabled - hGetEcho h
 hSetEcho h False
 str - hGetLine h
 hSetEcho wasEnabled
 return str

Should one enclose this in 'bracket'?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sinus in Haskell

2007-11-10 Thread Henning Thielemann

On Sat, 10 Nov 2007, Daniel Fischer wrote:

 Since you seem to know a lot about these things, out of curiosity, do you know
 how these functions are actually implemented? Do they use Taylor series or
 other techniques?

I think that for sin and cos the Taylor series are a good choice.  For
other functions like the square root, exponential, logarithm, inverse
trigonometric functions the CORDIC algorithms are to be prefered. They are
like a division, both in the idea and the speed.

http://en.wikipedia.org/wiki/CORDIC

E.g.
  exp(x1+x2+x3+...+xn) = exp(x1) * exp(x2) * ... * exp(xn)
 now you choose x1, x2, ..., xn such that exp(xi) is a number that allows
a simple multiplication.
 x1 = ln(1.1 bin)
 x2 = ln(1.01 bin)
 x3 = ln(1.001 bin)
  Multiplying with xi is just a shift and a sum. You only need to
precompute and store the xi.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sinus in Haskell

2007-11-10 Thread Jules Bean

Brent Yorgey wrote:


More generally, this is due to the fact that floating-point numbers can 
only have finite precision, so a little bit of rounding error is 
inevitable when dealing with irrational numbers like pi.   This problem 
is in no way specific to Haskell.


But some systems always display to a slightly lower precision than they 
calculate. Some pocket calculators work like this, and I suspect some 
programming languages might. You can conceal the first few instances of 
rounding errors this way (until they get a bit bigger and punch through 
your reduced precision).


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


[Haskell-cafe] FW: please help... small problem

2007-11-10 Thread Ryan Bloor
hi
 
I've attempted to cut down this module... but I cannot see where... can someone 
help... 
 
Ryan 
 
thanks


From: [EMAIL PROTECTED]: Subject: FW: please help... small problemDate: Fri, 9 
Nov 2007 21:57:30 +


sorry heres the code I always do that.


From: [EMAIL PROTECTED]: Subject: please help... small problemDate: Fri, 9 Nov 
2007 21:44:35 +

hi Is there anyway to cut down this code and to not use auxillary functons, but 
instead use pattern matching? The code basically splits up a list 'rslis' into 
a list of lists - but so each word is split up and the integers have been 
parsed. so [hi ryan 1,hi jeff 2] becomes [[hi,ryan 1], 
[hi,jeff, 2]].The code is far too long. I don't wanna use premade functions 
too much... pattern matching is required.  Ryan

The next generation of MSN Hotmail has arrived - Windows Live Hotmail 

Are you the Quizmaster? Play BrainBattle with a friend now! 
_
100’s of Music vouchers to be won with MSN Music
https://www.musicmashup.co.uk

Football.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Sinus in Haskell

2007-11-10 Thread jerzy . karczmarczuk
Carl Witty writes: 


On Sat, 2007-11-10 at 01:29 +0100, Daniel Fischer wrote:
... do you know 
how these functions are actually implemented? Do they use Taylor 
series or other techniques?


I don't really know that much about it; 
... It seems likely that this instruction (and library

implementations on architectures where sin is not built into the
processor) use Taylor series, but I don't know for sure.


== 

No, Gentlemen, nobody rational would use Taylor nowadays! It is lousy. 


First, Chebyshev approximations give better *uniform convergence*.
Then, a *rational* approximation gives you the same precision with
less coeffs. Nowadays the division is not sooo much more expensive
than the multiplication, so the efficiency doesn't suffer much. 

Then, you have plenty of recursive formulae, for example: 

sin 3x = 3*sin x - 4*(sin x)^3 


which converges as it does, x - x/3 for one step... There are more
complicated as well. Of course, for x sufficiently small use other
approx., e.g. sin x =  x. 


Finally, you have CORDIC (Volder, 1959).
Original CORDIC may be used for tan(x), then sin=tan/sqrt(1+tan^2), and
the square root can be obtained by Newton, *real fast*. 


CORDIC is explained everywhere, if you want to learn it. Start with
Wikipedia, of course... 

Jerzy Karczmarczuk 



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


[Haskell-cafe] recursion issues...

2007-11-10 Thread Ryan Bloor
hiya
 
I was wondering how I would get the second function do recursively do the 
function for poolNews xs tried that and it fails. 
 
Ryan
 
 
--Give wins, draws a rating.
 
poolNews :: Result - PoolNews - PoolNews
poolNews (a,b,c,d,e) (home,away,goaless,scoredraw) 
 | c  d = (home+1,away,goaless,scoredraw) 
 | c  d = (home,away+1,goaless,scoredraw)  
 |(c == 0)  (d == 0) = (home+1,away,goaless+1,scoredraw) 
  | otherwise = (home,away,goaless,scoredraw+1)
 

--Do for all Results
poolNewsB :: Results - PoolNews
poolNewsB (x:xs) = poolNews x (0,0,0,0)
_
Celeb spotting – Play CelebMashup and win cool prizes
https://www.celebmashup.com___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Some More Sinus Results

2007-11-10 Thread Hans van Thiel
Thanks to all who've replied; Carl's explanation in particular was very
interesting. So the precision, suggested by the many decimals in the
'show', is not the actual precision the user should 'count on'. If you
take 1/60 of a degree to be approximately 0.0003 radians, you should not
use sin for smaller values. In all cases the actual precision of sin
appears to be 4 to 5 decimals, and results should be rounded to that
before using them. Now I'm wondering about cos, tan and also the
inverses, asin etc. :-)

Regards,
Hans van Thiel

Hugs sin (1.000 * pi)
1.22460635382238e-16
Hugs sin (0.999 * pi)
0.00314158748587949
Hugs sin (1.1 * pi)
-3.14159265309255e-05
Hugs sin (0.9 * pi)
3.14159265307264e-05
Hugs sin (1.001 * pi)
-0.00314158748587925
Hugs sin (0.999 * pi)
0.00314158748587949
Hugs sin (1.0001 * pi)
-0.000314159260191213
Hugs sin (0. * pi)
0.000314159260191458
Hugs sin (1.1 * pi)
-3.14159265309255e-05
Hugs sin (1.0001 * pi)
-0.000314159260191213
Hugs sin (0. * pi)
0.000314159260191458
Hugs sin (1.1 * pi)
-3.14159265309255e-05
Hugs sin (0.9 * pi)
3.14159265307264e-05
Hugs sin (6.0001 * pi)
0.000314159260189269
Hugs sin (5. * pi)
-0.000314159260190738
Hugs sin (6.1 * pi)
3.14159265298692e-05
Hugs sin (5.9 * pi)
-3.14159265313387e-05
Hugs sin pi
1.22460635382238e-16

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


[Haskell-cafe] Trouble using unboxed arrays

2007-11-10 Thread Justin Bailey
I would like to create a data structure that uses an unboxed array as
one of its components. I would like the data structure to be
parameterized over the type of the elements of the array. Further, I'd
like to build the array using runSTUArray. I can't make the code work
though. My naive approach:

  data Ring a = Ring (UArray Int a)

and the code to make the array:

  makeArray :: [a] - Ring a
  makeArray ls = Ring (ST.runSTUArray (ST.newListArray (0, length ls - 1) ls))

But that doesn't work. I get from GHC (6.8.1):

  Could not deduce (MArray (STUArray s) a (ST s)) from the context ()
arising from a use of `newListArray'

I am pretty sure I need to constrain 'a' to primitive types only, but
how? Can I do it in the data definition?

Thanks in advance for any help!

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


Re: [Haskell-cafe] Some More Sinus Results

2007-11-10 Thread David Roundy
On Sat, Nov 10, 2007 at 06:56:23PM +0100, Hans van Thiel wrote:
 Thanks to all who've replied; Carl's explanation in particular was very
 interesting. So the precision, suggested by the many decimals in the
 'show', is not the actual precision the user should 'count on'. If you
 take 1/60 of a degree to be approximately 0.0003 radians, you should not
 use sin for smaller values. In all cases the actual precision of sin
 appears to be 4 to 5 decimals, and results should be rounded to that
 before using them. Now I'm wondering about cos, tan and also the
 inverses, asin etc. :-)

What you're observing in these calculations is not so much the inaccuracy
of sin as the inaccuracy of pi.  Pi is an irrational number, so the Double
constant pi is only an approximation, with an error probably around 3e-16
(1e-16 fractional error).  Simple calculus tells you that the error in
sin(pi) will thus be around:

sin(truepi+3e-16) ~ 0 + 3e-16

from which we conclude that the error in pi isn't really as bad as we'd
naively expect.

For small epsilon, we can see that

sin((1+/-epsilon)*(truepi+3e-16)) ~ 0 +/- pi*epsilon + 3e-16.

which roughly explains your data quoted.

Results of sin should *not* be rounded before using them, unless you really
want a less accurate answer.

Users who count on a particular precision, should not be using computers
to do their arithmetic.


The blog article on the accuracy of sine glossed over the relevant issue:
that there's no point in getting better accuracy.  It points out that
sin(pi) only has five or six digits of accuracy, it means that the
correct answer is about 1.225e-16, because correct is defined to mean
the sine of the double which is nearest to the actual value of pi.

It's nice to be accurate, but the claim that for large arguments the
computed value of sin is effectively random is pretty irrelevant, as the
same thing can be said of the true value of sin, when defined as the
sine of the double closest to your desired x value which is the closest we
could possibly come to a true sin.  If you're taking the sine of a large
number, your code is broken, and no sin function is going to fix it.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble using unboxed arrays

2007-11-10 Thread Stefan O'Rear
On Sat, Nov 10, 2007 at 11:09:54AM -0800, Justin Bailey wrote:
 I would like to create a data structure that uses an unboxed array as
 one of its components. I would like the data structure to be
 parameterized over the type of the elements of the array. Further, I'd
 like to build the array using runSTUArray. I can't make the code work
 though. My naive approach:
 
   data Ring a = Ring (UArray Int a)
 
 and the code to make the array:
 
   makeArray :: [a] - Ring a
   makeArray ls = Ring (ST.runSTUArray (ST.newListArray (0, length ls - 1) ls))
 
 But that doesn't work. I get from GHC (6.8.1):
 
   Could not deduce (MArray (STUArray s) a (ST s)) from the context ()
 arising from a use of `newListArray'
 
 I am pretty sure I need to constrain 'a' to primitive types only, but
 how? Can I do it in the data definition?
 
 Thanks in advance for any help!

What you're trying to do deliberately can't be done.  Polymorphism has a
runtime cost in GHC, and UArrays must specialize.  That said, have you
heard of Data.Array.IArray.listArray?

Stefan


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


Re: [Haskell-cafe] recursion issues...

2007-11-10 Thread Andrew Wagner
Looks to me like you want:
poolNewsB = foldr poolNews (0,0,0,0)

On Nov 10, 2007 11:54 AM, Ryan Bloor [EMAIL PROTECTED] wrote:

 hiya

  I was wondering how I would get the second function do recursively do the
 function for poolNews xs tried that and it fails.

  Ryan




 --Give wins, draws a rating.



 poolNews :: Result - PoolNews - PoolNews

 poolNews (a,b,c,d,e) (home,away,goaless,scoredraw)

  | c  d = (home+1,away,goaless,scoredraw)

  | c  d = (home,away+1,goaless,scoredraw)

  |(c == 0)  (d == 0) = (home+1,away,goaless+1,scoredraw)

   | otherwise = (home,away,goaless,scoredraw+1)





 --Do for all Results

 poolNewsB :: Results - PoolNews poolNewsB (x:xs) = poolNews x (0,0,0,0)

 
 Get free emoticon packs and customisation from Windows Live. Pimp My Live!
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


[Haskell-cafe] Re: Doubly-linked zipper list w/ insert implementation

2007-11-10 Thread apfelmus

Justin Bailey wrote:

The other day I decided to implement a ring buffer with a current
element (i.e. a doubly-linked zipper list).

[...]

p.s. The original motivation for writing this was to model cellular
automata. The CA world is circular, so that got me thinking about a
structure that made connecting the ends easy to do.


Note that depending on your concrete setting, you may not need a fancy 
ring structure for cellular automata. And with simple automata like


  c'_i = c_(i-1) `xor` c_i `xor` c_(i+1)

it may even be easier to generate fresh rings for each step in the 
automaton:


  data Context a = Context [a] a [a]
  -- rotate left
  rotL (Context ls x (r:rs)) = Context (x:ls) r rs

  -- description of a cellular automaton
  type Rule a= Context a - a
  example :: Rule Bool
  example (Context (cm:_) c (cp:_)) = cm `xor` c `xor` cp

  -- run a cellular automaton on an initial band of cells
  --   which is considered to be cyclic, i.e. a cylinder
  automate :: Rule a - [a] - [[a]]
  automate f xs = iterate (take n . map f . mkContexts) xs
where
-- length of the cell band
n = length xs

mkContexts (x:xs)= iterate rotL $
Context (cycle $ reverse xs) (head xs) (tail $ cycle xs)

Here,  mkContexts xs  initializes a new infinite cyclic ring for  xs 
and rotates it left ad infinitum.



Regards,
apfelmus

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


[Haskell-cafe] Queues and Rings (Re: Doubly-linked zipper list w/insert implementation)

2007-11-10 Thread apfelmus
(Btw, this ring stuff could be relevant for Xmonad, I don't know whether 
the workspace/window-ring implementation there is O(1). Not that it 
matters for 1000 windows, of course :)


Justin Bailey wrote:

apfelmus wrote:


Do you really need to realize the cycle by sharing? I mean, sharing
doesn't go well with insertion / updates / deletion since each of these
operations breaks it and needs to restore it everywhere. In other words,
your  insert  takes O(n) time. I'd simply drop the sharing and use two
double ended queues (or something like that) instead


Very good point, and much easier to implement with Data.Sequence to
boot. All that circular programming made my brain hurt.


There's also a direct and rather lightweight possibility to implement 
rings in the spirit of the classic O(1) lazy amortized functional queue 
implementation. This post will try to explain it.


Here's the basic idea for implementing queues in Haskell: we have a 
front  list to fetch items (head, tail) and a  rear  list to insert 
items (snoc) into the queue.


  data Queue a = Queue [a] [a]

  empty= Queue [] []
  head (Queue (x:f) r) = x
  tail (Queue (x:f) r) = Queue f r
  snoc (Queue f r) x   = Queue f (x:r)

Of course, this doesn't quite work yet, at some point we have to feed 
the items from the rear list into the front list. For example, the last 
possibility to do so is when the front list becomes empty.


  balance (Queue [] r) = Queue (reverse r) []
  balance q= q

  tail (Queue (x:f) r) = balance $ Queue f r
  snoc (Queue f r) x   = balance $ Queue f (x:r)

(Calling  balance  maintains the invariant that the front list is never 
empty except when the whole queue is empty, too.) Now, how much time 
will a single  snoc  or  tail  operation take? In the worst case, tail 
triggers a  reverse  and takes O(n) time whereas  snoc  always takes 
constant time. That's a big blow to our goal of O(1) time for both.


But luckily, queues don't come out of thin air, they all have to be 
constructed from the empty queue by a sequence of applications of snoc 
and  tail . Can the heavy O(n) cost of a worst case  tail  be spread 
over  the many good cases of  tail  and  snoc  in that sequence? Yes, it 
can. To that end, we increase the price of each  snoc  by 1 time coin. 
So, each item of the rear list gets inserted with one extra coin as 
credit. With these credits, we can pay the whole  length (rear list) 
cost of a reverse operation when it occurs, making  tail  O(1) again. 
This is also called _amortization_  and O(1) the _amortized_ cost of  tail .


The above works fine if the queue is used in a single-threaded way i.e. 
as _ephemeral_ data structure. But it doesn't work anymore when a queue 
is used multiple times in a _persistent_ setting. Assuming that  tail q 
 triggers a  reverse , the first evaluation of  q1  in


  let
 q1 = tail q
 q2 = tail q
 q3 = tail q
 ...
  in ... q1 .. q2 .. q3

will use up all credits and  q2, q3,...  don't have any to spend and are 
back to worst-case behavior.


In the persistent setting, lazy evaluation comes to the rescue. The idea 
is to create the (yet unevaluated) call to  reverse  earlier, namely 
when the rear list has more elements than the front list.


  balance (Queue f r)
 | length r = length f = Queue (f ++ reverse r) []
  balance q = q

(We assume that  length  has been made O(1) by storing the lengths 
explicitly.) Now, the O(length r)  reverse  will not be evaluated before 
having tailed through the previous front list with  length f == length 
r  items. Thus, we can spread the cost of  reverse  as debits over 
these elements. When finally executing  reverse , its debits have 
already been paid off and  tail  is O(1) again. And once executed, lazy 
evaluation memoizes the result, so that sharing doesn't duplicate the work.
(Note that strict languages without side effects are doomed to be slower 
when persistence matters. Ha! ;)


So much for a too short introduction to the classic purely functional 
queue implementation. For a detailed exposition and much more, see also


  Chris Okasaki. Purely Functional Data Structures. (Thesis)
  http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf

or his book with the same title which arose from this thesis.


Now, rings can be implemented in a similar style.

  data Ring a = Ring [a] a [a]

  rotL (Ring ls x (r:rs)) = balance $ Ring (x:ls) r rs
  rotR (Ring (l:ls) x rs) = balance $ Ring ls l (x:rs)

(For simplicity, we only deal with the case where the left and right 
list are non-empty.)
How to balance? In contrast to queues, doing a full  reverse  when one 
list is empty doesn't even work in the ephemeral case since a  rotR 
following a  rotL  will undo the  reverse  with yet another expensive 
reverse . But we can apply the same idea as for persistent queues and 
balance as soon as one list becomes like 2 times (or 3 or whatever) as 
large as the other one


  balance (Ring ls x rs)
| length 

[Haskell-cafe] Re: some links broken in 6.8.1 documentation

2007-11-10 Thread Ian Lynagh

Hi Daniil,

On Sun, Nov 04, 2007 at 03:49:54PM +0300, Daniil Elovkov wrote:
 
 A quick look at the 6.8.1 user's guide reveals some broken links:
 
 1)
 Obtaining code coverage, pointing to
 http://haskell.org/ghc/docs/6.8.1/html/users_guide/hpc.html
 
 redirects to http://projects.unsafeperformio.com/hpc.html which tells
 that it's not found but guesses at another location, where it is
 found.

I can't see any link to http://projects.unsafeperformio.com/hpc.html in
the users guide - am I missing something?

 2)
 Concurrent and parallel haskell
 http://haskell.org/ghc/docs/6.8.1/html/users_guide/lang-parallel.html
 (and possibly other pages)
 
 have links to libraries according to the pre-base-split structure,
 like .../base/.. instead of .../parallel/..., which results in those
 links being broken.

Thanks; I've filed a bug here:
http://hackage.haskell.org/trac/ghc/ticket/1864


Thanks
Ian

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


Re: [Haskell-cafe] Re: Doubly-linked zipper list w/ insert implementation

2007-11-10 Thread Justin Bailey
On Nov 10, 2007 12:24 PM, apfelmus [EMAIL PROTECTED] wrote:
 Note that depending on your concrete setting, you may not need a fancy
 ring structure for cellular automata. And with simple automata like

I realized that I never updated my automata once a row was created,
and ended up using an unboxed array with an index to represent the
ring. I just do some math when I want to rotate left or right and
the index falls off the edge.

The rules are much more complex though. I am using a genetic algorithm
technique to evolve 7 bit rules which can classify if an initial row
was mostly black or mostly white. This is loosely related to a class
assignment.

I'm finding that taking 100 initial rules, determining their fitness
on 100 initial automatas, and doing that for 100 generations is taking
a lng time. Our teacher's implementation, in C, does it in about a
minute. Mine takes hours :( . I think its becuase the C algorithm does
a lot of bit-twiddling to iterate the automata, while I'm using lists
of integers (1, 0).

Anyways, thanks for your thoughts!

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


Re: [Haskell-cafe] Some More Sinus Results

2007-11-10 Thread Hans van Thiel
On Sat, 2007-11-10 at 11:14 -0800, David Roundy wrote:
 On Sat, Nov 10, 2007 at 06:56:23PM +0100, Hans van Thiel wrote:
  Thanks to all who've replied; Carl's explanation in particular was very
  interesting. So the precision, suggested by the many decimals in the
  'show', is not the actual precision the user should 'count on'. If you
  take 1/60 of a degree to be approximately 0.0003 radians, you should not
  use sin for smaller values. In all cases the actual precision of sin
  appears to be 4 to 5 decimals, and results should be rounded to that
  before using them. Now I'm wondering about cos, tan and also the
  inverses, asin etc. :-)
 
 What you're observing in these calculations is not so much the inaccuracy
 of sin as the inaccuracy of pi.  Pi is an irrational number, so the Double
 constant pi is only an approximation, with an error probably around 3e-16
 (1e-16 fractional error).  Simple calculus tells you that the error in
 sin(pi) will thus be around:
 
 sin(truepi+3e-16) ~ 0 + 3e-16
 
 from which we conclude that the error in pi isn't really as bad as we'd
 naively expect.
 
 For small epsilon, we can see that
 
 sin((1+/-epsilon)*(truepi+3e-16)) ~ 0 +/- pi*epsilon + 3e-16.
 
 which roughly explains your data quoted.
 
 Results of sin should *not* be rounded before using them, unless you really
 want a less accurate answer.
 
 Users who count on a particular precision, should not be using computers
 to do their arithmetic.
A limitation in the technology, which derives from the floating point
representation, should not become a norm, IMHO. Every engineering
discipline uses error approximation and calculation of the
cumulation/cancelation of those errors to estimate the reliability of
the total. That's if you use a slide rule, that's if you use a computer.
There's no difference. If you mean that people should not do arithmetic
on computers, if the results are vital, unless they understand the scope
and limits of the tools they're using, I agree, of course.

 The blog article on the accuracy of sine glossed over the relevant issue:
 that there's no point in getting better accuracy.  It points out that
 sin(pi) only has five or six digits of accuracy, it means that the
 correct answer is about 1.225e-16, because correct is defined to mean
 the sine of the double which is nearest to the actual value of pi.
 
 It's nice to be accurate, but the claim that for large arguments the
 computed value of sin is effectively random is pretty irrelevant, as the
 same thing can be said of the true value of sin, when defined as the
 sine of the double closest to your desired x value which is the closest we
 could possibly come to a true sin.  If you're taking the sine of a large
 number, your code is broken, and no sin function is going to fix it.

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


Re: [Haskell-cafe] FW: please help... small problem

2007-11-10 Thread Yitzchak Gale
Hi Ryan,

You wrote:
  I've attempted to cut down this module... but I cannot see where... can
 someone help...

You don't need wordToInt - just use read instead.

Look at the type of the function map in the Prelude -
you can use it to get rid of method and test.
After that, your program will be very short.
Try it!

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


Re: [Haskell-cafe] Some More Sinus Results

2007-11-10 Thread Yitzchak Gale
Hans van Thiel wrote:
 If you mean that people should not do arithmetic
 on computers, if the results are vital, unless they understand the scope
 and limits of the tools they're using, I agree, of course.

My brother used to work for a certain well-known
manufacturer of CPUs. He told me that the engineers
who worked on the FPU would never fly in a
commercial airliner. Hmm...

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


[Haskell-cafe] C++ vs. Haskell: Type-Level Death Match

2007-11-10 Thread Don Stewart
http://www.rubinsteyn.com/template_insanity.html

The C++ response to Conrad's 'instant insanity' type program from the
last Monad.Reader !

Can we do better still with the planned type-level programming of type
families?

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


Re: [Haskell-cafe] recursion issues...

2007-11-10 Thread Brent Yorgey
On Nov 10, 2007 11:54 AM, Ryan Bloor [EMAIL PROTECTED] wrote:

 hiya

 I was wondering how I would get the second function do recursively do the
 function for poolNews xs tried that and it fails.

 Ryan



 --Give wins, draws a rating.



 poolNews :: Result
 *-* PoolNews *-* PoolNews

 poolNews (a,b,c,d,e) (home,away,goaless,scoredraw)

  | c  d = (home+1,away,goaless,scoredraw)

  | c  d = (home,away+1,goaless,scoredraw)

  |(c == 0)  (d == 0) = (home+1,away,goaless+1,scoredraw)

   |
 *otherwise* = (home,away,goaless,scoredraw+1)



 --Do for all Results

 poolNewsB :: Results
 *-* PoolNews poolNewsB (x:xs) = poolNews x (0,0,0,0)


As Andrew points out, really what you want is a fold.  However, perhaps
you're not supposed to use such Prelude functions in your assignment?  The
real issue here is that your definition of poolNewsB does not do anything
with xs.  You need to somehow incorportate a recursive call that will
process the rest of the list (xs) as well as the first item (x).

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


Re: [Haskell-cafe] Trouble using unboxed arrays

2007-11-10 Thread Bulat Ziganshin
Hello Justin,

Saturday, November 10, 2007, 10:09:54 PM, you wrote:

   makeArray :: [a] - Ring a
   makeArray ls = Ring (ST.runSTUArray (ST.newListArray (0, length ls - 1) ls))

unboxed arrays in std library are not polymorphic, look at
http://haskell.org/haskellwiki/Library/ArrayRef

ps: as Stefan said, you will get very low performance with polymorphic
code without 100% inlining


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] O'Reilly Real World Haskell book

2007-11-10 Thread Galchin Vasili
Hello,

 What is the proposed table of contents for Real World Haskell?

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


Re: [Haskell-cafe] O'Reilly Real World Haskell book

2007-11-10 Thread Thomas Schilling
On Sat, 2007-11-10 at 17:50 -0600, Galchin Vasili wrote:
 Hello,
 
  What is the proposed table of contents for Real World Haskell?

http://www.realworldhaskell.org/blog/2007/05/23/real-world-haskell-its-time/

as of May 2007

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


[Haskell-cafe] GHC 6.8.1 Documentation

2007-11-10 Thread Cale Gibbard
Hello all,

Recently I noticed that all of my bookmarks to the hierarchical
libraries documentation broke, and I'm not entirely happy with the
solution of just correcting all the links to point at the new URLs
since the URLs all have package version numbers in their names, which
means that I'll have to update them all over again next time. Is there
any chance we could get stable URLs for the latest version of each
module somewhere? (Perhaps via symlinks on the webserver?)

I also noticed that the links to the source code seem to be missing
from all the 6.8.1 Haddock docs now, which is something that I used
quite a lot in the past. It'd be nice to have those back.

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


Re: [Haskell-cafe] Sinus in Haskell

2007-11-10 Thread ajb

G'day all.

Quoting [EMAIL PROTECTED]:


== No, Gentlemen, nobody rational would use Taylor nowadays! It is
lousy.


This is correct.  Real implementations are far more likely to use the
minmax polynomial of some order.  However...


Then, a *rational* approximation gives you the same precision with
less coeffs. Nowadays the division is not sooo much more expensive
than the multiplication, so the efficiency doesn't suffer much.


It might not cost much in the way of time, but it might complicate the
implementation a lot.  Using polynomials only probably uses a smaller
number of transistors, disspiate less power and for all I know might be
easier to parallelise than the alternatives.

In general, if you can implement FP operations without using microcode,
that's a big win.

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


[Haskell-cafe] Re: Flymake Haskell

2007-11-10 Thread Daisuke IKEGAMI
[EMAIL PROTECTED]
[EMAIL PROTECTED]
[EMAIL PROTECTED]
Mime-Version: 1.0
Content-Type: Text/Plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Hi,

Stefan wrote:
 I looked at http://www.emacswiki.org/cgi-bin/emacs/FlymakeHaskell
 but it's not clear what's going on.

I've been written the instruction of Flymake Haskell for both Emacs21 
and Emacs22 at;
  http://www.emacswiki.org/cgi-bin/emacs/FlymakeHaskell

Note that it will not work in the future, since the flymake-mode
has been developed so actively.

I'm not a native English speaker. Please fix typo or inappropriate 
expressions. I wish it helps to write Haskell code on Emacs.

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


Re: [Haskell-cafe] WideFinder

2007-11-10 Thread Sterling Clover
http://www.tbray.org/tmp/o10k.ap is the basic data set. For heavier  
duty testing, folks seem to be appending it to itself 99 more times  
to yield a o1000k.ap dataset. I'd be curious for comments on my  
code or other suggestions to speed things up -- the strictness  
semantics of the mapUnionPar function seem pretty decent to me, but  
I'd like to find a way to give higher preference to evaluating later  
iterations of until as opposed to earlier ones (so as to improve  
memory performance) but can't think of any way to do that without  
explicit threads. Implementing memory mapped reads, as was suggested  
here recently in a different context, might be another big  
performance gain.


On my decidedly not powerful machine (Mac PowerPC G5, 1.8GHz) I can't  
get much lower than 12.25s for the 1000k dataset (out of which,  
roughly 3s in GC), which is 192M, which is actually slower than his  
sample ruby implementation. :-(. I'm sure parallel processing will  
help quite a bit, however, as profiling indicates that most time is  
spent in the count function. Maps are a good choice for parallelism  
because they merge efficiently, but for the iterative aspect their  
performance leaves a lot to be desired. This seems evident in that  
even on a single processor, lower sizes of chunks, at least to a  
point, still improve overall performance, although this may possibly  
be equally an issue with space efficiency.


I wonder if Haskell's lack of an efficient hashtable isn't hurting it  
here again too, but on the other hand for a real efficiency gain,  
switching to a custom-built trie that combined pattern matching and  
insertion into a single operation would probably be a significant  
win, and it would let us force unboxing ints too, for whatever that  
gains.


--S

On Nov 10, 2007, at 3:36 AM, Berlin Brown wrote:



Which data set did you test it on?


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


Re: [Haskell-cafe] WideFinder

2007-11-10 Thread Don Stewart
s.clover:
 http://www.tbray.org/tmp/o10k.ap is the basic data set. For heavier  
 duty testing, folks seem to be appending it to itself 99 more times  
 to yield a o1000k.ap dataset. I'd be curious for comments on my  
 code or other suggestions to speed things up -- the strictness  
 semantics of the mapUnionPar function seem pretty decent to me, but  
 I'd like to find a way to give higher preference to evaluating later  
 iterations of until as opposed to earlier ones (so as to improve  
 memory performance) but can't think of any way to do that without  
 explicit threads. Implementing memory mapped reads, as was suggested  
 here recently in a different context, might be another big  
 performance gain.
 
 On my decidedly not powerful machine (Mac PowerPC G5, 1.8GHz) I can't  
 get much lower than 12.25s for the 1000k dataset (out of which,  
 roughly 3s in GC), which is 192M, which is actually slower than his  
 sample ruby implementation. :-(. I'm sure parallel processing will  
 help quite a bit, however, as profiling indicates that most time is  
 spent in the count function. Maps are a good choice for parallelism  
 because they merge efficiently, but for the iterative aspect their  
 performance leaves a lot to be desired. This seems evident in that  
 even on a single processor, lower sizes of chunks, at least to a  
 point, still improve overall performance, although this may possibly  
 be equally an issue with space efficiency.
 
 I wonder if Haskell's lack of an efficient hashtable isn't hurting it  
 here again too, but on the other hand for a real efficiency gain,  
 switching to a custom-built trie that combined pattern matching and  
 insertion into a single operation would probably be a significant  
 win, and it would let us force unboxing ints too, for whatever that  
 gains.

Did you also try Bryan O'Sullivan's smp code, btw?


http://www.serpentine.com/blog/2007/09/25/what-the-heck-is-a-wide-finder-anyway/

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


Re: [Haskell-cafe] WideFinder

2007-11-10 Thread Bryan O'Sullivan

Sterling Clover wrote:

Maps are a good choice for parallelism because they merge 
efficiently, but for the iterative aspect their performance leaves a lot 
to be desired.


This is not consistent with my observations, I must say.

What I've found to dominate the benchmark are straightforward string 
search and manipulation.


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


[Haskell-cafe] How to do this in Haskell

2007-11-10 Thread Chris Smith
If you wanted to write a Haskell application that included a WYSIWYG 
HTML editor, how would you do it?

More details:

- I'll probably be using Gtk2Hs for the app, though that could change 
with a (very) good reason.

- The top priorities for the editor are that it resemble common word 
processors in editing functions, and that the display looks as near as 
possible to what can be expected from some major browser such as FireFox 
or IE.  If it's not possible to do extremely well in both of these 
criteria, then I may as well abandon the project now.

- I'd like for the result to be cross-platform, but Windows-only would 
be just as good from my boss's perspective.

So, with all that in mind, I'm looking for options.  What looks most 
realistic that I've found to date is building an XP-COM implementation 
for Haskell via the FFI and either a code generation tool or Template 
Haskell, and then using that to try to embed the Mozilla editor 
component.  Given my serious lack of knowledge in XP-COM or the Mozilla 
project or GTK, that looks sort of scary.

Any other ideas?

-- 
Chris Smith

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