[Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-19 Thread apfelmus
algorithms don't have an extra factor, although f is clearly larger for them. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-20 Thread apfelmus
. The naive 'filter (\x - x `mod` p /= 0)' is it as well. But I agree that the latter deserves more a name like transposed sieve of Eratosthenes. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Map list of functions over a single argument

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

[Haskell-cafe] Re: Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-20 Thread apfelmus
than the human who can see and cross numbers on a piece of paper at his choice. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: functional database queries

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

[Haskell-cafe] Re: functional database queries

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

[Haskell-cafe] Re: Leaves of a Tree

2007-02-22 Thread apfelmus
) = 1 fib' n = sumtree (fibtree n) = sumtree $ Branch (fibtree (n-1)) (fibtree (n-2)) = (sumtree $ fibtree (n-1)) + (sumtree $ fibtree (n-2)) = fib' (n-1) + fib' (n-2) Now, you can optimize the result by memoizing fib'. Regards, apfelmus

[Haskell-cafe] Re: functional database queries

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

[Haskell-cafe] Re: Safe lists with GADT's

2007-02-26 Thread apfelmus
to the equivalence exists a . f a ~= forall r . (forall a . f a - r) - r Both have of course the problem that we cannot simply write safeMap (fromList [1,2,3]) :: exists t . List a t Regards, apfelmus Exercise: Why is fromList :: exists t . [a] - List a t wrong as well

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

2008-01-14 Thread apfelmus
Felipe Lessa wrote: apfelmus wrote: Oh, what kind of generalization do you have in mind? Leaking Prompt(..) in the export list to the GUI code seems wrong to me, I like 'runPromptM' because it hides the Prompt(..) data type from the user [module]. But after some rest I think I found a nice

[Haskell-cafe] Re: Displaying # of reductions after eachcomputation in ghci?

