Re: lexer puzzle

2003-09-26 Thread Ketil Z. Malde
Brandon Michael Moore [EMAIL PROTECTED] writes: Or was that supposed to be composition of a constructor with a function, A . f? Function composition, and higher order functions in general are likely to confuse an imperative programmer, but I think there isn't much syntax can do there. I

Re: Poll: How to respond to homework questions

2003-08-29 Thread Ketil Z. Malde
Shawn P. Garbett [EMAIL PROTECTED] writes: For the How do I write a map function in Haskell?, how about an answer of drop course immediately before your GPA is impacted further. :-) Of course, this comes from someone whos made some stupid posts to this list, and gotten polite answers

Re: idiom for producing comma-seperated lists?

2003-08-14 Thread Ketil Z. Malde
Antony Courtney [EMAIL PROTECTED] writes: -- Example: format a list of strings, using a comma as a seperator: mkSepStr :: [String] - String mkSepStr xs = foldrs (\x s - x ++ , ++ s) xs t0 = mkSepStr [] -- == t1 = mkSepStr [hello]-- == hello t2 = mkSepStr

Re: [String]-[[Bool]] 2

2003-08-14 Thread Ketil Z. Malde
Tn X-10n [EMAIL PROTECTED] writes: change :: String - Bool change 1  = True change 0  = False conv :: [String] - [Bool]==unable to declare [[Bool]] Again: a String is a list of ? -kzm -- If I haven't seen further, it is by standing in the footprints of giants

Re: [String] - [[Bool]]

2003-08-14 Thread Ketil Z. Malde
Tn X-10n [EMAIL PROTECTED] writes: i am new wif haskell, i would like to know how can i get a list of string and convert it to a list of a list of bool [String]- [[Bool]] What is the definition of a String? (I.e. what is a String a list of?) Write a function to convert one of these to the

Re: Editor in Linux for Hint/Helium

2003-08-11 Thread Ketil Z. Malde
Glynn Clements [EMAIL PROTECTED] writes: Does anyone know of a good editor in Linux to do this or the commands for Emacs etc. that can be used from within Hint to achieve [jumping to lines with errors automatically]? Emacs and XEmacs allow you to go to a specified line using +number, If you

Re: [newbie] UTF-8

2003-08-11 Thread Ketil Z. Malde
Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes: Dnia pon 11. sierpnia 2003 00:49, Wolfgang Jeltsch napisa: The main problem is that you need binary I/O. Haskell 98 only provides text I/O. You don't need binary I/O for UTF-8 now; because implementations use ISO-8859-1, UTF-8 octets can

Re: Decimal Literals

2003-07-11 Thread Ketil Z. Malde
Ashley Yakeley [EMAIL PROTECTED] writes: There should be a separate syntax for that. As it stands, the string 3.1415926536 unambiguously specifies a rational number. Perhaps something like 3.1415926536... should be interpreted as the 'simplest' rational that agrees with the given digits,

Re: how to track down out-of-bounds error?

2003-05-29 Thread Ketil Z. Malde
David Roundy [EMAIL PROTECTED] writes: The problem is trying to figure out where I'm doing this. Unfortunately, I have only been able to see this error on a rather large test repository, where it takes seven minutes for the test to show up. Hah! *My* program can take hours before it

Re: parsing e-mail messages (Re: African money)

2003-03-25 Thread Ketil Z. Malde
Peter Simons [EMAIL PROTECTED] writes: Mark Carroll writes: Perhaps I'll have to look out for a library for parsing e-mail messages. I have written a set of parser functions for RFC 2822 messages, which should do exactly that. It's not finished yet, but if you're interested in using the

Re: Debugging haskell

2003-02-23 Thread Ketil Z. Malde
Joe English [EMAIL PROTECTED] writes: Sengan Baring-Gould wrote: http://www.catb.org/~esr/writings/taoup/html/ch01s06.html states that debugging often occupies three-quarters or more of development time. I don't think that is my experience in Haskell... more like 1/4 at most. I was

Re: Arrays and arrays

