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 - m a


Oh ok; I misguidedly took the line at the top to be the class definition. I'd 
still be interested if such a simple Failure class could be meaningful or 
useful for mere, say, Applicatives.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 (specifically, what's the Monad bit doing 
there)?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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
languages is to make a workflow that first i write in Haskell for
rapid prototyping and accuracy then rewrite in C++ for performance.)

I've compared them in performance. Then, although I have already done
optimization with profiler, the Haskell code is 20 times slower than
the C++ code.

I think the performance of the Haskell code is so slow that there can
be room for optimization. I'm happy if the Haskell code work 3 times
slower than the C++ code at worst.

How can I make the Haskell code faster?
What information should I refer?

The codes are here:
http://kamonama.sakura.ne.jp/sph/20091101/sph.hs.zip
http://kamonama.sakura.ne.jp/sph/20091101/sph.cpp

To run the code in Haskell:
$ ghc --make -O sph.hs
$ ./sph 300
(300 is the time step to be conputed)

To run the code in C++:
$ g++ -O2 -o sph sph.cpp
$ ./sph 300
(300 is the time step to be conputed)

thanks



I've not looked at the code, but you'll want ghc to do better optimizations 
than -O. -O2 is what you should use in general. Also, number-crunching often 
profits from -fexcess-precision.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 used to think that the definitions were equivalent... apparently not.

They are if you don't disallow division by zero with remainder. Namely, the
definition of “division with remainder” works as in (1).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 string in a rather primtive way).

-- | Break up a string the way a shell breaks up a command into arguments.
-- Similar to 'words', but respects quotes and escaped spaces.  TODO: Verify
-- this function.

shellWords :: String - [String]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 examples of Haskell
code in the rest of the presentation, the big topic I'd choose would be
called »How function definitions look like in Haskell«.

Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 is). 

I take it the above calling German agglutinative was sort of a typo,
because well, it isn't, except having many compound words. Esperanto, on
the other hand, is usually described as agglutinative.

Kalman

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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. But I know people
 who are the exact opposite. I wouldn't want to make an absolute rule.

Or like a local physics prof likes to put it: “I guess you all have an
idea of Ohm's law? Or wait, right, for the medics being with us, here
are the three Ohm's laws: U = RI, R = U/I, and I= U/R.”

Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 two values of the same type (m a), but you're giving
it values of different types.  That is, combining computations of
different types is not within the scope of MonadPlus.  In this case, it
makes sense to convert (Just 1) to [1] via Data.Maybe.maybeToList, thus:

m1 = Just 1
m2 = [2,3]
m3 = maybeToList m1 `mplus` m2   -- [1,2,3]

Note also that, in this example, Monoid (mappend) instead of MonadPlus
(mplus) would be sufficient.  Actually MonadPlus becomes useful only
when you are concerned about the extra properties that its instances are
expected to satisfy.

Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 to get only, say, (Ring, (*), one, ...).  But that would
 be too tedious in the Haskell hierarchical module system, which is why I
 was asking about others.
 
 It was precisely my goal to bundle the type with the functions that
 operate on it. Why do you want to separate them?

Sorry for the huge delay. Here are some reasons why I think such a
seperation can be handy:

 (1) If I need an import just to be able to write a type annotation
 (e.g.  I'm passing around a value of that type, but not doing
 anything specific to it), then I can just import a module that
 gives me the relevant types.

 (2) Similarly, I can, say, calculate with complex numbers and refer
 to them as Complex Double without importing (qualified) the
 Complex implementations of exp, signum etc., which I won't ever
 have to use directly, thanks to the relevant type class instances.

 (3) I can refer to a Ring as a Ring, rather than a Ring.C.


(1) may not be so important, given that I can just write an import list.
(2) means seperating interface and implementation (without hiding the
implementation). (3) is just a matter of taste.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 the organisation or about the identifiers? If
 you mean the former, then what organisation do you propose?

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 to get only, say, (Ring, (*), one, ...).  But that would
be too tedious in the Haskell hierarchical module system, which is why I
was asking about others.

 If you mean
 the latter ... Many proposals about extended import facilities I saw
 were complicated and could simply be avoided using the naming style I use.

I'm ready to believe you that the naming style you chose is optimal
within the hierarchical module system.

Regards,
Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 class
and type names appearing as just C or T.  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?

Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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?
 
 You can write 
 
 [a | b - [replicate n 'a' | n - [1..]], a - b ++ \n] 
 
 but does that replicate fail to meet your specification?

Since we're »holfing« again:

fix $ \xs - [ 'a':xs | xs - []:xs ]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 reasons: First, because the multiplication 
 of a field has an inverse. Second, because the multiplication of a ring is 
 not forced to have no inverse but may have one.

“A ring is like a field, but without a multiplicative inverse” is, in my
eyes, an acceptable formulation. We just have to agree that “without”
here refers to the definition, rather than to the definitum.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 preconditions do not hold.
 Whether that is because of impurity (segmentation fault?), a partial
 pattern match or a direct error bla is not that important. It might
 be important when determining why your program crashed, but the result
 is still the same.

Maybe for the purposes of naming functions it's sufficient to argument
that a crash is a crash whatsoever, but as for terminology in general, I
think it's good to distinguish (1) partial functions from (2) functions
that break purity, may lead to segmentation faults etc.  I suppose (2)
is the »traditional« meaning of unsafe.

The motivation for this distinction is that you can still reason to some
extent about (1) if you consider _|_, and that there are many functions
that, although useful and correct, aren't guaranteed to terminate on
infinite input, thus are partial.  On the other hand, functions from (2)
should always be called unsafeFoo, and/or wrapped by safe functions.

Kalman

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 (existant) law about observational equality:

(Eq2)   x = y   =  f x = f y,   for all f of appropriate type

Kalman

--
Finally - A spam blocker that actually works.
http://www.bluebottle.com/tag/4

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 randFloats
print $ sum xs
 
 But this overflows, because the list is created before being summed, and 
 the take function goes into awfully deep recursion:
 
 randFloats :: [Float]
 randFloats = randoms (mkStdGen 0)
 
 main = do
xs - return $ take 100 randFloats
print $ sum xs
 
 Is there a clean way to avoid this problem?

There is, and it has already been mentioned: It's the behaviour of
Prelude.sum that is bugging you. ‘sum’ will build an expression like
this, which is responsible for the stack overflow:

...(n1 + n2) + n3) + n4) + ...) + nm)
^ evaluation will start here
   ^ But this is the first addition to be performed

Instead, just use sum', which is defined just like sum, but with a
strict left fold instead of a lazy left fold:

import Data.List

sum' :: (Num a) = [a] - a
sum' = foldl' (+) 0

I don't know exactly why there is a difference between both programs.  
I suppose that in the first one, the strictness analyzer can optimize
sum into sum', but in the second one it cannot.

Kalman

--
Get a free email address with REAL anti-spam protection.
http://www.bluebottle.com/tag/1

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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, although its usage is commonly
discouraged in more complex UI settings because you cannot ever close
the file handle until the end of the program.  The relevant functions
are to be found in the Prelude (or in Data.ByteString.Lazy, for that
matter).

--
Get a free email account with anti spam protection.
http://www.bluebottle.com/tag/2

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 A there is a number N
 such that a_N  A for /all/ n  N.

You're right here. I tried to come up with a more wordy, informal description,
but failed on that.

 Your definition of (2) is usually termed as '(a_n) contains a subsequence
 that tends toward +infinity'.

May you elaborate? I don't see where a subsequence comes into play here.

Kalman

--
Get a free email account with anti spam protection.
http://www.bluebottle.com/tag/2

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 as '(a_n) contains a subsequence
  that tends toward +infinity'.
 I'll show (2) = (2'), where
 
 (2'): (a_n) contains a subsequence that tends toward +infinity

Only now did I understand that your point was to explain why and how my
definition (2) is incorrect.  It's clear to me now.

Kalman

--
Finally - A spam blocker that actually works.
http://www.bluebottle.com/tag/4

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 spam free email.
http://www.bluebottle.com/tag/3

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
 formalise n = 1, please speak up.

Sorry if I still don't follow at all.  Here is how I understand (i. e.
have learnt) lim notation, with n ∈ N, a_n ∈ R.  (Excuse my poor
terminology, I have to translate this in my mind from German maths
language ;-).  My point of posting this is that I don't see how to
accommodate the lim notation as I know it with your term. The limit of
infinity?  What is the limit of infinity, and why should I multiplicate
it with 0?  Why should I get 1?

(1) lim a_n  = a(where a ∈ R)
(2) lim a_n  = ∞
(3) lim a_n  = − ∞
(4) lim { x → x0 } f(x) = y (where f is a function into R)

(1) means that the sequence of reals a_n converges towards a.

(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.

(3) means that the sequence does not converge, because you can
always find a value that is /smaller/ than what you hoped might
be the limit.

(4) means that for any sequence of reals (x_n ∈ dom f) converging
towards x0, we have lim f(x_n) = y.  For this equation again, we
have the three cases above.

Kalman

--
Find out how you can get spam free email.
http://www.bluebottle.com/tag/3

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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' oscillates, so c_n »roughly
 oscillates«.
 
 You mean something like this x=a:b:x  ?

Ah, you try to be on-topic by using Haskell syntax :)

