[Haskell-cafe] Re: Cabal and linking with static libs (.a files)

2006-06-12 Thread Ketil Malde
Simon Marlow <[EMAIL PROTECTED]> writes: > What you actually want to do, I suspect, is to include verbatim copies > of the .a dependencies in your (binary) Cabal package, to make it > self-contained. Exactly. > But it's quite easy: just copy the .a files from /usr/lib (or > wherever) and put the

Re: [Haskell-cafe] Re: Cabal and linking with static libs (.a files)

2006-06-12 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes: >> But it's quite easy: just copy the .a files from /usr/lib (or >> wherever) and put them in the same place as your libHSpackage.a. > I managed to get it to work by following that advice, and also > renaming foo.a to libfoo.a,

Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread Ketil Malde
"Jared Updike" <[EMAIL PROTECTED]> writes: > On 6/12/06, Neil Mitchell <[EMAIL PROTECTED]> wrote: >> I tend to use the module TextUtil (or Util.Text) from Yhc for these >> kind of string manipulations: > Funny. I have a module called Useful.hs with some of these same sorts > of functions. (comin

Re: [Haskell-cafe] Closure trace?

2006-06-14 Thread Ketil Malde
Bulat Ziganshin <[EMAIL PROTECTED]> writes: > I'm not belittling the underlying problem, which is real. But there do > seem to be many possible design choices without an obvious optimium. If > someone can boil out a principled and simple solution, it'd be a good > contribution. You can also use

Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-23 Thread Ketil Malde
"Brian Hulley" <[EMAIL PROTECTED]> writes: >>> But how does this change the fact that y still has 1 more element >>> than yq? yq is after all, not a circular list. >> infinity+1 = infinity > Surely this is just a mathematical convention, not reality! :-) Not even that. Infinity isn't a number,

[Haskell-cafe] Re: Cabal and linking with static libs (.a files)

2006-06-27 Thread Ketil Malde
Simon Marlow <[EMAIL PROTECTED]> writes: > No idea, I'm afraid. ghc -v might help you. Try cut-and-pasting the > linker command line and play around with ordering of -l options. I noticed the linker is incredibly picky about the sequence of options. Anyway, I suspected that, but I couldn't see

[Haskell-cafe] Re: Packages and modules

2006-07-05 Thread Ketil Malde
"Brian Hulley" <[EMAIL PROTECTED]> writes: > because if the suggested syntax is used, import directives come in two > flavours: ones that use "from" to import from a different package and > ones that don't use "from" and therefore must refer to the current > package. What is the "current package"

[Haskell-cafe] Re: Packages and modules

2006-07-07 Thread Ketil Malde
"Simon Peyton-Jones" <[EMAIL PROTECTED]> writes: > Brian Hulley wrote: > | import A.B.C( T1 ) from "foo" > | import A.B.C( T2 ) from "bar" > | type S = A.B.C.T1 -> A.B.C.T2 > | I'd suggest that the above should give a compiler error that A.B.C is > | ambiguous (as a qualifier), rather than

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

2006-08-14 Thread Ketil Malde
Bulat Ziganshin <[EMAIL PROTECTED]> writes: >> The problem I'm having with SQL right now is that there are a number >> of not complete and splintered implementation efforts. Having one >> library outside GHCs libraries but still promoted as the default >> implementation (and hosted under haskell.o

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

2006-09-06 Thread Ketil Malde
Tamas K Papp <[EMAIL PROTECTED]> writes: > Most of the mistakes I make are related to indentation, I use Emacs, which has a reasonably decent mode for this. Hit TAB repeatedly to show the possible indentations. > precedence (need to remember that function application binds > tightly). It's no

Re: [Haskell-cafe] Slow IO

2006-09-12 Thread Ketil Malde
Daniel Fischer <[EMAIL PROTECTED]> writes: > Maybe I've misused the word segfault. I think so. A segfault is the operating-system complaining about an illegal memory access. If you get them from Haskell, it is likely a bug in the compiler or run-time system (or you were using unsafeAt, or FFI).

Re: [Haskell-cafe] Slow IO

2006-09-14 Thread Ketil Malde
Daniel Fischer <[EMAIL PROTECTED]> writes: > Yes, I did it wrong, but I didn't keep anything (but the first and last Char > of each line) in memory on purpose. I hoped for the lines to be read one > after the other, head and last extracted [...] > Profiling (hy,hc) shows that the IO part of

Re: [Haskell-cafe] Optimization problem

2006-09-14 Thread Ketil Malde
Magnus Jonsson <[EMAIL PROTECTED]> writes: > splitStreams::Ord a=>[(a,b)]->[(a,[b])] >> splitStreams [(3,x),(1,y),(3,z),(2,w)] > [(3,[x,z]),(1,[y]),(2,[w])] [...] > But is there any way to write it such that each element is touched > only once? Or at least an O(n*log(m)) algorithm? I guess i

