[Haskell-cafe] replicateM over vectors

2010-04-01 Thread Scherrer, Chad
Hi,

I'd like to be able to do replicateM, but over a vector instead of a list. 
Right now I'm doing this:
 
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Unboxed.Mutable as M
replicateM n action = do
  mu - M.unsafeNew n
  let go !i | i  n = action = M.unsafeWrite mu i  go (i+1)
 | otherwise = G.unsafeFreeze mu
  go 0

I thought it might be useful to express this in terms of the available 
primitives, since this might fuse more easily, but I don't yet see a way to do 
it.

Is there a better (more elegant and/or faster) way to write this?

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


RE: [Haskell-cafe] mapping unfreeze over an IntMap of IOUArrays

2008-11-11 Thread Scherrer, Chad
Bulat wrote:
 Hello Chad,
 
 Tuesday, November 11, 2008, 10:23:09 PM, you wrote:
  using unsafeFreeze. I'm getting stuck here, since the 
 IntMap library 
  is not so monad-friendly.
 
 Data.Hashtable is

Well, I need mutable update for a while... after that, I prefer a pure
interface, which is why I'm trying to freeze all the values. 

Anyway, I haven't used hashtables in Haskell, but I vaguely remember
some discussion about them being really slow. Is this no longer the
case?

I guess if I really need to go this route I could try out HsJudy or
something.

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


[Haskell-cafe] Trouble with Cabal

2006-05-22 Thread Scherrer, Chad
Thanks to all who responded about the benefits of using Cabal. After
trying out Bulat's Streams library, I thought I would download
ByteString (aka FPS) to compare the wc demos. To compile something using
Streams, I need to use a -i flag (thanks Bulat). When I followed the
README that comes with ByteString, I get this:

%  ./Setup.hs install
Installing: /f/g/lib/fps-0.7  /f/g/bin fps-0.7...
*** Exception: /f: createDirectory: permission denied (Permission
denied)

I don't have root on this machine, and it's not obvious (to me) how to
specify that everything should be installed locally. Any suggestions?

Thanks,

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Trouble with Cabal

2006-05-22 Thread Scherrer, Chad
 -Original Message-
 From: Henning Thielemann [mailto:[EMAIL PROTECTED] 
 
 Install locally after configuring this way:
   ./Setup.lhs configure --user --prefix=$HOME/yourlocalhaskelllibsdir
 

That seemed to do fine until it came to registering the package, which I
don't permission for. Any way around this?

Thanks,

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx 

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


RE: [Haskell-cafe] Trouble with Cabal

2006-05-22 Thread Scherrer, Chad
Ok, it works now. Thanks for the help!

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx 

 -Original Message-
 From: Lemmih [mailto:[EMAIL PROTECTED] 
 Sent: Monday, May 22, 2006 10:41 AM
 To: Scherrer, Chad
 Cc: Henning Thielemann; haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Trouble with Cabal
 
 On 5/22/06, Scherrer, Chad [EMAIL PROTECTED] wrote:
   -Original Message-
   From: Henning Thielemann [mailto:[EMAIL PROTECTED]
  
   Install locally after configuring this way:
 ./Setup.lhs configure --user 
   --prefix=$HOME/yourlocalhaskelllibsdir
  
 
  That seemed to do fine until it came to registering the 
 package, which 
  I don't permission for. Any way around this?
 
 Run:
   ./Setup.lhs install --user
 
 --
 Friendly,
   Lemmih
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell] parallel seq

2006-04-25 Thread Scherrer, Chad
I was thinking about the dynamic behavior of par, and there's something
that's a little confusing to me. Am I right in understanding that (x
`par` y) evaluates to y, and may or may not evaluate x along the way? 

I think it would be easier to reason about if we knew that x would be
evaluated, either by a newly-spawned thread or by the parent thread. If
I'm understanding this correctly, this could be done by defining

x `pSeq` y = x `par` y `seq` x `seq` y
(seq has higher precedence than par)

When (x `pSeq` y) is evaluated, x may or may not be evaluated by a new
thread. The parent thread continues along evaluating y. Then the parent
makes sure x was evaluated before finally returning y.

I've not seen this approach used before -- Is there something I'm
missing that makes using pSeq as above just silly?

Thanks!

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] Packed String parameters

2006-01-19 Thread Scherrer, Chad
Thanks, Bulat. Taking a look at Hal's FastIO library now...

Hal, it looks like your library could be helpful, especially if there is
a way to construct a FastIO.Handle from stdin. Can this be done, or do I
need to start with an actual file?

Thanks,
Chad


Hello Chad,

Thursday, January 19, 2006, 1:09:38 AM, you wrote:

SC parameter. The input file is over 1 million lines long. Any ideas?

see at the BlockIO and FastIO libraries

http://cryp.to/blockio/blockio-2004-10-10.tar.gz
http://www.isi.edu/~hdaume/haskell/FastIO.tar.gz



-- 
Best regards,
 Bulatmailto:bulatz at HotPOP.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Packed String parameters

2006-01-18 Thread Scherrer, Chad
To read a file using a packed string, I need to use this function,
right?

hGetPS :: Handle - Int - IO PackedString

What's the Int? Do you have to specify the length in advance? I don't
know how packed strings are implemented, and I'm having trouble finding
much documentation.

I'm trying to speed up this horribly slow thing:

dot :: [Double] - [Double] - Double
dot x y = sum $ zipWith (*) x y

main = getContents = sequence_ . map (print . dot weights . map read .
words) . lines

The idea is to take a dot product of each line of a file with a fixed
vector of weights, and send the result to stdout. I thought
PackedString's might help, but I'm not sure what to do with that
parameter. The input file is over 1 million lines long. Any ideas?

Thanks,

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] RE: Haskell vs. Clean

2006-01-05 Thread Scherrer, Chad
Daniel,

My knowledge of Clean is fairly limited (even more so than my knowledge
of Haskell), but no one seems to be responding to this, so I'll take a
crack at it. Here is why I've stuck with Haskell instead of Clean:

1. It runs well on Linux
2. The license is more open
3. There is a (comparatively) large, active research community
4. Mailing list support is very good (haven't looked at Clean's for
this)
5. It strikes me as more elegant

Clean does seem to have a claim to speed. But given (3) and the fact
that the languages are, after all, fairly similar, I wonder if (and hope
that) Haskell may be able to make similar claims before long. 

Actually, this makes me wonder... Is Clean's claim to speed due to raw
performance being a very high priority for its implementers, or is there
something inherent in its semantics that will always give it an edge?
Will Haskell be able to catch up?

Chad



Daniel Carrera daniel.carrera at zmsl.com wrote:
Hi all,

How would you compare Haskell and Clean? It looks like they are both 
pure functional languages with very similar syntax. It also appears that

Clean is faster than Haskell, it appears to be fairly fast. I'm curious 
to learn about relative advantages and disadvantages of each.


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


RE: [Haskell-cafe] RE: Haskell vs. Clean

2006-01-05 Thread Scherrer, Chad
Interesting. Have there been any performance comparisons vs GHC et al?

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx 

 -Original Message-
 From: Neil Mitchell [mailto:[EMAIL PROTECTED] 
 Sent: Thursday, January 05, 2006 1:58 PM
 To: Scherrer, Chad
 Cc: [EMAIL PROTECTED]; haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] RE: Haskell vs. Clean
 
 Hi
 
  My knowledge of Clean is fairly limited
 Mine too, but one of the biggest differences is that Clean 
 has uniqueness types instead of Monads.
 
 They are in fact so similar that you can convert between them, using
 Hacle: http://www-users.cs.york.ac.uk/~mfn/hacle/
 
 I believe also that Clean has a lot more facilities for 
 strictness annotations, which may help with the speed.
 
 Thanks
 
 Neil
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Shootout favoring imperative code

2006-01-04 Thread Scherrer, Chad
Several people on this list have said that the shootout favors imperative code. 
Is this really the case? Why is it Clean seems to have no trouble (for the 
incomplete set of benchmarks that are written in it)?

http://shootout.alioth.debian.org/clean.php

How difficult would it be to translate the Clean algorithms into Haskell?

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


RE: [Haskell-cafe] Shootout favoring imperative code

2006-01-04 Thread Scherrer, Chad
 --- Sebastian Sylvan [EMAIL PROTECTED]
 wrote:
 Some of the problems seem to be heavily geared towards an 
 imperative *implementation*, meaning that a Haskell version 
 is hardly idiomatic Haskell (and as such I , and I suspect 
 otehrs, really have no inclination to work on it).

This may be correct, but it still doesn't address the question. 
Why does Clean fare so much better? Clean is purely functional, right?

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx 

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


RE: [Haskell-cafe] RE: module names

2005-12-29 Thread Scherrer, Chad
Yes, good point. I suppose there's really no need to re-declare main once it's 
been imported. Thanks!

-Original Message-
From: Remi Turk [mailto:[EMAIL PROTECTED]
Sent: Thu 12/29/2005 4:34 PM
To: Scherrer, Chad
Cc: S Koray Can; haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] RE: module names
 
On Fri, Dec 16, 2005 at 07:55:50AM -0800, Scherrer, Chad wrote:
 From: S Koray Can [mailto:[EMAIL PROTECTED]
 Why not do this: name none of those modules Main.hs, and have an empty 
 module Main.hs with only import MainDeJour and main = 
 MainDeJour.main so you can just edit just that file.
 
 Cheers,
 Koray
 
 --
 Yeah, I like that approach. That saves me from having to remember which 
 file I most recent used as main. Seems easy enough to even set it up so
 that
 load MainDuJour
 writes the file Main.hs with
 
 import MainDuJour
 main = MainDuJour.main

A rather late reply I realize, but this slightly less verbose
version also works:

 module Main where

 import MainDuJour

Remi

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


[Haskell-cafe] Re: problems with square roots...

2005-12-21 Thread Scherrer, Chad

From: Daniel Carrera [EMAIL PROTECTED]


Hey,

The sqrt function is not doing what I want. This is what I want:

round sqrt(2)
---
Daniel,

A lot of Haskell folks like to avoid parentheses as much as possible, and 
there's a really
convenient way to do this. There is a Prelude function
($) f x = f x
which is right-associative, so you can write
round $ sqrt x == round (sqrt x)
This becomes really convenient when multiple application is involved:
print $ round $ sqrt x == print (round (sqrt x))

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


[Haskell-cafe] RE: Haskell-Cafe Digest, Vol 28, Issue 66

2005-12-20 Thread Scherrer, Chad
 From: Daniel Carrera [EMAIL PROTECTED]
 Robert Dockins wrote:
  -divides a b = (mod a b == 0)
  +divides a b = (mod b a == 0)
 
 Oh, thanks. My program assumed one way to define 'divides' 
 and the example assumed the other.
 
 When I wrote it I was thinking of (divides a) being a 
 function that tells me if the input divides 'a'.
 
 Thanks!
 
 Cheers,
 Daniel.

Daniel, 

Have you used Haskell's infix notation? It can help keep the order
straight for operators like these. You can write

a `mod` b  -- instead of mod a b
a `divides` b -- instead of divides a b.

This can help with readability, too.

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


[Haskell-cafe] RE: module names

2005-12-16 Thread Scherrer, Chad
-Original Message-
From: S Koray Can [mailto:[EMAIL PROTECTED]

Why not do this: name none of those modules Main.hs, and have an empty 
module Main.hs with only import MainDeJour and main = 
MainDeJour.main so you can just edit just that file.

Cheers,
Koray

--
Yeah, I like that approach. That saves me from having to remember which 
file I most recent used as main. Seems easy enough to even set it up so
that
load MainDuJour
writes the file Main.hs with

import MainDuJour
main = MainDuJour.main

and then and then calls
ghc --make Main.hs -o mainDuJour

This will do for now, but still feels really kludgy, especially for Haskell.

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


[Haskell-cafe] module names

2005-12-15 Thread Scherrer, Chad
Something about the way module names are specified in a file seems
really strange to me. When I first started learning Haskell (I had used
OCaml previously), I tried things like

module Main where
import A
import B
main = A.f  B.f

  module A where
f = ...

  module B where
f = ...

in a single file. This example is straight from chapter 5 of the Report,
and no mention is made (that I could find) about modules needing to be
in separate files. But this won't load in ghci! (Even if ... is changed
to putStr hi). Eventually I figured out that it works fine if it's
split over three separate files.

So here's what I'm trying to figure out: If every file corresponds to
exactly one module (is that true?), then why must the module name be
given again in the text of the file? When I'm using ghci, I have lots of
modules that I sometimes want to load as Main, and sometimes I only
want them loaded as a dependency from another module. Currently, I have
to go into each file to change the module Foo where line to do this.

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


[Haskell-cafe] STM reference?

2005-12-08 Thread Scherrer, Chad
Hi,

Can anyone suggest some references to learn how to program using GHC
with threads? I've read a little bit about STM, but it's still pretty
mysterious to me. Is this the best approach to take? I've never used
threads in any language, but monads are fairly comfortable for me.

Thanks!

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Verbosity of imperative code

2005-12-07 Thread Scherrer, Chad

 On Tue, Dec 06, 2005 at 10:58:45PM +0300, Bulat Ziganshin wrote:
  the third-priority problem is language itself. in particular, i hate
  Haskell school of imperative manipulations:
  
  x' - readIORef x
  y' - readIORef y
  writeIORef z (x'*y')

Here's a way to make some of this less messy:

class PlusEq a b m | a - m where
(+=) :: a - b - m ()

instance (Num a) = PlusEq (IORef a) a IO where
xRef += y = do x - readIORef xRef
   writeIORef xRef (x + y)

instance (Num a) = PlusEq (IORef a) (IORef a) IO where
xRef += yRef = do y - readIORef yRef
  xRef += y

Then instead of 

do x - xRef
   y - yRef
   writeIORef yRef (x + y)

you can just say y += x. I've started on an InPlace module to do things
like this in general.

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


[Haskell-cafe] Re: returning lists

2005-12-02 Thread Scherrer, Chad
raptor [EMAIL PROTECTED] writes,

 ]- that is the problem :), 'cause such functions should accept Char and
 String, but return a Tuple of Strings, but it is recursive (so that it fetch
 next,next,next char :)) i.e. it is own consumer and should return String

 --this is wrong, just tring grab char (x:xs)

