Re: [Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-02-25 Thread ajb
G'day all. This one is pretty elegant. A Pritchard sieve is actually an Eratosthenes sieve with the loops reversed. Unfortunately, it's a bit slower. Maybe someone else can speed it up a bit. mergeRemove :: [Integer] - [Integer] - [Integer] mergeRemove [] ys = [] mergeRemove xs [] = xs

Re: [Haskell-cafe] Re: Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-02-23 Thread ajb
G'day all. Quoting Melissa O'Neill [EMAIL PROTECTED]: Cool, thanks. When I ran your code trying to find the 10,000th prime, I got AtkinSieveTest: Ix{Integer}.index: Index (36213) out of range ((0,36212)) but that went away when I made your array one bigger. Fixed, thanks. Cheers,

Re: [Haskell-cafe] Code and Perf. Data for Prime Finders (was: Genuine Eratosthenes sieve)

2007-02-22 Thread ajb
G'day all. Quoting Melissa O'Neill [EMAIL PROTECTED]: But talk is cheap. What about some actual numbers, and some code for some actual implementations...? Just to fill out the implementations: http://andrew.bromage.org/darcs/numbertheory/ Math/Prime.hs has an implementation of the

Re: [Haskell-cafe] speeding up fibonacci with memoizing

2007-02-18 Thread ajb
G'day all. Quoting Stefan O'Rear [EMAIL PROTECTED]: Prior art trumps all. (by a few %) granted it doesn't do much memoizing anymore :) Ah, butbutbut... of course the Gosper/Salamin one is going to be faster if you only compute one Fibonacci number per instance. The memoed version is

Re: [Haskell-cafe] How is laziness defined?

2007-02-05 Thread ajb
G'day all. Quoting Matthew Brecknell [EMAIL PROTECTED]: Although it covers irrefutable (lazy) pattern matching in the second section, it does appear to miss the point that let bindings are always irrefutable. Thus, there is no difference between these two: let (x,y) = foo in ... let

Re: [Haskell-cafe] How is laziness defined?

2007-02-05 Thread ajb
G'day all. Quoting Matthew Brecknell [EMAIL PROTECTED]: In other words, the irrefutability of a pattern match does not distribute inside the top-level data constructor of the pattern. I wasn't disagreeing with you, which is why I didn't comment. Note also that if Haskell prime incorporates

Re: [Haskell-cafe] Alternate instance Show (Maybe a)?

2007-02-04 Thread ajb
G'day all. Quoting Sergey Zaharchenko [EMAIL PROTECTED]: Yes, I think another Show-like class will probably be a better solution... This is the one that I use. Very simple. import Text.PrettyPrint.HughesPJ class Pretty a where -- Equivalent of showsPrec prettyP ::

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread ajb
G'day all. Quoting TJ [EMAIL PROTECTED]: I would think that with 100% laziness, nothing would happen until the Haskell program needed to output data to, e.g. the console. Quite obviously that's not it. So how is laziness defined in Haskell? It means that the program behaves as if things are

Re: [Haskell-cafe] How is laziness defined?

2007-02-04 Thread ajb
G'day all. tjay.dreaming: So it's just IO which makes things run huh? OK that's basically what I said there. Cool. Yeah, but you said output. Sending a signal to another process in Unix is I/O, which would force the process id to be evaluated, but there's no output as such. Cheers, Andrew

Re: [Haskell-cafe] Fractional sqrt

2007-01-20 Thread ajb
G'day all. I said: I've also extended the range for approxSmallSqrt here from (0,255) to (0,271). It is left as an exercise as to why this might be a good idea. (Hint: 272 is approximately 16.5*16.5.) The correct answer, for those playing at home, is it's because it WAS a good idea when I

Re: [Haskell-cafe] Fractional sqrt

2007-01-19 Thread ajb
G'day all. Quoting Henning Thielemann [EMAIL PROTECTED]: Newton method for sqrt is very fast. It converges quadratically, that is in each iteration the number of correct digits doubles. The problem is to find a good starting approximation. Yup. So how might we go about doing this? First

Re: [Haskell-cafe] IO in lists

2007-01-17 Thread ajb
G'day all. Quoting Yitzchak Gale [EMAIL PROTECTED]: What can be done to get an improved list transformer into MTL? Not sure. But a lot of people use mine: http://sigcomp.srmr.co.uk/~rjp/Nondet.hs (My darcs repository is down at the moment, unfortunately.) Cheers, Andrew Bromage

Re: [Haskell-cafe] IO in lists

2007-01-16 Thread ajb
G'day all. On Tue, Jan 16, 2007 at 14:06:08 +0200, Yitzchak Gale wrote: But the list monad [] is not a transformer, so you can't lift in it, even if the contained type happens also to be a monad. Quoting Magnus Therning [EMAIL PROTECTED]: Yeah, I had some vague thought of that being a

Re: [Haskell-cafe] constant functions

2006-12-29 Thread ajb
G'day all. Quoting Matthew Brecknell [EMAIL PROTECTED]: Yes. Function application (-) is right-associative in a type expression. What about a value expression? f a b === (f a) b Looks like an inconsistency? Not if you think about it. :-) And if you don't want to think about it, this

Re: [Haskell-cafe] Re: A suggestion for the next high profile Haskell project

2006-12-23 Thread ajb
G'day all. Quoting Sebastian Sylvan [EMAIL PROTECTED]: There are of course other real world scenarios. For example you may have competitors. I currently write C++ for my day job because in my industry (games) speed is a major bullet point on which you get judged. I have a suspicion that

Re: [Haskell-cafe] Re: A suggestion for the next high profile Haskell project

2006-12-23 Thread ajb
G'day all. Quoting Tomasz Zielonka [EMAIL PROTECTED]: I think it's high time to remind the very true Hoare's words: Premature optimization is the root of all evil in programming It's strange nobody mentioned it earlier. You have yeard it said in the past that the three rules of

Re: [Haskell-cafe] Re: A suggestion for the next high profile Haskell project

2006-12-22 Thread ajb
G'day all. Bulat Ziganshin [EMAIL PROTECTED] writes: of course, we can fool any topic by changing the names. no one will say that Haskell is small productive language, the topic was just about speed of code generated Actually, the topic was performance. What performance means to a modern

Re: A suggestion for the next high profile Haskell project [Was: Re: [Haskell-cafe] What is a hacker?]

2006-12-17 Thread ajb
G'day all. Quoting Bulat Ziganshin [EMAIL PROTECTED]: Haskell can't provide fast execution speed unless very low-level programming style is used (which is much harder to do in Haskell than in C, see one of my last messages for example) AND jhc compiler is used I've written an implementation

Re: [Haskell-cafe] Re: A suggestion for the next high profile Haskell project

2006-12-17 Thread ajb
G'day all. Quoting Neil Mitchell [EMAIL PROTECTED]: I believe that compilers can get a lot cleverer - my hope is that one day the natural Haskell definition will outperform a C definition. First off, let's get something straight: Everyone's metric for performance is different. When someone

Re: [Haskell-cafe] Re: what are the points in pointsfree?

2006-12-14 Thread ajb
G'day all. Quoting Steve Downey [EMAIL PROTECTED]: from what you just told me, it's not an artifact of the pf style, but that maximally reusable functions will be expressible in a pointsfree style. Not necessarily. (There's a fairly obvious reductio ad absurdum argument as to why: at least

Re: [Haskell-cafe] Re: Writing Haskell For Dummies Or At Least For People Who Feel Like Dummies When They See The Word 'Monad'

2006-12-14 Thread ajb
G'day all. Quoting Donn Cave [EMAIL PROTECTED]: Well, maybe not Patterns, but wouldn't there be important skills relating to patterns in a more general sense? Like fold, for example, seems to be a pattern, with several standard implementations and no doubt countless others to suit

Re: Re: [Haskell-cafe] Writing Haskell For Dummies Or At Least For People Who Feel Like Dummies When They See The Word 'Monad'

2006-12-11 Thread ajb
G'day all. Quoting Kirsten Chevalier [EMAIL PROTECTED]: I suppose I should have clarified that I meant a dead-trees book with a real publisher, [...] Something more like this, then: http://phptr.com/perens Maybe we should come up with an outline and a sample chapter or two, then talk to

Re: [Haskell-cafe] There's nothing wrong with infinite types!

2006-12-05 Thread ajb
G'day all. Quoting Stefan O'Rear [EMAIL PROTECTED]: I for one took that as a challenge, and have implemented a type inference engine for infinite types. Very nice! But there's plenty wrong with infinite types... The fact is that infinite types are almost never what you want. In the few

Re: [Haskell-cafe] How to design default implementations of type class methods?

2006-11-08 Thread ajb
G'day all. Quoting Henning Thielemann [EMAIL PROTECTED]: I like to hear some opinions about how to implement class method defaults. In this case, don't. Use instance defaults instead. class (Eq a) = Ring a where (*),(+),(-) :: a - Integer zero, one :: a negate :: a - a

Re: [Haskell-cafe] Very Small Program

2006-11-02 Thread ajb
G'day all. Quoting Bernie Pope [EMAIL PROTECTED]: This is a weird example of a pattern binding, and it is surprising (to me) that the syntax is valid. Maybe. But you wouldn't balk at this: numzeroes xs = sum [ 1 | 0 - xs ] ...even if you wouldn't naturally express it that way.

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

2006-10-15 Thread ajb
G'day all. Quoting Tamas K Papp [EMAIL PROTECTED]: 2. Newton's method is not guaranteed to converge. For computing square roots, it is. The square root function is exceedingly well-behaved. But you can make things better by choosing a smart initial estimate. The initial estimate in this

Re: [Haskell-cafe] Re: function result caching

2006-10-14 Thread ajb
G'day all. Carl Witty wrote: Instead of using an infinite list, you can use an infinite binary tree, with a cached result at every node. Quoting [EMAIL PROTECTED]: This, also known as patricia tree, is indeed the canonical answer. A Patricia tree is but one infinite tree data structure.

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-14 Thread ajb
G'day all. Quoting Henning Thielemann [EMAIL PROTECTED]: A monoid operation is associative, isn't it? Duh. Yes. Sorry. Need caffeine. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all. Quoting Jason Dagit [EMAIL PROTECTED]: I was making an embedded domain specific language for excel spreadsheet formulas recently and found that making my formula datatype an instance of Num had huge pay offs. Just so you know, what we're talking about here is a way to make that

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-13 Thread ajb
G'day all. Quoting Henning Thielemann [EMAIL PROTECTED]: ... which got the same name, too, namely 'foldl'. You mean foldr. The place of foldl is a bit tricky, but in this case it requires that the monoid be Abelian. Cheers, Andrew Bromage ___

Re: [Haskell-cafe] Re: Numeric type classes

2006-09-12 Thread ajb
G'day all. Quoting Henning Thielemann [EMAIL PROTECTED]: It seems we are at a point, where we have to define what is a 'number'. For backwards compatibility, I'd say a Num is what it is at the moment. One of the proposals that comes up every so often is to allow the declaration of a typeclass

Re: [Haskell-cafe] Monad laws

2006-09-07 Thread ajb
G'day all. Quoting Deokhwan Kim [EMAIL PROTECTED]: What is the practical meaning of monad laws? Interesting philosophical question. There will be an article on this topic in the next The Monad.Reader, so watch this space. But what practical problems can unsatisfying them cause? Pretty much

Re: Quantification in free theorems (Was: [Haskell-cafe] Exercise in point free-style)

2006-09-05 Thread ajb
G'day all. Quoting Janis Voigtlaender [EMAIL PROTECTED]: I find the omission of quantifications in the produced theorems problematic. I agree. Indeed, if you look at the source code, the quantifications _are_ generated, they're just not printed. The reason is that the output was

[Haskell-cafe] Re: Quantification in free theorems

2006-09-05 Thread ajb
G'day all. Quoting Janis Voigtlaender [EMAIL PROTECTED]: Maybe it is just an accidental swapping of the arguments to (.) in your implementation. That was it, yes. Thanks for debugging my code for me. :-) (For those keeping score, it was actually the incorrect unzipping of a zipper data

Re: [Haskell-cafe] Exercise in point free-style

2006-09-04 Thread ajb
G'day all. Quoting Donald Bruce Stewart [EMAIL PROTECTED]: Get some free theorems: lambdabot free f :: (b - b) - [b] - [b] f . g = h . f = map f . f g = f h . map f I finally got around to fixing the name clash bug. It now reports: g . h = k . g = map g . f h = f k . map g Get

Re: [Haskell-cafe] A free monad theorem?

2006-09-03 Thread ajb
G'day all. Quoting Benjamin Franksen [EMAIL PROTECTED]: As we all know, the monadic bind operation has type: bind :: Monad m = m a - (a - m b) - m b My intuition says that in order to apply the second argument to some non-trivial (i.e. non-bottom) value of type a, the bind operator

Re: [Haskell-cafe] Re: Why does Haskell have the if-then-else syntax?

2006-08-16 Thread ajb
G'day all. Quoting Benjamin Franksen [EMAIL PROTECTED]: For what it's worth, I have been asking myself the same question several times. If/then/else syntax could be replaced by a regular (lazy) function without any noticeable loss. I believe that if-then-else cannot be replaced by a regular

Re: [Haskell-cafe] iterative algorithms: how to do it in Haskell?

2006-08-16 Thread ajb
G'day all. Quoting Chris Kuklewicz [EMAIL PROTECTED]: The compiler may not deforest that list, so creating the list may be a small overhead of this method. And in return, you get: - Code that is smaller than the imperative version, AND - a reusable function, making the next

Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread ajb
G'day all. Quoting Udo Stenzel [EMAIL PROTECTED]: Uh, this one's wrong. Does C++ of 15 years ago support today's programs? C++ of _today_ doesn't support today's programs in some cases. Just ask the Boost developers about the various workarounds they still have to deal with. No. C++ of 10

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread ajb
G'day all. Quoting Robert Dockins [EMAIL PROTECTED]: Edison's design hails from a time when MPTCs were not only non-standard (as they still are), but also not widely used, and before fundeps were avaliable (I think). Yes. Chris Okasaki's original version of Edison was standard H98. I've

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread ajb
G'day all. Quoting Brian Hulley [EMAIL PROTECTED]: The problem is that some people will be using Data.Edison.Seq at the moment and will naturally not want it to change. However I'd suggest that all the common operations be factored out into separate classes eg: While I think the huge

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread ajb
G'day all. Quoting David Menendez [EMAIL PROTECTED]: That's a tough call to make. Changing the kind of Sequence to * from * - * means losing the Functor, Monad, and MonadPlus superclasses and all the various maps and zips. And on the other hand, containers that need extra constraints (e.g.

Re: [Haskell-cafe] Where is Data.Atom ?

2006-07-02 Thread ajb
G'day all. Quoting Brian Hulley [EMAIL PROTECTED]: I can see that an unsafe global ref to a Trie of Char with Unique as the value of a node would allow me to implement fromString, toString, and instance Eq Atom, but I've got no idea how to implement instance Ord Atom so that the order is

Re: [Haskell-cafe] Functional programming for processing of large raster images

2006-06-22 Thread ajb
G'day all. Quoting [EMAIL PROTECTED]: Recently Vo Minh Thu wondered if Haskell (or, I generalize, functional programming) can be of much use for computer graphics programming. As others have pointed out, it's Haskell (and its laziness) that he perceived to be the problem. However, I'd like

Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-18 Thread ajb
G'day all. Quoting Mathew Mills [EMAIL PROTECTED]: I guess I don't get any points for an approximate solution, ay? If only there was an iterative algorithm. Then you could use your method to get a great initial estimate... Cheers, Andrew Bromage

Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-16 Thread ajb
G'day all. Quoting Mathew Mills [EMAIL PROTECTED]: How about the closed form ;) -- fib x returns the x'th number in the fib sequence fib :: Integer - Integer fib x = let phi = ( 1 + sqrt 5 ) / 2 in truncate( ( 1 / sqrt 5 ) * ( phi ^ x - phi' ^ x ) ) Seems pretty quick to

Re: [Haskell-cafe] Fibonacci numbers generator in Haskell

2006-06-15 Thread ajb
G'day all. Quoting Vladimir Portnykh [EMAIL PROTECTED]: I wrote my own Fibonacci numbers generator: fib :: Int - [Int] fib 0 = [0,0] fib 1 = [1,0] fib n = [sum prevFib, head prevFib] where a = fib (n - 1) To get the k-th number you do the following: result = head (fib k) [...] Can

RE: [Haskell-cafe] shared local definitions

2006-05-18 Thread ajb
G'day all. Quoting Simon Peyton-Jones [EMAIL PROTECTED]: So the best way to transform f depends on how it is used. When it's used locally and just once, GHC inlines it at the call site and all is good. But when it's exported or called many times, GHC never floats a let *between* two

Re: [Haskell-cafe] Justification for Ord inheriting from Eq?

2006-04-06 Thread ajb
G'day all. Quoting Robert Dockins [EMAIL PROTECTED]: Eww! Be careful how far you depend on properties of typeclasses, and make sure you document it when you do. The behaviour of NaN actually makes perfect sense when you realise that it is Not a Number. Things that are not numbers are

Re: [Haskell-cafe] Re: Positive integers

2006-03-26 Thread ajb
G'day all. Quoting Jared Updike [EMAIL PROTECTED]: Surprisingly, there is a page on MathWorld about Torsors but it is empty. Google turned up the following page with a good explanation. http://math.ucr.edu/home/baez/torsors.html Ah, right. So torsor is just a short name for regular group

Re: [Haskell-cafe] Looking for an efficient tree in STM

2006-03-18 Thread ajb
G'day all. On Wed, Mar 08, 2006 at 01:50:06PM +0200, Einar Karttunen wrote: Does anyone have an efficient tree implemented in STM that supports concurrent updates in an efficient fashion? One could easily rewrite this question as: Does anyone have an efficient tree that supports

[Haskell-cafe] Re: haskell programming guidelines

2006-02-28 Thread ajb
G'day all. Quoting Christian Maeder [EMAIL PROTECTED]: I suggested: f . g $ h x or f $ g $ h x Of these, the first version only makes sense if you want to single out h for some reason. I'm known to do this, for example, if h is a record accessor. The second is just plain

Re: [Haskell-cafe] Re: haskell programming guidelines

2006-02-22 Thread ajb
G'day all. Quoting Christian Maeder [EMAIL PROTECTED]: I see this differently. Expressions may be succinct! I find $ and . similar enough for non-obfuscation. But they're _not_ similar! Compare this notation: f . g . h $ x with the one you suggested: f $ g $ h $ x Advantages of

Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread ajb
G'day all. Quoting Tomasz Zielonka [EMAIL PROTECTED]: Probably it was anticipated that right associative version will be more useful. You can use it to create a chain of transformations, similar to a chain of composed functions: (f . g . h) x = f $ g $ h $ x Of course, if $ were

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread ajb
G'day all. Quoting Paul Hudak [EMAIL PROTECTED]: Actually, one of the main reasons that we chose (:) is that that's what Miranda used. So, at the time at least, it was not entirely clear what the de facto universal inter-language standard was. Exactly. One point that's often not

Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread ajb
G'day all. Quoting [EMAIL PROTECTED]: This is the way that I normally express it. Partly because I find function application FAR more natural than right-associative application, I meant to say that I find function COMPOSITION more natural than right-associative application. It certainly

Re: [Haskell-cafe] Substring replacements

2005-12-14 Thread ajb
G'day all. Quoting Branimir Maksimovic [EMAIL PROTECTED]: After seeing that your program is fastest (I've also tried one from http://haskell.org/hawiki/RunTimeCompilation but perhaps I'm not that good in converting to search replace?) You probably did it right, but you could post your

Re: [Haskell-cafe] Tail-call optimization

2005-12-11 Thread ajb
G'day. Quoting Joel Reymont [EMAIL PROTECTED]: writeLoop :: (Event a - IO ()) - Handle - (SSL, BIO, BIO) - IO () writeLoop post h ssl = do handle (\e - post $ NetworkError e) $ do cmd - read h ssl post $! Cmd $! cmd writeLoop post h ssl Good,

Re: [Haskell-cafe] Tail-call optimization

2005-12-11 Thread ajb
G'day all. Quoting Joel Reymont [EMAIL PROTECTED]: Thank you Andrew! Does it have any effect on performance? Yes, however I believe that GHC can perform this transformation automatically at high optimisation levels. Even so, for portability, it's wise not to rely on your implementation

[Haskell-cafe] Re: [Haskell] specification of sum

2005-11-01 Thread ajb
(Moving this to the cafe.) G'day all. Quoting Cale Gibbard [EMAIL PROTECTED]: We already do rely on them in most cases. Of course, not every property can be proved by the compiler, but many pieces of code are going to assume quite a lot. Agreed. I think that the assumption that (+) and

Re: [Haskell-cafe] 14-queens Problem

2005-10-02 Thread ajb
G'day all. Quoting Yousry Abdallah [EMAIL PROTECTED]: is it fast to calculate all solutions for the 14-queens problem in 7 minutes? No. % time ./queens 14 365596 solution(s). real0m4.045s user0m3.928s sys 0m0.008s The program is a minimal cover solver

Re: [Haskell-cafe] Updating the Haskell Standard

2005-07-21 Thread ajb
G'day all. Quoting Brian Smith [EMAIL PROTECTED]: Even if undecidable instances was standardized, would we want it turned on by default? I am trying to write real programs in Haskell and I have never even comtemplated using undecidable instances. There's only one situation where I've found

Re: [Haskell-cafe] Re: [Haskell] Re: A MonadPlusT with fair operations and pruning

2005-07-21 Thread ajb
G'day all. Quoting [EMAIL PROTECTED]: We chose c === (true; true), t' === e' === fail, t === e === true. Thus, Good point. It becomes even more obvious when you have a monad transformer. If e === (lift m), then this: mif (mif c t' e') t e translates to (lift m), but this: mif c (\x -

[Haskell-cafe] Re: [Haskell] Re: A MonadPlusT with fair operations and pruning

2005-07-17 Thread ajb
G'day all. (Moving the discussion to haskell-cafe.) Quoting [EMAIL PROTECTED]: The last statement should probably be `return (otherState w,b')', right? Yes, I think so. mif (mif c t' e') t e translates to ((X=1 ; X=2) *- X=1 ; fail) *- true; true. Using the predicate: test(X) :-

Re: [Haskell-cafe] haskell parser for java bytecode?

2005-06-29 Thread ajb
G'day all. Quoting [EMAIL PROTECTED]: Now I am surprised. Why for goodness' sake, people interested in Haskell *should* worry about parsing of Java bytecode chunks? Upgrading legacy code, of course. Cheers, Andrew Bromage legacy: adj. Perjorative term used to describe any technology

Re: [Haskell-cafe] (**) over integers

2005-06-14 Thread ajb
G'day all. Quoting Maurício [EMAIL PROTECTED]: but I see that I can't because ** only operates on floats. Is there an equivalent operator that works on integers? How should I do that? Prelude :t (**) (**) :: forall a. (Floating a) = a - a - a Prelude :t (^) (^) :: forall a b. (Integral b, Num

Re: [Haskell-cafe] class Ref...

2005-06-07 Thread ajb
G'day all. Quoting Gracjan Polak [EMAIL PROTECTED]: class Monad m = Ref m r | m - r where newRef :: a - m (r a) readRef :: r a - m a writeRef :: r a - a - m () [...] Is there something like this in standard libraries? No. Is there any reason why isn't it included? Nobody

Re: [Haskell-cafe] Type extensions

2005-06-01 Thread ajb
G'day all. Quoting Thomas Davie [EMAIL PROTECTED]: Essentially I would like some sort of inderritance property for Haskell types, I often find myself wanting to for example extend a tree with black/white colouring, or later extend the tree with some sort of ID, etc. Have you had a look at

Re: [Haskell-cafe] APIs

2005-05-24 Thread ajb
G'day all. Quoting John Meacham [EMAIL PROTECTED]: I think it is easier just to declare it as Enum.. data ParentsFlag = DontCreateParents | CreateParents deriving(Enum) now (toEnum . fromEnum) will convert between ParentsFlag and Bool. Except that it's still not clear whether True

Re: [Haskell-cafe] APIs (was: Unexported functions are evil)

2005-05-19 Thread ajb
G'day all. Quoting Jérémy Bobbio [EMAIL PROTECTED]: One of the best bad example is the use of boolean as arguments. Oh, yes. That's a pet peeve of mine. About 99% of boolean arguments should be meaningful two-valued enumerated types. It's literally a one-liner to create such an enumerated

[Haskell-cafe] Re: APIs (was: Unexported functions are evil)

2005-05-18 Thread ajb
G'day all. Quoting Graham Klyne [EMAIL PROTECTED]: I think you raise an important point. Reading this, I realize that I have no principled basis for deciding what makes a good API, in any language. Me neither. Though I have short reading list. First off, this series of articles by Ken

Re: [Haskell-cafe] Text search

2005-05-16 Thread ajb
G'day all. Quoting Gracjan Polak [EMAIL PROTECTED]: Simple question: I need a function that matches string in another string. Something like: find (isSuffixOf needle) (inits haystack) This one is beautiful, but not very practical. This one is fairly practical, but not very beautiful:

Re: [Haskell-cafe] NumberTheory library

2005-05-16 Thread ajb
G'day all. I've finally had a chance to implement some of these changes. Quoting Yitzchak Gale [EMAIL PROTECTED]: o I think you are testing w' * w' n each time, even when you are repeating factors of the same prime p. You only need to do that when you move to the next p. Actually, it

Re: [Haskell-cafe] Unexported functions are evil

2005-05-15 Thread ajb
G'day all. Quoting Peter Simons [EMAIL PROTECTED]: I was wondering: Is there any reason why you would have a function in one of your modules and _not_ export it? The short answer: Because that function is nobody else's business. The long answer: The reason why programming is hard is that

Re: [Haskell-cafe] When to use fancy types [Re: NumberTheory library]

2005-05-12 Thread ajb
G'day all. Quoting Jan-Willem Maessen [EMAIL PROTECTED]: Why not use a function? What's wrong with a function? There no need to go leaping for a multiparameter type class with a functional dependency! Just use a function. [With apologies to John Cleese] A reasonable question, and one

Re: [Haskell-cafe] NumberTheory library

2005-05-11 Thread ajb
G'day all. Quoting John Meacham [EMAIL PROTECTED]: Ack. I use the MTL quite extensivly in most of my projects. I hope it won't disapear from the standard libraries completely. For the record, I have no information that the MTL will disappear any time soon. However, the proposed roadmap is to

Re: [Haskell-cafe] NumberTheory library

2005-05-09 Thread ajb
G'day all. Quoting Jan-Willem Maessen [EMAIL PROTECTED]: How about one that's actually H98? The types here aren't *that* fiddly... :-) Well, part of what I was doing was experimenting with what a library like this should look like, even more than what it should do. For some reason, I kind

Re: [Haskell-cafe] (Newbie) Dynamic Programming, Memoizing Etc.

2005-03-16 Thread ajb
G'day. Quoting Bryce Bockman [EMAIL PROTECTED]: How would you guys memoize the following code. Take a look here: http://haskell.org/hawiki/MemoisingCafs Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Numeric vs. relative precedences of infix operators

2005-02-28 Thread ajb
G'day all. Quoting [EMAIL PROTECTED]: Widely accepted is a widely accepted relativism... I am also annoyed by the precedences 0,1,2, ...,9, etc. Why not 10, 20, 30,... ?? I _think_ we had this back around Haskell 1.1 (which I never used, but early Gofers also had it). Moreover, operators

Re: [Haskell-cafe] [darcs #222] performance problem with massive changes in a single file

2005-02-21 Thread ajb
G'day all. Quoting David Roundy via RT [EMAIL PROTECTED]: Indeed. The issue here is that darcs uses the exact Hunt-Szymanski LCS algorithm when it computes the diff, while GNU diff uses an approximate --but faster--algorithm, which works almost as well. The approximate algorithm is

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-14 Thread ajb
G'day all. Quoting Josef Svenningsson [EMAIL PROTECTED]: You're of course absolutely right that it doesn't make sense to talk about mzero being a right-identity for bind if the monad doesn't support mzero. I should have been more clear. Let me have another try at explaining myself. OK.

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-14 Thread ajb
G'day all. Quoting Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED]: I agree. They as well could be said to break the core monad laws. It's not their fault. I disagree. This: instance (Monad m) = Monad (TransformerT m) says that if m satisfies the requirements of a Monad (including the core

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-13 Thread ajb
G'day all. Quoting Remi Turk [EMAIL PROTECTED]: According to http://www.haskell.org/hawiki/MonadPlus (see also the recent thread about MonadPlus) a MonadPlus instance should obey m mzero === mzero, which IO doesn't. IOW, the MonadPlus instance for IO (defined in Control.Monad.Error)

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-13 Thread ajb
G'day all. Quoting David Roundy [EMAIL PROTECTED]: It might be interesting to write a backtracking IO-like monad which obeyed m mzero === mzero. I imagine you could do it for something like an ACID database, if you define === as meaning has the same final result on the database, which of

Re: [Haskell-cafe] What is MonadPlus good for?

2005-02-13 Thread ajb
G'day all. Quoting Josef Svenningsson [EMAIL PROTECTED]: I think it's unfair to the monad transformers to simply say that they don't obey the law. The interesting thing is whether they *preserve* the law. A monad transformer T preserves a law if given a monad M which obeys the law holds then

RE: [Haskell-cafe] Point-free style

2005-02-13 Thread ajb
G'day all. Ketil Malde wrote: (.) . (.) .(.) I entered it into GHCi, and got :: forall a a b c a. (b - c) - (a - a - a - b) - a - a - a - c I got this: Prelude :t (.) . (.) . (.) (.) . (.) . (.) :: forall a a1 b c a2. (b - c) - (a - a1 -

Re: [Haskell-cafe] What are the MonadPlus laws?

2005-01-26 Thread ajb
G'day all. Quoting Iavor Diatchki [EMAIL PROTECTED]: This is not enough, at least in some cases. Consider lists, and m being an infinite list, e.g. [1..] Then we need that the inifinte concatenation of a empty lists gives us the empty list which is not the case. It also doesn't work for

Re: [Haskell-cafe] What are the MonadPlus laws?

2005-01-25 Thread ajb
G'day all. Quoting Jules Bean [EMAIL PROTECTED]: So, anyone? What are the laws that MonadPlus is supposed to satisfy? The problem is this law: m = \k - mzero === mzero I think this law is untrue for _all_ MonadPlus instances, and you can trivially check this by setting m to bottom.

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

2005-01-24 Thread ajb
G'day all. Quoting Daniel Fischer [EMAIL PROTECTED]: The sad truth is that IO actions in general aren't well defined entities (unless we index them with the space-time-coordinates of their invocation). Not really. One of the ways that IO used to be implemented (still might be on some Haskell

Re: [Haskell-cafe] Signature of a function

2005-01-12 Thread ajb
G'day all. Quoting Jules Bean [EMAIL PROTECTED]: I meant that, especially when you are figuring out a new language, getting the types inferred for you is helpful and also instructive... I strongly disagree with that. Certainly in Haskell, I found early on that putting in type signatures

Re: [Haskell-cafe] Initial (term) algebra for a state monad

2005-01-05 Thread ajb
G'day all. Quoting Iavor Diatchki [EMAIL PROTECTED]: Apologies if I missed the point of the post (I couldn't fnid the original), but there is yet another even simpler way to define such term algebras, and it works in Haskell'98. The idea is that operations are paremeterized by their

Re: [Haskell-cafe] Re: Typed Lambda-Expressions withOUT GADTs

2005-01-03 Thread ajb
G'day all. Quoting Conor McBride [EMAIL PROTECTED]: Where now? Well, counterexample fiends who want to provoke Oleg into inventing a new recipe had better write down a higher-order example. I just did, then deleted it. Discretion is the better part of valour. Thankfully, I'm the sort of

Re: [Haskell-cafe] Mutable data design question

2004-12-05 Thread ajb
G'day all. Quoting Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED]: 2. Use a persistent data structure with logarithmic cost of most operations: a balanced tree of text fragments, called a rope (Hans Boehm has made one for C). Undo can be made by simply keeping old versions. Hard

Re: [Haskell-cafe] Re: The State Monad

2004-10-08 Thread ajb
G'day all. Quoting Paul Hudak [EMAIL PROTECTED]: Sorry to nit-pick, but state monads are NOT syntactic sugar -- they're just an example of good old data/functional abstraction, that also happens to be in the form of a monad. Right. State monads help to future-proof your code because you

Re: [Haskell-cafe] Re: Strings - why [Char] is not nice

2004-09-28 Thread ajb
G'day all. Quoting John Goerzen [EMAIL PROTECTED]: * (++) is both a list and a string concatenation operator This could easily be handle by a typeclass. * Pattern matching works well with strings (that's my #1 gripe about strings in OCaml) * Thanks to the laziness of Haskell lists,

Re: [Haskell-cafe] mutually recursive modules

2004-09-24 Thread ajb
G'day all. Quoting Henning Thielemann [EMAIL PROTECTED]: Why can't GHC and Hugs go this way? As Alastair noted, the problem is that Haskell allows you to export symbols from a module whose types are unknown unless you type-check modules that it imports. Simple example: module A where

Re: [Haskell-cafe] Strings - why [Char] is not nice

2004-09-20 Thread ajb
G'day all. Quoting Henning Thielemann [EMAIL PROTECTED]: Efficiency is always a reason to mess everything. OTOH, when efficiency matters, it REALLY matters. (The flip side of this is that efficiency doesn't always mean what you think it means.) The problem is that the current representation

Re: [Haskell-cafe] Closed Classes

2004-08-12 Thread ajb
G'day all. Quoting [EMAIL PROTECTED]: Informally, what I see as the defining rule for closed world is: an expression is typed according to the set of definitions that are visible in the context in which it is used. Other possibilities exist, but the nice thing about this is that it is an

Re: [Haskell-cafe] Combination-lock problem

2004-08-10 Thread ajb
G'day all. At 06:01 10/08/04 +0200, Florian Boehl wrote: If I know the length 'l' of the 'locklist', I can solve the problem via generators. E.g.: l = 2: [[a,b] | a - [0..locklist!!0], b - [0..locklist!!1]] But if the length is unknown (because it's dynamic) this solutions (of course) fails.

Re: [Haskell-cafe] Roman Numerals and Haskell Syntax abuse

2004-07-05 Thread ajb
G'day all. Quoting George Russell [EMAIL PROTECTED]: The following declaration for a function for converting positive integers to Roman numerals is 181 characters long. Is there a shorter one? Being a judge, I can't write your obfuscated haskell contest entry for you. However, as a

<    1   2   3   4   >