Re: [Haskell-cafe] Problems interpreting

2006-09-18 Thread Ketil Malde
Carajillu <[EMAIL PROTECTED]> writes: > I get "line 18:parse error (possibly incorrect indentation)" ..which is a bit misleading, as the problem is on the preceeding line of code. > if x == e then return l2 And if x /= e? What is check_elem then?¹ > -- Tries to match two lists

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

2006-09-20 Thread Ketil Malde
Carajillu <[EMAIL PROTECTED]> writes: > compare function just compares the two lists and return true if they are > equal, or false if they are not. > find_match "4*h&a" "4*5&a" 'h' > returns '5' (5 matches with the h) > find_match "4*n&s" "4dhnn" "k" > returns '' (no match at all - lists

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

2006-09-20 Thread Ketil Malde
Andrea Rossato <[EMAIL PROTECTED]> writes: > I forgot, obviously, that lists are an instance of the Eq class... > so, this is enough: > comp l1 l2 = if l1 == l2 then True else False Or why not: > comp l1 l2 = l1 == l2 Or simply: > comp = (==) :-) -k -- If I haven't seen further, it is by s

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

2006-09-27 Thread Ketil Malde
"Jason Dagit" <[EMAIL PROTECTED]> writes: > Ubuntu seems to be a bit behind then. The current official release of > the 6.4 branch is at 6.4.2. Debian seems to provide this version, > maybe you can use the debian package? But, if I were you I wouldn't > worry so much about upgrading ghc but ins

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

2006-09-27 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes: > I filed a request to backport [ghc 6.4.2 to Ubuntu Dapper], but for > some reason, I am unable to find it again. Hah! Found it (with some IRC assistance): https://launchpad.net/distros/ubuntu/+source/ghc6/+bug/56516 -k -- If I haven&#x

Re: [Haskell-cafe] Optimizing a title matcher

2006-09-27 Thread Ketil Malde
Lyle Kopnicky <[EMAIL PROTECTED]> writes: >> If you have some other metric other than prefix in mind for partial >> matches, then things probably get a lot more complicated. You're >> probably looking at calculating minimum distances in some >> feature-space, which calls for pretty sophisticated

Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-11 Thread Ketil Malde
Mikael Johansson <[EMAIL PROTECTED]> writes: > * It violates the principle of least damage, and it encourages a > failure mode that can be extremely embarrassing -- or worse. > I'd be surprised if private mail leakage happens that much to > Haskell-cafe, or for that matter if it'd be embarrassi

Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-12 Thread Ketil Malde
Udo Stenzel <[EMAIL PROTECTED]> writes: >> However, I don't recall problems with multiple copies of emails. > I did get your mail twice, which I don't consider a huge problem. And for people who do, perhaps they can set up procmail to deal with this? E.g., http://www.greatcircle.com/lists/m

Re: [Haskell-cafe] function result caching

2006-10-13 Thread Ketil Malde
"Silviu Gheorghe" <[EMAIL PROTECTED]> writes: > slowFunctionCacheList= [slowFunction (i) | i <-[0..500]] > and use "slowFunctionCacheList !! i" instead of "slowFunction (i)" > i am still curious about a better method (and a general one) Not much different in principle, but better in practice

Re: [Haskell-cafe] function result caching

2006-10-14 Thread Ketil Malde
Robert Dockins <[EMAIL PROTECTED]> writes: >>> slowFunctionCacheList= [slowFunction (i) | i <-[0..500]] >>> and use "slowFunctionCacheList !! i" instead of "slowFunction (i)" >> Not much different in principle, but better in practice - you could >> use an array rather than a list. O(1) looku

Re: [Haskell-cafe] Debugging Newton's method for square roots

2006-10-16 Thread Ketil Malde
Clifford Beshers <[EMAIL PROTECTED]> writes: > There was some excellent advice in the other responses, but I thought > it worth mentioning that your Haskell code converges if you step up > from Float -> Float to Double -> Double. Used to be faster, too, IIRC. Is that still the case? -k -- If I

Re: [Haskell-cafe] Newbie and working with IO Int and Int

2006-10-18 Thread Ketil Malde
Daniel Fischer <[EMAIL PROTECTED]> writes: > ghci-6.6 [prints the result of IO actions] by default I consider printing the value when it is used in an assignment a bug. It makes it more difficult to test laziness issues or behavior on e.g. large files. Anybody know why it was changed to the cur

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