You might also have a look at
http://haskell.org/hawiki/WorkerWrapper

This idea should apply here.

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


[Haskell-cafe] syntactic sugar for comonads

2005-12-02 Thread Scherrer, Chad
Hi, 

I'm wondering about a syntactic sugar for comonads. These are still very
new to me, but it seems like their usage will become much more common
once manipulations are more convenient (I believe this was the case with
monads and arrows, correct?).

Here's an example for motivation. Consider the data type

data Stream a = a : Stream a

and suppose we want to write a function
movingWindow :: Stream a - Stream [a]
so that, for example,

movingWindow 3 (1 : 2 : 3 : ...)
evaluates to
[1,2,3] : [2,3,4] : [3,4,5] : ...

Recognizing Stream as a comonad, this is pretty easy:

movingWindow n s = s = (take n . toList)

toList :: Stream a - [a]
toList (x : xs) = x : toList xs

If the second argument of (=) is written in lambda form, this comes
out as

movingWindow n s = s = \x -
   take n $ toList x

This looks analogous to the way do is translated for monads, so a sugary
alternative could be

movingWindow n s = do x - s
  take n $ toList x

Note that the presence of - tells us we're in a comonad, rather than
a monad.

I'm not at all stuck on this, but I think it would be good to get the
ball rolling. What do you think?


Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: :t main

