Namespaces (was Re: GUI Library Task Force)

2001-10-10 Thread Hal Daume III
(just like Java has java.*). -- Lennart ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell ~~ Hal Daume III

Re: Namespaces (was Re: GUI Library Task Force)

2001-10-10 Thread Hal Daume III
is there a third option that I'm missing? How do other people handle this issue? - Hal On Wed, 10 Oct 2001, Mark Carroll wrote: On Wed, 10 Oct 2001, Hal Daume III wrote: (snip) least) is that the Java compiler knows how to interpret the .s and will use them to navigate directory

Re: Namespaces

2001-10-10 Thread Hal Daume III
~~ Hal Daume III [EMAIL PROTECTED] arrest this man, he talks in maths www.andrew.cmu.edu/~hcd

bug in report? empty datatypes

2001-11-30 Thread Hal Daume III
error and i can't get nhc to accept empty datatypes at all... - hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL

class parameters to existential datatypes

2001-12-06 Thread Hal Daume III
Hi, I would like to be able to write something like this: data Foo c = forall a . c a = Foo a Unfortunately, this isn't allowed (apparently) because it's an illegal class assertion (or at least that's what ghc tells me). My motivation for doing this is I want to have something like List, but

Re: Strict foldl

2001-12-06 Thread Hal Daume III
Hi, Is this what I think it is? Do you benchmark the interpreter? Interpreted code isn't optimised. When I compile main = print $ sum [1..1000] with -O2, it takes 13s on a 600MHz P3 and runs in 1.5MB of space. Out of curiousity, why doesn't this get compiled down to main

Re: We need Documentation

2001-12-13 Thread Hal Daume III
I taught myself Python in about two weeks with the online Python tutorial, I think something similar for Haskell would greatly increase the number of Haskell users. I'm not familiar with the Python tutorial, but the Java tutorial which resides at java.sun.com is pretty much the most highly

Re: We need Documentation

2001-12-13 Thread Hal Daume III
I think we should move this off the mailing list. I'm willing to spear-head such an effort. Anyone who is interested in contributing, please email me. I'll compile a list of people and we can figure out what we want to do. - Hal -- Hal Daume III Computer science is no more about computers

global counters

2001-12-19 Thread Hal Daume III
Please, no tirade about banishing unsafePerformIO. I've seen this done before I just don't remember how. I want to use a state monad to count things, but don't want to monadify the thing I'm using the counter in. basically, i want a function getVar :: () - String which returns a new string

Re: Report Issues

2002-01-04 Thread Hal Daume III
_) /= (U _ ) = False This probably isn't good, but it suited my purposes. I agree in general, though, I don't think /= should be in the class, even though I've capitalized on it. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about

readfile not so lazy

2002-01-09 Thread Hal Daume III
Why, in the following program: createFile = unsafePerformIO $ writeFile test.xxx ('1' : (take 1000 (repeat '0')) ++ 1) processFile = unsafePerformIO $ do f - readFile test.xxx return (dropWhile (=='0') $ dropWhile

rank x polymorphism

2002-01-17 Thread Hal Daume III
i'm familiar with ranks 1 and 2 of polymorphism. what are the higher ones (are there any). is there a good summary anywhere? -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

dependent type query

2002-01-18 Thread Hal Daume III
even write: data (MyClass f a) = MyData2 f = MyData2 f This makes no sense to me whatsoever. This problem can the thwarted by moving the contraint to only the function definitions, but for MyData itself, it's really a hassle. Please could someone explain what's going on? -- Hal Daume III

question about kinds

2002-01-18 Thread Hal Daume III
this? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo

Re: question about kinds

2002-01-18 Thread Hal Daume III
this be? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Fri, 18 Jan 2002, Hal Daume III wrote: I have the following definition: class Traversable d where traverse :: d

Re: question about kinds

2002-01-18 Thread Hal Daume III
Oops, nevermind; that was dumb of me. I spoke too quickly. Of course that would produce overlapping instances :) -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Fri, 18 Jan 2002, Hal

type specs not making it in to functions

2002-01-25 Thread Hal Daume III
::a). But is there a better/preferred way to do this? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http

compilation using MPI

2002-02-01 Thread Hal Daume III
are there any MPI bindings for any version of Haskell (or related language or any FPL for that matter)? - hal (please respond to my email and not just to the ng) -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes

why is this legal

2002-02-01 Thread Hal Daume III
f x = f' 0 x where f' acc [] = acc f acc (x:xs) = f' (x+acc) xs why are we allowed to rebind f in the where clause? this is clearly a typo (in this instance) but it seems really strange to me that this would be allowed. -- Hal Daume III Computer science is no more about

Re: why is this legal

2002-02-01 Thread Hal Daume III
then, why are we allowed to rebind f in a let clause :) -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Fri, 1 Feb 2002, David Feuer wrote: Hal Daume III wondered: f x = f' 0 x

Re: Position of arguments in function definition and performance

2002-02-06 Thread Hal Daume III
-- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Wed, 6 Feb 2002, [iso-8859-1] José Romildo Malaquias wrote: Hello. Please, tell me which set of definitions below should I expected

Re: String manipulation.

2002-02-07 Thread Hal Daume III
to a list of integers, you could do: map (\x - (read x)::Double) [list of strings] Hope that helps. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Thu, 7 Feb 2002, DK wrote

efficiency question

2002-02-08 Thread Hal Daume III
), but test2 is still much slower. i *expected* test2 to be much faster because you're only traversing the list once. presumably the two elements a and b in test2 could be put in registers and i'd imagine test2 should be faster (it certainly would be if written in c). - hal -- Hal Daume III Computer

RE: efficiency question

2002-02-08 Thread Hal Daume III
I've tried using a strict fold: foldl' f a [] = a foldl' f a (x:xs) = (foldl' f $! f a x) xs but that has no effect (or minimal effect). -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu

RE: efficiency question

2002-02-08 Thread Hal Daume III
This doesn't seem to make a difference, eithr (I just tried it). - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Fri, 8 Feb 2002, Konst Sushenko wrote: Did you try strict

Re: efficiency question

2002-02-08 Thread Hal Daume III
I agree that it's the overhead of (,), but I don't see why there would be any overhead for doing this. -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Sat, 9 Feb 2002, Jorge Adriano

what does fixST do?

2002-02-09 Thread Hal Daume III
subject says it all... -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org

allowing non-sequentiality in IO

2002-02-16 Thread Hal Daume III
be to define a new nonsequential IO monad that basically used unsafePerformIO to do the computations. So it would basically transform the above from to: main = unsafePerformIO (putStrLn hi) `seq` unsafePerformIO (putStrLn bye) and then order wouldn't be guarentee, right? - Hal -- Hal Daume III

haskell sparse matrices

2002-02-17 Thread Hal Daume III
Are there any Haskell libs for dealing with sparse matrices (or even just libraries for writing to and reading from a standard format, say, harwell boeing? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes

Re: Composition Monad

2002-02-17 Thread Hal Daume III
this monadically? -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Mon, 18 Feb 2002, Andre W B Furtado wrote: Roughly speaking, I'm in need of a monad (say MyIO) that interprets

Re: a universal printer for Haskell?

2002-02-19 Thread Hal Daume III
Hi, Doesn't Hugs basically do just this when you don't have +u set? Why not simply mimick their approach? I mean, sure, it's not written in haskell, but does that really matter for the printing for debugging issue? - Hal -- Hal Daume III Computer science is no more about computers

library design conventions

2002-02-27 Thread Hal Daume III
in the first position of the pair. it's probably hopeless to get Random to change at this point, as with the mapAccum functions. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

Re: library design conventions

2002-02-27 Thread Hal Daume III
So I just checked and what Java does is it always loads the unqualified import, so it doesn't do my stuff with automatically adding the package name to imports, which is reasonable. -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about

Re: library design conventions

2002-02-27 Thread Hal Daume III
oops! that was supposed to be a follow up to my post about pacakge, not about this. sorry :) -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Wed, 27 Feb 2002, Hal Daume III wrote

multiparameter generic classes

2002-02-28 Thread Hal Daume III
are there any papers/webpages/implementations/etc. of using multiparameter classes in a generic framework, with or without dependencies? thanks! - hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra

Re: rank-n polymorphism

2002-03-07 Thread Hal Daume III
to the front in type inference. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Thu, 7 Mar 2002, Artem S Alimarine wrote: Dear all, GHC 5.0.3 supports rank-n polymorphism. Could

HGL ang GHC on Win32

2002-03-08 Thread Hal Daume III
... Any ideas? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman

Re: Isn't this tail recursive?

2002-03-12 Thread Hal Daume III
of $! are: f $! a = f a but the difference is that $! causes a to be reduced completely, so it won't build a huge thunk. at least that's my understanding; i'm willing to be corrected :) - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about

Re: Isn't this tail recursive?

2002-03-12 Thread Hal Daume III
Oops, I made a false statement: f $! a = f a but the difference is that $! causes a to be reduced completely, so it won't build a huge thunk. This isn't true. $! will only perform one reduction, so for instance: id $! (a+1,b+1) will not cause a+1 and b+1 to be calculated; it will only

RE: HGL ang GHC on Win32

2002-03-13 Thread Hal Daume III
: linking ... all of which scares me, and now no window even pops up :) sigh. - hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Wed, 13 Mar 2002, Simon Marlow wrote: I'm hoping

un-layout program

2002-03-13 Thread Hal Daume III
does there exist a program that'll take a layed out haskell program and output one that uses braces and semis to delimit? - hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

Re: using less stack

2002-03-20 Thread Hal Daume III
strict a = seq a False foldl' f a l | strict a = annotation foldl' f a [] = a foldl' f a (x:xs) = foldl' f (f a x) xs Or, perhaps strict a = a `deepSeq` False or strict a = rnf a `seq` False if you prefer the rnf notation instead. depending on what you want...

Re: using less stack

2002-03-23 Thread Hal Daume III
Hi, You don't have to define cpsfold explicitly recursively since it can be expressed in terms of foldr: Is this generally considered good design? That is, is it generally preferred to express functions in a nonrecursive style if that can be done using standard library functions like foldr

Z_n in Haskell

2002-03-28 Thread Hal Daume III
-- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Double - non-double function :)

2002-04-03 Thread Hal Daume III
suggestions are welcome (yes, I know I can use show and read, but I'm looking for something which will keep the # of bytes down). - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

Re: Double - non-double function :)

2002-04-03 Thread Hal Daume III
writeIntArray arr 2 i2 readDoubleArray arr 1) But this is dumb and very slow (also note that the array has to be indexed to 2 even though it's only storing one double; this is because readIntArray checks the double bounds). Ideas *other* than this are still welcome :) -- Hal Daume III

deriving over renamed types

2002-04-03 Thread Hal Daume III
there was (supposed to be) a difference between these two declarations? Is there? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

explicitly quantified classes in functions

2002-04-04 Thread Hal Daume III
Foo p where instance Foo Double where data T = forall q . Foo q = T q foo :: Double - T foo p = T p which is very similar, except that the explicit universal quantification is happening in in the datatype and not the function type. why is the former disallowed? -- Hal Daume III Computer

Re: explicitly quantified classes in functions

2002-04-04 Thread Hal Daume III
class Foo p where instance Foo Double where foo :: Double - (forall q . Foo q = q) foo p = p From my humble (lack of) knowledge, there seems to be nothing wrong here, but ghc (5.03) complains about unifying q with Double. Well, of course! The

does this have a name (recusive datatypes)

2002-04-10 Thread Hal Daume III
want to write a show instance for S s, this seems to be impossible. Is it? If so, is this a weakness in Haskell (cyclic instance declarations) or is it theoretically not possible? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy

Re: does this have a name (recusive datatypes)

2002-04-10 Thread Hal Daume III
map f (S a ss) = S (f a) (map f ss) This should have been ... = S (f a) (map (map f) ss) i believe. Sorry. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: does this have a name (recusive datatypes)

2002-04-10 Thread Hal Daume III
[Lots of very useful information snipped...] Not true. Binary leaf trees cannot be captured as `S' always has a label in the internal nodes: data LTree a = Leaf a | Fork (LTree a) (LTree a) Well, you could say: ltree2s (Leaf a) = S a (Pair (Nil,Nil)) ltree2s (Fork l r) = S

trying to tie the knot

2002-04-12 Thread Hal Daume III
of the idiosyncracies in the file format... - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume module DecisionTree where import IO import List data DecisionTree = Test

Introducing Parallelism in a Lazy Functional Language

2002-04-13 Thread Hal Daume III
him? -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

data structure question

2002-04-17 Thread Hal Daume III
than the Double corresponding to element 'b'. does anyone have any suggestions for data structures to solve such a problem. i'm currently using FiniteMap, but would like something faster (btw, there are a LOT of these elements -- around 1million or so). - Hal -- Hal Daume III Computer science

module namespaces with Prelude

2002-04-22 Thread Hal Daume III
so I can hide a few definitions, but then it looks at NLP/Prelude.lhs and complains that the name of that module NLP.Prelude doesn't match Prelude. SHould I simply name my module NLP.NLPPrelude or something (which is ugly, imo) or what? -- Hal Daume III Computer science is no more about

defining (- Bool) as a set

2002-04-22 Thread Hal Daume III
lambda restriction that's been discussed recently on the mailing list? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list

Re: defining (- Bool) as a set

2002-04-22 Thread Hal Daume III
Yeah, both options suggested are valid, of course. But I really don't want to have a constructor and I'm using Edison where Coll is defined something like: class Coll c e where empty :: c e insert :: c e - e - c e etc., which precludes the fun dep solution. - Hal -- Hal Daume III

Re: module namespaces with Prelude

2002-04-22 Thread Hal Daume III
be allowed to (try to) import NLP.Prelude simply as Prelude, thus messing stuff up... -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On 23 Apr 2002, Alastair Reid wrote: #Hal == Hal Daume

semi-private exports

2002-04-22 Thread Hal Daume III
need to be able to access it directly. In Java/C#, I would make Token public and the constructor protected (i.e., public for the current package but private for other people). I would really like to be able to do something similar. Any ideas? - Hal -- Hal Daume III Computer science is no more

style questino: where to put instances

2002-04-23 Thread Hal Daume III
. How do people resolve this problem? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http

Re: defining (- Bool) as a set

2002-04-23 Thread Hal Daume III
it would have been single x = \y - x == y; I think single = (==) is much more difficult to understand at first glance. Doesn't really matter though; presumably the compiler would fix all of this :). -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than

duplicate instance declarations

2002-05-03 Thread Hal Daume III
Why is this a duplicate instance declaration: class C a class D b data T a b instance (C (T a b), C a) = D b instance (C (T a b), C b) = D a These are symmetric, but not duplicate, as I see it. -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than

updating labelled fields

2002-05-06 Thread Hal Daume III
, and, if not, is there any chance it could exist, or is it just syntactic salt to too many people? :) - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

Re: updating labelled fields

2002-05-06 Thread Hal Daume III
$=? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Tue, 7 May 2002, Bryn Humberstone wrote: Hi Hal, 2) update values in the structure, as in: let myData

Re: updating labelled fields

2002-05-09 Thread Hal Daume III
[SNIP] I don't think this is ambigous -- do is a keyword, so no record field update can be assumed after it. Okay, I thought about it some more and I agree. So, as it stands the proposal is to add the following pieces of sugar: 1) ({assignments}) becomes \x-x{assignments} 2)

Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Hal Daume III
to. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Tue, 14 May 2002, Ken Shan wrote: On 2002-05-14T12:32:30-0400, Jan-Willem Maessen wrote: And I'd really much rather we cleaned up

Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Hal Daume III
True, but using seq you can define deepSeq/rnf (depening on which camp you're from), which isn't misleading in this way. -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Tue, 14 May

Re: What does FP do well? (was How to get functional software engineering experience?)

2002-05-15 Thread Hal Daume III
On Wed, 15 May 2002, Karl-Filip Faxen wrote: On the performance (or not) of high level code: I'm working on a compiler with a strong emphasis on generating good code for I wish you luck! It is going to be interesting to see how much this will give. I suspect that part of the performance

reverse function application

2002-05-29 Thread Hal Daume III
to write something like: action1 = action2 = somefunction instead of action1 = \x - action2 = \y - somefunction x y so if it can be done for =, i can make it to work. any advice? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy

Haskell HBLAS Library

2002-06-03 Thread Hal Daume III
. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo

Re: Binary question

2002-06-12 Thread Hal Daume III
There are a few Binarys for GHC out there; I'm not sure which one you're using, but the one I use (that compiles fine) you can grab from me at: http://www.isi.edu/~hdaume/hnlp/Binary.hs (you'll also need hnlp/FastMutInt.lhs) In the meantime i have a temporary version of binary but its

trees with pointers to parents memory gobbling

2002-06-14 Thread Hal Daume III
$ last $ take 10 $ iterate (findLeftMostChild . findRoot) fbtree even if i put an appropriate call to seq in the iteration, i still get lots of memory eaten up, can someone say how i can fix this? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than

Re: Overloading and Literal Numerics

2002-06-26 Thread Hal Daume III
The problem is that you might have: instance Poly Double where ... and then when you say: po 5 it doesn't know whether this is an Int or a Double. writing po (5::Int) should be sufficient. -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than

using hmake with hat

2002-06-27 Thread Hal Daume III
imagine people haven't hit this wall before... - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED

unsafePerformIO around FFI calls

2002-07-08 Thread Hal Daume III
maxEigenvalue so the question is: Under what circumstances is it safe to make instead: compEig' :: [[Double]] - Double compEig' m = unsafePerformIO $ withHMatrix m maxEigenvalue ??? Thanks! - Hal p.s., Please continue to CC Carl as this issue came up in conversations with him -- Hal Daume III

creating a new array vs updating an old one

2002-07-09 Thread Hal Daume III
in *theory* the compile could do it in place, which would make the first much better; in practice, this doesn't seem to always happen (though I haven't looked at it vigorously -- how could i find out?). -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy

RE: comparison of execution speed of array types

2002-07-22 Thread Hal Daume III
Could you try IOUArray for completeness too? (An IOUArray is the unboxed version of IOArray, it can be found in Data.Array.IO). It fits in as the fastest: IOUnboxedMutArray 0.48u 0.04s 0:00.58 89.6% NormalArray 1.65u 0.20s 0:01.89 97.8% NormalArrayReplace

Re: unsafePerformIO around FFI calls

2002-07-23 Thread Hal Daume III
)) [0..255] readIORef foo = return ? (don't call me on syntax errors -- i haven't checked this at all, but you should get the idea) - hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

overloaded num types, but not string types?

2002-07-24 Thread Hal Daume III
into drift??? - hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman

Re: still random number problem

2002-07-24 Thread Hal Daume III
There are a few things wrong with this... uni :: IO () - Float uni = do xs - newStdGen let m = (head (randoms xs) :: Float ) presumably, you want 'uni' to produce a random float. in this case, it has the wrong type; it is actually an IO action that returns a Float,

slightly ot: data structure question

2002-07-29 Thread Hal Daume III
through the elements very quickly. I'm thinking hash tables, but I'm not sure. Does anyone have any thoughts on this? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

Re: edison question

2002-07-30 Thread Hal Daume III
like: let sorted = ... :: SOMETYPEHERE hopefully someone will provide a more complete answer soon, but since no one has replied yet... - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu

good advanced fp (haskell) book

2002-07-31 Thread Hal Daume III
for doesn't exist, and in the absense of a book, perhaps people could point me to good extended (perhaps journal?) papers -- though papers tend to largely ignore the efficiency stuff and serve as very poor references. Thanks! - Hal -- Hal Daume III Computer science is no more about computers

can't write instance Storable

2002-08-01 Thread Hal Daume III
: (r :: Int) - peek addr Failed, modules loaded: none. it's like it doesn't realize that peek is part of the class and can be overloaded. someone please clear this up and tell me what obvious thing i'm missing... Thanks! - Hal -- Hal Daume III Computer science is no more about computers

idiom for different implementations of same idea

2002-08-01 Thread Hal Daume III
other than satisfy the typechecker There are probably a plethora of alternatives I haven't considered, but I'm sure people have done something similar to this before and I'm curious how they handled it... Thanks for reading this far :) - Hal -- Hal Daume III Computer science is no more

Re: idiom for different implementations of same idea

2002-08-01 Thread Hal Daume III
One way to do this would be to import all of the models qualified and then if they choose Model0, pass to the go function Model0.prepareData, Model0.initialize, etc. This is fine, simple, good. But it doesn't enforce at all the types of the functions. I don't understand what you mean

Re: idiom for different implementations of same idea

2002-08-02 Thread Hal Daume III
Hi, In similar situations, especially if there is more than one useful way to use the various parts of an algorithm, I used often prefer existentials: data Model = forall markup table alignments. Model { prepareData :: Data () - Data markup, initialize :: Data

Announce: APP: The Haskell Array Preprocessor

2002-08-13 Thread Hal Daume III
Hi all...I'd read through the results of the survey and there seemed to be a sentiment that people tend to build their own in-house utilities and don't share them. I have a small one, but if anyone wants to use it, they're of course welcome. I have made it available at:

Re: More suitable data structure needed

2002-08-22 Thread Hal Daume III
Hi, On Wed, 2002-08-21 at 16:52, Hal Daume III wrote: I would consider using a prefix trie. Unfortunately, such a structure is not built in to Haskell. Thanks for this! It seems that this kind of data structure is what I am looking for. Excellent. [(a, (Bool

Re: Good layout style? (was: Re: where block local to a guard?)

2002-09-17 Thread Hal Daume III
by user. if/then/else seems to be highly variable. i personally like if foo then bar else baz but opinions are likely to vary widely. likely, |{different offered layout options}| = |{people who respond to this email}|, though, so take anything with a grain of sand. - hal -- Hal Daume

Re: layout problem

2002-09-19 Thread Hal Daume III
Here's one error: ___|n1 do putChar '' ___putSpc (n-1) return() this needs to line up. if that doesn't fix your problem, please try to narrow it down to just one or two function definitions and point out exactly which line is causing the

report definition of field names

2002-09-24 Thread Hal Daume III
or unlabelled fields, but different constructors of a datatype may use whichever, independent of the other constructors. Or something like that. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra

empty field label constructor infelicity

2002-09-24 Thread Hal Daume III
expressions, Hugs generates INTERNAL ERROR: depConFlds for F and 1 for G. Arguably, this is weirdness in the report, but I think it's clear that GHC isn't doing the right thing (where right thing is defined to be what the report says). - Hal -- Hal Daume III Computer science is no more about

efficiency of mfix

2002-09-27 Thread Hal Daume III
point version (loop). On the normal version, it just about triples the speed across the board. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

quantum computing, monads, and FP in general

2002-10-04 Thread Hal Daume III
. Obviously I don't know much about monads and I know even less about quantum computing. Does anyone know if anyone has taken the approach outlined above or anything similar or can point out that I'm just way off track Thanks! - Hal -- Hal Daume III Computer science is no more about

Re: efficiency of mfix

2002-10-14 Thread Hal Daume III
to reconcile this? - Hal p.s., I've attached the code and results (as comments in the code). -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On Sat, 28 Sep 2002, Levent Erkok wrote: On Friday

Re: Q: GHC, Parallel libraries

2002-10-15 Thread Hal Daume III
the updated source files. - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume On 15 Oct 2002, Jan Kybic wrote: Hello, I would like to parallelize my program in Haskell but I have

new version of edison?

2002-10-15 Thread Hal Daume III
Hi all, I was wondering if anyone has a brand-spaking-new version of edison or anything like it. The edison docs still refer to ghc 4.06, which can't be good. If not, is there an edison-like project out there? - Hal -- Hal Daume III Computer science is no more about computers| [EMAIL

Re: Feature Structures

2002-11-20 Thread Hal Daume III
/ot.tar.gz. It includes the source, some tests, some OT features, an incomplete chart parser (oh well) and, of course, a feature structure implementation. -- Hal Daume III Computer science is no more about computers| [EMAIL PROTECTED] than astronomy is about telescopes. -Dijkstra | www.isi.edu

  1   2   3   4   5   >