2006-10-30 Thread Ketil Malde
[EMAIL PROTECTED] (Donald Bruce Stewart) writes: > But we could do with more information on: [...] How to make cabal projects into distribution-specific (.deb, .rpm, and so on) packages? -k -- If I haven't seen further, it is by standing in the footprints of giants

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

2006-11-12 Thread Ketil Malde
Grady Lemoine wrote: I use Ubuntu, Me too, and I'm fairly happy with it. My only complaint Haskell-wise is that GHC 6.6 hasn't made it into the package system yet; the latest available from the package system is 6.4.1, 6.4.2 is in the latest version (Edgy). I've tried to pester them into

Re: [Haskell-cafe] Re: Debugging partial functions by the rules

2006-11-15 Thread Ketil Malde
Lennart Augustsson <[EMAIL PROTECTED]> writes: > Should Haskell also provide unrestricted side effects, setjmp/ > longjmp, missile launching functions, etc? After all, people who > don't want to use them can just avoid them. :) Yes. It is indeed a common problem that programs have unintended be

Re: [Haskell-cafe] optimising for vector units

2004-07-26 Thread Ketil Malde
Jan-Willem Maessen - Sun Labs East <[EMAIL PROTECTED]> writes: > There are, I believe, a couple of major challenges: >* It's easy to identify very small pieces of parallel work, but much > harder to identify large, yet finite, pieces of work. Only the > latter are really worth paral

Re: [Haskell-cafe] optimising for vector units

2004-07-27 Thread Ketil Malde
Jan-Willem Maessen - Sun Labs East <[EMAIL PROTECTED]> writes: I missed this bit: > I'm building compilers for supercomputers at Sun So, any plans for compilers for functional languages making use of Niagara? -kzm -- If I haven't seen further, it is by standing in the footprints of giants ___

Re: [Haskell-cafe] Hello and help request

2004-07-31 Thread Ketil Malde
Graham Klyne <[EMAIL PROTECTED]> writes: > I made some notes about this, but they're in no sense authoritative: > http://www.ninebynine.org/Software/Learning-Haskell-Notes.html#type-class-misuse I think it's easy for the OO-programmer to start designing programs using Haskell classes as if they w

Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Ketil Malde
Graham Klyne <[EMAIL PROTECTED]> writes: > 2. I like to distinguish between "expected errors" and "unexpected > errors". Having been burned in the past by using exceptions (not FP), > I try to use them only for conditions that are truly unexpected; > i.e. _exceptional_. Bad input, IMO, is someth

Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Ketil Malde
MR K P SCHUPKE <[EMAIL PROTECTED]> writes: > head :: [a] -> Maybe a > head (a0:_) = Just a0 > head _ = Nothing Argh, no! Violating the precondition of head is a bug in the caller, I want it to crash, but I also want to know where. Wrapping it up in Maybe (or any other error propagation) is not

Re: [Haskell-cafe] exceptions vs. Either

2004-08-03 Thread Ketil Malde
MR K P SCHUPKE <[EMAIL PROTECTED]> writes: >> As for head, I think it's fine that it throws an error because it is >> specified to be defined for only non-empty lists. > But surely it is better to encode this fact in the type system by > useing a separate type for non-empty lists. Yes, in princi

Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
MR K P SCHUPKE <[EMAIL PROTECTED]> writes: >> mins = map ((\(x:_)->x).sort) > maybe what you meant was: > case sort x of > (x:_) -> ... do whatever with x ... > _ -> ... do failure conition ... No, I don't think so. I only want the bug to be reported, and the umatched p

Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
David Roundy <[EMAIL PROTECTED]> writes: > Here "bug" is a function that just calls "error" with a little prefix > explaining that there is a bug in darcs, and would the user please report > it. Obviously, defining a head here would be just as easy, Cool! The basic trick is just to inline the a

Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes: > Unless I'm overlooking something Which I of course did. > #define at (let {at (y:_) 0 = y; at (y:ys) n = at ys (n-1); at _ _ = bug "at" > __FILE__ __LINE__} in \a x -> at a x) No prize for spotting the bug here. -

Re: [Haskell-cafe] exceptions vs. Either

2004-08-04 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes: > import Prelude hiding (head,(!!),read) > Any comments? Here's one: I thought this would make it difficult to have other imports of Prelude, hiding other pieces of it (e.g. catch, to avoid ambiguities with Control.Exception.catch) (Als

Re: [Haskell-cafe] closed classes

2004-08-06 Thread Ketil Malde
Duncan Coutts <[EMAIL PROTECTED]> writes: > closed class GConfValue v where Hmm...doesn't --8<-- module Closed(foo) where class C a where foo = ... instance C ... --8<-- module Main where import Closed ...foo... --8<-- do what you want? You can only use ex