2005-12-02 Thread Scherrer, Chad
 From: Cale Gibbard [mailto:[EMAIL PROTECTED] 
 See: 
 http://haskell.org/pipermail/haskell-cafe/2003-January/003794.html
 
 The OI comonad as previously envisioned breaks referential 
 transparency. I/O just doesn't seem to be something which one 
 can easily do comonadically, since once coeval/extract is 
 applied, you're back to plain values, and there's no 
 imposition of sequencing.
 
  - Cale

Hmm, I hadn't seen that. The asymmetry is pretty frustrating in that
case.

After poking around a bit more, I (re)discovered some discussion of this
on Hawiki:
http://www.haskell.org/hawiki/CoMonad

After reading Dave Menendez's comments, I'm wondering...
If we consider
IO a = Realworld - (Realworld, a)
then wouldn't we dually have something like
OI a = (Realworld, Realworld - a)?

Could this be what screws things up? Right now it seems like OI is
acting like it has the same type as IO, with a different name.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx 

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


[Haskell-cafe] :t main

2005-11-29 Thread Scherrer, Chad
I've been reading some of the articles about comonads, and I thought the idea 
of giving main the type OI () - () was pretty interesting. So I was wondering, 
would it be possible to allow the type of main to be inferred? It seems like 
IO ()
OI () - ()
OI () - IO ()

all make sense (at least I think they do). One particularly nice side effect of 
this (pardon the pun) is that a good number of useful programs can be written as

getContentsW :: OI () - a
doSomeStuff :: (Show b) = a - b
print :: (Show b) = b - IO ()
main = print . doSomeStuff . getContentsW

so much less understanding about monads et al is required to do some basic 
stuff. I think it would be much easier in this case to make the transition to 
Haskell.

Also, has anyone given any thought to syntactic sugar for comonads? Since 
arrows and monads share the (-) symbol, it seems like a nice unification could 
be possible... Maybe (-) alone could be used similarly?

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


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Scherrer, Chad
Henning Thielemann [EMAIL PROTECTED] writes:

 Since
   (a . b) x
   a $ b x
   a (b x)
 
 are equivalent, do you also want to reverse function and 
 argument in order to match argument order of . and $ ?
 
 That is
   x (b . a)
   x b $ a
   (x b) a
 ?

I'm sorry, I'm not sure I understand your question. Are you asking
whether one should be allowed to write x f instead of f x? I don't think
anyone is advocating this, but is can be convenient to have an infix
operator for this purpose.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx 

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


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Scherrer, Chad
Henning Thielemann [EMAIL PROTECTED] writes:

   I want to say, that the order of symbols for ($), (.) and 
 function application is consistent. This is a fine thing. I 
 think that shall not be distroyed by giving ($) and (.) 
 reversed argument order.

I see. I like the argument order also, since it so nicely reflects
mathematical notation. But I do think there's a place for (flip ($)) and
(flip (.)). The problem is that the assignment of fixities is much more
subtle and requires a consideration of what should be considered proper
style.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx 

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


RE: [Haskell-cafe] Function application like a Unix pipe

2005-11-23 Thread Scherrer, Chad
Udo Stenzel [EMAIL PROTECTED] writes:

 The unix pipe is actually function composition.  Its argument 
 (standard
 input) isn't explicitly mentioned

Then it seems Unix must overload the | operator. I typically use it to
do things like
grep . *.hs | wc

So I think of the types as being 
grep . *.hs :: String
wc :: String - Int  -- ok, not really, but it shows the point better.

So we'd have to have 
(|) :: a - (a - b) - b

And (flip ($)) is the only thing that makes sense. Is it the case that a
Unix pipe is analagous to (flip ($)) or (flip (.)) depending on the
context?

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Function application like a Unix pipe

2005-11-22 Thread Scherrer, Chad
Albert Lai [EMAIL PROTECTED] writes:

 I offer a simpler, more direct, and pre-existing correspondence
between a functional 
 programming construct and unix pipes:

Maybe my point wasn't clear. Of course this idea of comparing lazy
evaluation to Unix pipes is very old (long before July 2004, I'm sure).
The point I'm making is that there is an old idea that may be underused.
We use ($) all over the place, but if there are a lot of them (and
especially if they are spread over several lines) it becomes awkward to
read the whole thing backward to trace through the function from
beginning to end. In these cases, it's much simpler to use 

(\|) = flip ($) -- (#) seems to me too pretty for other purposes to use
it here.
infixl 0 \| -- Again, why can't this be negative or Fractional??

What I'm asking is really a question of pedagogy and style. This style
seems reasonable to me. OTOH, there are some reasons not to do things in
this way. Maybe any function big enough to benefit from writing it this
way should be broken up anyway. Or maybe getting used to this style
where the laziness is right in your face could make it more difficult
for people to learn to reason through less obvious laziness. I'm really
trying to figure out whether this approach is worth pursuing, rather
than imply that this is a completely original idea.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Function application like a Unix pipe

2005-11-18 Thread Scherrer, Chad
I'm still trying to settle on a feel for good programming style in
Haskell. One thing I've been making some use of lately is

(\|) = flip ($)
infixl 0 \|

Then expressions like

f4 $ f3 $ f2 $ f1 $ x

become

x  \|
f1 \|
f2 \|
f3 \|
f4

I've seen something like this on haWiki using (#), but I prefer this
notation because it looks like a Unix pipe, which is exactly how it's
used. 

This style makes the sequential feel of monadic do notation available to
non-monadic functions, and would seem to ease the initial confusion most
people experience when they first program using lazy evaluation. Many
newbies have experience with Unix pipes, and this notation makes that
analogy explicit.

I have a couple of questions about this...

First, it would be convenient if ($) could appear in an fi without extra
parentheses, but this would require infixl (-1) \|. Is there a reason
this isn't allowed? The current fixities don't seem to allow much room
for expansion. Would it be possible to either (1) allow negative and/or
fractional fixities, or (2) shift and spread out the current fixities to
allow more flexibility in the introduction of new operators?

I'm also trying to determine to what extent this style should really be
used. Does anyone see this as bad style? Is there an argument why this
might not be such a good way to ease someone into the language? 

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell] specification of sum

2005-11-02 Thread Scherrer, Chad


 Surely not... sum is defined by Haskell 98 as:
 
  sum = foldl (+) 0
 
 and this is exactly what GHC provides.  Furthermore we have 
 specialised strict versions for Int and Integer.
 

I'd been using ghci for testing along the way and getting terrible
results; does the specialization only apply to ghc per se?

 
 Cheers,
   Simon
 

Also, Cale, I was thinking about your comment about formal power series,
and I don't see that (+) should not be strict in this case. In
particular, if they are represented as infinite lists, I agree that
zipWith (+) works just fine, though it is strict but lazy.

Here is the strictness:
zipWith (+) undefined [1,2,3] == undefined
zipWith (+) [1,2,3] undefined == undefined

And here is the laziness:
head $ zipWith (+) (1:undefined) (2:undefined) == 3

Or am I missing something?

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


[Haskell] specification of sum

2005-11-01 Thread Scherrer, Chad
I was wondering... In my experience, it's worked much better to use

sum' = foldl' (+) 0

than the built-in sum function, which leaks memory like crazy for
large input lists. I'm guessing the built-in definition is

sum = foldr (+) 0

But as far as I know, (+) is always strict, so foldl' seems much more
natural to me. Is there a case where the build-in definition is
preferable?

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] specification of sum

2005-11-01 Thread Scherrer, Chad
 
 You don't always want (+) to be strict. Consider working with 
 the ring of formal power series over, say, the integers. You 
 don't want (+) to force the evaluation of an infinite formal 
 summation which is passed to it, since that's an infinite 
 loop, so it will have to be non-strict, somewhat like zipWith 
 (+) over the lists of coefficients.
 
  - Cale

Hmm, this is a good point, but for most people, It seems like the most
common usage would be to add up a list of actual concrete numbers, and
the resulting memory leak in the code using sum is at least a minor
annoyance. It's hard to say how much time a given newbie will take to
catch this nuance. Since 

sum' = foldl' (+) 0

(like foldl', the ' means strict ) is so often preferable, I'll go so
far as to suggest it be included it in upcoming versions of Data.List.
That way it would be hard to miss, and would remove what could otherwise
be a very common stumbling block for anyone doing numerical work with
Haskell.

I haven't used product so extensively, but I suspect there may be
similar issues with it?

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


[Haskell] RE: specification of sum

2005-11-01 Thread Scherrer, Chad
 The solution would be to bring 'sum' and 'product' into the Num class so
 the most efficient version for each type can be used and the default is
 no worse than the current non-class versions. (this is even pretty much
 completly backwards compatable so could be considered for haskell 06)
 
 I'd also like to see 'join' and 'ap' added to Monad while we are at it.

John

Ooo, that's much better. I'll retract my sum' suggestion in that case.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-26 Thread Scherrer, Chad
Sorry to drag this thread out, but here's one more thing you might
try...

I was thinking, if we just wanted something like
intTable :: [Int] - [(Int, Int)]
we could just replace Map with IntMap in the previous solution:

intTable xs = IntMap.assocs $! foldl' f IntMap.empty xs
where f m x = let  m' = IntMap.insertWith (+) x 1 m
   Just v = IntMap.lookup x m'
  in v `seq` m'

To get another polymorphic version, we could just write this wrapper:

freq :: (Enum a) = [a] - [(a,Int)]
freq = map fstToEnum . intTable . map fromEnum
where fstToEnum (x,y) = (toEnum x, y)

This seems to run faster than the other polymorphic version on my
machine.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Nice way to calculate character frequency in a string

2005-10-25 Thread Scherrer, Chad
 Hello, I need to calculate the frequency of each character in a 
 String. And if I can do this really well in C, I don't find a nice
(and 
 fast) answer in haskell. I tried several functions, listed below, and 
 even the fastest do a lot of unnecessary things :

A while back, I was trying to build a table function similar to what
you describe, and Dean Herrington helped me speed it up and stop the
stack overflows I had been getting. Here it is, in case this is useful
to you...

table :: (Ord a) = [a] - [(a,Int)]
table xs = Map.assocs $! foldl' f Map.empty xs
where f m x = let  m' = Map.insertWith (+) x 1 m
   Just v = Map.lookup x m'
  in v `seq` m'

I would be interested in whether this is much slower than the other
approaches you've tried. If a faster approach could be made polymorphic,
I'd have a faster way to build tables!

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] RE: Typing problems with basic arithmetic - help!

