[Haskell-cafe] Re: MonadFix

2007-12-21 Thread apfelmus
Daniel Fischer wrote: apfelmus writes: | r == 0= p : f (p:ps) q | p*p n = [n] | otherwise = f ps n However, when you do the sensible thing (which Joost did) and have the intsqrt a parameter of the function, like in factorize :: Integer - [Integer

[Haskell-cafe] Re: MonadFix

2007-12-22 Thread apfelmus
Joost Behrends wrote: apfelmus writes: Huh? p intsqrt n is evaluated just as often as p*p n , with changing n . Why would that be less expensive? Btw, the code above test for r==0 first, which means that the following p*p n is tested exactly once for every prime candidate p

[Haskell-cafe] Re: Printing and Referential transparency excuse

2007-12-24 Thread apfelmus
returned by g better not have a polymorphic type). Which programming language should the argument String be written in? Regards apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Wikipedia on first-class object

2007-12-27 Thread apfelmus
indices). But the standard == for lists has indeed the stated property. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Wikipedia on first-class object

2007-12-27 Thread apfelmus
Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Wikipedia on first-class object

2007-12-28 Thread apfelmus
that. Concerning books, maybe The Haskell Road to Logic, Maths and Programming http://www.cwi.nl/~jve/HR is for you. More books on http://haskell.org/haskellwiki/Books You don't have to buy them, borrow them from a library. Regards, apfelmus

[Haskell-cafe] Re: Wikipedia on first-class object

2007-12-28 Thread apfelmus
store that way, it may do more and hence break the extensional semantics a bit. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Difference lists and ShowS

2008-01-03 Thread apfelmus
. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: An interesting monad: Prompt

2008-01-04 Thread apfelmus
, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: US Homeland Security program language security risks

2008-01-06 Thread apfelmus
/ Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Basic question concerning the category Hask (was: concerning data constructors)

2008-01-06 Thread apfelmus
, it would be impossible to distinguish _|_ from its eta-expansion \x._|_ . Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Concurrency questions

2008-01-07 Thread apfelmus
threads can read it simultaneously... This is also known as I-structures i.e. IVar. I think you can simulate them via MVar with the readMVar function? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] Re: PROPOSAL: Some more 'Applicative' combinators

2008-01-09 Thread apfelmus
. But I'm not sure whether many :: Alternative f = f a - f [a] and friends have any uses outside of parsing. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Difference lists and ShowS

2008-01-09 Thread apfelmus
Albert Y. C. Lai wrote: apfelmus wrote: I don't know a formalism for easy reasoning about time in a lazy language. Anyone any pointers? Note that the problem is already present for difference lists in strict languages. http://homepages.inf.ed.ac.uk/wadler/topics/strictness-analysis.html

[Haskell-cafe] Re: Difference lists and ShowS

2008-01-10 Thread apfelmus
Achim Schneider wrote: Henning Thielemann wrote: apfelmus wrote: So, difference lists are no eierlegende wollmilchsau either. LEO's forum suggests 'swiss army knife' as translation. :-) But you really need one with 5 differently-sized blades plus three spezialized carving blades, an USB

[Haskell-cafe] Re: Displaying steps in my interpreter

2008-01-11 Thread apfelmus
loops forever. (Cave: this is only true for the writer monad in Control.Monad.Writer.Lazy which is imported by default. The writer monad in Control.Monad.Writer.Strict intentionally behaves differently.) Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: [newbie question] Memoization automatic in Haskell?

2008-01-13 Thread apfelmus
/GGTries.ps.gz as Luke pointed out. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: [newbie question] Memoization automatic in Haskell?

2008-01-13 Thread apfelmus
are better left to the programmer. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: MonadPrompt + Gtk2Hs = ?

2008-01-13 Thread apfelmus
. Unfortunately, I still haven't come up with a nice higher order function that generalizes this work without reinventing Prompt on an isomorphic type. Oh, what kind of generalization do you have in mind? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell

[Haskell-cafe] Re: practice problems?