2008-01-14 Thread apfelmus
beta reduction step like (\x.c(d(e(f(x) g = c(d(e(f(g may take 5 steps in some reduction strategies since you have to walk down the expression tree to find the variable and replace it with its value. In the end, seconds are a better measure for time :) Regards, apfelmus

[Haskell-cafe] Re: Simulating client server communication with recursive monads

2008-01-16 Thread apfelmus
/projects/rmb/ 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-16 Thread apfelmus
Felipe Lessa wrote: apfelmus wrote: The type of contPromptM is even more general than that: casePromptOf' :: (r - f b) - (forall a,b. p a - (a - f b) - f b) - Prompt p r - f b casePromptOf' done cont (PromptDone r) = done r casePromptOf' done cont

[Haskell-cafe] Re: Reflection.Emit in Haskell

2008-01-18 Thread apfelmus
This way, every match_RE r will evaluated to the function corresponding to r and the result will be shared. In your code, match_RE r s will be run-time compile the regex matcher for each string s again and again. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: STM in F#

2008-01-18 Thread apfelmus
a reason the STM monad hatched in Haskell: how does the above STM in F# handle side-effects like launchMissile ? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Deleting list of elements from Data.Set

2008-01-30 Thread apfelmus
. In contrast, Duncan's code evaluates to Data.Set , that's what you want to be strict in. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Relevance and applicability of category theory

2008-01-31 Thread apfelmus
Monoid m = Category (Mon m) where id= Mon mempty (Mon f) . (Mon g) = Mon (f `mappend` g) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: [Haskell] Why functional programming matters

2008-01-31 Thread apfelmus
(OrdBy p a)) instance Heap (HeapP p) where ... Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Data.Ord and Heaps (Was: Why functional programming matters)

2008-02-01 Thread apfelmus
Stephan Friedrichs wrote: apfelmus wrote: [...] Feedback: I think the HeapPolicy thing is too non-standard. The canonical way would be to use a MinHeap and let the Ord instance handle everything. A MaxHeap can then be obtained via a different Ord instance newtype Ord a = Reverse

[Haskell-cafe] Re: Data.Ord and Heaps

2008-02-06 Thread apfelmus
) data Lowered a = Lower a | Top deriving (Eq, Ord) instead of type Raised a = OrdBy Down (Maybe a) type Lowered a = OrdBy Up (Maybe a) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: Data.Ord and Heaps (Was: Why functional programming matters)

2008-02-06 Thread apfelmus
p a = Ord (OrdBy p a) where ... is shorter but not H98 either. The name could be a mot juste, too. class Rearranged p a where ... class Ord' p a where ... class OrdBy p a where ... -- clashes with the name of the type Regards, apfelmus

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

2008-02-11 Thread apfelmus
is the interpretation of = in terms of sequencing actions with side effects. The law is probably best demonstration with its special case x (y z) = (x y) z In other words, it signifies that it's only the sequence of x,y,z and not the nesting that matters. Regards, apfelmus

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

2008-02-12 Thread apfelmus
m does not fulfill the monad laws, it just shows that naïvely using m [a] to implement the list monad transformer is incorrect for general m . In other words, there is a big bug in Control.Monad.List and that's all there is to it. Regards, apfelmus

[Haskell-cafe] Re: [Haskell] Mailing List Archive: Search Broken?

2008-02-15 Thread apfelmus
Janis Voigtlaender wrote: apfelmus wrote: The subject line is a hyperlink that points to the context thread of the message (which is displayed with frames). only in the case of haskell.cafe, but not for haskell.general. (see my response to Calvin Smith on the cafe list) Actually

[Haskell-cafe] Re: Doubting Haskell

2008-02-17 Thread apfelmus
Colin Paul Adams wrote: Left? Right? Hardly descriptive terms. Sounds like a sinister language to me. The mnemonics is that Right x is right in the sense of correct. So, the error case has to be Left err . Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: Doubting Haskell

2008-02-17 Thread apfelmus
cover the System.IO stuff, but you've got the #haskell irc channel and the mailing list for that. So, the textbook remark is in anticipation of the questions that you are going to have :) (if you decide to pursue Haskell further, that is). Regards, apfelmus

[Haskell-cafe] Re: Graphical graph reduction

2008-02-22 Thread apfelmus
simple examples since those are better done by hand. But an unsophisticated tool is useless for the more complicated cases too, since no one can make sense of the output anymore! Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: fast graph algorithms without object identities

2008-02-23 Thread apfelmus
understand why this works, and these ad-hoc unique numbers bother me.) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Generating a random list

2008-03-01 Thread apfelmus
-recursive. Sometimes, GHCs strictness analyzer is able to optimize that away. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Generating a random list

2008-03-02 Thread apfelmus
in the library doesn't behave as nicely as I'd have expected. I'd consider the first definition a strictness bug; the general etiquette is to force arguments from left to right. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

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

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

[Haskell-cafe] Specification for Eq?

2008-03-14 Thread apfelmus
De Bruijn indices and even representations based on parametric polymorphism. But I think that this doesn't touch the issue of alpha-conversion being a natural Eq instance.) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: deconstruction of the list/backtracking applicative functor?

2008-03-24 Thread apfelmus
here? Something with sequence :: Applicative f = [f a] - f [a] being the cartesian product for the list monad? Or simpler pure (,) :: Applicative f = (f a, f b) - f (a,b) somehow crossing the elements of f a and f b ? Regards, apfelmus

[Haskell-cafe] Re: Type constraints for class instances

2008-03-24 Thread apfelmus
xs ~ merge [x] (merge xs ys) , but merge3 incorporates the additional insight that we don't need to pit x against the xs anymore. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: deconstruction of the list/backtracking applicative functor?

2008-03-24 Thread apfelmus
7 of the applicative functor paper. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Random Monad

2008-03-24 Thread apfelmus
Matthew Pocock wrote: Who currently maintains the Random monad code? /me whispers: have a look at http://code.haskell.org/monadrandom/MonadRandom.cabal Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Sorting with a weaker form of Ord (Re: Type constraints for class instances)

2008-03-24 Thread apfelmus
apfelmus wrote: Krzysztof Skrzętnicki wrote: class YOrd a where ycmp :: a - a - (a,a) Unfortunately, the performance of ysort is rather low. I believe that it is impossible to create any sorting algorithm that uses ycmp instead of compare, that is faster than O(n^2). It is possible

[Haskell-cafe] Re: FW: Haskell

2008-04-01 Thread apfelmus
, well, where to start? Girard and Reynolds? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Typing with co/contra-variance.

2008-04-03 Thread apfelmus
meeting: http://bayfp.org/talks/slides/philip_wadler_1_jan_08_bayfp.pdf Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Role based access control via monads or arrows or... something

2008-04-03 Thread apfelmus
which knows these constants has -- corresponding permissions data Restricted p a = Restricted a readRestricted :: Permission p - Restricted p a - a Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Sorting with a weaker form of Ord (Re: Type constraints for class instances)

2008-04-03 Thread apfelmus
, namely O(n (log n)^2) and even better. Sorting algorithms based on a comparator function like ycmp are called sorting networks and in fact well-known. See also http://en.wikipedia.org/wiki/Sorting_network Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: Role based access control via monads or arrows or... something

2008-04-06 Thread apfelmus
David Roundy wrote: apfelmus wrote: David Roundy wrote: porrifolius wrote: (7) ideally required permissions would appear (and accumulate) in type signatures via inference so application code knows which are required and type checker can reject static/dynamic role constraint violations

[Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread apfelmus
. The subtle difference in the type synonym family case is that a is more parametric there. At least, that's my feeling. In full System F , neither definition would be a problem since the type a is an explicit parameter. Regards, apfelmus

[Haskell-cafe] Re: type families and type signatures

2008-04-09 Thread apfelmus
Manuel M T Chakravarty wrote: apfelmus: Manuel M T Chakravarty wrote: Let's alpha-rename the signatures and use explicit foralls for clarity: foo :: forall a. Id a - Id a foo' :: forall b. Id b - Id b GHC will try to match (Id a) against (Id b). As Id is a type synonym family, it would

[Haskell-cafe] Re: type families and type signatures

2008-04-11 Thread apfelmus
Tom Schrijvers wrote: apfelmus wrote: However, I have this feeling that bar :: forall a . Id a - String with a type family Id *is* parametric in the sense that no matter what a is, the result always has to be the same. Intuitively, that's because we may not pattern match on the branch

[Haskell-cafe] Re: Laziness and Either

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

[Haskell-cafe] Re: Stronger STM primitives needed? Or am I just doing it wrong?

2008-04-23 Thread apfelmus
when the left argument changes. In essence, we have the same problem with parser combinators. Applicative functors to the rescue! Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

[Haskell-cafe] Re: Stronger STM primitives needed? Or am I just doing it wrong?

2008-04-24 Thread apfelmus
ReadOnlySTM a = StateT TVarEnvironment STM a Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Stronger STM primitives needed? Or am I just doing it wrong?

2008-04-24 Thread apfelmus
to express both the continuation-logging and read-only-fail optimization in terms of type STM a = Maybe a or similar? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Stronger STM primitives needed? Or am I just doing it wrong?

2008-04-24 Thread apfelmus
Chris Smith wrote: apfelmus wrote: For 1), it's enough to have a primitive scheduleWriteTVar :: TVar a - a - STM () that ensures to write the TVar at the very end of the atomically block.. Unfortunately, though, this breaks the very thing that makes STM attractive: namely

[Haskell-cafe] Re: Help me refactor this type!

2008-04-25 Thread apfelmus
(= g) f Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Control.Exception.evaluate - 'correct definition' not so correct

2008-05-03 Thread apfelmus
that the implementation given in the documentation is wrong. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Parsec on TeX

2008-05-05 Thread apfelmus
Don Stewart wrote: Yeah, if you're on Debian it would make sense to install GHC -- its much more active, much faster, and supports more things. [than Hugs] Except for compile and load time, Hugs is really fast there. Regards, apfelmus ___ Haskell

[Haskell-cafe] Re: Control.Exception.evaluate - 'correct definition' not so correct

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

[Haskell-cafe] Re: Control.Exception.evaluate - 'correct definition' not so correct

2008-05-07 Thread apfelmus
http://en.wikibooks.org/wiki/Haskell/Denotational_semantics Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Write Haskell as fast as C. [Was: Re: GHC predictability]

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

[Haskell-cafe] Re: another Newbie performance question

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

[Haskell-cafe] Re: appending an element to a list

2008-06-01 Thread apfelmus
/gmane.comp.lang.haskell.cafe/34398/focus=34435 Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: appending an element to a list

2008-06-03 Thread apfelmus
Okasaki's book. [1]: Chris Okasaki. Purely Function Data Structures. http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf (This is the thesis on which the book is based.) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Rewrite class with fundeps in pure h98?

2008-06-03 Thread apfelmus
is feels wrong, something like Serialize is probably a better fit. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: [ANNOUNCE] git-darcs-import 0.1

2008-06-04 Thread apfelmus
, the whole point of rebasing seems to be to somehow bring set semantics into the tree semantics.) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Laziness leaks

2008-06-04 Thread apfelmus
a paradox :) as Okasaki already points out in his book. Eager evaluation may waste both time and space compared to alternative course of reduction. Regards, apfelmus PS: The reduction strategies we compare to don't evaluate under lambdas. ___ Haskell

[Haskell-cafe] Re: What is the maturity of Haskell Web Frameworks

2008-06-05 Thread apfelmus
. http://web.cecs.pdx.edu/~cklin/papers/unimo-143.pdf [MonadPrompt]: Ryan Ingram. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadPrompt Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Laziness leaks

2008-06-05 Thread apfelmus
, but again, they haven't been running for very long yet.) Yeah :( When a piece of softwares wastes time and memory, they should have written it in Haskell, so that at least the other bugs wouldn't plague me as well. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: appending an element to a list

2008-06-07 Thread apfelmus
Ronald Guida wrote: Thank you, apfelmus. That was a wonderful explanation; the debit method in [1] finally makes sense. A diagram says more than a thousand words :) My explanation is not entirely faithful to Okasaki, let me elaborate. In his book, Okasaki calls the process of transferring

[Haskell-cafe] Re: Quick question for a slow program

2008-06-08 Thread apfelmus
as advertised. I've fixed that and also cleaned up the page a bit, moving this sieve to the section Implicit Heap. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Quick question for a slow program

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

[Haskell-cafe] Re: Strange space leak

2008-07-14 Thread apfelmus
= foldl' (zipWith' (+)) zero . map (foldl' (zipWith' max) zero . map bits) where zero = map (const 0) ws bits v = map (fromEnum . (== v)) ws Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Euler 201 performance mystery