2005-09-24 Thread Scherrer, Chad
 For some reason the following code is producing an error 
 message from ghci that the the patterns are non-exhaustive. 
 Does anyone have any idea why that could be, given that the 
 patterns are, at least in my meaning, provably exhaustive?
 

You forgot to match against the empty list. Try adding 
choosenonuniqueset n [] = []

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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Scherrer, Chad
One of Mark Jones's articles suggests something like

class Plus a b c | a b - c where
  (+) :: a - b - c

Would

instance (Plus a b c, Monad m) = Plus (m a) (m b) (m c) where
  mx + my = do x - mx
   y - my
   return (x + y)

do what you're looking for?

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx

--
Original message:

Hi,

Sean's comment (yeah, it was like a billion years ago, just catching
up) is something that I've often thought myself. 

I want the type system to be able to do automatic lifting of monads,
i.e., since [] is a monad, I should be able to write the following:

[1,2]+[3,4]

and have it interpreted as do {a-[1,2]; b-[3,4]; return (a+b)}.

Also, I would have

Reader (+1) + Reader (+4) == Reader (\x - 2*x+5)

The point I want to make is that this is much more general than IO or
monads! I think we all understand intuitively what mathematicians mean
when they add two sets

{1,2}+{3,4}  (i.e. { x+y | x\in {1,2}, y\in {3,4}})

or when they add functions 

(f+g)(x) where f(x)=x+1 and g(x)=x+4

So automatic lifting is a feature which is very simple to describe,
but which gives both of these notations their intuitive mathematical
meaning - not to mention making monadic code much tidier (who wants to
spend their time naming variables which are only used once?). I think
it deserves more attention.

I agree that in its simplest incarnation, there is some ugliness: the
order in which the values in the arguments are extracted from their
monads could be said to be arbitrary. Personally, I do not think that
this in itself is a reason to reject the concept. Because of currying,
the order of function arguments is already important in Haskell. If
you think of the proposed operation not as lifting, but as inserting
`ap`s:

return f `ap` x1 `ap` ... `ap` xn

then the ordering problem doesn't seem like such a big deal. I mean,
what other order does one expect, than one in which the arguments are
read in the same order that 'f' is applied to them?

Although it is true that in most of the instances where this feature
would be used, the order in which arguments are read from their monads
will not matter; yet that does not change the fact that in cases where
order *does* matter it's pretty damn easy to figure out what it will
be. For instance, in

print (a:  ++ readLn ++ \nb:  ++ readLn)

two lines are read and then printed. Does anybody for a moment
question what order the lines should be read in?

Frederik


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


[Haskell] FunDeps and MArray

2005-09-05 Thread Scherrer, Chad
Hi,

I'm trying to use functionally dependent typeclasses to create an
overloaded (+=) function. A simplified example of a first bit of code
is...

class PlusEq a b c | a b - c where
(+=) :: a - b - c

instance (MArray a e m, Num e, Ix i) = 
PlusEq (a i e) (a i e) (m ()) where
(+=) x y = let updateX i = do xi - readArray x i
  yi - readArray y i
  writeArray x i (xi + yi)
   in  sequence_ . map updateX $ indices x