2006-09-04 Thread apfelmus
Haskell challenge is of course the ICFP contest http://icfpcontest.org/ There is also the International ACM Programming Contest http://acm.uva.es/problemset/ Your country surely has some kind of high school computing science competition to get problems from. Regards, apfelmus

[Haskell-cafe] Re: Monad laws

2006-09-08 Thread apfelmus
to be void of the intended meaning. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: evaluate vs seq

2006-09-10 Thread apfelmus
a) is not _|_, but does throw an exception when executed. The appended code shows the differences. Regards, apfelmus import Prelude hiding (return,catch) import qualified Control.Monad as M import Control.Exception a = undefined :: () return = M.return :: a - IO a e 0 = return a e 1 = a `seq

[Haskell-cafe] Re: evaluate vs seq

2006-09-11 Thread apfelmus
x) can be implemented as follows: evaluate x = catch (x `seq` return x) throw Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: evaluate vs seq

2006-09-13 Thread apfelmus
, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Optimization problem

2006-09-14 Thread apfelmus
a bimap then id else insert a (sz+1)) bimap Note that update actually generates fresh constructors, so the structure of our tails-Imp is not really static. But this is no problem as the form of the constructors is completely known: there is only one. Regards, apfelmus

[Haskell-cafe] Re: Optimization problem

2006-09-15 Thread apfelmus
to wait on them. Also, if your argument would have been correct, then the version without balancing wouldn't work either because insert already exchanges Leafs for Nodes in m. So the top of the map would be unavailable until all Leafs have been exchanged. Regards, apfelmus

[Haskell-cafe] Re: foreach

2006-09-15 Thread apfelmus
Bulat Ziganshin wrote: because REAL code is somewhat larger than examples. try to rewrite the following: directory_blocks - (`mapM` splitBy (opt_group_dir command) files_to_archive) ( \filesInOneDirectory - do datablocks - (`mapM` splitToSolidBlocks filesInOneDirectory)

[Haskell-cafe] Re: Optimization problem

2006-09-15 Thread apfelmus
) a map map'= (if Map.member a map then id else Map.insert a (sz+1)) map Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Optimization problem

2006-09-17 Thread apfelmus
on the map'. uninsert does not have information about the single steps that have been done, it only knows what should come out. From that, it would have to reconstruct quickly what happened, if it wants to be fast. Regards, apfelmus ___ Haskell-Cafe mailing

[Haskell-cafe] Re: Optimization problem

2006-09-19 Thread apfelmus
a)) is the best type for insertdelete. Here, it is clear that insertdelete likely can do a fast uninsert. Btw, why are there no irrefutable patterns for GADTs? I mean, such a sin should be shame for a non-strict language... Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: Optimization problem

2006-09-19 Thread apfelmus
on, but otherwise, for this special splitSeq-problem, one runs into the more haste less speed dilemma (i mean Wadler's paper ). Bertram's lazy algorithm actually is an online-algorithm and it should remain one when making it type safe. Regards, apfelmus ___ Haskell

[Haskell-cafe] irrefutable patterns for existential types / GADTs

2006-09-29 Thread apfelmus
Ross Paterson wrote: The story so far: apfelmus: why are there no irrefutable patterns for GADTs? Conor: because you could use them to write unsafeCoerce Ross: how about irrefutable patterns (or newtypes) for existential types? Simon: Try giving the translation into System F + (existential

[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-09-30 Thread apfelmus
, strictness is not absolutely necessary (see upcoming mail on this thread). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-09-30 Thread apfelmus
falls into the more haste, less speed category) while staying more type safe. @Conor: how does this issue look like in Epigram? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-09-30 Thread apfelmus
safe _|_ instead of a nasty unsafe segfault? I agree. The only practical problem I can imagine is that GHC internally treats existentials as GADTs. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-10-01 Thread apfelmus
in ((a, b:bs) : rs, m') To summarize, the problem can be solved without irrefutable patterns for GADTs: the code above works for infinite lists. Yet, they are handy and can be introduced safely in the case where the type indices are known in advance and no type refinement happens. Regards, apfelmus

[Haskell-cafe] Re: question - which monad to use?

2006-10-02 Thread apfelmus
as unfoldr iterate f x0 = unfoldr g x0 where g x = let x' = f x in Just (x',x') Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: How would you replace a field in a CSV file?

2006-10-02 Thread apfelmus
are *the* natural data structure for (in)finite maps in functional languages, see also Ralf Hinze. Generalizing generalized tries. Journal of Functional Programming, 10(4):327-351, July 2000 http://www.informatik.uni-bonn.de/~ralf/publications/GGTries.ps.gz Regards, apfelmus

[Haskell-cafe] Re: Problematic irrefutable pattern matching of existentials

2006-10-02 Thread apfelmus
. Indeed, the above shows the subtle difference: with type classes, one may not pass an undefined dictionary as this is an unresolved overloading. Irrefutable patterns for existential types somehow disturb things. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-10-03 Thread apfelmus
because the latter would in principle allow to supply different dictionaries for one and the same type. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: irrefutable patterns for existential types / GADTs

2006-10-04 Thread apfelmus
proposed by Löh and Hinze http://www.informatik.uni-bonn.de/~ralf/publications/OpenDatatypes.pdf Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell performance (again)!

2006-10-08 Thread apfelmus
-rounding Finger Tree, see also Finger Trees: A Simple General-purpose Data Structure Ralf Hinze and Ross Paterson. in Journal of Functional Programming16:2 (2006), pages 197-217 http://www.soi.city.ac.uk/~ross/papers/FingerTree.pdf Regards, apfelmus

[Haskell-cafe] Re: optimization help

2006-10-12 Thread apfelmus
be interleaved lazily, this has to be simulated with appendFile. We can read files lazily but we cannot output them lazily. Can this be remedied? Can there be a version of writeFile which is, in a sense, dual to getContents? Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: tail-recursing through an associative list

2006-10-12 Thread apfelmus
) Just v' - (k', v') : tail where v' = bestKey k (key x) should be (?) where k' = bestKey k (key x) | otherwise = (k, v) : (myFunction tail x) Regards, apfelmus

[Haskell-cafe] Re: optimization help

2006-10-12 Thread apfelmus
) is a pure function. I think some kind of lazy writeFile could allow this. thanks for your help, No problem. :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: function result caching

2006-10-13 Thread apfelmus
be constructed by hand in plain Haskell. To apply this to Ints, one should view them as type Int = [Digit] data Digit = Zero | One Also note that there is absolutely no balancing involved (which would break infinite and lazy stuff). Regards, apfelmus

[Haskell-cafe] Re: optimization help

2006-10-13 Thread apfelmus
The (almost) point-free versions run faster than my fast imperative version and take up significantly less heap space-- even the version which reads everything and then writes takes up about 1/3 the heap space as my version. That was not intended, though I'm very pleased :-D I get the

[Haskell-cafe] Re: optimization help

2006-10-14 Thread apfelmus
Paul Hudak wrote: In fact avoiding space leaks was one of the motivations for our moving to an arrow framework for FRP (now called Yampa). Arrows amount to a point-free coding style, although with arrow syntax the cumbersomeness of programming in that style is largely alleviated. I think

[Haskell-cafe] Re: optimization help

2006-10-17 Thread apfelmus
space time= (inject sf) . (inject sf') and the same for all other operations you provide besides `o`. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: optimization help

2006-10-18 Thread apfelmus
#When_can_I_rely_on_full_laziness.3F I think the reason given there is wrong, it's not about efficiency but about space leaks. The map showcase suggests that (map (`elem` tags) cols) is computed only once, though personally, I don't rely on that (yet). Regards, apfelmus

[Haskell-cafe] Re: Lexically scoped type variables

2006-10-18 Thread apfelmus
appear on the lhs of a let or a lambda. In the definition of f above, (f :: Int - Int) and (x+1 :: a) are judgments and (f :: a - a) is a variable binding. Any confusion between judgment and binding is just like a confusion between constructor application and pattern. Regards, apfelmus

[Haskell-cafe] Re: optimization help

2006-10-18 Thread apfelmus
not gain additional clarity. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: don't: a 'do' for comonads?

2006-11-09 Thread apfelmus
14:43 dons yes! 14:44 pkhuong- mm. the opposite of do, eh? do for comonads? :) So now a prize to the person who comes up with the best use for the identifier: don't :: ? -- Don don't :: IO a - a example :: () example = don't (do erase /dev/hda) Regards, apfelmus

[Haskell-cafe] Re: aggressiveness of functional dependencies

2006-11-09 Thread apfelmus
depending on s. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: aggressiveness of functional dependencies

2006-11-11 Thread apfelmus
on (perhaps in a different module), things will break. The flexibility comes at a price: Gofer's type class system was unsound and I don't know how much Hugs comes close to this. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Difficult memory leak in array processing

2006-11-23 Thread apfelmus
) is missing, too. Regards, apfelmus PS: did you try worker low (i `seq` i-1) ? PSS: The strictness analyzer is likely to insert that automatically if you compile with -O or -O2. Niko Korhonen wrote: Hi everyone, I have the following code whose purpose is to add dither (noise) to a given

[Haskell-cafe] Re: Difficult memory leak in array processing

2006-11-23 Thread apfelmus
. The strictness analyzer likes Udo more than Niko, does it? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Optimizing a hash function

2006-11-26 Thread apfelmus
, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Difficult memory leak in array processing

2006-11-27 Thread apfelmus
commandlings that will literally work for just for the Brain Food. Regards, Nik The Blak, Necromancer of the Glorious Forces of Evil This is indeed very tempting :) Though I suspect that the glory of forces built on (IO a) will be very limited. Regards, apfelmus, Golden Delicious of the Shining

[Haskell-cafe] Re: Difficult memory leak in array processing

2006-11-29 Thread apfelmus
I personally find doing higher order functions with IO extremely difficult, and the resulting compiler errors are often downright scary. But this is probably a direct consequence my rather limited understanding of the monadic operators that the do notion hides. It seems that one has to be

[Haskell-cafe] Re: Difficult memory leak in array processing

2006-11-30 Thread apfelmus
, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Generate 50 random coordinates

2006-12-02 Thread apfelmus
-- from the random seed above Regards, apfelmus PS: As you may have guessed, any similarity with living people is either randomRIO or accidental ... I hope that you accept my apologies for the latter. ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: (a - [b]) - [a - b] ?

2006-12-06 Thread apfelmus
butsequence . unsequence =/= id Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: How to combine Error and IO monads?

2006-12-07 Thread apfelmus
It happens that you can parametrize this on IO: newtype ErrorT m a = ErrorT (m (Either String a)) typeErrorIO a = ErrorT IO a instance Monad m = Monad (ErrorT m) where ... -- same as above And you just rediscovered monad transformers. Regards, apfelmus PS: In the special case

[Haskell-cafe] Re: Why so slow?

2006-12-11 Thread apfelmus
Lyle Kopnicky wrote: The code below is using way more RAM than it should. It seems to only take so long when I build the 'programs' list - the actual reading/parsing is fast. For a 5MB input file, it's using 50MB of RAM! Any idea how to combat this? (ethereal voice) ... Children of Amaunator

[Haskell-cafe] Re: Well-typed functions with nonexisting signatures [Was: type variable question]

2006-12-16 Thread apfelmus
. [...] Prelude let g :: (Show a, Show b) = a - b; g = undefined; h :: Show a = b - a; h x = g (h x) in h 1 *** Exception: Prelude.undefined but not from a file to be loaded. Hugs +98 does not accept it on command line as expected. What's going on? Regards, apfelmus

[Haskell-cafe] Re: Seeking advice on a style question

2006-12-27 Thread apfelmus
). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Seeking advice on a style question

2006-12-29 Thread apfelmus
'questions', 'bands' and 'pages'. Only cumbersome derivations like 'groupedBands' or names with additional ticks are really redundant. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Seeking advice on a style question

2006-12-31 Thread apfelmus
= buildPages . questions2rectangles . expandMacros Now, you get 2/3 of TeX or another desktop publishing system for free, you only have to replace (questions2rectangles) by (text2rectangles). Regards, apfelmus Footnote: * Well, it is possible to recover insert, but only by introducing a contradiction

[Haskell-cafe] Re: Possible (GHC or HGL) bug or ??

2007-01-01 Thread apfelmus
, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Composing functions with runST

2007-01-04 Thread apfelmus
are encouraged to learn about System F to get a grasp of what is going on, but spending this one $ will be much cheaper. Regards, apfelmus [1] Concerning library documentation, I think that literate Haskell sources have the drawback that they are either tied to TeX (\begin{code}..\end{code}) or that every

[Haskell-cafe] Re: Composing functions with runST

2007-01-04 Thread apfelmus
time. Yuck. If the programmer needs to adhere to a policy, the type system may well enforce it for him. No unsafeRunST. It's far better to struggle with the safety device than to discover the hard way that running without it will directly lead into the debugging hell. Regards, apfelmus

[Haskell-cafe] Re: Seeking advice on a style question

2007-01-07 Thread apfelmus
data using exactly the same software, that's 110 pages that they have to inspect. X-) Thanks for all of the discussion. I think I have a lot to ponder May the λ guide your path ;) And of course, you can always outsource some pondering to the mailing list. Regards, apfelmus

[Haskell-cafe] Re: State monad strictness - how?

2007-01-11 Thread apfelmus
) time, this is something only the programmer can do. But the compiler's job is to figure out the `seq`s, fusions and inline definitions because I am too lazy to mark them explicitly. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: advice on architecting a library (and haskell software in general)

2007-01-12 Thread apfelmus
of your ideas is your business :) In this sense, monadic parser combinators are not an inherent strength of the language, they happen to be powerful by themselves. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: different performance of equivalent expression

2007-01-13 Thread apfelmus
manual). The choice must be up to the programmer. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: strange performance of expression evaluators

2007-01-13 Thread apfelmus
in (Add (Value 1) (Add (Value 2) (Variable 1))) Now, it is clear that analyzing the expression again and again every time it needs to be evaluated (interpretation) is wasted work. Regards, apfelmus PS: data Expr = Const !Value | Var !Int | Add !Expr !Expr | Sub !Expr !Expr | Mul !Expr

[Haskell-cafe] Re: Article review: Category Theory

2007-01-19 Thread apfelmus
. they are lifted by an extra _|_: newtype ClosureInt2Int = Closure (Integer - Integer)# Thus, Hask is not a category, at least not as defined in the article. The problem is that (either) morphisms or the morphism composition ('.') are not internalized correctly in Haskell. Regards, apfelmus

[Haskell-cafe] Re: seq (was: Article review: Category Theory)

2007-01-20 Thread apfelmus
, it still does a correct internalization of morphism composition. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: [Haskell] [Fwd: Re: Computer Language Shootout]

2007-01-25 Thread apfelmus
for it is the purely functional style that counts). And sorry, but using the number of gzipped bytes for comparing the code length is just ridiculous. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org

[Haskell-cafe] OOP parametric polymorphism

2007-01-28 Thread apfelmus
, it's forall that makes things happen. Regards, apfelmus (*) We don't consider Eq because given a test on type equality, we can generalize the signature of (==) (==) :: (Eq a, Eq b) = a - b - Bool Indeed, this is what OOP equality does

[Haskell-cafe] Re: Channel9 Interview: Software Composability and the Future of Languages

2007-01-28 Thread apfelmus
to enable you to actually express the proof, the insight as a program. Only few programming languages can do that. And you know: computers and Haskell itself are products of mathematics. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Paths to tree

2007-01-29 Thread apfelmus
in Haskell and a detailed explanation of why the code above works, can be found in Ralf Hinze. Generalizing generalized tries. Journal of Functional Programming, 10(4):327-351, July 2000 http://www.informatik.uni-bonn.de/~ralf/publications/GGTries.ps.gz Regards, apfelmus import Data.Tree import

[Haskell-cafe] Re: Paths to tree

2007-01-30 Thread apfelmus
k0 k1) v where v = Map.unionWith (unionWith f) v0 v1 union = unionWith (\_ y - y) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Haskell Cookbook?

2007-01-31 Thread apfelmus
for Haskell yet. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: ANNOUNCE: The Monad.Reader - Issue 6

2007-01-31 Thread apfelmus
) | otherwise = (next:xs, next:xs) base = ([], []) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: GADTs: the plot thickens?

2007-01-31 Thread apfelmus
' can be correct. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Channel9 Interview: Software Composability and the Future of Languages

2007-01-31 Thread apfelmus
them in a non-chunked way. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Let's welcome the Ruby hackers!

2007-02-02 Thread apfelmus
. In the end, the alphas and betas are noisy braggarts, talking very long about what they want to do without doing anything at all. It's the lambdas who do all the real work. Fortunately, they most often don't need the signature from their alpha bosses. Regards, apfelmus PS: This mail is best

[Haskell-cafe] Re: (a - [b]) vs. [a - b]

2007-02-03 Thread apfelmus
. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Generalizing three programs

2007-02-05 Thread apfelmus
measure. Customers have different processing times and one could weight mean wait time with that, so that people buying few stuff have much shorter waiting times than people with several full shopping carts. Regards, apfelmus ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: Optimization fun

2007-02-10 Thread apfelmus
of the 104 list elements just to return False afterwards. As every second number is even, your all' is busy wasting time like crazy. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Optimization fun

2007-02-10 Thread apfelmus
You're right, 'fix' is *not* a fix for non-termination, this is better fixed in the type system (with the right fixed points or you're in a fix) ;) Fixed regards, apfelmus Lennart Augustsson wrote: This is actually a pretty good algorithm. And also a rather subtle one when it comes

[Haskell-cafe] Re: Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread apfelmus
Bernie Pope wrote: Lennart Augustsson wrote: Sure, but we also have para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs Nice one. Nice one is an euphemism, it's exactly solution one :) Regards, apfelmus ___ Haskell-Cafe mailing

[Haskell-cafe] Re: Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-13 Thread apfelmus
Lennart Augustsson wrote: para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs I thought solution one was missing the ~ ? Yes, that's irrefutably right ;) I mean solution one modulo the laziness bug. Regards, apfelmus ___ Haskell

[Haskell-cafe] Re: Strange memory consumption problems in something that should be tail-recursive

2007-02-13 Thread apfelmus
not being overly slow. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Is lazyness make big difference?

2007-02-15 Thread apfelmus
', but the dependencies in your code don't express this. One should switch from Log - (a, Log) to (a, Log - Log) or even (a, Log) if Log already has a natural monoid structure. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Is lazyness make big difference?

2007-02-15 Thread apfelmus
is strictly more powerful than eager evaluation (in a pure language, that is) with respect to asymptotic complexity: Richard Bird, Geraint Jones and Oege de Moor. More Haste, Less Speed. http://web.comlab.ox.ac.uk/oucl/work/geraint.jones/morehaste.html Regards, apfelmus

[Haskell-cafe] Re: Is lazyness make big difference?

2007-02-16 Thread apfelmus
exemplified above happens subconsciously. So indeed, it looks like - and only looks like - one could easily turn a lazy language into a strict one. Isn't that the good thing about laziness that nobody notices it in the code? Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: stateful walk through a tree?

2007-02-19 Thread apfelmus
they are useful for. How would I do that in Haskell? I'd like to avoid using mutable variables for now (mostly for didactic puproses). Well, Haskell doesn't have mutable variables as LISP or ML do. In the end, avoiding mutable variables is more useful for non-didactic purposes :) Regards, apfelmus

<    1   2   3   4   5   6   7   8   9   >