[Haskell] Re: ANN: Efficient, dynamically compiled, lazy functional semantics on JVM, having tight integration with the Java language

2006-09-29 Thread apfelmus
(software reuse!) is obvious, then. 2. Software for a banking-house that handles all the financial transactions just cannot be shut down for bug fixing or rewrites. The same goes for lambdabot :) Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org

[Haskell] Re: Common library for generic programming

2006-10-03 Thread apfelmus
If you want to get involved (or just want to see the discussion), you can subscribe to the mailing list [EMAIL PROTECTED], see http://www.haskell.org/mailman/listinfo/generics -- Johan Jeuring and Andres Loeh Can you add the mailing list to GMANE?

[Haskell] Re: Replacing and improving pattern guards with PMC syntax

2006-10-03 Thread apfelmus
Right q - return p guard (p 5) return (p-5) One last thing is to eliminate fromJust: f x | (interesting things here) should be syntactic sugar for f x = fromJust $ | (interesting things here) Regards, apfelmus

[Haskell] Re: Replacing and improving pattern guards with PMC syntax

2006-10-03 Thread apfelmus
follow-ups (possibly indented). This expends of any unnecessary ; do/choose | Right q ~ p val - lookup key v - do/choose | Left v ~ val return v | Right v - val return v return (v+1) | Left q ~ p Regards, apfelmus

[Haskell] Re: Monad transformer question

2006-10-26 Thread apfelmus
conditions b to filter things out. Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: I18N, external strings

2006-11-16 Thread apfelmus
startup which is probably what you want. If not, then you just have to float (\s -) out of unsafePerformIO: getString = \s - unsafePerformIO $ do ... return $ fromJust' ... Of course, you can also integrate the initialization into (getString). Regards, apfelmus

[Haskell] Re: GHCi and Hugs ASCII logos

2006-12-13 Thread apfelmus
I think I remember that some program was used to generate either the Hugs or GHCi ascii logo that appears when you fire up the interpreter. While not being the same, there's a similar program in the Hugs demos directory: /usr/lib/hugs/demos/Say.hs Say putStr $ say Hugs H H U U

[Haskell] Re: Converting a 'streaming' monad into a list

2006-12-30 Thread apfelmus
) and not that of (foldl) as the latter can be recovered from the former but not the other way round. Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: Converting a 'streaming' monad into a list

2006-12-31 Thread apfelmus
out is evaluated strictly, only that the pair constructor is matched by a refutable pattern. In other words, is there an example where one would prefer (foo (a,b) = ...) over (foo ~(a,b) = ...) for reasons of time and space? If not, then I think it's a bug. Regards, apfelmus

[Haskell] Re: Views in Haskell

2007-01-24 Thread apfelmus
such a list. Intentions: I need views for ... * pattern matching on abstract data types (John Meacham, apfelmus) examples: - Okasaki: Breath first numbering - lessons from a small exercise in graph theory view Queue a = Empty | Cons a (Queue a) - ByteStrings view

[Haskell] Re: Profiling Feedback to Optimize Memoization Caching

2007-02-23 Thread apfelmus
. The countdown problem. Journal of Functional Programming, 12(6):609-616, November 2002 http://www.cs.nott.ac.uk/~gmh/countdown.pdf Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: Profiling Feedback to Optimize Memoization Caching

2007-02-23 Thread apfelmus
of Programming. Prentice Hall, 1996. but it's not introductory in nature. It seems to be out of print, is there any way to get a (perhaps electronic) copy? Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo

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

2007-02-27 Thread apfelmus
, the SML version uses Vectors, polymorphic vectors, immutable sequences with constant-time access. I wonder how immutable these are. I suspect that changing elements does updates in place with history tracking? Regards, apfelmus ___ Haskell mailing list

[Haskell] Re: Quicksearch vs. lazyness

2007-03-19 Thread apfelmus
to hit the bottom. Putting both together, we see that we have to pay O(n + k*log n) steps to build the expression and to fetch the first k elements. Making this argument rigorous with a suitable debit invariant is left to the attentive reader :) Regards, apfelmus

[Haskell] Re: Software Engineering and Functional Programming (withHaskell)

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

[Haskell] Re: The real Warm, fuzzy thing Transformer

2007-04-04 Thread apfelmus
, fuzzy thing sequence $ words Warm, fuzzy thing [M,o,n,a,d] Oh, this output is unexpectedly cold and clear. Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: Quicksearch vs. lazyness

2007-04-14 Thread apfelmus
apfelmus wrote: Steffen Mazanek wrote: From my understanding for small k's lazy evaluation already does the trick for the naive quicksort algorithm (quicksort smaller ++ [x] ++ quicksort greater), doesn't it? Is there a search algorithm that makes better use of lazy evaluation out of the box

[Haskell] Re: Quicksearch vs. lazyness

2007-04-17 Thread apfelmus
with lazy evaluation. Isn't it great that finding the k-th minimum is not only an adaption of quicksort but can readily be obtained from it by _composing_ it with (!! k)? Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org

[Haskell] Re: ANNOUNCE: Harpy -- run-time code generation library

2007-05-12 Thread apfelmus
is a monad that generates code without any execution taking place. The execution part is already handled by runCodeGen. Having liftIO means that arbitrary Haskell programs can be intertwined with assembly generation and I doubt that you want that. Regards, apfelmus

[Haskell] Re: type class instance selection search

2007-08-01 Thread apfelmus
invariants on one and the same map type. In other words, the different Ord instances for A will mess up the invariants of the Map A a implementation and will eventually even lead to pattern match failures. Being able to mess up invariants by class export/import is quite dangerous. Regards, apfelmus

[Haskell] Re: [Haskell-cafe] PROPOSAL: Rename haskell@ to haskell-announce@

2007-09-24 Thread apfelmus
(sounds silly for mail-only but is extremely useful for read-through-gmane). Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: Fingerprints and hashing

2007-10-11 Thread apfelmus
. But for CSE, we have to carry the collection around anyway. I don't know any references for that method since I came up with it myself and haven't searched around yet. Any pointers? Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org

[Haskell] Re: ANNOUNCE: fixpoint 0.1

2007-11-20 Thread apfelmus
type signatures cata :: Fixpoint f t = (f s - s) - t - s size :: (Fixpoint f t, Foldable f) = t - Int Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: Empty instance declaration

2007-12-28 Thread apfelmus
or multi parameter type classes exist. Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell] Re: Probably a trivial thing for people knowing Haskell

2008-10-21 Thread apfelmus
It's much shorter and should run in constant memory as well. Regards, apfelmus ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

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

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

Re: [Haskell-cafe] class default method proposal

2007-12-11 Thread apfelmus
[] where fmap = fmapDefault fmap is already written for you, the instance declaration is only boilerplate. I first saw this in Data.Traversable . Regards, apfelmus ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org

Re: Replacing and improving pattern guards with PMC syntax

2006-10-03 Thread apfelmus
Right q - return p guard (p 5) return (p-5) One last thing is to eliminate fromJust: f x | (interesting things here) should be syntactic sugar for f x = fromJust $ | (interesting things here) Regards, apfelmus

Re: Fractional/negative fixity?

2006-11-07 Thread apfelmus
fixity levels as fixed points of continuous functionals! Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Re: Fractional/negative fixity?

2006-11-08 Thread apfelmus
fixity levels are useful, too. A further step to complex numbers is not advised because those cannot be ordered. But ordering of the computable reals is not computable. So it could cause the compiler to loop during parsing. :) Actually, that's one of the use cases ;) Regards, apfelmus

Re: String literals

2006-11-13 Thread apfelmus
are to be allowed in pattern matching. Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Re: Are pattern guards obsolete?

2006-12-13 Thread apfelmus
be r - lookup m x Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Higher order syntactic sugar

2006-12-14 Thread apfelmus
apfelmus suggested to use '=' for this purpose, so that, wherever monadic generators are permitted pattern = expr ~~ pattern - return expr It was to late when i realized that = is already used as smaller than or equal to :) Obviously, the difference between the pattern guard

Re: Higher order syntactic sugar

2006-12-17 Thread apfelmus
the limits of Haskell syntax. True. Compared to Template Haskell, a preprocessor allows syntactic extensions but is weak at type correctness. Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman

Re: Make it possible to evaluate monadic actions when assigning record fields

2007-07-11 Thread apfelmus
the join. In any case, I'm *strongly against* further syntactic sugar for monads, including #1518. The more tiresome monads are, the more incentive you have to avoid them. Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http

Re: Make it possible to evaluate monadic actions when assigning record fields

2007-07-12 Thread apfelmus
apfelmus wrote: In the end, I think that applicatively used monads are the wrong abstraction. Simon Peyton-Jones wrote: Can you be more explicit? Monadic code is often over-linearised. I want to generate fresh names, say, and suddenly I have to name sub-expressions. Not all sub-expressions

Re: Status of Haskell Prime Language definition

2007-10-16 Thread apfelmus
, they have to stand some test of time before Haskell' can pick one of the two (probably the latter). Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Re: Status of Haskell Prime Language definition

2007-10-16 Thread apfelmus
Iavor Diatchki wrote: apfelmus wrote: fundeps are too tricky to get powerful and sound at the same time. I am not aware of any soundness problems related to functional dependencies---could you give an example? http://hackage.haskell.org/trac/haskell-prime/wiki/FunctionalDependencies

Re: Status of Haskell Prime Language definition

2007-10-18 Thread apfelmus
are not reported early via the consistency condition but late when actually constructing terms. The consistency condition should be enough for soundness (no inconsistent axioms accepted), but I didn't dwell enough into FD to know such things for sure. Regards, apfelmus

Re: patch applied (haskell-prime-status): add Make $ left associative, like application

2008-04-23 Thread apfelmus
) - a - b for the /identity functor/. In other words, the current ($) and (.) are just special cases of the general fmap . Unfortunately, the identity functor currently can't be overloaded, although I think it would be unambiguous. Regards, apfelmus

Re: Meta-point: backward compatibility

2008-04-24 Thread apfelmus
for all eternity :) Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Re: Suggestion regarding (.) and map

2008-04-25 Thread apfelmus
~) where (.) = () Regards, apfelmus ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

[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

  1   2   3   4   5   6   7   8   9   >