[Haskell-cafe] Re: a regressive view of support for imperative programming in Haskell

2007-08-14 Thread apfelmus
Stefan O'Rear wrote: apfelmus wrote: My assumption is that we have an equivalence forall a,b . m (a - m b) ~ (a - m b) because any side effect executed by the extra m on the outside can well be delayed until we are supplied a value a. Well, at least when all arguments are fully applied

[Haskell-cafe] Re: Diagnosing stack overflow

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

[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread apfelmus
Justin Bailey wrote: apfelmus wrote: Extracting the head and tail of ss with a let statement could lead to a huge unevaluated expression like rest = tail (tail (tail (...))) Even though they are probably forced, would breaking the head and tail apart via pattern-matching or a case

[Haskell-cafe] Re: List comprehension desugaring

2007-08-19 Thread apfelmus
as an intermediate result in the translation for empty Q. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Bi-directional Maps

2007-08-20 Thread apfelmus
(\new old - new) 'a' 1 (fromList [('a',2),('b',1)]) do? I can't yield fromList [('a',1),('b',1)] since 1 has two keys now. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Bi-directional Maps

2007-08-21 Thread apfelmus
be a bijection http://en.wikipedia.org/wiki/Bijective_map Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Newbie question: Where is StackOverflow on the Wiki?

2007-08-21 Thread apfelmus
:) ) Yes! We'd need such an automatic tool for the wikibook, too. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Newbie question: Where is StackOverflow on the Wiki?

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

[Haskell-cafe] Re: help understanding lazy evaluation

2007-08-23 Thread apfelmus
with the formalizer :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: IO inside CGI

2007-08-24 Thread apfelmus
I can perform to make this possible? Abracadabra, the incantation is liftIO :: IO a - CGI a i.e. parse :: Maybe String- CGI StdGen parse (Just x) = return $ read x parse Nothing = liftIO getStdGen Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: nested datatypes

2007-08-26 Thread apfelmus
already automated this with Template Haskell or other other preprocessing tools. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: quoting in Haskell

2007-08-28 Thread apfelmus
it is not part of the context = [add] I'm not sure why you'd want to do that, but it's not well-defined. What would selectiveQuote [add] ((1 `add` 2) `mul` 3) be? How to expand `mul` here when `add` isn't expanded? Regards, apfelmus ___ Haskell

[Haskell-cafe] Re: Mutable but boxed arrays?

2007-09-06 Thread apfelmus
? Exactly. Put differently, writeArray :: STUArray - .. is strict in the third argument whereas writeArray :: STArray - .. is not. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] Re: turning an imperative loop to Haskell

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

[Haskell-cafe] Re: ((a - b) - c) - (a - m b) - m c

2007-09-10 Thread apfelmus
convert :: (a - m b) - m (a - b) between those two types for a given monad m is equivalent to the existence of magic :: ((a - b) - c) - (a - m b) - m c since we have convert = magic id magic f g = return f `ap` convert g Regards, apfelmus

[Haskell-cafe] Re: Data.Binary Endianness

2007-09-10 Thread apfelmus
... Oh, and the 8,16,32 and 64 are good candidates for phantom type/associated data types, too. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Sequencing Operations in a Monad

2007-09-15 Thread apfelmus
mult x x with onlyOnce :: IO Int mult :: Int - Int - IO Int ? If you want mult = liftM2 something :: IO Int - IO Int - IO Int you can do x' - onlyOnce let x = return x' mult x x which is do x - return `liftM` onlyOnce mult x x for short. Regards, apfelmus

[Haskell-cafe] Re: Type-Marking finite/infinte lists?

2007-09-16 Thread apfelmus
it via the isomorphism exists e . expr e = forall w . (forall e . expr e - w) - w Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Type-Marking finite/infinte lists?

2007-09-17 Thread apfelmus
Roberto Zunino wrote: apfelmus wrote: cons:: a - List e f a - List Nonempty f a But unfortunately, finiteness is a special property that the type system cannot guarantee. The above type signature for cons doesn't work since the following would type check bad :: a - List Nonempty

[Haskell-cafe] Re: Building production stable software in Haskell

2007-09-18 Thread apfelmus
is *hard*, especially since you can think about it for weeks without touching a computer. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Type-Marking finite/infinte lists?

2007-09-18 Thread apfelmus
xs) we can write fromList :: [a] - ListFinite a fromList [] = nil fromList (x:xs) = cons x (fromList xs) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: [Haskell] simple function: stack overflow in hugs vs none in ghc

2007-09-24 Thread apfelmus
(_,...))) ) and it seems that Hugs fails to evaluate the tail recursive chain of snd ?? In the end, here's our decisive result: either Hugs or my analysis has a bug :D Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: simple function: stack overflow in hugs vsnonein ghc

2007-09-24 Thread apfelmus
be up to the programmer's choice (partial reduction may be expensive), so is there a way to specify that in code? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Shouldnt this be lazy too?

2007-09-24 Thread apfelmus
/gmane.comp.lang.haskell.cafe/26329 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Math.Statistics

2007-09-26 Thread apfelmus
at home. Didn't he say something about the mean formula? Or was it the standard derivation?). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: isWHNF :: a - IO Bool ?

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

[Haskell-cafe] Re: isWHNF :: a - IO Bool ?

2007-09-27 Thread apfelmus
Tristan Allwood wrote: Does anyone know if there is a function that tells you if a haskell value has been forced or not? e.g. isWHNF :: a - IO Bool apfelmus wrote: Note that this function [isWHNF :: a - Bool] is not referentially transparent Indeed. Does it still mess up with the result

[Haskell-cafe] Re: SOE/GLFW compilation problems

2007-10-07 Thread apfelmus
/users_guide/ separate-compilation.html#using-make for an example Makefile that shows how it's done. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Data types, opengl display loop and readIORef/writeIORef

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

[Haskell-cafe] EnableGUI hack changes working directory

2007-10-09 Thread apfelmus
Hello, the EnableGUI hack for getting a window in GHCi on Mac OS X (10.3.9 for me) unexpectedly changes the working directory for the running ghci [...] apfelmus$ ghci -i../../Hackage/SOE/src [...] GHC Interactive, version 6.6.1, for Haskell 98. *Main :! pwd /Users/apfelmus/Documents

[Haskell-cafe] Re: symbol type?

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

[Haskell-cafe] Can every monad can be implemented with Cont? (was: New slogan for haskell.org)

2007-10-13 Thread apfelmus
how it can be done with Cont in all cases. It works for the above state monad (*) but what about primitives like mplus :: m a - m a - m a callcc :: ((a - m r) - m r) - m a that have monadic arguments in a contravariant position (possibly even universally quantified)? Regards, apfelmus

[Haskell-cafe] Re: Filesystem questions

2007-10-14 Thread apfelmus
started). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: On the verge of ... giving up!

2007-10-14 Thread apfelmus
to Functional Programming using Haskell. For other books, see also http://haskell.org/haskellwiki/Books_and_tutorials#Textbooks Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] Re: On the verge of ... giving up!

2007-10-14 Thread apfelmus
everything I (thought I) knew (about programming). The reward was worth it. Why do people want side effects? Purity is soo much simpler. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: On the verge of ... giving up!

2007-10-15 Thread apfelmus
no infantilizing. A stronger condition would be that every valid LearningPrelude program should be a valid RealHackersPrelude program. This is probably preferred, but may be tricky due to overloading ambiguities. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: On the verge of ... giving up!

2007-10-15 Thread apfelmus
Felipe Lessa wrote: apfelmus wrote: Of course, the solution is to first drop n elements and then take tails instead of dropping n elements every time. map (drop n) . tails = tails . drop n O(m*n) O(m) Nice identity. I'll remember this one. Oops, please don't

[Haskell-cafe] Existential types (Was: Type vs TypeClass duality)

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

[Haskell-cafe] Re: XML parser recommendation?