Re: [Haskell-cafe] closed classes

2004-08-06 Thread Ketil Malde
Malcolm Wallace <[EMAIL PROTECTED]> writes: > Ah, but now you cannot use (Closed t) => as a predicate in type > signatures, and since you cannot write a partial signature, you must > omit the signature altogether... Hmm..yes, that would be a disadvantage. :-) -ketil -- If I haven't seen further

Re: [Haskell-cafe] Re: exceptions vs. Either

2004-08-06 Thread Ketil Malde
André Pang <[EMAIL PROTECTED]> writes: > As Keith said, Java will check at compile time whether or not you > handle the exception. This sounds very tedious! The right thing to do if you don't handle them, is of course to propagate exceptions up; however, then you need to update a 'throws' clause

Re: [Haskell-cafe] Re: exceptions vs. Either

2004-08-09 Thread Ketil Malde
Alastair Reid <[EMAIL PROTECTED]> writes: > Do you just want exceptions to be displayed by an interpreter or do you want > them used in the compiler (i.e., part of the Haskell language). I think it would be difficult, and perhaps undesirable, to make it part of the language. So my immediate tho

Re: [Haskell-cafe] cost of List.// for Ord types?

2004-09-07 Thread Ketil Malde
Fergus Henderson <[EMAIL PROTECTED]> writes: >> Basically, I'm wondering if I should avoid using the standard library \\, > If efficiency is a significant concern, and the lists involved may be long, > yes, you should. I'm not sure how to preserve the semantics, either. (\\) seems to delete the

Re: [Haskell-cafe] Writing binary files?

2004-09-13 Thread Ketil Malde
Glynn Clements <[EMAIL PROTECTED]> writes: > Right now, the attempt at providing I18N "for free", by defining Char > to mean Unicode, has essentially backfired, IMHO. Anything that isn't > ISO-8859-1 just doesn't work for the most part, and anyone who wants Basically, I'm inclined to agree with w

Re: [Haskell-cafe] Re: OCaml list sees abysmal Language Shootoutresults

2004-10-13 Thread Ketil Malde
Shawn Garbett <[EMAIL PROTECTED]> writes: > viewpoint: What if List were a type class? Or, what if String were one? Could we have painless read/show with arrays of Char, as well as lists, for instance? -kzm -- If I haven't seen further, it is by standing in the footprints of giants ___

Re: [Haskell-cafe] OCaml list sees abysmal Language Shootout results

2004-09-30 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes: >> wc :: !(Int,Int,Int) -> Char -> (Int, Int, Int) > I'm not sure if that was your question Sorry about that, brain malfunction, bangs are for data declarations, I'll get that cup of coffee now. I guess what you really wa

Re: [Haskell-cafe] OCaml list sees abysmal Language Shootout results