Obviously though, I really forgot to consider the case a = b... But that's
enough OT for today, I guess.

Kalman

--
Get a free email account with anti spam protection.
http://www.bluebottle.com/tag/2

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 should then
tell us what Exp exactly looks like; and it would be nice, too, to
explain to me what the function in question is supposed to achieve then.
He doesn't seem to want to reduce the expression, after all.

Kalman

--
Free pop3 email with a spam filter.
http://www.bluebottle.com/tag/5

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 = LitI Int 
| LitB Bool 
| Add Exp1 Exp1 
| And Exp1 Exp1 
| IfThenElse Exp1 Exp1 Exp1

But in this case, using GADTs (beware: not Haskell 98, but a very popular
extension) makes for a more elegant solution. Note the strong types, disallowing
e. g. the addition of a number to a boolean value:

data Exp2 a where
LitI:: Int  - Exp2 Int
LitB:: Bool - Exp2 Bool
Add :: Exp2 Int  - Exp2 Int  - Exp2 Int
And :: Exp2 Bool - Exp2 Bool - Exp2 Bool
IfThenElse  :: Exp2 Bool - Exp2 a - Exp2 a - Exp2 a

Kalman

--
Get a free email address with REAL anti-spam protection.
http://www.bluebottle.com/tag/1

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 its argument, f nevertheless evaluates it
 too.

I'm replying to a guru here, so I should keep my voice low; but I'd like to
point out what might result in a misunderstanding for other readers of
haskell-cafe. Contrasting both the bang pattern and the usage of length causing
f to be strict, one might suppose that a bang pattern, when used on a list, will
cause it to be evaluated in the same way as length does. However,

 the *first* thing length does is evaluate its argument,

and it will furthermore evaluate the argument list recursively, as much as is
necessary to determine its length. On the other hand, given

g !xs = ()

evaluating g [0..] will terminate, because g is only strict in the constructor
of its argument, which is (:). The list data type itself, however, is
non-strict.

Kalman

--
Free pop3 email with a spam filter.
http://www.bluebottle.com/tag/5

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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)
 | otherwise  = factor m ps

Your definition gives a strange meaning to primeFactors. I'd want that for all
n,  product (primeFactors n) == n.  I think this law holds for the code posted
by Olivier. Of course I'd beautify his definition slightly by writing

primes = 2 : filter isPrime [3,5..]

isPrime = null . drop 1 . primeFactors

primeFactors n | n = 2 = factor primes n

factor pr@(p:ps) n 
| p*p  n   = [n]
| r == 0= p : factor pr q
| otherwise = factor ps n
where (q,r) = quotRem n p

Kalman

--
Get a free email account with anti spam protection.
http://www.bluebottle.com/tag/2

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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, too.

Kalman

--
Get a free email account with anti spam protection.
http://www.bluebottle.com/tag/2

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 

f :: (forall a. a) - T

which is different from 

g :: forall a. a - T

although both are not particularly useful. (The only argument that f will ever
take is bottom!)

In the context of existentially quantified types, however, the forall keyword is
used probably to make the use of an extension more explicit. Without the forall
keyword, 

data U = C a

would be an existential, while the programmer maybe really wanted the usual

data U a = C a

Kalman

--
Find out how you can get spam free email.
http://www.bluebottle.com/tag/3

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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, or a
list of Doubles, or ..., but not a heterogeneous list.  Slightly varying the
type does not help, either:

[forall a. Num a = a]

This would mean that each and every value in the list is itself polymorphic.
What we ultimately need could be written as

[exists a. Num a = a]

i. e. for each value in the list there is a Num type to which the value belongs.
While there is no “exists” quantifier in Haskell types, you can use
existentially quantified types (existentials) for your purpose. Given the
following data type ExistsNumber

data ExistsNumber = forall a. Num a = Number a
instance Show Number where  -- So we can try this in ghci
show (Number a) = show a

You may read the data declaration as: “(Number a) has type ExistsNumber if a
belongs to the type class Num, i. e. for all a in Num.”

Now you can “wrap” any value in the type class Num into an ExistsNumber value,
thus “forgetting” its concrete type. You can then construct a list of type
[ExistsNumber] easily:

[ Number 1, Number (2::Int), Number (3::Double) ]

Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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, though, the two typos in your example, which should read instead:

data ExistsNumber where
Number :: forall a. Num a = a - ExistsNumber

Kalman
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe