Re: [Haskell-cafe] Re: capture of idioms and patterns

2010-09-22 Thread ajb
G'day all. Quoting Johannes Waldmann : you got this backwards: what some folks call "idioms and (design) patterns" actually *is* FP, because it is just this: higher order functions. And it's been there some decades (lambda calculus). That also explains the absence of any Design Patterns/Gang-of

Re: [Haskell-cafe] lambdacats

2010-08-07 Thread ajb
G'day all. Quoting Dan Doel : Simon cat and Oleg cat are also missing, unfortunately. http://andrew.bromage.org/pictures/simon.jpeg http://andrew.bromage.org/pictures/oleg.jpeg I can't remember if this one made it to the site or not: http://andrew.bromage.org/pictures/dilimitd.j

Re: [Haskell-cafe] lambdacats

2010-08-07 Thread ajb
G'day all. Quoting Andrew Coppin : Heh. unsafePerformDoggeh# still amuses me... I still have the original at full resolution of all the ones I did (including unsafeDoggeh#), plus a couple that didn't make it to the web site because they were deemed too obscure. For your viewing pleasure:

Re: [Haskell-cafe] Tiger compiler in Haskell: annotating abstract syntax tree

2010-07-19 Thread ajb
G'day all. Quoting José Romildo Malaquias : I am writing here to ask suggestions on how to annotate an ast with types (or any other information that would be relevant in a compiler phase) in Haskell. This might help: http://www.haskell.org/haskellwiki/Indirect_composite Andrew Bromage _

Re: [Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-08 Thread ajb
G'day all. Quoting Ertugrul Soeylemez : Do you realize at what level we are complaining? Yes, we're complaining at the level of the frustrated idealist, which is what many Haskell programmers are. Cheers, Andrew Bromage ___ Haskell-Cafe mailing lis

Re: [Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-07 Thread ajb
G'day all. Quoting Ertugrul Soeylemez : In its highest level "not fragmenting the user base" means going back to C++ and Windows. Ha. You wouldn't say that if you were familiar with the current state of C++ on Windows. Since nobody has come out and admitted it, here's the real problem: What

Re: [Haskell-cafe] Huffman Codes in Haskell

2010-06-22 Thread ajb
G'day all. Quoting Andrew Coppin : What the...? Oh, I see. It uses another package to handle the tricky sorting and searching stuff. Well, yeah, that would make the code a bit shorter... ;-) Even so, it's not nearly as elegant to behold as, say, the quicksort algorithm, despite being of rough

Re: [Haskell-cafe] Haskell and the Software design process

2010-05-02 Thread ajb
G'day all. Quoting aditya siram : I'm a little confused about this too. I've seen many functions defined like: f x = (\s -> ...) which is a partial function because it returns a function and is the same as: f x s = ... Off the top of my head the State monad makes extensive use if this style. I

Re: [Haskell-cafe] Re: Are there any gay haskelleres?

2010-03-28 Thread ajb
G'day all. Am 28.03.10 23:25, schrieb Ketil Malde: Look, Günther, I'll give you credit for trying, but you might as well accept the fact that using Haskell isn't going to get you laid. For what it's worth, I got away with naming a daughter "Miranda". Cheers, Andrew Bromage __

Re: [Haskell-cafe] lawless instances of Functor

2010-01-04 Thread ajb
G'day all. Quoting Derek Elkins : Ignoring bottoms the free theorem for fmap can be written: If h . p = q . g then fmap h . fmap p = fmap q . fmap g Setting p = id gives h . id = h = q . g && fmap h . fmap id = fmap q . fmap g Using fmap id = id and h = q . g we get, fmap h . fmap id = fmap h

Re: [Haskell-cafe] Zumkeller numbers

2009-12-09 Thread ajb
G'day all. Quoting Dan Weston : Ouch. That's what happens when you let a machine do the translation. How about: "Once your good name is trashed, you can live unabashed." "Until you've lost your reputation, you never realize what a burden it was." -- Margaret Mitchell Cheers, Andrew Brom

Re: [Haskell-cafe] Zumkeller numbers

2009-12-07 Thread ajb
G'day all. Quoting Richard O'Keefe : These lines of Haskell code find the Zumkeller numbers up to 5000 in 5 seconds on a 2.2GHz intel Mac. The equivalent in SML took 1.1 seconds. Note that this just finds whether a suitable partition exists; it does not report the partition. This takes 0.1

Re: [Haskell-cafe] What's the deal with Clean?

2009-11-03 Thread ajb
G'day all. Quoting wren ng thornton : Sometimes in Haskell I've thought about how uniqueness typing would make something faster, but in general all the plumbing associated with it in Clean makes me feel like I'm writing systems-level code (i.e. C, asm) instead of using a high-level language. Th

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread ajb
G'day all. On Tue, Jun 30, 2009 at 08:02:48PM -0400, Daniel Peebles wrote: But we don't want to imply it's commutative either. Having something "bidirectional" like <> or <+> feels more commutative than associative to me. Quoting John Meacham : Not really, think of '++', which doesn't commu

Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-06-30 Thread ajb
G'day all. Quoting John Meacham : (+>) seems to imply to me that the operator is non-associative. Something like (<>) or (<+>) would be better. I tend to agree. Moreover, and I realise this may be a losing battle, I want (++) to be the generic operator. I understand the argument. I even ag

Re: [Haskell-cafe] ANN: TernaryTrees-0.1.1.1 - An efficient ternary tree implementation of Sets and Maps

2009-06-29 Thread ajb
G'day all. Quoting Andrew Coppin : That's just scary. I was just in the middle of writing the exact same thing! :-D (I read that very article...) When you're both done, please compare with the implementation that's been in Edison for about five years: http://www.cs.princeton.edu/~rdockins/ed

Re: [Haskell-cafe] type checking that I can't figure out ....

2009-06-02 Thread ajb
G'day Vasili. This should do it: remLookupFwd :: (ReVars m t) => SimplRe t -> ReM m t (ReInfo t) remLookupFwd re = do fwd <- gets resFwdMap let { Just reinfo = fromJust (M.lookup re fwd) } return reinfo The FiniteMap lookup operation took its arguments in the opposite order. Tha

Re: [Haskell-cafe] the problem of design by negation

2009-05-25 Thread ajb
G'day all. Quoting Conal Elliott : The main objection I have to the negative process (can't be done) is that is so often bogus. "Proof by lack of imagination". I guess it works for Richard, though not for Michael's architect, because Richard is able to catch his bogus reasoning *and he is wil

Re: [Haskell-cafe] Looking for the fastest Haskell primes algorithm

2009-04-19 Thread ajb
G'day all. Quoting Dan Weston : Unless primesUpTo n goes from highest to lowest prime (ending in 2), I don't see how sharing is possible (in either space or time) between primesUpTo for different n. Given that it's a mistake for a library to leak memory, there are essentially three possibilit

Re: [Haskell-cafe] Looking for the fastest Haskell primes algorithm

2009-04-16 Thread ajb
G'day all. Quoting Eugene Kirpichov : I'd suggest also primesFrom :: Integer -> [Integer] This: primes :: [Integer] isn't as useful as you might think for a library, because it must, by definition, leak an uncontrolled amount of memory. This: primesUpTo :: Integer -> [Integer] is a bett

[Haskell-cafe] Re: [Haskell] [OT] Plural forms of the word "octopus" [Was: Re: Marketing Haskell]

2009-04-06 Thread ajb
[Shifted to haskell-cafe.] G'day all. Quoting "Benjamin L.Russell" : According to the Merriam-Webster Online Dictionary, it is "topoi" (see http://www.merriam-webster.com/dictionary/topos). Topoi form a certain class of category. You can study topous, you can prove theorems about topois and

Re: [Haskell-cafe] Looking for practical examples of Zippers

2009-03-31 Thread ajb
G'day all. Quoting Gü?nther Schmidt : my quest for data structures continues. Lately I came across "Zippers". Can anybody point be to some useful examples? This is a good example, currently in use in GHC: http://www.cs.tufts.edu/~nr/pubs/zipcfg-abstract.html Cheers, Andrew Bromage __

Re: [Haskell-cafe] Unique monad?

2009-03-30 Thread ajb
G'day all. Quoting Lennart Augustsson : I think Data.Unique is horrible and should be banned. It encourages a global variable style of programming that will just bite you in the end. In the sense that it doesn't give you anything that Monad.Supply or Control.Comonad.Supply doesn't, I agree.

Re: [Haskell-cafe] Design Patterns by Gamma or equivalent

2009-03-15 Thread ajb
G'day all. Quoting wren ng thornton : Most of the (particular) problems OO design patterns solve are non-issues in Haskell because the language is more expressive. ...and vice versa. Some of the "design patterns" that we use in Haskell, for example, are to overcome the fact that Haskell does

Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread ajb
G'day all. I wrote: - Intuitionistic logic systems. - The "truth values" of an arbitrary topos (i.e. the points of the subobject classifier). Sorry, I misread the question. These are _not_ instances of Boolean (or at least the latter isn't an instance in general). Cheers, Andrew Bromage __

Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread ajb
G'day all. Quoting David Menendez : Are there any instances of Boolean that aren't isomorphic to Bool? Sure. Two obvious examples: - The lattice of subsets of a "universe" set, where "or" is union "and" is intersection and "not" is complement with respect to the universe. - Many-valued log

Re: [Haskell-cafe] Re: Improved documentation for Bool

2009-01-19 Thread ajb
G'day all. On Mon, 2009-01-19 at 19:33 +, Andrew Coppin wrote: My only problem with it is that it's called Bool, while every other programming language on Earth calls it Boolean. (Or at least, the languages that *have* a name for it...) Jonathan Cast commented: Except C++? And perhaps

Re: [Haskell-cafe] MonadTrans lift implementation

2009-01-19 Thread ajb
G'day all. Quoting Jonathan Cast : (By the way, you *do* have the equations lift (return x) = return x [...] Right. And you could, at least in principle, implement "return" this way in all monad transformers. Cheers, Andrew Bromage ___ Haskel

Re: [Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-17 Thread ajb
G'day all. Dan Weston wrote: Richard Feinman once said: "if someone says he understands quantum mechanics, he doesn't understand quantum mechanics". But what did he know... Presumably not quantum mechanics. Cheers, Andrew Bromage ___ Haskell-Ca

Re: [Haskell-cafe] Comments from OCaml Hacker Brian Hurt

2009-01-17 Thread ajb
G'day all. Quoting John Goerzen : If I see Appendable I can guess what it might be. If I see "monoid", I have no clue whatsoever, because I've never heard of a monoid before. Any sufficiently unfamiliar programming language looks like line noise. That's why every new language needs to use cu

Re: [Haskell-cafe] Re: Comments from OCaml Hacker Brian Hurt

2009-01-17 Thread ajb
G'day all. Quoting Gracjan Polak : I remember my early CS algebra courses. I met cool animals there: Group, Ring, Vector Space. Those beasts were very strong, but also very calm at the same time. Although I was a bit shy at first, after some work we became friends. I don't know about you, bu

Re: [Haskell-cafe] Don't make 'show*' functions

2008-12-27 Thread ajb
G'day all. Quoting Jeff Heard : I don't think that making Show a type class was a mistake. I don't either. Two main reasons: 1. [Char] should not be shown ['l','i','k','e',' ','t','h','i','s']. 2. Default implementations of Show can break abstractions by leaking implementation details.

Re: [Haskell-cafe] The Haskell re-branding exercise

2008-12-21 Thread ajb
G'day all. Quoting Sebastian Sylvan : Personally I find the current logo horrendous. I think it's ugly and intimidating at the same time. I don't really care too much which one of the proposals should win, just so long as I can weed out some of the ones I really hate. I guess this is one diff

Re: [Haskell-cafe] Re: Functional version of this OO snippet

2008-12-05 Thread ajb
G'day all. Thomas Davie wrote: class IEngine a where foo :: a -> String bar :: a -> String -> String "Apfelmus, Heinrich" <[EMAIL PROTECTED]> replied: You don't even need a type class, a simple data type is enough. data Engine = Engine { foo :: IO (), bar :: String -> IO () } There

Re: [Haskell-cafe] The Knight's Tour: solutions please

2008-12-02 Thread ajb
G'day all. Quoting Bertram Felgenhauer <[EMAIL PROTECTED]>: successors n b = sortWith (length . succs) . succs [...] successors n b = sortWith (length . (succs =<<) . succs) . succs [...] successors n b = sortWith (length . (succs =<<) . (succs =<<) . succs) . succs [...] These im

Re: [Haskell-cafe] The Knight's Tour: solutions please

2008-11-30 Thread ajb
G'day all. Quoting Don Stewart <[EMAIL PROTECTED]>: So, team, anyone want to implement a Knight's Tour solver in a list monad/list comprehension one liner? These little puzzles are made for fast languages with backtracking monads I conjecture that any one-liner won't be efficient. Anyway

Re: [Haskell-cafe] What *not* to use Haskell for

2008-11-13 Thread ajb
G'day all. Quoting Lennart Augustsson <[EMAIL PROTECTED]>: People have been admitting to using Haskell like that for quite a while now. I think it's an excellent use of Haskell as a DSEL host. DSL is a proper superset of DSEL. Just saying. Cheers, Andrew Bromage

Re: [Haskell-cafe] What *not* to use Haskell for

2008-11-12 Thread ajb
G'day all. Quoting Tom Hawkins <[EMAIL PROTECTED]>: Actually, Haskell is an excellent language for hard real-time applications. At Eaton we're using it for automotive powertrain control. Of course, the RTS is not running in the loop. Instead, we write in a DSL, which generates C code for our

Re: [Haskell-cafe] Re: Efficient parallel regular expressions

2008-11-04 Thread ajb
G'day all. Quoting Achim Schneider <[EMAIL PROTECTED]>: Considering that he's talking about a mud, I figure the grammar is a quite straightforward command = l[eft] | r[ight] | ... | t[ake] | c[ast] That is, I'd be very surprised if you even need more than two or three characters lookahead,

Re: [Haskell-cafe] Re: Efficient parallel regular expressions

2008-11-04 Thread ajb
G'day all. Quoting Achim Schneider <[EMAIL PROTECTED]>: Considering that he's talking about a mud, I figure the grammar is a quite straightforward command = l[eft] | r[ight] | ... | t[ake] | c[ast] That is, I'd be very surprised if you even need more than two or three characters lookahead,

RE: [Haskell-cafe] Why 'round' does not just round numbers ?

2008-10-27 Thread ajb
G'day all. Henning Thielemann suggested: In measured data the .5-case should be very rare - a "null set"? However I assume that .5 happens more often in practice - because of prior rounding, which was shown to be bad practice in this thread. The usual case in floating point is usually not

Re: [Haskell-cafe] Re: Why 'round' does not just round numbers ?

2008-10-27 Thread ajb
G'day all. Quoting Daniel Fischer <[EMAIL PROTECTED]>: Who does such horrible things? Repeat after me: 1 is NOT a prime. Never, under no circumstances. The definition of "prime" is well-understood standard terminology, but that doesn't escape the fact that it's arbitrary and human-defined. I

RE: [Haskell-cafe] Why 'round' does not just round numbers ?

2008-10-27 Thread ajb
G'day all. Quoting "Mitchell, Neil" <[EMAIL PROTECTED]>: With rounding to the nearest even integer for 0.5's you get 6, otherwise if you always round up you get 7. If you bias towards rounding up you get a general upwards trend as numbers are rounded, which is bad, while the even condition ensu

Re: [Haskell-cafe] Re: A heretic question

2008-10-23 Thread ajb
G'day all. Quoting Dan Weston <[EMAIL PROTECTED]>: For the record, C++ (and a crippled scripting language call MEL that makes C look good) [...] To be fair, MEL does exactly what it's designed to do. It was supposed to powerful enough to be a scripting language, UI builder and save file form

Re: [Haskell-cafe] Re: A heretic question

2008-10-20 Thread ajb
G'day aoll. Quoting "Benjamin L.Russell" <[EMAIL PROTECTED]>: Interesting argument. At first I thought that the following uncensored interview with Bjarne Stroustrup was a joke, but your argument makes it seem all the more plausible: That's not quite what I meant. What I meant is that Visua

Re: [Haskell-cafe] A heretic question

2008-10-19 Thread ajb
G'day all. On Sun, 2008-10-19 at 23:08 +0200, Achim Schneider wrote: I'm asking 'cos I'm learning C++ and can't get the proper motivation to do any program I can think of in it: If I need abstraction, I'm thinking Haskell or Scheme, and if I'm thinking performance, C itself more than suffices.

Re: [Haskell-cafe] Name for Haskell based VPN Client/Server

2008-10-06 Thread ajb
G'day all. Quoting John Van Enk <[EMAIL PROTECTED]>: I'm working on a Haskell based VPN. I can't think of any good names, so I'm crowd sourcing it. The naming of code is a difficult matter, It isn't just one of your LAN party games; You may think at first I'm as mad as a hatter

[Haskell-cafe] Model-driven development (was: Haskell participting in big science like CERN Hadrian...)

2008-10-03 Thread ajb
G'day all. Quoting Don Stewart <[EMAIL PROTECTED]>: How about EDSLs for producing high assurance controllers, and other robust devices they might need. I imagine the LHC has a good need for verified software components... On a related topic, I'm curious if anyone apart from me has been secret

Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread ajb
G'day all. Quoting Lennart Augustsson <[EMAIL PROTECTED]>: But I called it One. That's a _terrible_ name. One, surely is (), just as Zero is Void. While I'm at it, I really don't like the lexical syntax of comments. Someone should fix that. Cheers, Andrew Bromage __

Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-03 Thread ajb
G'day all. I asked: But more to the point: Can it send email? Quoting John Dorsey <[EMAIL PROTECTED]>: Can you give an example of a use case? I don't need one. It's not maximally flexible until it can send email. Cheers, Andrew Bromage ___ Has

Re: [Haskell-cafe] Announcing OneTuple-0.1.0

2008-10-02 Thread ajb
G'day all. Quoting John Dorsey <[EMAIL PROTECTED]>: Contributions are welcome. The project could use a tutorial, and a decent test suite. Strict singleton tuples are planned for the next version. I hope it has a Monad instance. But more to the point: Can it send email? Cheers, Andrew Brom

Re: [Haskell-cafe] Health effects

2008-10-01 Thread ajb
G'day all. Quoting Adrian Neumann <[EMAIL PROTECTED]>: I often wonder how many cuts you need to divide a steak in n pieces. One, if the cut is allowed to be curved and self-intersecting. I think that the spirit of the problem, though is encapsulated in this question: Given a circle, what is

Re: [Haskell-cafe] Shooting your self in the foot with Haskell

2008-10-01 Thread ajb
G'day all. On Wed, Oct 1, 2008 at 3:42 PM, Jake McArthur <[EMAIL PROTECTED]> wrote: Couldn't match expected type 'Deer' against inferred type 'Foot' No instance for (Target Foot) arising from use of `shoot' at SelfInflictedInjury.hs:1:0 Possible fix: add an instance declaration

Re: [Haskell-cafe] Hmm, what license to use?

2008-09-28 Thread ajb
G'day all. Quoting Magnus Therning: Recently I received an email with a question regarding the licensing of a module I've written and uploaded to Hackage. I released it under LGPL. The sender wondered if I would consider re-licensing the code under BSD (or something similar) that would remove

Re: [Haskell-cafe] Is there already an abstraction for this?

2008-09-23 Thread ajb
G'day. Quoting Jeremy Shaw <[EMAIL PROTECTED]>: I have an expression data-type: data Expr = Quotient Expr Expr | Product Expr Expr | Sum Expr Expr | Difference Expr Expr | Lit Double | Var Char deriving (Eq, Ord, Data, Typeable, Read, Show) And I want to write a func

Re: [Haskell-cafe] [m..n] question

2008-09-21 Thread ajb
G'day. Quoting wren ng thornton <[EMAIL PROTECTED]>: I'm sure you know *why* it's an infinite list[1], but as for why that's useful I can't say. It has the feel of a bug in implementation, though it is ...consistent. Right. I have no problem with [5,5..5] being logically an anamorphism, but

Re: [Haskell-cafe] [m..n] question

2008-09-21 Thread ajb
G'day all. Quoting "Richard A. O'Keefe" <[EMAIL PROTECTED]>: I'm currently arguing that lists:seq(1, 0) should be [], not an exception. Oddly enough, I'm being beaten over the head with Haskell, of all things. [...] Does anyone remember why the definition of enumFromTo is the way it is? I

Re: [Haskell-cafe] Haskell Propeganda

2008-08-23 Thread ajb
G'day all. Quoting Don Stewart <[EMAIL PROTECTED]>: We promise both safety and efficiency. We also provide (though don't promise) modularity, robustness and correctness, which is not something that Java gives you out of the box. Cheers, Andrew Bromage

Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread ajb
G'day all. Quoting "Richard A. O'Keefe" <[EMAIL PROTECTED]>: Just an idiot-level question: so these "constants" are subject to revision, but *how often*? Good question. For leap seconds: - The data can change no quicker than once every 6 months. - The shortest time between changes was 6 m

Re: [Haskell-cafe] Reader monad, implicit parameters, or something else altogether?

2008-08-18 Thread ajb
G'day all. Quoting Bjorn Buckwalter <[EMAIL PROTECTED]>: I'd store the constants in a data structure along the lines of: data AstroData a = AstroData { mu_Earth:: GravitationalParameter a , leapSeconds :: LeapSecondTable } I would like to know if there is any consensus on what is

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-13 Thread ajb
G'day. Quoting "C.M.Brown" <[EMAIL PROTECTED]>: However I saw no real argument for not having cyclic inclusions. You say we shouldn't have to spend time writing hi-boot files, and yet you also think that GHC should not do it automatically. So we have to restrict all programmers to never wri

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-13 Thread ajb
G'day all. Quoting Thomas Davie <[EMAIL PROTECTED]>: To be honest, ghc compiles things so fast (at least on any of my systems) that I couldn't care less if it took 10 times as long (I would however like some added convenience for that time spent) Have you ever compiled GHC itself? Just curio

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-13 Thread ajb
G'day all. Quoting "C.M.Brown" <[EMAIL PROTECTED]>: But isn't this exactly the point I was trying to make!? The whole point, to me, in functional programming, is that we shouldn't have to worry about the underlying implementation. It is not exposing an underlying implementation detail to mand

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread ajb
G'day all. Quoting Henning Thielemann <[EMAIL PROTECTED]>: As far as I know the real difficulties come from mutually recursive class definitions. I wouldn't be surprised, because that's a more blatant instance of the same problem. With classes and instances, there is no way to specify whethe

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread ajb
G'day all. Quoting Thomas Davie <[EMAIL PROTECTED]>: Why is separate compilation important? I'm a little shocked that anyone on this list should have to ask this question. Two people have asked it now. The simplest answer is that unless your program fits in cache, it takes longer to compile

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-12 Thread ajb
G'day all. Quoting Thomas Davie <[EMAIL PROTECTED]>: I'm not sure that it does make a lot of sense -- we allow (mutually) recursive functions, even though they come with an efficiency penalty. Why should we not allow (mutually) recursive modules, even though they too come with an efficiency pen

Re: [Haskell-cafe] Cyclic Inclusions

2008-08-11 Thread ajb
G'day all. Quoting "C.M.Brown" <[EMAIL PROTECTED]>: Yes, I saw that, thanks! I guess this is because it's hard to compile a mutually recursive module... It's because you don't need to declare the types of exported definitions. Consider, this highly artificial example: module A where

Re: [Haskell-cafe] Design your modules for qualified import

2008-06-07 Thread ajb
G'day all. Quoting Jan-Willem Maessen <[EMAIL PROTECTED]>: There's one caveat: Always choose descriptive names, even if you are assuming that you will usually use a qualified import. The following are wonderful names, even though they conflict with the prelude: null filter map lookup

Re: [Haskell-cafe] How would you hack it?

2008-06-05 Thread ajb
G'day. Quoting Andrew Coppin <[EMAIL PROTECTED]>: Right. So a "Markov chain" is actually a technical way of describing something that's intuitively pretty obvious? (E.g., PPM compression works by assuming that the input data is some sort of Markov chain with as-yet unknown transition probabilit

Re: [Haskell-cafe] Mutually Recursive Modules

2008-06-02 Thread ajb
G'day all. Quoting Isaac Dupree <[EMAIL PROTECTED]>: Luckily, it is very often the case that your code will be better off anyway if refactored to have less module recursion. (though not always.) Nonetheless, I prefer not to leave the robustness of my code to luck. Besides, if I liked structur

Re: [Haskell-cafe] Re: [ANN] bloomfilter 1.0 - Fast immutable and mutable Bloom filters

2008-05-31 Thread ajb
G'day all. Quoting Achim Schneider <[EMAIL PROTECTED]>: Please tell me that this isn't reversible. It isn't reversible. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-ca

Re: [Haskell-cafe] Data.Tree.Zipper in the standard libraries

2008-05-23 Thread ajb
G'day all. Quoting Don Stewart <[EMAIL PROTECTED]>: This is Haskell, we should use Maybe. This is Haskell, more abstract is good. I do agree, though, that Monad is arguably the wrong abstraction. Something like this would arguably be better: class (Functor f) => Fail f where return ::

Re: [Haskell-cafe] one-way monads

2008-05-20 Thread ajb
G'day all. Quoting Dan Piponi <[EMAIL PROTECTED]>: For any specific monad, m, it's usually possible to write a function m a -> a. Actually, it's true less than 50% of the time. In particular, it's not true of any monad transformer. Cheers, Andrew Bromage

Re: [Haskell-cafe] List concat

2008-05-11 Thread ajb
G'day all. Quoting Andrew Coppin <[EMAIL PROTECTED]>: The function (++) :: [x] -> [x] -> [x] has O(n) complexity. That's not entirely true. When you call (++), it does O(1) work. If you evaluate k cons cells. it takes O(min(k,n)) work. Cheers, Andrew Bromage ___

Re: [Haskell-cafe] A bright future for Haskell

2008-04-29 Thread ajb
G'day all. Quoting John Peterson <[EMAIL PROTECTED]>: Especially if SPJ decides to grow a beard. Unfortunately Paul is now clean shaven so maybe Haskell is in trouble. This explains why Clean never made it: Rinus Plasmeijer can't compete with Phil Wadler in the beard department. I should

Re: [Haskell-cafe] Longest increasing subsequence

2008-04-11 Thread ajb
G'day all. Quoting Matt Amos <[EMAIL PROTECTED]>: http://en.wikipedia.org/wiki/Longest_increasing_subsequence The most efficient algorithm relies on destructive updates, so a simple translation doesn't seem possible. Given that it's based on binary search, you might like to try using a binar

Re: [Haskell-cafe] instance Monad m => Functor m

2008-04-09 Thread ajb
G'day all. Quoting Jules Bean <[EMAIL PROTECTED]>: Other solutions, such as class Functor m => Monad m are frequently discussed. I see no H' ticket for it, though. Then add it. :-) You'll probably want to make it depend on Ticket #101, because making class hierarchies more granular generall

Re: [Haskell-cafe] Re: Doing without IORef

2008-04-03 Thread ajb
G'day all. Quoting Jinwoo Lee <[EMAIL PROTECTED]>: Thanks everyone! Now I think using IORef is the most practical way to do this. Just a suggestion: Store it in a ReaderT instead of a StateT. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Has

Re: [Haskell-cafe] Dynamic typing makes you more productive?

2008-03-18 Thread ajb
G'day all. Quoting Jeremy Shaw <[EMAIL PROTECTED]>: I like to imagine it works like this: bad static type < dynamic typing < good static typing. More succinctly: Algol < Smalltalk < ML Or perhaps: C < Ruby < Haskell Cheers, Andrew Bromage _

Re: [Haskell-cafe] "GADT" rhymes with "cat"

2008-03-16 Thread ajb
G'day all. Quoting Jeremy Apthorp <[EMAIL PROTECTED]>: Clearly, this pronounciation is "gay dee tea." I always new those types were a bit queer. Not that there's anything wrong with that. Cheers, Andrew Bromage ___ Haskell-Cafe mailing list Haskell

Re: [Haskell-cafe] "GADT" rhymes with "cat"

2008-03-15 Thread ajb
G'day all. Quoting Ashley Yakeley <[EMAIL PROTECTED]>: "GADT" rhymes with "cat". The "d" is silent, like the Danish "godt", or the German "Stadt", or the American trademark "Bundt". I pronounce it so that it rhymes with "ADT". Cheers, Andrew Bromage __

Re: [Haskell-cafe] A question about "monad laws"

2008-03-15 Thread ajb
G'day all. Quoting askyle <[EMAIL PROTECTED]>: Yup: bind f = f <=< id -- whence you can say (>>=) = flip bind Ah, yes. My point is that (as far as I can see) you cannot prove the properties of bind by only assuming identity and associativity for (<=<). One thing that may help is t

Re: [Haskell-cafe] Type system

2008-03-14 Thread ajb
G'day all. Quoting Andrew Coppin <[EMAIL PROTECTED]>: And yet they commonly pop up in Haskell. Can anybody put their finger on precisely why that is? One of the reasons why advanced type hackery shows up a lot in Haskell is that Haskell has never taken the easy way out. When confronted with

Re: [Haskell-cafe] A question about "monad laws"

2008-03-13 Thread ajb
G'day all. Quoting askyle <[EMAIL PROTECTED]>: So you're either not taking (>=>) as primitive or you're stating the additional property that there exists (>>=) such that f >=> g === (>>= g) . f (from which you can easily show that (f . g) >=> h === (f >=> h) . g ). If you wanted to prove tha

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-13 Thread ajb
G'day all. Quoting Adrian Hey <[EMAIL PROTECTED]>: If that's supposed it imply you think I'm in a minority of one I don't think you've been following this thread very well. Sorry, that was a bit of hyperbole. Even the report uses the word "equality" in the prose. Indeed, and the only sens

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-13 Thread ajb
G'day all. Quoting Conor McBride <[EMAIL PROTECTED]>: How depressing! Sorry, I don't understand that. Quotient types are good, but they're not the whole story. They just happen to be one use case with a solid history behind them. it's just that we need to manage information hiding properl

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-13 Thread ajb
G'day all. Quoting Adrian Hey <[EMAIL PROTECTED]>: I take it you mean something like .. Err... yes, I did. Where's the Eq instance for OrdWrap? Omitted for brevity. This may or may not satisfy the law: (compare a b) = EQ implies (a == b) = True. I think everbody agrees about that, but I

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-12 Thread ajb
G'day all. Quoting David Menendez <[EMAIL PROTECTED]>: Adrian is arguing that compare a b == EQ should imply compare (f a) (f b) == EQ for all functions f (excluding odd stuff). Thus, the problem with your example would be in the Ord instance, not the sort function. Understood, and the Schwar

Re: [Haskell-cafe] A question about "monad laws"

2008-03-12 Thread ajb
G'day all. Quoting askyle <[EMAIL PROTECTED]>: If you use this presentation you also need the following law: (a . b) >=> c = (a >=> c) . b that is, compatibility with ordinary function composition. I like to call this "naturality", since it's instrumental in proving return and bind to be natu

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-12 Thread ajb
G'day all. Adrian Hey wrote: This might be a reasonable thing to say about *sortBy*, but not sort as the ordering of equal elements should not be observable (for any correct instance of Ord). It should be impossible to implement a function which can discriminate between [a,a],[a,b],[b,a],[b,b]

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-10 Thread ajb
G'day all. Quoting Dan Weston <[EMAIL PROTECTED]>: 6.3.2 (The Ord Class): "The Ord class is used for totally ordered datatypes." So... Double shouldn't be there, then? As previously noted, nowhere is it even required that x /= y should "do the same thing" as not (x == y). Cheers, Andrew Br

Re: [Haskell-cafe] Functional programmer's intuition for adjunctions?

2008-03-05 Thread ajb
G'day all. Quoting Derek Elkins <[EMAIL PROTECTED]>: Of course, this is a concrete example using basic ideas of programming and not some "intuitive analogy". I feel comfortable working with adjunctions, but I don't have some general analogy that I use. I think this is important. The concept

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread ajb
G'day all. Quoting Cetin Sert <[EMAIL PROTECTED]>: It is astonishing to see that your version actually performs the worst (at least on my machine). On your example, I'm not surprised: plong 0 = Var 0 plong n | even n= Or (Var n) (plong (n-1)) | otherwise = And (Var n) (plong (n

Re: [Haskell-cafe] Re: The Proliferation of List-Like Types

2008-02-20 Thread ajb
G'day all. Quoting Neil Mitchell <[EMAIL PROTECTED]>: Yes, its the projection onto another type: [] = Nothing (x:xs) = Just (x, xs) Also known as msplit: http://www.haskell.org/haskellwiki/New_monads/MonadSplit Cheers, Andrew Bromage ___ Hask

Re: [Haskell-cafe] what is the fastest way to extract variables from a proposition?

2008-02-20 Thread ajb
G'day all. Quoting Cetin Sert <[EMAIL PROTECTED]>: -- proposition data Prp a = Var a | Not (Prp a) | Or (Prp a) (Prp a) | And (Prp a) (Prp a) | Imp (Prp a) (Prp a) | Xor (Prp a) (Prp a) | Eqv (Prp a) (Prp a) | Cns Boo

Re: [Haskell-cafe] Re: A question about "monad laws"

2008-02-14 Thread ajb
G'day all. Quoting Thorkil Naur <[EMAIL PROTECTED]>: Finding the "machine epsilon", perhaps, that is, the smallest (floating point, surely) number for which 1.0+machine_eps==1.0 would be a candidate? The machine epsilon is the smallest relative separation between two adjacent normalised fl

Re: [Haskell-cafe] Re: A question about "monad laws"

2008-02-14 Thread ajb
G'day all. Richard A. O'Keefe wrote: That's one of the warning signs I watch out for. "Never compare floats for equality" is a sure sign of someone who thinks they know about floats but don't. Quoting Roman Leshchinskiy <[EMAIL PROTECTED]>: Hmm. Personally, I've never seen an algorithm

Re: [Haskell-cafe] Re: Datatypes - Haskell

2008-02-10 Thread ajb
G'day all. On Feb 10, 2008 3:40 PM, Mattes Simeon <[EMAIL PROTECTED]> wrote: Though in comparison with C or C++ I can't figure out so clear the syntax. Quoting Victor Nazarov <[EMAIL PROTECTED]>: I think this is the most native way to do it in C++: Herb Sutter and Andrei Alexandrescu will

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread ajb
G'day all. On Feb 6, 2008 12:45 PM, Felipe Lessa <[EMAIL PROTECTED]> wrote: I guess your parser is a monad transformer, so *maybe* the solution is to require MonadError from the inner monad. Quoting Bas van Dijk <[EMAIL PROTECTED]>: Indeed my parser 'P t m a' is a monad transformer. I wil

Re: [Haskell-cafe] Re: The programming language market

2008-01-27 Thread ajb
G'day all. Quoting [EMAIL PROTECTED]: Algol is dead. No sense in disputing it. And yet Delphi is still alive. So is Modula-3, though it tends to be referred to as "Java" these days. And, of course, Haskell is ensuring that Miranda will never really die. Cheers, Andrew Bromage _

  1   2   3   4   >