2008-07-16 Thread apfelmus
is it?). Regards, apfelmus Footnote: We still have to prove the identity (length sum) . (x:) = (\(n,s) - (n+1,s+x)) . (length sum) I mean, you can figure this out in your head, but a formal calculation best proceeds with the two identities length . (x:) = (1+) . length -- definition

[Haskell-cafe] Re: Strange space leak

2008-07-16 Thread apfelmus
. Thanks, No problem, it was not obvious to me and I had fun trying to figure it out :) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Euler 201 performance mystery

2008-07-16 Thread apfelmus
apfelmus wrote: In other words, we have now calculated the more efficient program euler201 = map snd . filter ((==50) . fst) . subsums $ squares where subsums [] = singleton (0,0) subsums (x:xs) = map (\(n,s) - (n+1,s+x)) (subsums xs) `union` subsums xs I forgot something

[Haskell-cafe] Re: BLAS Solve Example

2008-07-23 Thread apfelmus
, this is unsuitable for serious floating point calculations. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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

2008-08-19 Thread apfelmus
, just hide (*) and (+) from the prelude and define your own.) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Parsec and network data

2008-08-30 Thread apfelmus
* tree does not depend on import statements? I.e. Chasing imports is performed after you've got an abstract syntax tree. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Proofs and commercial code -- was Haskell Weekly News: Issue 85 - September 13, 2008