I keep getting this error in GHCi:

Illegal instance declaration for `PlusEq (a i e) (a i e) (m ())'
(the instance types do not agree with the functional dependencies of
the class)
In the instance declaration for `PlusEq (a i e) (a i e) (m ())'
Failed, modules loaded: none.

Looking at GHC's documentation for MArray, the definition starts out

class (HasBounds a, Monad m) = MArray a e m where
...

It seems to me if MArray were written using fundeps (something like
MArray a e m | a e - m) things may work out. Is there a reason it's not
written this way? If so, is there another way to do what I'm trying to
do? Thanks.

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

Time flies like an arrow; fruit flies like a banana. -- Groucho Marx
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] reading call graphs

2005-08-23 Thread Scherrer, Chad
When I compile with ghc -prof -auto-all, I end up with a .prof file that
starts out like this:

individualinherited
COST CENTRE  MODULE   no.entries  %time %alloc   %time %alloc
 

MAIN MAIN  1   0   0.00.0   100.0  100.0
 mainMain228   92329   0.20.999.8   99.8
  step   Main259 679  38.4   26.656.6   39.2

I'm trying to understand the entries column. I thought this was the
number of times a given function is called. But main is nonrecursive,
and only calls step (also nonrecursive) once. Where are the 92329 and
679 coming from? Am I mistakenly calling the functions more than I think
I am?

Thanks,
Chad
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] RE: Random matrices

2005-08-22 Thread Scherrer, Chad
 
 Ah ha. That'll do.
 Lesson: avoid hidden space leaks in monads.

Hmm, I'm still missing something. It seems a good lesson, but
practically speaking, it doesn't help me any more than saying write
efficient programs. What could I have looked for in the original code
to predict it may be leaky? Is there a way of thinking about this that
can help me stop hitting space leaks like this?

BTW, I really do appreciate the help. I've been amazed at the level of
effort put forth by the Haskell community as a whole to help out
newcomers.

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


RE: [Haskell] Random matrices

2005-08-21 Thread Scherrer, Chad
Thanks, Don. I need some time to take a closer look at this. I'm trying to see, 
what is it about the code you posted that makes it so much more efficient? Is 
it the loop in the IO monad is compiled into an honest-to-goodness loop? Is 
this specific to IO, or does it work out this way for monads in general? Or 
maybe some gains were made by switching from using StdGen with a specified seed 
to using the OS-supplied random number generator?

-Chad


-Original Message-
From: Donald Bruce Stewart [mailto:[EMAIL PROTECTED]
Sent: Fri 8/19/2005 7:42 PM
To: Scherrer, Chad
Cc: haskell@haskell.org
Subject: Re: [Haskell] Random matrices
 
Chad.Scherrer:
 
I'm doing some statistical calculations, and I decided to
try this out in Haskell to see how it goes. I'm really
enjoying using the language, so I hope I can straighten this
out so I can keep using it at work.
 
I keep getting stack overflows, so I think my code must be
too lazy somewhere (that's what that means, right?) Here is
my code to build random vectors and matrices.

I was suspicious about all those zips and repeats, so did a bit of
profiling. This only revealed that the creation of random floats was
chewing up about 70% of time and space. Still suspicious of that
replicate code, I decided to rewrite it as a loop (I moved the code
into the IO monad just because it is easier to hack in IO). This fixed the
issue.

-- Don

Before:

paprika$ ghc -package mtl -O -prof -auto-all N.hs
paprika$ ./a.out +RTS -p
Stack space overflow: current size 8388608 bytes.
Use `+RTS -Ksize' to increase it.

total time  =0.16 secs   (8 ticks @ 20 ms)
total alloc =  42,614,984 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc
randomEntryMain  50.0   78.0
randomArrayMain  50.0   19.6



After:
paprika$ ghc -O -prof -auto-all M.hs 
paprika$ ./a.out +RTS -p
array (1,10) 
[(1,0.73394084),(2,0.39095977),(3,0.18828022),(4,0.19094983),(5,0.83119744),(6,0.3594179),(7,0.43519533),(8,0.39867708),(9,0.15676379),(10,0.4503187)]

total time  =0.00 secs   (0 ticks @ 20 ms)
total alloc = 141,368 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc
CAFSystem.Random  0.05.6
CAFGHC.Handle 0.01.0
CAFGHC.Float  0.0   35.2
randomEntryMain   0.0   25.7



import Data.Array.Unboxed
import Data.Array.Diff
import System.Random
import Control.Monad

type Vector = UArray Int Float
type Matrix = DiffArray Int Vector

-- Generate a random number from the unit interval
randomEntry :: IO Float
randomEntry = getStdRandom (randomR (0,1))

-- Build an array of n random things
randomArray :: (IArray arr a) = Int - IO a - IO (arr Int a)
randomArray n x = do
let loop i | i == 0= return []
   | otherwise = do f  - x
fs - loop (i-1)
return (f : fs)
fs - loop n
return $ listArray (1,n) fs

-- A random vector is an array of random entries
randomVector :: Int - IO Vector
randomVector n = randomArray n randomEntry

-- a random matrix is an array of random vectors.
randomMatrix :: Int - Int - IO Matrix
randomMatrix i j = randomArray i (randomVector j)

tester :: Int - IO [Matrix]
tester n = liftM repeat $ randomMatrix n n

main :: IO ()
main = tester 10 = \as - print $ (as !! 1) ! 5



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


RE: [Haskell] stack overflow - nonobvious thunks?

2005-07-29 Thread Scherrer, Chad
Thanks! I was confused at first because ghci still runs into memory
problems, though no longer stack overflows. ghc runs it beautifully,
though.

-Chad 

-Original Message-
From: Amanda Clare [mailto:[EMAIL PROTECTED] 
Sent: Thursday, July 28, 2005 3:20 AM
To: Dean Herington
Cc: Scherrer, Chad; haskell@haskell.org
Subject: Re: [Haskell] stack overflow - nonobvious thunks?

Dean's version certainly seems the neatest, but just for interest you
can also do it with a cps fold instead of foldl' too:

table xs = assocs $! cpsfold f empty xs
 where
 f x m k = case Map.lookup x m of
   Just v  - v `seq` (k $ Map.adjust (+1) x m)
   Nothing - k $ Map.insert x 1 m


cpsfold f a [] = a
cpsfold f a (x:xs) = f x a (\y - cpsfold f y xs)


As far as I understand it this just makes sure the seq happens before
the folding continues.

When compiled with ghc, both solutions are very well behaved, and seem
to take the same small amount of memory whether for 1000 or
1.

Amanda


Dean Herington wrote:
 The following version seems to do the trick (and still remain quite 
 readable).  It worked for 1 as well.
 
 import Data.Map as Map
 import System.Random
 import Data.List (foldl')
 
 table :: (Ord a) = [a] - [(a,Int)]
 table xs = Map.assocs $! foldl' f Map.empty xs
 where f m x = let  m' = Map.insertWith (+) x 1 m
Just v = Map.lookup x m'
   in v `seq` m'
 
 unif :: [Int]
 unif = randomRs (1,10) $ mkStdGen 1
 
 f :: Int - [(Int, Int)]
 f n = table $ take n unif
 main = print $ f 1000
 
 - Dean

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


[Haskell] stack overflow - nonobvious thunks?

2005-07-27 Thread Scherrer, Chad
Title: stack overflow - nonobvious thunks?






I'm trying to write a function to build a table of values from a list. Here's my current attempt:


table :: (Ord a) = [a] - [(a,Int)]

table xs = Map.assocs $! foldl' f Map.empty xs

 where

 f m x = Map.insertWith (+) x 1 m


The ($!) and the foldl' were my clumsy attempts to avoid the stack overflows I keep getting, but it's not working right yet. If I set

unif :: [Int]

unif = randomRs (1,10) $ mkStdGen 1


then I should be able to use


f :: Int - [(Int, Int)]

f n = table $ take n unif


I would think this should work using very little memory, since unif is evaluated lazily, and the table is built eagerly. But I must be keeping around more thunks than I think, since I get (in ghci)

*Main f 100

[(1,99816),(2,100187),(3,99969),(4,99892),(5,100194),(6,100190),(7,99776),(8,100347),(9,100125),(10,99504)]

*Main f 1000

[(1,*** Exception: stack overflow


So it works on big lists, but not huge ones. What am I missing? Is there a way to do this other than just increasing the memory allocation?

Thanks,

Chad Scherrer



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


RE: [Haskell] combining IntMaps

2005-07-27 Thread Scherrer, Chad
Ok, it looks like I have some more reading to do. Do you know where I
can find a description of the Hedge algorithm?

Also, I'm pretty new here - these conversations eventually need to get
moved to haskell-cafe, right? Is there any concrete guidance regarding
when that should happen? The distinction between the two lists is still
vague to me.

-Chad

-Original Message-
From: Adrian Hey [mailto:[EMAIL PROTECTED] 
Sent: Wednesday, July 27, 2005 12:04 AM
To: Scherrer, Chad
Cc: haskell@haskell.org
Subject: Re: [Haskell] combining IntMaps

Hello,

On Tuesday 26 Jul 2005 7:58 pm, Scherrer, Chad wrote:
 Thanks! It's interesting the way your AVL tree library is set up -- 
 there seems to be a much broader degree of functionality than that 
 provided by Data.Set. But I'm trying to see, is there a significant 
 difference in the fundamental data structure.

Well Data.Set is based on a different balanced tree type (weight
balanced trees), similar to those used in the Adams paper. I'm also
quite sceptical about the Hedge algorithm, so the AVL library doesn't
use it. It uses divide and conquer, but not quite as Adams describes it.

But IMO the biggest problem with Data.Set is the inflexible API.
For example..

From Data.Set:
 union :: Ord a = Set a - Set a - Set a  intersect :: Ord a = Set a
- Set a - Set a

From Data.Tree.AVL:
 genUnion :: (e - e - COrdering e) - AVL e - AVL e - AVL e
genIntersection :: (a - b - COrdering c) - AVL a - AVL b - AVL c

Of course there's no reason why similar functions could not be provided
by Data.Set, but they're not there at present.

 or is the main point that
 the additional functionality could not have otherwise been provided in

 an efficient way without going into the guts of Data.Set?

Yes. This why producing useable libraries like this is so difficult.
There's plenty of reasonable things you just can't do efficiently with
Data.Set. Same is probably true of Data.Tree.AVL of course, but I'm
trying to make it more complete all the time.

Anyway, please try out AVL and let me know if there's anything more
missing.

Regards
--
Adrian Hey

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


RE: [Haskell] stack overflow - nonobvious thunks?

2005-07-27 Thread Scherrer, Chad
Adrian, Does your AVL library have an insertWith'-type function
mentioned by Udo? 

If I lookup and insert into the table separately, forcing evaluation at
each step, I can do

table' :: (Ord a) = [a] - [(a, Int)]
table' xs = Map.assocs $! foldl' f Map.empty xs
where
f m x = (Map.insert x $! 1 + Map.findWithDefault 0 x m) $! m

This helps with the stack overflow problem, but now I'm hitting a
different wall:

*Main table $ take 1000 unif
[(1,999662),(2,1000220),(3,998800),(4,1000965),(5,999314),(6,1001819),(7
,1000997),(8,999450),(9,999877),(10,998896)]

*Main table $ take 1 unif
interactive: out of memory (requested 1048576 bytes)

I thought I may have found a good approach using an idea from one of
Amanda Clare's pages 
http://users.aber.ac.uk/afc/stricthaskell.html

If I write 

eqSeq x y = if x==x then y else y

this forces evaluation of x further than seq alone. Then I can write

table :: (Ord a) = [a] - [(a, Int)]
table xs = Map.assocs $! foldl' f Map.empty xs
where
f m x = m `eqSeq` Map.insertWith (+) x 1 m

Same result as Udo's suggestion - out of memory.

I still don't see why this function should need any more than a few
kilobytes, even for very large n like this.

-Chad

-Original Message-
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] 
Sent: Wednesday, July 27, 2005 11:02 AM
To: Scherrer, Chad
Cc: haskell@haskell.org
Subject: Re: [Haskell] stack overflow - nonobvious thunks?

Scherrer, Chad wrote:
 
 f m x = Map.insertWith (+) x 1 m

insertWith is inserting the nonobvious thunks.  Internally it applies
(+) to the old value and the new one, producing a thunk.  There is no
place you could put a seq or something to force the result.  You
basically need insertWith', which isn't there.

I think, your best best is to manually lookup the old value, combine
with the new, force the result, then insert that, overwriting the old
value.

On top of that you still need foldl' to avoid building long chains of
Map.insert.


Udo.
--
The Second Law of Thermodynamics:
If you think things are in a mess now, just wait!
-- Jim Warner
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] combining IntMaps

2005-07-26 Thread Scherrer, Chad
Thanks! It's interesting the way your AVL tree library is set up --
there seems to be a much broader degree of functionality than that
provided by Data.Set. But I'm trying to see, is there a significant
difference in the fundamental data structure, or is the main point that
the additional functionality could not have otherwise been provided in
an efficient way without going into the guts of Data.Set? 

Chad Scherrer

-Original Message-
From: Adrian Hey [mailto:[EMAIL PROTECTED] 
Sent: Wednesday, July 20, 2005 10:57 PM
To: Scherrer, Chad; haskell@haskell.org
Subject: Re: [Haskell] combining IntMaps

On Wednesday 20 Jul 2005 4:05 am, Scherrer, Chad wrote:
 I'm using the (IntMap Int) type to implement functions (Int - Int), 
 by treating non-keys as values that map to zero. I'd like to be able 
 to add two of these pointwise, and delete the key from the resulting 
 map when the sum of the values is zero. My specification is

 addMaps :: IntMap Int - IntMap Int - IntMap Int addMaps m = 
 IntMap.filter (/= 0) . IntMap.unionWith (+) m

 But I'm not really happy with this because it traverses both maps for 
 the union, and then traverses the result to get rid of all the zeros.
 (This function is a performance bottleneck in my current code).

Examples like this are interesting because they show just how difficult
it is produce a comprehensive library for even one common or garden data
structure. I thought my AVL library was reasonably complete when I
released it, but I've subsequently thought of plenty of stuff that's
still missing (arguably), and you've just given me more.

Anyway, you might like to try using AVL trees which I have just upgraded
to provide the necessary functions..
 http://homepages.nildram.co.uk/~ahey/HLibs/Data.Tree.AVL/

You should be able to produce a reasonable alternative to Data.IntMap
with this. I'd be interested to know how it performs. I won't do the
whole thing myself, but here's a start (uses GHCs unboxed Ints).

{-# OPTIONS -fglasgow-exts #-}

import Data.COrdering
import Data.Tree.AVL
import GHC.Base

data IntAssoc = IntAssoc Int# Int# --Perhaps use boxed values instead??
newtype IMap = IMap (AVL IntAssoc)

emptyIMap :: IMap
emptyIMap = IMap empty

lookUp :: IMap - Int - Int
lookUp (IMap avl) (I# skey)  = genReadDefault 0 avl cmp  where cmp
(IntAssoc key v) = case compareInt# skey key of
  LT - Lt
  EQ - Eq (I# v)
  GT - Gt

set :: Int - Int - IMap - IMap
set (I# k) (I# v) (IMap avl) = IMap avl'
 where avl' = if v ==# 0# then genDel cmp avl
  else genPush ccmp ia avl
   ia = IntAssoc k v
   cmp  (IntAssoc k' _) = compareInt# k k'
   ccmp (IntAssoc k' _) = case compareInt# k k' of
  LT - Lt
  EQ - Eq ia
  GT - Gt

addMaps :: IMap - IMap - IMap
addMaps (IMap avl0) (IMap avl1) = IMap (genUnionMaybe ccmp avl0 avl1)
where ccmp (IntAssoc k0 v0) (IntAssoc k1 v1) =
case compareInt# k0 k1 of
 LT - Lt
 EQ - let s = v0 +# v1 
   in if s ==# 0# then Eq Nothing
  else Eq (Just (IntAssoc k0 s))
 GT - Gt

Regards
--
Adrian Hey





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


[Haskell] combining IntMaps

2005-07-19 Thread Scherrer, Chad
Title: combining IntMaps






I'm using the (IntMap Int) type to implement functions (Int - Int), by treating non-keys as values that map to zero. I'd like to be able to add two of these pointwise, and delete the key from the resulting map when the sum of the values is zero. My specification is

addMaps :: IntMap Int - IntMap Int - IntMap Int

addMaps m = IntMap.filter (/= 0) . IntMap.unionWith (+) m


But I'm not really happy with this because it traverses both maps for the union, and then traverses the result to get rid of all the zeros. (This function is a performance bottleneck in my current code).

I thought I could do something like


addMaps' :: IntMap Int - IntMap Int - IntMap Int

addMaps' = IntMap.foldWithKey f

 where

 f k x = IntMap.update (maybeAdd x) k

 maybeAdd x v = let s = v + x in if s == 0 then Nothing else Just s


But this is no good, because IntMap.update only affects those keys where lookup succeeds, so

IntMap.update (maybeAdd 3) 8 IntMap.empty

returns IntMap.empty, rather than a map with 8 - 3 as I had hoped.


What would you suggest to help addMaps run faster? Do I need to pry open the IntMap implementation to do better?


Thanks so much,

Chad Scherrer


PS - I mistakenly crosslisted this to the GHC users list, because I didn't realize how the mailing lists were set up. Please excuse my noobiness.


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