2007-10-24 Thread apfelmus
the memory reduction for large XML trees which are likely to have many many identical tag names. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Existential types (Was: Type vs TypeClass duality)

2007-10-25 Thread apfelmus
can be translated into math-speak and are then called parametricity. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Existential types (Was: Type vs TypeClass duality)

2007-10-25 Thread apfelmus
- a) are isomorphic. (And you're right, the only thing this function can do is to return _|_.) In contrast, ∃a means I choose a concrete type a at will and you will have to deal with all of my capricious choices. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: Existential types (Was: Type vs TypeClass duality)

2007-10-25 Thread apfelmus
about existentials under the terms noted on http://en.wikibooks.org/wiki/User:Apfelmus. (This also means that I don't allow to put them on the haskellwiki which has a more liberal license.) Thanks for posting this, I finally understand existentials! λ(^_^)λ Regards, apfelmus

Re: [Haskell-cafe] Existential types (Was: Type vs TypeClass duality)

2007-10-25 Thread apfelmus
Ryan Ingram wrote: On 10/24/07, apfelmus [EMAIL PROTECTED] wrote: So, instead of storing a list [∃a. Show a = a], you may as well store a list of strings [String]. I've seen this before, and to some extent I agree with it, but it breaks down for bigger examples due to sharing. In most cases

[Haskell-cafe] Re: Existential types (Was: Type vs TypeClass duality)

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

[Haskell-cafe] Re: viewing HS files in Firefox

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

[Haskell-cafe] Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-01 Thread apfelmus
- ((),*World) loop w = loop w loop' w = let (_,w') = print x w in loop' w' both have denotation _|_ but are clearly different in terms of side effects. (The example is from SPJs awkward-squad tutorial.) Any pointers? Regards, apfelmus ___ Haskell

[Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread apfelmus
Brandon S. Allbery KF8NH wrote: apfelmus wrote: during function evaluation. Then, we'd need a purity lemma that states that any function not involving the type *World as in- and output is indeed pure, which may be a bit tricky to prove in the presence of higher-order functions

[Haskell-cafe] Re: Semantics of uniqueness types for IO (Was: Why can't Haskell be faster?)

2007-11-02 Thread apfelmus
- ... - (*World, ...). In contrast, we can see IO a as an abstract (co-)data type subject to some straightforward operational semantics, no need to mess with the pure - . So, in a sense, the Haskell way is cleaner than the Clean way ;) Regards, apfelmus

[Haskell-cafe] Re: FP design

2007-11-07 Thread apfelmus
implement and let some law intuition guide you. Well-known example: darcs. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Doubly-linked zipper list w/ insert implementation

2007-11-07 Thread apfelmus
rotations like rotL xs n in O(log n) time. (I keep mixing up the meaning of rotL and rotR , does L push the current element to the left or does it rotate the ring clockwise?) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Should I step into a minefield? / Writing a trading studio in Haskell

2007-11-08 Thread apfelmus
to the difficulty of designing a powerful trading DSL in the first place :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: About Fibonacci again...

2007-11-08 Thread apfelmus
+ foldr1 (+) [f k | k - [0..n]] This identity allows us to write f ∞ = f 1 + foldr1 (+) [f k | k - [0..]] and hence rs_bp' = 1: foldr1 (.) mrs' undefined To close the circle, Alfonso's solution is in fact the deforestation of this one. Regards, apfelmus

[Haskell-cafe] Re: Doubly-linked zipper list w/ insert implementation

2007-11-10 Thread apfelmus
$ Context (cycle $ reverse xs) (head xs) (tail $ cycle xs) Here, mkContexts xs initializes a new infinite cyclic ring for xs and rotates it left ad infinitum. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Queues and Rings (Re: Doubly-linked zipper list w/insert implementation)

2007-11-10 Thread apfelmus
(Btw, this ring stuff could be relevant for Xmonad, I don't know whether the workspace/window-ring implementation there is O(1). Not that it matters for 1000 windows, of course :) Justin Bailey wrote: apfelmus wrote: Do you really need to realize the cycle by sharing? I mean, sharing

[Haskell-cafe] Re: Renaming constructors for readability

2007-11-14 Thread apfelmus
? The thing you want is called views. See http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns#Relatedwork for more. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: List of all powers

2007-11-14 Thread apfelmus
gmane gradually forget old messages?). The only problem is to make this work on an infinite list. Dave Bayer discovered a great way to do this, here's an explanation http://thread.gmane.org/gmane.comp.lang.haskell.cafe/26426/focus=26493 Regards, apfelmus

[Haskell-cafe] Re: List of all powers

2007-11-15 Thread apfelmus
Brent Yorgey wrote: apfelmus, does someone pay you to write so many thorough, insightful and well-explained analyses on haskell-cafe? I'm guessing the answer is 'no', but clearly someone should! =) Depending on length, my prices for posts range between λ9.99 and λ29.99 ;) Regards, apfelmus

[Haskell-cafe] Re: Knot tying vs monads

2007-11-16 Thread apfelmus
blo indent es = Blo es indent . sum . map size $ es ( sum is a function from the Prelude.) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: List of all powers

2007-11-16 Thread apfelmus
Calvin Smith wrote: I really look forward to apfelmus' consistently outstanding explanations on haskell-cafe. If some of the especially good ones were bundled up as book -- *Intermediate/Advanced Functional Programming with Haskell* -- I would buy it sight unseen (hint, hint). :) I intend

[Haskell-cafe] Re: Knot tying vs monads

2007-11-17 Thread apfelmus
to make it so. As Derek said, strict data types are probably the easiest way to go here. Or you can use custom strict constructors, like str s = s `deepSeq` Str s or something. But again, I don't know why you would want that at all. Regards, apfelmus

[Haskell-cafe] Re: Knot tying vs monads

2007-11-18 Thread apfelmus
better, although it's a bit messy for my taste. I've scribbled a hopefully gentler explanation at http://en.wikibooks.org/wiki/Haskell/Performance_Introduction . Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: What is the role of $!?

2007-11-18 Thread apfelmus
different things nonetheless. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Knot tying vs monads

2007-11-19 Thread apfelmus
John D. Ramsdell wrote: On Nov 17, 2007 3:04 PM, apfelmus [EMAIL PROTECTED] wrote: Unfortunately, I don't have Paulson's book (or any other ML book :) at home. I'm too lazy to figure out the specification from the source code, I guess the code is too opaque, as my colleague claimed

[Haskell-cafe] Re: expanded standard lib

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

[Haskell-cafe] Re: -O2 bug in GHC 6.8.1?

2007-11-20 Thread apfelmus
Christian Maeder wrote: good bug! -O or -O2 is irrelevant but it works if compiled with -fvia-C You (or someone else) should add it to http://hackage.haskell.org/trac/ghc I guess that this is related to http://thread.gmane.org/gmane.comp.lang.haskell.cafe/31675 Regards, apfelmus

[Haskell-cafe] Re: Knot tying vs monads

2007-11-20 Thread apfelmus
the O(n^2) degenerate case. In any case, I prefer Wadler's combinators. With line being more rigid than Brk , nest and group basically factor the monolithic Blk which makes more laws and available and hence gives a more elegant implementation. Regards, apfelmus

[Haskell-cafe] Re: ANNOUNCE: fixpoint 0.1

2007-11-21 Thread apfelmus
Bertram Felgenhauer wrote: [redirecting from [EMAIL PROTECTED] apfelmus wrote: [...] I wonder whether a multi parameter type class without fundeps/associated types would be better. class Fixpoint f t where inject :: f t - t project :: t - f t [...] Interestingly, this even

[Haskell-cafe] Re: ANNOUNCE: fixpoint 0.1

2007-11-21 Thread apfelmus
Roman Leshchinskiy wrote: apfelmus wrote: Making f an associacted type synonym / fundep instead of a associated data type is still worth it, since we can use it for Mu f But alas, this breaks hylomorphisms: hylo :: Fixpoint t = (Pre t s - s) - (p - Pre t p) - p - s If Pre is a type

[Haskell-cafe] Re: Knot tying vs monads

2007-11-21 Thread apfelmus
John D. Ramsdell wrote: All I know is it was dog slow without any annotations, and spaying them on the suspect data structures cured that problem. Ah ok, that makes sense :) although it's a bit unsatisfactory to be forced to do that blindly. Regards, apfelmus

[Haskell-cafe] Re: ANNOUNCE: fixpoint 0.1

2007-11-21 Thread apfelmus
Roman Leshchinskiy wrote: apfelmus wrote: Ah, right. But unlike size , this is unambiguous since t can (and probably should) be fused away: hylo :: Functor f = (f s - s) - (p - f p) - p - s hylo f g = f . fmap (hylo f g) . g Excellent point! When I originally developed the code

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

2007-11-21 Thread apfelmus
when the user submits a form i.e. answers to a prompt. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: expanded standard lib

2007-11-22 Thread apfelmus
consistent across distributions, and if there were a corresponding installer for those other operating systems. Meta-packages on hackage would do the trick, no? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: nhc vs ghc

2007-11-24 Thread apfelmus
, so no multi parameter type classes, rank-n-polymorphism or GADTs. It does support existential types, though. In particular, the popular monad transformer library isn't Haskell98, at least concerning the type classes. Regards, apfelmus ___ Haskell

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

2007-11-24 Thread apfelmus
Derek Elkins wrote: Ryan Ingram wrote: apfelmus wrote: A context passing implementation (yielding the ContT monad transformer) will remedy this. Wait, are you saying that if you apply ContT to any monad that has the left recursion on = takes quadratic time problem

[Haskell-cafe] Re: New slogan for haskell.org

2007-11-26 Thread apfelmus
probably need the glossary articles first before linking to them :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: is there a more concise way to generate helper functions for a datatype built on records?

2007-11-27 Thread apfelmus
Isaac Dupree wrote: apfelmus wrote: dup :: Lens a (a,a) dup = id id Which component of the pair should put dup :: a - (a,a) - (a,a) change? The first, the second, or even both? [...] put :: Lens s a - a - s - s put x = flip $ snd . focus x wouldn't put dup

[Haskell-cafe] Re: New slogan for haskell.org

2007-11-27 Thread apfelmus
. Such power! Hearing just this was more than enough reason for me to learn Haskell and to never look back. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: New slogan for haskell.org

2007-11-27 Thread apfelmus
Henning Thielemann wrote: apfelmus wrote: Back then, I was given the task to calculate some sequence of numbers which I did in one page of C code. So far so good, but when I asked the task assigner about his solution, he responded: Ah, this problem, that's 1 line in Haskell. Well, 2 lines

[Haskell-cafe] Re: New slogan for haskell.org

2007-11-29 Thread apfelmus
Laurent Deniau wrote: apfelmus wrote: Back then, I was given the task to calculate some sequence of numbers which I did in one page of C code. import Data.Set xs = let f x m = x: let y = x `div` 2 in f (if member y m then 3*x else y) (insert x m) in f 1 (singleton 0

[Haskell-cafe] Re: Trees

2007-12-03 Thread apfelmus
the subtrees u and v in the first place? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Possible Improvements

2007-12-03 Thread apfelmus
evaluate it's second argument occurs m r if the first argument occurs m l turns out to be already True. In other words, thanks to lazy evaluation, the search stops if m has been found in the left subtree, it won't search the right subtree anymore. Regards, apfelmus

[Haskell-cafe] Re: New slogan for haskell.org

2007-12-03 Thread apfelmus
Stefan O'Rear wrote: In my C programming, I've taken to using gdb as a REPL: Ah, that's a nice trick, thanks! I wish I there had been a gdb on MacOS 8.5 back then ;) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Trees

2007-12-03 Thread apfelmus
Thomas Davie wrote: apfelmus wrote Well, this problem doesn't make much sense in Haskell. How do you specify the subtrees u and v in the first place? One could alway store a node's depth at each node -- then you must search for u and v, creating a list of what nodes you found at each depth

[Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-08 Thread apfelmus
is instantiated, like in map ((+1) :: Int - Int) [1..5] = map (+1) ([1..5] :: [Int]) = (map (+1) [1..5]) :: [Int] Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-11 Thread apfelmus
Dan Weston wrote: Questioning apfelmus definitely gives me pause, but... Don't hesitate! :) Personally, I question everyone and everything, including myself. This is a marvelous protection against unintentionally believing things just because I've heard them several times like Monads

[Haskell-cafe] Re: class default method proposal

2007-12-11 Thread apfelmus
/gmane.comp.lang.haskell.general/15471 In other words, the main problem of all those superclass/explicit import/export proposals is that there are no proofs of the fact that they only allow well-defined programs. The homework isn't done yet, discussing adoption is too early. Regards, apfelmus

[Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-11 Thread apfelmus
jerzy karczmarczuk wrote: apfelmus: As Feynman put it: What do you care what other people think? It was not Feynman, but his wife. Thanks, I should have questioned my claim :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: New slogan for haskell.org

2007-12-12 Thread apfelmus
want it, so be it. We provide data points (I have written a big but robust program, it's called insert name here, We have a FFI and its use is explained here, look, this quicksort function is so beautiful) but judgment is what everybody has to do for himself. Regards, apfelmus

[Haskell-cafe] Re: Software Tools in Haskell

2007-12-12 Thread apfelmus
'\t' = cs -- replace with adequate number of spaces replace _ char = [char] -- pass through How about that? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: class default method proposal

2007-12-13 Thread apfelmus
as an exercise for the reader :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Software Tools in Haskell

2007-12-13 Thread apfelmus
Tommy M McGuire wrote: apfelmus wrote: tabwidth = 4 -- tabstop !! (col-1) == there is a tabstop at column col -- This is an infinite list, so no need to limit the line width tabstops = map (\col - col `mod` tabwidth == 1) [1..] -- calculate spaces needed to fill

[Haskell-cafe] Re: Examples of useful functions of order = 3?

2007-12-14 Thread apfelmus
functions probably aren't that useful anymore, but they once were :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Software Tools in Haskell

2007-12-15 Thread apfelmus
automatically forces the elements. This makes sense to do early and we can use normal list functions after that. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: New slogan for haskell.org

2007-12-15 Thread apfelmus
Henning Thielemann wrote: apfelmus wrote: gwern wrote: Now, the Main Page on haskell.org is not protected, so I could just edit in one of the better descriptions proposed, but as in my Wikipedia editing, I like to have consensus especially for such visible changes. Hey, why has the front

[Haskell-cafe] Re: Monads that are Comonads and the role of Adjunction

2007-12-16 Thread apfelmus
,a) and the stream comonad (f `O` f) a = (S, S - a) out of that. Regards apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: OOP'er with (hopefully) trivial questions.....

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

[Haskell-cafe] Re: Foldable Rose Trees

2007-12-18 Thread apfelmus
[Rose' 2 [Rose' 3 []],Rose' 4 [],Rose' 5 []],Rose' 6 []] This can be made shorter: Data.Traversable.mapM m = unwrapMonad . traverse . (\x - WrapMonad (m x)) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: New to Haskell: The End

2007-12-18 Thread apfelmus
because monads were such a cool use case). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: MonadFix

2007-12-20 Thread apfelmus
primes' = 2:[3,5..] f (p:ps) n | r == 0= p : f (p:ps) q | p*p n = [n] | otherwise = f ps n where (q,r) = n `divMod` p For a faster factorization, just plug in a better primes' . Regards, apfelmus

[Haskell-cafe] Re: MonadFix

2007-12-21 Thread apfelmus
Joost Behrends wrote: apfelmus writes: How about separating the candidate prime numbers from the recursion factorize :: Integer - [Integer] factorize = f primes' where primes' = 2:[3,5..] f (p:ps) n | r == 0= p : f (p:ps) q | p*p n = [n

  1   2   3   4   5   6   7   8   9   >