Re: [Haskell-cafe] Polymorphic (typeclass) values in a list?

2007-10-19 Thread Kalman Noel
TJ wrote: Why is it illegal to store values of differing types, but which instance the same class, into a list? e.g. a = [ 1, 2.0 ] :: Num a = [a] The problem is that Num a = [a] really means: forall a. Num a = [a] That is, a list of type Num a = [a] could either be a list of Integers,

Re: [Haskell-cafe] Polymorphic (typeclass) values in a list?

2007-10-19 Thread Kalman Noel
Jules Bean wrote: This looks very very much clearer in GADT syntax, since in GADT syntax you always give constructors explicit types: type ExistsNumber where Number :: forall a . Num a = ExistsNumber a The questions in response to my post have been answered already; I'd like to mention,

Re: [Haskell-cafe] Re: Polymorphic (typeclass) values in a list?

2007-10-21 Thread Kalman Noel
Peter Hercek wrote: When 'exists' is not a keyword, why 'forall' is needed at all? Isn't everything 'forall' qualified by default? “forall” isn't a keyword in Haskell 98. As an extension to the language, however, it makes certain types expressible that can not be written in H98, for example

Re: [Haskell-cafe] Rose Tree

2007-11-04 Thread Kalman Noel
Ryan Bloor: Data Tree a = Empty | Leaf a | Node a [(Tree a)] The Leaf constructor seems superfluous to me. Any (Leaf x) value is equivalent to (Node x []). So I rather just have data Tree a = Empty | Node a [Tree a] which will mean less work for your task of writing processing functions,

Re: [Haskell-cafe] A tale of three shootout entries

2007-11-28 Thread Kalman Noel
Simon Peyton-Jones wrote: You might think that unnecessary bangs shouldn't lead to unnecessary work -- if GHC knows it's strict *and* you bang the argument, it should still only be evaluated once. But it can happen. Consider f !xs = length xs Even though 'length' will evaluate

Re: [Haskell-cafe] A tale of Project Euler

2007-11-28 Thread Kalman Noel
Sebastian Sylvan: primes :: [Integer] primes = 2 : filter (null . primeFactors) [3,5..] primeFactors :: Integer- [Integer] primeFactors n = factor n primes where factor m (p:ps) | p*p m= [] | m `mod` p == 0 = p : factor (m `div` p) (p:ps)

Re: [Haskell-cafe] foild function for expressions

2007-12-03 Thread Kalman Noel
Carlo Vivari wrote: data AlgExp a = AlgExp { litI :: Int - a, litB :: Bool - a, add :: a - a - a, and :: a - a - a, ifte :: a - a - a - a} You're confusing sum and product types. That is, you're using a product type, but you probably need a sum type, like this: data Exp1 =

Re: [Haskell-cafe] foild function for expressions

2007-12-04 Thread Kalman Noel
Ryan Ingram wrote: On 12/3/07, Kalman Noel [EMAIL PROTECTED] wrote: You're confusing sum and product types. I'm not so sure; it looks like they already have that type (Exp) and wants to use AlgExp to hold the folding functions used. Ah, I didn't catch that on the first read. I suppose Carlo

Re: [Haskell-cafe] Re: 0/0 1 == False

2008-01-12 Thread Kalman Noel
Achim Schneider wrote: whereas lim( 0 ) * lim( inf ) is anything you want Indeed I suppose that »lim inf«, which is a notation I'm not familiar with, is not actually defined to mean anything? Kalman -- Find out how you can get

Re: [Haskell-cafe] Re: 0/0 1 == False

2008-01-12 Thread Kalman Noel
Achim Schneider wrote: Actually, lim( 0 ) * lim( inf ) isn't anything but equals one, and the anything is defined to one (or, rather, is _one_ anything) to be able to use the abstraction. It's a bit like the difference between eight pens and a box of pens. If someone knows how to properly

Re: [Haskell-cafe] Re: 0/0 1 == False

2008-01-12 Thread Kalman Noel
Cristian Baboi wrote: Cristian Baboi: Suppose lim a_n = a , lim b_n = b, c_2n = a_n, c_2n+1 = b_n. What is lim c_n ? If my intuition was of any importance here, it would claim that c_n diverges, because if I roughly approximate c_n by the sequence c' = ⟨a,b,a,b,...⟩, then I note that c'

Re: [Haskell-cafe] Re: Re: 0/0 1 == False

2008-01-19 Thread Kalman Noel
Ben Franksen wrote: Kalman Noel wrote: (2) lim a_n = ∞ [...] (2) means that the sequence does not converge, because you can always find a value that is /larger/ than what you hoped might be the limit. (2) usually rather mean that for each positive limit

Re: [Haskell-cafe] Re: Re: Re: 0/0 1 == False

2008-01-19 Thread Kalman Noel
Ben Franksen wrote: Kalman Noel wrote: Ben Franksen wrote: Kalman Noel wrote: (2) means that the sequence does not converge, because you can always find a value that is /larger/ than what you hoped might be the limit. Your definition of (2) is usually termed

Re: [Haskell-cafe] Mutable arrays

2008-02-05 Thread Kalman Noel
Jeff φ wrote: Changing the subject slightly, I once wrote code in Concurrent Clean that filtered a file that was larger than the available memory on my PC. I did this by creating a function that returned the contents of the original file as a lazy list. Doing this is idiomatic in Haskell,

Re: [Haskell-cafe] Generating a random list

2008-03-01 Thread Kalman Noel
Milos Hasan wrote: Here's a minimal summing example that illustrates the difference. The following works fine, since the elements are generated lazily and summed on the fly, as expected: randFloats :: [Float] randFloats = randoms (mkStdGen 0) main = do let xs = take 100

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

2008-03-10 Thread Kalman Noel
Neil Mitchell wrote: instance Eq Foo where (==) (Foo a _) (Foo b _) = (==) a b [...] Please give the sane law that this ordering violates. I can't see any! The (non-existant) law would be (Eq1) x == y = f x == f y, for all f of appropriate type which is analogous to this

[Haskell-cafe] Re: How to optimize the performance of a code in Haskell?

2009-11-04 Thread Kalman Noel
(I take it you accidently wrote to fa.haskell, which is just a mirror of -cafe and -beginners, so I'm cc-ing the Café with a full quote.) Masayuki Takagi: I'm writing fluid simulation programs with SPH(Smoothed particle hydrodynamics) in Haskell and C++. (The purpose that I write in two

Re: [Haskell-cafe] ANNOUNCE: control-monad-failure and safe-failure

2009-11-16 Thread Kalman Noel
Michael Snoyman schrieb: control-monad-failure provides a basic notion of failure which does not commit to any concrete representation. It is just a version of the MonadError class without the annoying bits. class MonadFailure e m where failure :: e - m a Why is it called MonadFailure

Re: [Haskell-cafe] ANNOUNCE: control-monad-failure and safe-failure

2009-11-17 Thread Kalman Noel
Nicolas Pouillard schrieb: class MonadFailure e m where failure :: e - m a Why is it called MonadFailure (specifically, what's the Monad bit doing there)? Because of 'Monad m' being a superclass of 'MonadFailure e m'. Here is the class: class Monad m = MonadFailure e m where failure :: e -

[Haskell-cafe] Re: Numeric Prelude and identifiers

2009-04-26 Thread Kalman Noel
Henning Thielemann schrieb: On Mon, 6 Apr 2009, Kalman Noel wrote: I'm not complaining, and I'm not sure what I mean :) I may like a scheme where functions operating on a type or type class live in a module seperate from the type (class) definition, so you could import a specific module

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Kalman Noel
michael rice schrieb: let m1 = Just 1 let m2 = [] let m3 = m1 `mplus` m2 == [1] --if the Maybe is not Nothing, add it to the list Or am I misunderstanding combining computations? You just got the type of mplus wrong: mplus :: (MonadPlus m) = m a - m a - m a Note that it takes

[Haskell-cafe] OT: Languages (was: Is Haskell a Good Choice for Web Applications? (ANN: Vocabulink))

2009-05-08 Thread Kalman Noel
wren ng thornton schrieb: Chris Forno (jekor) wrote: That being said, Esperanto, and even Japanese sentence structure perhaps is not as different as an agglutinative language like German. I'll need to study it more to find out. Actually, Japanese is agglutinative too (moreso than German

Re: [Haskell-cafe] Re: Is Haskell a Good Choice for Web Applications? (ANN: Vocabulink)

2009-05-08 Thread Kalman Noel
Daniel Carrera schrieb: I think it largely depends on the learner. Some people find vocabulary easier, or more interesting, others not. I have a hard time learning a lot of isolated facts (e.g. vocabulary), but I find it easier and more enjoyable to learn a rule that I can apply many times.

Re: [Haskell-cafe] Haskell in 3 Slides

2009-05-21 Thread Kalman Noel
Joe Fredette schrieb: 3-4 slides imply 3-4 topics, so the question is what are the 3-4 biggest topics in haskell? I would think they would be: * Purity/Referential Transparency * Lazy Evaluation * Strong Typing + Type Classes * Monads If the goal is to be able to talk about different

Re: [Haskell-cafe] Parsing command lines

2009-05-31 Thread Kalman Noel
Patai Gergely schrieb: is there a function that can safely split a command line into a FilePath to the executable and its parameters? In the yi source code, in HConf.Utils, there's a function that does part of what you want, but maybe incorrectly (because I wrote it, and it traverses the

Re: [Haskell-cafe] Re: Simple quirk in behavior of `mod`

2009-07-22 Thread Kalman Noel
Thomas ten Cate schrieb: There are two ways of looking at the mod operator (on integers): 1. As a map from the integers Z to Z/pZ. [...] 2. As the remainder under division by p. Since n mod 0 would be the remainder under division by 0, this correctly gives a division by zero error. I

Re: [Haskell-cafe] Re: [Haskell-beginners] Just how unsafe is unsafe

2009-02-07 Thread Kalman Noel
As I didn't catch the whole thread, I hope I'm not just repeating everyone else: Roel van Dijk wrote: I guess what unsafe should mean is a matter of taste. Personally I find correctness more important that pureness. An unsafe function will crash your program if evaluated when its

Re: [Haskell-cafe] Re: Query on list comprehension

2009-03-18 Thread Kalman Noel
Jon Fairbairn schrieb: Melanie_Green jac_legend_...@hotmail.com writes: What are the limitations of list comprehension. [...] a aa aaa I'm not clear what you mean by the question. Why do you want to use list comprehensions? What if they aren't the best way of getting the result you want?

Re: [Haskell-cafe] Re: categories and monoids

2009-03-18 Thread Kalman Noel
Wolfgang Jeltsch schrieb: Okay. Well, a monoid with many objects isn’t a monoid anymore since a monoid has only one object. It’s the same as with: “A ring is a field whose multiplication has no inverse.” One usually knows what is meant with this but it’s actually wrong. Wrong for two

Re: [Haskell-cafe] ANNOUNCE: fad 1.0 -- Forward Automatic Differentiation library

2009-04-05 Thread Kalman Noel
Henning Thielemann schrieb: with advanced type classes: http://hackage.haskell.org/packages/archive/numeric-prelude/0.0.5/doc/html/MathObj-PowerSeries.html I'll take this as another opportunity to point out that the Haddock docs of the Numeric Prelude are highly unreadable, due to all qualified

[Haskell-cafe] Re: Numeric Prelude and identifiers (Was: fad 1.0 -- Forward AutomaticDifferentiation library)

2009-04-06 Thread Kalman Noel
Henning Thielemann schrieb: On Sun, 5 Apr 2009, Kalman Noel wrote: I'm wondering, too, if the Numeric Prelude could be organized more cleanly if we had a fancier module system - does someone have sufficient experience with, say, ML-style module systems to tell? Are you complaining about