2003-01-23 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes: OTOH, doing lots of small (//) seems to be faster than doing a few large ones (containing the same updates). Go figure. That's bizarre. Perhaps the results are obscured by some other optimisations which are happening. It is probably an operator

Re: Arrays and arrays

2003-01-22 Thread Ketil Z Malde
Simon Marlow [EMAIL PROTECTED] writes: That's because currently large objects aren't included in the profile. Okay, I didn't know that. I'll look into fixing this. Great! But just knowing about it also helps a lot. Since you're on the line, could you confirm or deny that the (//) operator

Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes: Hal Daume III [EMAIL PROTECTED] writes: Yes, (//) is terrible. It *never* tries to update in-place. Any reason it couldn't be done in-place? (I.e. thaw, update all, and freeze again) Am I missing something -- Could partial results be used

Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes: [EMAIL PROTECTED] (Ketil Z. Malde) writes: Hal Daume III [EMAIL PROTECTED] writes: Yes, (//) is terrible. It *never* tries to update in-place. replace :: UArray Int Int - [(Int,Int)] - UArray Int Int replace a p = runST (thaw a = \u

Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
[EMAIL PROTECTED] (Ketil Z. Malde) writes: replace :: UArray Int Int - [(Int,Int)] - UArray Int Int replace a p = runST (thaw a = \u - update u p freeze u) update :: STUArray s Int Int - [(Int,Int)] - ST s () update u ps = mapM_ (uncurry (writeArray u)) ps (I'll be right back

Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
Hal Daume III [EMAIL PROTECTED] writes: [snip my functions that use the ST monad to do (//)] You shouldn't try to write these functions. You should do all array modifications within the ST monad, rather than looking for a pure solution. All right, but why? It seems an obvious trick, take

Re: Arrays and arrays

2003-01-21 Thread Ketil Z. Malde
Hal Daume III [EMAIL PROTECTED] writes: Any reason it couldn't be done in-place? (I.e. thaw, update all, and freeze again) Am I missing something -- Could partial results be used, the update list be infinite, or anything like that? I believe that's essentially what normal arrays are doing,

Arrays and arrays

2003-01-20 Thread Ketil Z. Malde
Hi Having written a suffix-array based program using lists, I thought I'd speed it up a bit, and perhaps more importantly, save space, using arrays. Basically, the problem is to sort all suffixes of a string, represented as an array of offsets, alphabetically. (Does anybody have such code?

Re: Arrays and arrays

2003-01-20 Thread Ketil Z. Malde
Hal Daume III [EMAIL PROTECTED] writes: Yes, (//) is terrible. It *never* tries to update in-place. Any reason it couldn't be done in-place? (I.e. thaw, update all, and freeze again) Am I missing something -- Could partial results be used, the update list be infinite, or anything like

non-question, instance decl

2003-01-14 Thread Ketil Z. Malde
Hi, experimenting with QuickCheck, I write instance (Arbitrary e) = Arbitrary (Array Int e) where arbitrary = undefined and I get: |Illegal instance declaration for `Arbitrary (Array Int e)' | (The instance type must be of form (T a b c) |where T is not a synonym,

Re: Parsing date and time specifications

2002-12-26 Thread Ketil Z Malde
Simon Marlow [EMAIL PROTECTED] writes: That may well be true, and I've heard others suggest that the library is inconvenient. I'm trying to get at whether that is due to current bugs in the implementation, or whether the design is fundamentally broken. Well; perhaps the right thing to do is

Re: Parsing date and time specifications

2002-12-20 Thread Ketil Z. Malde
Peter Simons [EMAIL PROTECTED] writes: CalendarTime [...] TimeDiff [...] I briefly looked at the Posix module [...] non-standard. *sigh* [...] Any suggestions what I could do? Yes. I think it is widely agreed that the time and date structures in the standard libraries are

Re: Tree insert, lookup with keys

2002-12-20 Thread Ketil Z. Malde
Ingo Wechsung [EMAIL PROTECTED] writes: class Keyed a where { -- Type a is keyed if it has a key function. key :: Ord b = a - b; -- key is a function, that, when applied to a yields some b that is comparable } But it isn't obvious what b is supposed to be. Try multi-parameter

Re: Parsing date and time specifications

2002-12-20 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes: (My preju^H^Hference would be to store a date-time internally in a posix-like manner (seconds,microsecond since the epoch).) I'm still not sure I understand why the Time library is considered to be broken I was probably a bit quick on the trigger

Re: Random

2002-12-18 Thread Ketil Z. Malde
Mark Carroll [EMAIL PROTECTED] writes: On 17 Dec 2002, Ketil Z. Malde wrote: Ah - I was never sure what to make of that - I normally just use the GHC online Haddockised stuff which tells me no more than the type signatures, but I suppose split must be more than (\x-(x,x))! Well, as SPJ

Re: Random

2002-12-17 Thread Ketil Z. Malde
Mark Carroll [EMAIL PROTECTED] writes: The dice function gives you back the new state of the rng which maybe you should keep around to start the next set of rolls with. (main throws it away with snd.) I'd certainly be interested to see how this could be written more nicely. I avoided making

Re: Random

2002-12-17 Thread Ketil Z. Malde
Mark Carroll [EMAIL PROTECTED] writes: On 17 Dec 2002, Ketil Z. Malde wrote: (snip) dice :: Integer - StdGen - [Integer] dice n g = take n $ randomRs (1,6) g Can we still do this concisely and get the new state of the rng back out the other end after the die has been thrown

Re: AW: Editor Tab Expansion

2002-12-10 Thread Ketil Z. Malde
matt hellige [EMAIL PROTECTED] writes: I would PREFER if haskell enforeced a strict distinction between spaces and tabs for layout purposes, i.e., this: let x = y ^I z = q ^Iw = l in ... should be an error. Simon¹ is usually very positive to adding enhancements, if this really

Re: Editor Tab Expansion

2002-12-06 Thread Ketil Z. Malde
John Meacham [EMAIL PROTECTED] writes: rather than start layout blocks right after the 'let' 'do' or 'where', put them on the next line with one more tabstop than the current line. I've also a bit baffled by all the people apparently struggling with layout; I realize the rules are a bit

Re: Completeness of pattern matching

2002-12-06 Thread Ketil Z. Malde
Malcolm Wallace [EMAIL PROTECTED] writes: Ingo Wechsung [EMAIL PROTECTED] writes: I wonder if the compiler could check, if all possible combinations have been checked in a pattern match. In ghc, use the compile-time option -fwarn-incomplete-patterns Is there a warning to warn if a block is

Re: AW: Editor Tab Expansion

2002-12-06 Thread Ketil Z. Malde
Ingo Wechsung [EMAIL PROTECTED] writes: Simon wrote: There's no reason not to use 8 column tab stops, so please don't do it. Ok, if it just looks better to me is no reason, Tabs and spaces aren't visually distinguishable, so I'm not sure why you conclude that looks don't matter. As has

infinite (fractional) precision

2002-10-10 Thread Ketil Z. Malde
Hi I was just browsing around on comp.arch a bit, and there was this discussion about various ways to represent non-integer numeric values. It seems one could easily (I'll get back to that in a moment) calculate the fractional part of numbers lazily, generating the needed precision, and

Re: infinite (fractional) precision

2002-10-10 Thread Ketil Z. Malde
Ashley Yakeley [EMAIL PROTECTED] writes: At 2002-10-10 01:29, Ketil Z. Malde wrote: I realize it's probably far from trivial, e.g. comparing two equal numbers could easily not terminate, and memory exhaustion would probably arise in many other cases. I considered doing something very

Re: Question about sets

2002-08-20 Thread Ketil Z. Malde
Scott J. [EMAIL PROTECTED] writes: I have a question. Why are sets not implemented in Haskell? What do you mean? Isn't http://www.haskell.org/ghc/docs/latest/html/hslibs/set.html sufficient? (Remember to tell GHC '-package data') -kzm -- If I haven't seen further, it is by

Re: Analyzing Efficiency

2002-08-14 Thread Ketil Z. Malde
Shawn P. Garbett [EMAIL PROTECTED] writes: I've come up with three different methods of approach to solve the same problem in haskell. I would like to compare the three in terms of reductions, memory usage, and overall big O complexity. What's the quickest way to gather these stats? I

Re: User-Defined Types

2002-05-01 Thread Ketil Z. Malde
Matthias [EMAIL PROTECTED] writes: Type Constructors and data Constructors are in separate namespaces. [example] But according to the chapter (2.2.1) Recursive Types i see the polymorphic definition of a tree is: data Tree a = Leaf a | Branch (Tree a) (Tree a) where (Tree a) is

Re: ASSISTANCE NEEDED.

2002-04-15 Thread Ketil Z. Malde
Brian Tawney [EMAIL PROTECTED] writes: REQUEST FOR ASSISTANCE- STRICTLY CONFIDENTIAL This is a common scam. It is also a common spam. How about closing the list for non-subscribers? -kzm -- If I haven't seen further, it is by standing in the footprints of giants

Re: partial application

2002-03-18 Thread Ketil Z. Malde
Koen Claessen [EMAIL PROTECTED] writes: Suppose I have a function f which is defined to have 3 arguments: f x y z = ... Now, when I want to partially apply f to two arguments, say 1 and 2, I can say this: ... (f 1 2) ... However, if I want to leave out the middle argument, I

Re: Conversion/porting to mainstream languages

2002-03-11 Thread Ketil Z. Malde
Mark Carroll [EMAIL PROTECTED] writes: One criticism I've received of the suggestion that we use Haskell in our business is that some particularly large clients will demand code in some 'standard' language How big a project would it be to translate, say, from Haskell to C or Java? How

Re: date sorting II

2002-03-10 Thread Ketil Z. Malde
Michael Ruth [EMAIL PROTECTED] writes: start:: IO() start = do { putStr Enter a filename: ; theFile - getLine; myfile - openFile theFile ReadMode; myList - getInput myfile; myDates - stripSpaces myList; myDates - qSort myDates; myList -

Re: Date Sorting...

2002-03-08 Thread Ketil Z. Malde
David Feuer [EMAIL PROTECTED] writes: Sorting is probably easiest if you use the standard sort function. I'm still kind of interested in whether anyone has done work on which purely-functional sorts are efficient, and particularly which ones are efficient in GHC. I've implementing a

Re: Haskell-Cafe digest, Vol 1 #342 - 1 msg

2002-03-05 Thread Ketil Z. Malde
Zhe Fu [EMAIL PROTECTED] writes: But when there is a type error: [...] How can I solve it? I often remove the type declaration, load the code in GHCi or Hugs, and do a :t my_function. The interpreter then tells me what /it/ thinks is the type, and quite often it is smarter than I am :-)

laziness again...

2002-02-18 Thread Ketil Z. Malde
Hi, I'm a bit puzzled by this observatio that I made. I have a function that, pseudocoded, lookes somewhat like f i as bs cs = ins i (f (i+1) as) ++ ins i (f (i+1) bs) ++ ins i (f (i+1) cs) where ins i = manipulates the first element of the list Now, without the ins'es, the

Re: laziness again...

2002-02-18 Thread Ketil Z. Malde
Jay Cox [EMAIL PROTECTED] writes: where ins i = manipulates the first element of the list if you mean that (ins i) :: [a] - [a] manipulates the first element of the list it takes then of course it is strict. because in It is strict in the head of the list, yes. I.e. it is defined

Re: Random questions after a long haskell coding day

2002-01-29 Thread Ketil Z. Malde
Simon Marlow [EMAIL PROTECTED] writes: Can we also rely on destructive updates for the monadic arrays? In GHC, yes :-) Goodie! One more question: I imagine arrays give an opportunity to optimize by unboxing the contained type -- any chance of that? How much space would an array of Chars

Re: State Transformer

2002-01-07 Thread Ketil Z Malde
Jorge Adriano [EMAIL PROTECTED] writes: Anyway, I was coding some simple GA, and as you probably know I need to use random values. The most elegant way I could think of was to generate some [...] Monads! (right?) Well, I suppose so. Generally speaking. But, you might want to consider

Re: instance declarations

2001-12-10 Thread Ketil Z Malde
David Feuer [EMAIL PROTECTED] writes: 1. Why can't [instances] be hidden in module imports/exports? The way I see it, an instance declaration is an assertion that a certain data type supports a certain set of operations. Thus, if the data type and the operations on it are in scope, it makes