2004-10-06 Thread Ketil Malde
Greg Buchholz <[EMAIL PROTECTED]> writes: > I've been looking at the other shootout results (with the hope of > learning something about making haskell programs faster/less memory > hungry) and I couldn't quite figure out why the "Hashes, part II" test > comsumes so much memory ( http://shooto

Re: [Haskell-cafe] OCaml list sees abysmal Language Shootout results

2004-10-06 Thread Ketil Malde
Ketil Malde <[EMAIL PROTECTED]> writes: > To get memory consumption down, I tried a strict "update" function: >update k fm = let x = (get hash1 k + get fm k) > in x `seq` addToFM fm k x > which slowed the program down(!), I wonder if this i

Re: [Haskell-cafe] Can I determin the function name passed in?

2004-10-07 Thread Ketil Malde
Keith Wansbrough <[EMAIL PROTECTED]> writes: > Instead, you should pass around data items that > contain both the function and its name - either just pairs, [...] > or proper data types ...or both, using records: data NamedFunc a b = NamedFunc { nameOf :: String, apply :: (a->b) } f = Nam

Re: [Haskell-cafe] Re: OCaml list sees abysmal Language Shootout results

2004-10-07 Thread Ketil Malde
Peter Simons <[EMAIL PROTECTED]> writes: > Keith Wansbrough writes: >> Count me as a vote for the better-but-slightly-slower wc. > How about the attached program? On my machine it faster than > Tomasz's version, and I think it's still a fairly clean > source code I guess it's possible to submit

Re: [Haskell-cafe] Re: OCaml list sees abysmal Language Shootout results

2004-10-07 Thread Ketil Malde
Peter Simons <[EMAIL PROTECTED]> writes: > The problem is not Haskell, nor is it the implementation. > The problem is that beginners, including yours truly, tend > to write awfully inefficient code once you give them a > "String" and tell them: Here, that's the contents of your > file. And it's

Re: [Haskell-cafe] Re: OCaml list sees abysmal Language Shootoutresults

2004-10-08 Thread Ketil Malde
William Lee Irwin III <[EMAIL PROTECTED]> writes: >> Actually, I've been wondering about this. If my understanding is >> correct, Haskell lists are basicly singly-linked lists of cons cells (is >> that correct?) A simple (I think) thing to do would be to make the >> lists doubly-linked and ci

Re: [Haskell-cafe] Subsequence near solved hopefully

2004-10-17 Thread Ketil Malde
Remi Turk <[EMAIL PROTECTED]> writes: > You might also want to look at the earlier `any prefix of tails' > suggestion, as it makes the solution a rather simple one-liner. Wouldn't that be looking for a sub*string*, and not a (general) sub*sequence* (which I think does not have to be contigous?)

Re: [Haskell-cafe] Subsequence near solved hopefully

2004-10-17 Thread Ketil Malde
Peter Stranney <[EMAIL PROTECTED]> writes: > Thanks guys for all your help, finally through code, sweat and > tears i have found the solution; Well done! I hope you don't mind some further comments? > isSubStrand:: String -> String -> Bool > isSubStrand [] [] = True > isSubStrand [] (y:ys) = Fa

Re: [Haskell-cafe] Subsequence near solved hopefully

2004-10-17 Thread Ketil Malde
Remi Turk <[EMAIL PROTECTED]> writes: >> Wouldn't that be looking for a sub*string*, and not a (general) >> sub*sequence* (which I think does not have to be contigous?) > Do you mean "subset" with "subsequence"? No, since a set isn't ordered. I would say a subset needs to contain some of the

Re: [Haskell-cafe] Are handles garbage-collected?

2004-10-24 Thread Ketil Malde
Remi Turk <[EMAIL PROTECTED]> writes: > IMO, [bracket] does indeed have those same drawbacks. (Although the > traditional "explicit memory management model" is alloc/free, > which is much worse than bracket/withFile) Isn't bracket more like stack allocated memory? And most problems with explicit

Re: [Haskell-cafe] Are handles garbage-collected?

2004-10-26 Thread Ketil Malde
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes: > - 8 times more popular on c.l.python than c.l.java, > - 11 times more popular on c.l.python than c.l.perl, > - 16 times more popular on c.l.python than c.l.c, but finally > - 4 times *less* popular on c.l.python than c.l.scheme, > i.e

Re: [Haskell-cafe] Set of reals...?

2004-10-28 Thread Ketil Malde
Stijn De Saeger <[EMAIL PROTECTED]> writes: > But, like you mentioned in your post, now I find myself needing a > notion of subset relations, and since you obviously can't define > equality over functions, i'm stuck again. Perhaps one can define an approximate equality, with an error bound? Def

Re: [Haskell-cafe] Processing of large files

2004-11-01 Thread Ketil Malde
"Alexander N. Kogan" <[EMAIL PROTECTED]> writes: > How should I modify it to make it useful on large file? > It eats too much memory... > procFile = > putStrLn . > show . > foldl merge [] . ^ > words foldl is infamous for building the complete list, be

Re: [Haskell-cafe] Newbie Question on type constructors

2004-11-02 Thread Ketil Malde
Ben Rudiak-Gould <[EMAIL PROTECTED]> writes: > In particular, your notation with type signatures makes it totally > unclear that Circle and Square have disjoint ranges; in fact it looks > like they have the same range. : > The syntax that would have made the most sense to me would have been > s

Re: [Haskell-cafe] Re: Processing of large files

2004-11-02 Thread Ketil Malde
Alexander Kogan <[EMAIL PROTECTED]> writes: > Thanks! I did the following: For extra credit, you can use a FiniteMap to store the words and counts. They have, as you probably know, log n access times, and should give you a substantial performance boost. :-) (I have a feeling FMs are slow when t

Re: [Haskell-cafe] Re: Processing of large files

2004-11-04 Thread Ketil Malde
Tomasz Zielonka <[EMAIL PROTECTED]> writes: >> Thank you. It works for me too, but I don't understand why and how ;-)) >> Could you explain? I'm a bit puzzled by this discussion, as strictness of FiniteMaps have rarely been (perceived to be?) a problem for me. > Scott's solution forces (lookupFM

Re: [Haskell-cafe] Sound library?

2004-12-03 Thread Ketil Malde
Henning Thielemann <[EMAIL PROTECTED]> writes: > On Fri, 3 Dec 2004, Jason Bailey wrote: >> Would anyone know of packages out there for Haskell that support mp3's >> or ogg files? > Do you mean realtime unpacking and playback? I'm afraid without hacking > Haskell programs are too slow for that.

Re: [Haskell-cafe] Re: Non-technical Haskell question

2004-12-06 Thread Ketil Malde
John Goerzen <[EMAIL PROTECTED]> writes: >> sensibly share libraries between apps. Anyway, disc is cheap. > Memory not so much, though. One advantage of having something in .so > form is that every instance of every application that uses it shares the > same in-memory image of the code. Well,

Re: [Haskell-cafe] Re: Non-technical Haskell question

2004-12-06 Thread Ketil Malde
Philippa Cowderoy <[EMAIL PROTECTED]> writes: > The strip utility helps somewhat You're right, of course. My executable (incidentally on Sparc) seems to have an overhead of approximately one megabyte when just considering the text segment (that is, subtracting the text sizes of my own .o files).

Re: [Haskell-cafe] Parse text difficulty

2004-12-09 Thread Ketil Malde
Douglas Bromley <[EMAIL PROTECTED]> writes: > I've show(n) a particular data type and it shows up as: > [([2,6],"British"),([1],"Charles"),([1,8],"Clarke"),([2,6],"Council"),([2],"Edinburgh"),([1],"Education"),([4],"Increasingly")] Let me guess: type [([Integer],String)]? > What I want to do is

Re: [Haskell-cafe] Parse text difficulty

2004-12-09 Thread Ketil Malde
Robert Dockins <[EMAIL PROTECTED]> writes: > > And I thought that most programmers used "zipWith", which has to be > > prefix. > [1..5] `zipWith (+)` [7..] You don't have a computer at your end of the internet? :-) Prelude> [1..5] `zipWith (+)` [7..] :1: parse error on input `(' Prelude

Re: [Haskell-cafe] Non-technical Haskell question

2004-12-10 Thread Ketil Malde
> clearly this guy has never seen Phil Wadler. Some people may find this tasteless - I thought it was funny, so I guess those people will find me tasteless also. In that case, I'm probably already in their kill files, so this won't offend anybody. http://www.malevole.com/mv/misc/killer

Re: [Haskell-cafe] AbstractDataType question

2004-12-13 Thread Ketil Malde
Tomasz Zielonka <[EMAIL PROTECTED]> writes: > Record field labels can be also used in pattern matching and in > record update. Especially the latter is very useful. But not quite as elegant -- while record query lets you modify the underlying structure and replace the old record queries with fu

Re: [Haskell-cafe] Begginer question

2005-01-06 Thread Ketil Malde
Maurício <[EMAIL PROTECTED]> writes: > complex_root :: (Float, Float, Float) -> (Complex Float, Complex Float) > complex_root (a,b,c) = (x1,x2) where { > delta = b * b - 4 * a * c :: Float; > sqr_delta = if delta >= 0 then (sqrt delta) :+ 0 else 0 :+ > (sqrt delta) :: (Co

Re: [Haskell-cafe] Re: Utility functions

2005-01-06 Thread Ketil Malde
"Simon Marlow" <[EMAIL PROTECTED]> writes: > There are already a couple of bits of (L)GPL under fptools: GMP and > readline. GMP we'd like to replace because it is necessarily a part of > every compiled Haskell program; readline isn't so important but it would > be nice to have a BSD-licensed rep

Re: [Haskell-cafe] Some random newbie questions

2005-01-07 Thread Ketil Malde
[EMAIL PROTECTED] writes: > I'm constantly surprised hearing from so many people about their space > problems. I cannot remember having space problems with my programs. I > don't know what everybody else is doing wrong :-) At least two common cases. Extracting compact data structures from large

Re: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some random newbiequestions

2005-01-10 Thread Ketil Malde
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes: >> - Do the character class functions (isUpper, isAlpha etc.) work >>correctly on the full range of Unicode characters? > It's not obvious what the predicates should really mean, e.g. should > isDigit and isHexDigit include non-ASCII digi

Re: [Haskell-cafe] Re: Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-11 Thread Ketil Malde
"Simon Marlow" <[EMAIL PROTECTED]> writes: >> For unix, there are couple different tacks one could take. The locale >> system is standard, and does work, but is ugly and a pain to work >> with. In particular, it's another (set of) global variables. And >> what do you do with a character not expr

Re: [Haskell-cafe] Typing question

2005-01-11 Thread Ketil Malde
Dmitri Pissarenko <[EMAIL PROTECTED]> writes: > a) How should I define the types of the attributes correctly? data Purchase = P Double Double data Customer = C Int [Purchase] or, if you want named fields: data Purchase = P { price, rebate :: Double } data Customer = C { id :: Int, purch

Re: [Haskell-cafe] Re: Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-11 Thread Ketil Malde
Okay, I've taken a look (there seems to be some differences between the web page and the tgz from the wiki - fileGet seems to have disappeared). I still don't grok much of it, so just ignore me if I'm being overly naive. Anyway. Let's see, I can now open a stream from a file by doing: f <

Re: [Haskell-cafe] Signature of a function

2005-01-11 Thread Ketil Malde
Dmitri Pissarenko <[EMAIL PROTECTED]> writes: > When I remove the line > activityIndicator :: Customer -> Num > What is wrong in the signature above? Try ':i activityIndicator'? -kzm -- If I haven't seen further, it is by standing in the footprints of giants ___

Re: [Haskell-cafe] Signature of a function

2005-01-11 Thread Ketil Malde
Keith Wansbrough <[EMAIL PROTECTED]> writes: >> One might replace type signatures with comments, of course > You mean one might add comments _as well as_ type signatures, of > course. The only thing worse than no comment is an incorrect > comment. Personally, I'd be inclined to extend that list

[Haskell-cafe] Re: Character predicates

2005-01-11 Thread Ketil Malde
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes: > Dimitry Golubovsky <[EMAIL PROTECTED]> writes: [Proposal: ASCII.isDigit is true for '0'..'9', Unicode.isDigit is true for whatever Unicode defines as digits] >> So there might be a bunch of (perhaps autogenerated, from localedef >> files) m

Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Ketil Malde
Keean Schupke <[EMAIL PROTECTED]> writes: > At the end of the day IO is serial by nature (to one device anyway), > so the way to do this into one file is to have one thread that reads > and writes, and to 'send' read and write requests over channels from > the threads that need the work done Woul

Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Ketil Malde
Keean Schupke <[EMAIL PROTECTED]> writes: > No I meant Channels (from Data.Concurrent)... you can use a structure like: Yes, I realize that (although I haven't yet used Data.Concurrent). It seemed to me, though, that streams are related to channels, and that it may be possible to use the same (o

Re: [Haskell-cafe] Re: I/O interface

2005-01-13 Thread Ketil Malde
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes: > Ketil Malde <[EMAIL PROTECTED]> writes: >> It seemed to me, though, that streams are related to channels, > I'm not sure what exactly do you mean by streams (because they are > only being design

Re: [Haskell-cafe] Question about instance

2005-01-14 Thread Ketil Malde
John Velman <[EMAIL PROTECTED]> writes: >> data Relation a i b = Rel {name::RN, arity::Int, members::(Set [EN])} Why do you parametrize the data type when you don't use the parameters? Either do data Relation = Rel {name::RN, arity::Int, members::Set [EN]} or data Relation a i b = {

Re: [Haskell-cafe] Linear shuffle

2005-01-14 Thread Ketil Malde
Gracjan Polak <[EMAIL PROTECTED]> writes: > shuffle :: [a] -> IO [a] > shuffle [] = return [] > shuffle x = do > r <- randomRIO (0::Int,length x - 1) > s <- shuffle (take r x ++ drop (r+1) x) > return ((x!!r) : s) > This algorithm seems not effective, length, take, drop and (!!) a

Re: [Haskell-cafe] Linear shuffle

2005-01-14 Thread Ketil Malde
Tomasz Zielonka <[EMAIL PROTECTED]> writes: > On Fri, Jan 14, 2005 at 09:17:41AM +0100, Gracjan Polak wrote: >> This algorithm seems not effective, length, take, drop and (!!) are >> costly. Is there any better way to implement shuffle? > You can use mutable arrays (modules Data.Array.MArray, Da

Re: [Haskell-cafe] Linear shuffle

2005-01-14 Thread Ketil Malde
Tomasz Zielonka <[EMAIL PROTECTED]> writes: >> But is that better, really? IIUC, you will now need to shift the first >> part of the string to the right, so it's still a linear operation for >> each shuffle. > Perhaps I don't know this particular algorithm, but you can shuffle the > array with l

Re: [Haskell-cafe] Linear shuffle

2005-01-14 Thread Ketil Malde
Keean Schupke <[EMAIL PROTECTED]> writes: > Please see: http://okmij.org/ftp/Haskell/perfect-shuffle.txt > For an explanation of the algorithm. Right. I was commenting based on the source posted by Gracjan. (And http://c2.com/cgi/wiki?LinearShuffle contains a variety of shuffling algorithms).

Re: [Haskell-cafe] RE: Answers to Exercises in Craft of FP

2005-01-19 Thread Ketil Malde
"David Owen" <[EMAIL PROTECTED]> writes: >> Do you know if there are solutions to exersises available somewhere? >> Have you gone through the whole book, i.e. all the exercises? > Unfortuantely I don't know of anywhere that the exercise answers can > be found, even after some google searching. A

Re: [Haskell-cafe] Math libraries for Haskell

2005-01-19 Thread Ketil Malde
Keean Schupke <[EMAIL PROTECTED]> writes: > Can I request 2 types, one for dense (complete) matricies and > another for sparse matricies? ...and maybe also put (!) in a class, so that it can be used as a general indexing operator for all indexed data structures? (Or is this already possible? I

Re: [Haskell-cafe] Re: [Haskell] Re: Why is getArgs in the IO monad?

2005-01-19 Thread Ketil Malde
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes: > This suggests that making global parameters available only as > arguments of main would be a bad idea. But they should be settable, > to account for the rare case of wanting to substitute something else > to a library which reads them itself.

Re: [Haskell-cafe] Reading images (PGM)

2005-01-20 Thread Ketil Malde
Greg Buchholz <[EMAIL PROTECTED]> writes: >> I need to write a function in Haskell, which >> 1) reads a greyscale image (for instance, in JPEG, PNG or the like) and > If you can specify any image format you want, and you're not > concerned with efficiency, you can't beat the simplicity of the

Re: [Haskell-cafe] Re: Hugsvs GHC (again)was: Re: Somerandomnewbiequestions

2005-01-21 Thread Ketil Malde
Duncan Coutts <[EMAIL PROTECTED]> writes: > The point is that the Unix documentation does not consider the short > pause as data is read off your hard drive to be blocking. So that's why > select will always report that data is available when you use it with a > file handle. Isn't this also for h

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-24 Thread Ketil Malde
Daniel Fischer <[EMAIL PROTECTED]> writes: >> 'everything matters' is wrong even for IO actions, because the >> actual value returned when the action is executed is completely >> irrelevant to the IO action's identity. > Now that I cannot swallow, that would mean > return 4 == return 5. I would

Re: [Haskell-cafe] Re: what is inverse of mzero and return?

2005-01-25 Thread Ketil Malde
Daniel Fischer <[EMAIL PROTECTED]> writes: >> getChar = 'the action that, when executed, reads a character from stdin and >> returns it' > I still say, getChar is not a well defined value of IO Char. By this line of reasoning, I think any imperative, real-world interacting program is ill-defined

Re: [Haskell-cafe] using Map rather than FiniteMap

2005-01-25 Thread Ketil Malde
"S. Alexander Jacobson" <[EMAIL PROTECTED]> writes: > Just did a search after my last post and learned that FiniteMap is > bad. Discoverd that Data.Map is the intended replacement. Downloaded > it and modified it to work with 6.2. Blazingly fast! Oh? I was aware that Data.Map was supposed to

Re: [Haskell-cafe] Converting from Int to Double

2005-01-26 Thread Ketil Malde
Dmitri Pissarenko <[EMAIL PROTECTED]> writes: > How can I convert an Int into a Double? You don't convert to, you convert from :-) The function 'fromIntegral' is probably what you want. -kzm -- If I haven't seen further, it is by standing in the footprints of giants ___

Re: [Haskell-cafe] RE: Answers to Exercises in Craft of FP

2005-01-28 Thread Ketil Malde
Christian Hofer <[EMAIL PROTECTED]> writes: >> That is perfectly alright with me. The problem that we are >> discussing is that it would be helpful to have the solutions to the >> exercises for a book that I buy for studying on my own. How about: 1) Solve the excercises, and publish the solution

Re: [Haskell-cafe] Re: mathematical notation and functional programming

2005-01-28 Thread Ketil Malde
Chung-chieh Shan <[EMAIL PROTECTED]> writes: >> O(n) >>which should be O(\n -> n) (a remark by Simon Thompson in >>The Craft of Functional Programming) It's a neat thought, IMHO. I usually try to quantify the variables used, making the equivalent of 'let n = .

Re: [Haskell-cafe] Re: ocr'ed version of "The implementation offunctional languages"

2005-01-31 Thread Ketil Malde
"Simon Peyton-Jones" <[EMAIL PROTECTED]> writes: > What would OCR buy us? Searching, I guess, which is a fantastic > plus. Anything else? - The ability to cut and paste passages into e.g. e-mail. - Availability for text-only access - e.g. for the vision impaired, or people on low bandwidth co

[Haskell-cafe] Re: UTF-8 BOM, really!?

2005-01-31 Thread Ketil Malde
"Bayley, Alistair" <[EMAIL PROTECTED]> writes: >> How can it make sense to have a BOM in UTF-8? > "Q: Where is a BOM useful? > A: A BOM is useful at the beginning of files that are typed as text, but for > which it is not known whether they are in big or little endian format..." I think the qu

<    4   5   6   7   8   9   10   >