2008-09-15 Thread apfelmus
Hola amigos del Foro ( México ), alguno de ustedes sabe donde se puede adquirir en nuestro país pedacitos de fibra de coco, lo que en inglés llaman coconut husk chips...?? He tenido noticia acerca de su uso exitoso como ingrediente en la preparación de sustrato, en USA se puede conseguir

[Haskell-cafe] Re: Comparing GADTs for Eq and Ord

2008-09-15 Thread apfelmus
of your program as well. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Comparing GADTs for Eq and Ord

2008-09-16 Thread apfelmus
Tom Hawkins wrote: apfelmus wrote: So, in other words, in order to test whether terms constructed with Equal are equal, you have to compare two terms of different type for equality. Well, nothing easier than that: (===) :: Expr a - Expr b - Bool Const === Const

[Haskell-cafe] Re: Library design question

2008-09-19 Thread apfelmus
Andre Nathan wrote: I'm trying to write a simple graph library for a project of mine There's also Martin Erwig's functional graph library in Data.Graph.Inductive ( fgl on hackage). Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Ropes

2008-09-20 Thread apfelmus
). Are you sure that there is no unintentional bug in your implementation that slows things down? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Red-Blue Stack

2008-09-25 Thread apfelmus
, in a subsequent post, I'll turn the above ideas into a better solution and I'll also explain why implementing this data structure seems more difficult in Haskell than in Java. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Red-Blue Stack

2008-09-26 Thread apfelmus
apfelmus wrote: data Stack2 r b = Empty | S [r] (Stack2 b r) deriving (Eq, Show) In the previous post, I considered an implementation of red-blue stacks with the data type above. Unfortunately, it failed to perform in O(1) time because list concatenation needs linear time: xs ++ ys takes

[Haskell-cafe] Re: Red-Blue Stack

2008-09-27 Thread apfelmus
I'm not aware of any such results. Yes, lazy evaluation makes persistent data structures much easier, sometimes even possible. It only gives amortized times, though. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Red-Blue Stack

2008-09-27 Thread apfelmus
Empty Empty The red element got lost in the first case. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Health effects

2008-09-30 Thread apfelmus
I have something wrong with me... A much more important question is: how many break bar in two operations did you perform? Can you do it with less? Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

[Haskell-cafe] Re: Total Functional Programming in Haskell

2008-10-01 Thread apfelmus
Jason Dagit wrote: apfelmus wrote: It seems to me that dependent types are best for ensuring totality. Bear with me, as I know virtual nothing about dependent types yet. Ah, my bad. Time to change that ;) Personally, I found Th. Altenkirch, C. McBride, J. McKinna. Why dependent types

[Haskell-cafe] Re: Inferred type is less polymorphic than expected, depends on order

2008-10-07 Thread apfelmus
one has to produce one x that works for all b at once. Here's an example for natural numbers that illustrates the difference: ∀m.∃n.n m -- we can always find a larger number (sure, use n=m+1) ∃n.∀m.n m -- we can find a number larger than all the others! Regards, apfelmus PS

[Haskell-cafe] Re: Interesting new user perspective

2008-10-11 Thread apfelmus
... ... and a solution to a problem that you souldn't have in the first place. I mean, if you want to construct XML or SQL statements, you ought to use an abstract data type that ensures proper nesting etc. and not a simple string. Regards, apfelmus ___ Haskell-Cafe

[Haskell-cafe] Re: Interesting new user perspective

2008-10-13 Thread apfelmus
Andrew Coppin wrote: apfelmus wrote: ... and a solution to a problem that you souldn't have in the first place. I mean, if you want to construct XML or SQL statements, you ought to use an abstract data type that ensures proper nesting etc. and not a simple string. Right. And if you

[Haskell-cafe] Re: Interesting new user perspective

2008-10-13 Thread apfelmus
Devin Mullins wrote: apfelmus wrote: Yes. Just an injection problem is an understatement. And its the implementation of the abstract data type that determines how fast things are. Who said that it may not simply be a newtyped String ? I think the attraction to the SafeString example

[Haskell-cafe] Re: Interesting new user perspective

2008-10-14 Thread apfelmus
Ryan Ingram wrote: Normally I agree with you, apfelmus, but here at least I have to differ! /me considers map crushToPurée . filter disagrees ;) On Mon, Oct 13, 2008 at 11:50 AM, apfelmus [EMAIL PROTECTED] wrote: *HTML toString $ tag b [] [tag i [] [text ], text test] bilt;gt;/itest/b

[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread apfelmus
, but the attitude you complain about is the exact opposite of the attitude of any five year old children that *I* know (well, my son primarily ;-). Derek probably meant kids that are three quarters through school ... and thus no longer interesting in anything. :( Regards, apfelmus

[Haskell-cafe] Re: howto tuple fold to do n-ary cross product?

2008-11-24 Thread apfelmus
]] [[1,3],[1,4],[2,3],[2,4]] Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: MPTCs and rigid variables

2007-03-07 Thread apfelmus
inference already is a kind of mini-prolog. Of course, that doesn't simplify their semantics at all. In a sense, knowing AT is knowing how much functional in style type inference can be. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe

[Haskell-cafe] Re: Distributing a GHC-compiled binary for Macs (x86)

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

[Haskell-cafe] Re: Foralls in records

2007-03-14 Thread apfelmus
(Transaction c) where ... getConnection :: Transaction c c ... Note that Control.Monad.State does the same. Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Defining types (newbie)

2007-03-14 Thread apfelmus
= () `by` field_three Appealing to the famous instance Monad ((-) a), you can also say and, or :: BoolOp a - BoolOp a - BoolOp a and = liftM2 $ liftM2 () or = liftM2 $ liftM2 (||) Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: Foralls in records

2007-03-14 Thread apfelmus
the parameter c altogether? Why do you intend 'Transaction' to be a state monad, I mean why is the only thing you can do with the state something of type (c - String - IO ())? Btw, this has been (c - String - Transaction ()) in your original post. Regards, apfelmus

[Haskell-cafe] Re: small boys performance

2007-03-14 Thread apfelmus
://www.nt.ntnu.no/users/haugwarb/Programming/haskell_automatic_differentiation_III.pdf Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Performance Help

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

[Haskell-cafe] Re: what I learnt from my first serious haskell programm

2007-03-19 Thread apfelmus
. Recursive modules are the lazy evaluation of modules and One should not obstruct access to such a vital tool. I want recursive modules for free! Regards, apfelmus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman

<    1   2   3   4   5   6   7   8   9   >