[Haskell-cafe] Re: Interval Arithmetics

2007-08-19 Thread Henning Thielemann
The page http://www.haskell.org/haskellwiki/Applications_and_libraries/Mathematics#Number_representations lists several implementations of several flavours of computable reals, which may be useful for you. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Generic data constructor in pattern?

2007-08-21 Thread Henning Thielemann
On Tue, 21 Aug 2007, Peter Verswyvelen wrote: Consider the following example code: data Vector = V Float Float data Matrix = M Vector Vector liftV1 f (V x y) = V (f x) (f y) liftV2 f (V x1 y1) (V x2 y2) = V (f x1 x2) (f y1 y2) liftM1 f (M x y) = M (f x) (f

RE: [Haskell-cafe] Yet another stupid question about numeric conversion

2007-08-22 Thread Henning Thielemann
On Tue, 21 Aug 2007, Peter Verswyvelen wrote: Yes indeed, I realized that. I oversimplified my question. I'm basically trying to model 4D CG/HLSL operations (pixel/vertex shaders) in Haskell. I tried realToFrac, but that did not work. Then I tried splitting the instances into Fractional and

Re: [Haskell-cafe] Style

2007-08-24 Thread Henning Thielemann
On Fri, 24 Aug 2007, Arie Groeneveld wrote: I defined several functions for calculating the number of trailing zero's of n! tm = sum . takeWhile(0) . iterate f . f where f = flip div 5 This is very elegant! You could also inline 'f' tm4 = sum . takeWhile(0) . tail . iterate (flip div 5)

Re: [Haskell-cafe] Text.Xhtml.Strict

2007-08-26 Thread Henning Thielemann
On Sat, 25 Aug 2007, Marco Túlio Gontijo e Silva wrote: Hello there. I don't know if it's off topic, but I don't know where else to ask. I've been using Text.Xhtml.Strict, and I'm wondering why the functions are mostly Html - Html and not HTML a = a - Html, or something similar. If they were

Re: [Haskell-cafe] Ideas

2007-08-26 Thread Henning Thielemann
On Sat, 25 Aug 2007, Andrew Coppin wrote: Would be nice if I could build something in Haskell that overcomes these. OTOH, does Haskell have any way to talk to the audio hardware? Maybe a JACK interface? http://haskell.org/haskellwiki/Applications_and_libraries/Music_and_sound

Re: [Haskell-cafe] Ideas

2007-08-26 Thread Henning Thielemann
On Sat, 25 Aug 2007, Evan Laforge wrote: Reaktor has a few limitations though. 1. It's virtually impossible to debug the thing! (I.e., if your synth doesn't work... good luck working out why.) 2. It lacks looping capabilities. For example, you cannot build a variable-size convolution block -

[Haskell-cafe] Audio output (Was: Re: Ideas)

2007-08-26 Thread Henning Thielemann
On Sat, 25 Aug 2007, Andrew Coppin wrote: Evan Laforge wrote: To get this back to haskell, at the time I wondered if a more natural implementation might be possible in haskell, seeing as it was more naturally lazy. Not sure how to implement the behaviours though (which were simply macros

Re: [Haskell-cafe] Ideas

2007-08-26 Thread Henning Thielemann
On Sat, 25 Aug 2007, Andrew Coppin wrote: How easy would it be to make / would anybody care / has somebody already made ... in Haskell? - An interactive function plotter. (GNUplot is nice, but it can't plot recursive functions...) I'm be interested to use such a library. - A graphical

Re: [Haskell-cafe] Ideas

2007-08-26 Thread Henning Thielemann
On Sun, 26 Aug 2007, Andrew Coppin wrote: The only thing I'm uncertain about is whether it would have good enough time and space performance. All the real work is writing yet another set of basic envelope, oscillator, and fft primitives. You *should* be able to go all the way down to the

RE: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Henning Thielemann
On Thu, 30 Aug 2007, Peter Verswyvelen wrote: infixl 0 \ -- I just took the first weird symbol combination that came to mind, this does not mean anything (I hope ;-) x \ fx = fx x f x = x * scale \ \x - x + transform \ \x - g x like this you don't have to invent new names,

Identifer name style (Was: [Haskell-cafe] let and fixed point operator)

2007-09-03 Thread Henning Thielemann
On Fri, 31 Aug 2007, Brandon S. Allbery KF8NH wrote: On Aug 31, 2007, at 16:01 , Sterling Clover wrote: In particular for a function -- n, m, etc or x, y, etc? What about for f' defined in a let block of f? If I use x y at the top level I need to use another set below -- is that where x'

[Haskell-cafe] Hawiki articles

2007-09-03 Thread Henning Thielemann
In the current Haskell Wiki (haskell.org/haskellwiki) I found references to articles of the old Hawiki (haskell.org/hawiki), like OnceAndOnlyOnce and SeparationOfConcerns. Are the files still available somewhere? ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Extending the idea of a general Num to other types?

2007-09-03 Thread Henning Thielemann
On Mon, 3 Sep 2007, Peter Verswyvelen wrote: Okay. Now the following might not make sense at all, but... isn't the abstract concept of a list just a sequence of elements (okay, with a whole lot of extra properties)? So couldn't we write: do { 1;2;3;4 } instead of [1,2,3,4] somehow for some

Re: [Haskell-cafe] Hawiki articles

2007-09-03 Thread Henning Thielemann
On Mon, 3 Sep 2007, Derek Elkins wrote: On Mon, 2007-09-03 at 14:57 +0200, Henning Thielemann wrote: In the current Haskell Wiki (haskell.org/haskellwiki) I found references to articles of the old Hawiki (haskell.org/hawiki), like OnceAndOnlyOnce and SeparationOfConcerns. Are the files

Re: [Haskell-cafe] Code from Why Functional Programming Matters

2007-09-03 Thread Henning Thielemann
On Mon, 3 Sep 2007, Andrew Wagner wrote: I've been reading the classic Why functional programming matters paper [1] lately, particularly looking at the alpha beta stuff. I've ported all his code to haskell, but I have a question. His algorithm takes a board position, creates a gametree out

Re: [Haskell-cafe] Hawiki articles

2007-09-03 Thread Henning Thielemann
On Tue, 4 Sep 2007, Donald Bruce Stewart wrote: lemming: ... and there was unfortunately no support in porting the stuff. I guess some simple program (perl -p -e 's/{{{/hask/g' :-) could have simplified a lot. Its however more difficult for me to do this via the web interface, than

Re: [Haskell-cafe] Hawiki articles

2007-09-03 Thread Henning Thielemann
On Mon, 3 Sep 2007, Derek Elkins wrote: The issue is that we don't know what the license is for the -content- of HaWiki. HaskellWiki explicitly states that all the content in it has a specific license. We can't take the old content and put it on HaskellWiki because that would imply that it

Re: [Haskell-cafe] Hawiki articles

2007-09-03 Thread Henning Thielemann
On Mon, 3 Sep 2007, Neil Mitchell wrote: 2) Licensing - the old content cannot be dumped onto the new wiki. My personal view is who cares. I like the German phrase Wo kein Kläger, da kein Richter. (no complaint, no redress ?

Re: [Haskell-cafe] About mplus

2007-09-05 Thread Henning Thielemann
On Tue, 4 Sep 2007, David Benbennick wrote: On 9/4/07, ok [EMAIL PROTECTED] wrote: I've been thinking about making a data type an instance of MonadPlus. From the Haddock documentation at haskell.org, I see that any such instance should satisfy mzero `mplus` x = x x `mplus`

Re: [Haskell-cafe] About mplus

2007-09-05 Thread Henning Thielemann
On Wed, 5 Sep 2007, ok wrote: On 5 Sep 2007, at 6:16 pm, Henning Thielemann wrote: I think it is very sensible to define the generalized function in terms of the specific one, not vice versa. The specific point at issue is that I would rather use ++ than `mplus`. In every case where both

[Haskell-cafe] Block-wise lazy sequences in Haskell

2007-09-05 Thread Henning Thielemann
I want to have a data structure like Data.ByteString.Lazy, that is block-wise lazy, but polymorphic. I could use a lazy list of unboxed arrays (UArray) but the documentation says, that the element types are restricted. But I will need (strict) pairs of Double and the like as elements. It

Re: [Haskell-cafe] Block-wise lazy sequences in Haskell

2007-09-05 Thread Henning Thielemann
On Wed, 5 Sep 2007, Bryan O'Sullivan wrote: Henning Thielemann wrote: I thought it must be possible to define an unboxed array type with Storable elements. Yes, this just hasn't been done. There would be a few potentially tricky corners, of course; Storable instances are not required

Re: [Haskell-cafe] numeric types

2007-09-06 Thread Henning Thielemann
On Wed, 5 Sep 2007, Thomas Hartman wrote: I think you want something like this {-# OPTIONS -fglasgow-exts #-} Why glasgow-exts? You may also want to read and extend the discussion generic number type vs. distinct numeric types http://www.haskell.org/haskellwiki/Generic_number_type

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

2007-09-06 Thread Henning Thielemann
On Wed, 5 Sep 2007, Jonathan Cast wrote: On Wed, 2007-09-05 at 20:37 +0200, Henning Thielemann wrote: Can someone explain me, why there are arrays with mutable but boxed elements? I thought that boxing is only needed for lazy evaluation. However if I access an element of an array

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

2007-09-06 Thread Henning Thielemann
On Thu, 6 Sep 2007, Axel Gerstenberger wrote: module Main where import System.IO import Text.Printf main :: IO () main = do let all_results1 = take 2 $ step [1] --print $ length all_results1 -- BTW: if not commented out, -- all values of

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

2007-09-06 Thread Henning Thielemann
On Thu, 6 Sep 2007, Axel Gerstenberger wrote: Thanks to all of you. The suggestions work like a charm. Very nice. I still need to digest the advices, but have already one further question: How would I compute the new value based on the 2 (or even more) last values instead of only the last

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

2007-09-09 Thread Henning Thielemann
On Sun, 9 Sep 2007, Stuart Cook wrote: (Inspired by this[1] reddit thread.) When combining monadic and non-monadic code, I've often wished for a magical combinator of type (Monad m) = ((a - b) - c) - (a - m b) - m c which would let me inject a monadic function into a pure one, then wrap

Re: [Haskell-cafe] Custom unary operator extension?

2007-09-09 Thread Henning Thielemann
On Sun, 9 Sep 2007, Peter Verswyvelen wrote: I find it unfortunate that one can't (I guess) define custom unary operators in Haskell. Why? What is your application? In fact, alphanumeric identifiers are used as unary operators. Is this correct? If so, is this just because eg (* 100)

Re: [Haskell-cafe] zip, map and zipWith for arrays

2007-09-09 Thread Henning Thielemann
On Sun, 9 Sep 2007, Axel Gerstenberger wrote: I am used to work with map, zip and zipWith, when working with lists, however, I could not find such functions for Arrays. Since 'Array' is an instance of Functor you can use 'fmap' for applying a function to all elements. For example, in my

Re: [Haskell-cafe] Custom unary operator extension?

2007-09-09 Thread Henning Thielemann
On Sun, 9 Sep 2007, Peter Verswyvelen wrote: Why? What is your application? In fact, alphanumeric identifiers are used as unary operators. Why? Well, why are binary operators allowed and unary operators not? Isn't that some kind of discrimination? In math, many many operators are unary.

Re: [Haskell-cafe] Custom unary operator extension?

2007-09-10 Thread Henning Thielemann
On Sun, 9 Sep 2007, Peter Verswyvelen wrote: Henning Thielemann wrote: The more syntactic constructs exist, the more complicated it becomes to read such programs. Today, if you read a symbolic operator which is not -, not a single dot with a capital identifier to the left (qualification

Re: [Haskell-cafe] Is take behaving correctly?

2007-09-12 Thread Henning Thielemann
On Wed, 12 Sep 2007, Conor McBride wrote: Hi folks On 12 Sep 2007, at 00:38, Brent Yorgey wrote: On 9/11/07, PR Stanley [EMAIL PROTECTED] wrote: Hi take 1000 [1..3] still yields [1,2,3] I thought it was supposed to return an error. [..] If for some reason you want a version that does

[Haskell-cafe] Re: Is take behaving correctly?

2007-09-12 Thread Henning Thielemann
On Wed, 12 Sep 2007, PR Stanley wrote: I quite like the argument that take is a total function and as such all its return values are from teh specificed range. I can also see the logic in take n [] = [] where n 0 taking n from nothing, or the empty set, returns nothing! The same should apply

Re: [Haskell-cafe] How can I stop GHCi from calling show for IO actions?

2007-09-17 Thread Henning Thielemann
On Sat, 15 Sep 2007, Sam Hughes wrote: That's weird. Prelude (x,y) - return $ (repeat 1, repeat 2) You didn't tell, which Monad this shall be. Prelude Just x - return $ Just (repeat 1) [1,1,1,... Prelude (x,_) - return $ (repeat 1, repeat 2) [1,1,1,... Prelude Just (x,y) - return $ Just

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

2007-09-17 Thread Henning Thielemann
On Sat, 15 Sep 2007, Joachim Breitner wrote: today while mowing the lawn, I thought how to statically prevent some problems with infinte lists. I was wondering if it is possible to somehow mark a list as one of finite/infinite/unknown and to mark list-processing functions as whether they can

Re: [Haskell-cafe] Why isn't pattern matching lazy by default?

2007-09-19 Thread Henning Thielemann
On Wed, 19 Sep 2007, Peter Verswyvelen wrote: I got stuck with an endless loop when trying to split a stream into a pair of two streams (a kind of reactive if/then/else). Luckily I first read the Haskell School of Expression so I remembered that pattern matching is not lazy and this could be

Re: [Haskell-cafe] Why isn't pattern matching lazy by default?

2007-09-19 Thread Henning Thielemann
On Wed, 19 Sep 2007, Miguel Mitrofanov wrote: Now why isn't pattern matching lazy by default? This seems odd for a newbie since everything else is lazy by default. It's even more confusing that pattern matching in 'let' _is_ lazy. No, it's not. See, in let or where constructs you don't

Re: [Haskell-cafe] length defined with foldr

2007-09-20 Thread Henning Thielemann
On Wed, 19 Sep 2007, Stefan O'Rear wrote: On Thu, Sep 20, 2007 at 04:17:54AM +0100, PR Stanley wrote: Hi length = foldr (. n . 1 + n) 0 Any idea how to define length with foldr. The above definition doesn't make much sense. Many thanks, Paul or, in ASCII concrete syntax length = foldr (\_

Re: [Haskell-cafe] Troubles understanding memoization in SOE

2007-09-24 Thread Henning Thielemann
On Sat, 22 Sep 2007, Peter Verswyvelen wrote: Hi, in SOE, the following memoization function is implemented: memo1 :: (a-b) - (a-b) memo1 f = unsafePerformIO $ do cache - newIORef [] return $ \x - unsafePerformIO $ do vals - readIORef cache case x `inCache` vals of

Re: [Haskell-cafe] C's fmod in Haskell

2007-09-24 Thread Henning Thielemann
On Sun, 23 Sep 2007, Thomas Conway wrote: In Prelude there is a function properFraction which splits a RealFrac into its integer part and its fractional part. You can use this to implement fmod. Assuming properFraction is efficient (which it probably isn't), you can implement fmod really quite

Re: [Haskell-cafe] Noob question and sequence of operations (print then do something else)

2007-09-24 Thread Henning Thielemann
On Mon, 24 Sep 2007, John Wicket wrote: I am still in an imperative way of thinking. In this example here; how would I call putStrLn and then set the function with a value. Eg: aa :: String - IO () aa instr = do putStrLn abc putStrLn abc return 123 The article

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

2007-09-24 Thread Henning Thielemann
On Mon, 24 Sep 2007, Vimal wrote: Hi all, I was surprised to find out that the following piece of code: length [1..] 10 isnt lazily evaluated! http://www.haskell.org/haskellwiki/Things_to_avoid#Don.27t_ask_for_the_length_of_a_list_when_you_don.27t_need_it

Re: [Haskell-cafe] C's fmod in Haskell

2007-09-25 Thread Henning Thielemann
On Tue, 25 Sep 2007, ok wrote: On 25 Sep 2007, at 10:55 am, Thomas Conway wrote: This old chestnut! It's a common problem in practice. As I recall, the behaviour of C's % operator allows implementations to yield either behaviour. I just checked ISO 9899:1999 which defines fmod. It specifies

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

2007-09-25 Thread Henning Thielemann
On Mon, 24 Sep 2007, Neil Mitchell wrote: Hi In this world, use length (take 11 [1..]) 10... not (null (drop 10 [1..])) is surely faster (not tested...) Faster? There might be a few microseconds in it. Clearer? Possibly... ;-) lengthNat [1..] 10 Couldn't be clearer, and can be made

Re: [Haskell-cafe] representing differencial equations in haskell

2007-09-25 Thread Henning Thielemann
On Tue, 25 Sep 2007, Thomas Girod wrote: Let's say I have mathematical model composed of several differential equations, such as : di/dt = cos(i) dc/dt = alpha * (i(t) - c(t)) (sorry my maths are really bad, but I hope you get the point) I would like to approximate the evolution of such a

Re: [Haskell-cafe] C's fmod in Haskell

2007-09-26 Thread Henning Thielemann
:58 pm, Henning Thielemann wrote: Why is this particular behaviour useful in connection with trigonometric functions? Range reduction. sin(x) = sin(fmod(x, M_TWOPI)). Whether that is the *best* way to handle range reduction is another matter. This would work with any reasonable definition

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann
On Tue, 25 Sep 2007, Brian Hulley wrote: Jonathan Cast wrote: Of course, this is all a consequence of the well-known failure of natural language: verbs come before their objects. It is thus natural to write f(x), when in fact it is the object that should come first, not the function.

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann
On Tue, 25 Sep 2007, Brian Hulley wrote: To be consistent this would also have to apply to the use of (-) in types to get: a - b === (-) b a Since there are many type class instances for the Reader Monad, in this case the order of argument seems to be appropriate.

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann
On Tue, 25 Sep 2007, Dan Piponi wrote: It's not so clear to me what the syntax for types should be in a postfix language. Postfix, of course! So you'd write data a Tree = Leaf | a a Tree Confusingly, ocaml does something like this, with postfix notation for types and prefix notation for

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann
On Tue, 25 Sep 2007, Brian Hulley wrote: Of course the problem disappears if you just discard multiple clause syntax and use: (list :: a List) (f :: a - b) map :: b List = case list of Empty - Empty h t PushF - (h f) (t f map) PushF This would also have the

Re: [Haskell-cafe] Troubles understanding memoization in SOE

2007-09-26 Thread Henning Thielemann
On Wed, 26 Sep 2007, Peter Verswyvelen wrote: I hope I won't come to the conclusion that after one year learning the cool lazy functional programming language Haskell (which I want to use for making simple videogames in a clean way for teaching), I haven't tested it, but know of the

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-26 Thread Henning Thielemann
On Tue, 25 Sep 2007, Brian Hulley wrote: Ryan Ingram wrote: A couple off the top of my head: (:) :: a - [a] - [a] Yes that's one that had totally slipped my mind ;-) I like to add 'div' and 'mod' as examples for wrong argument order. ___

Re: [Haskell-cafe] Re: Math.Statistics

2007-09-26 Thread Henning Thielemann
On Wed, 26 Sep 2007, apfelmus wrote: ok wrote: I believe the author may have misunderstood numerically stable. The obvious (sum xs)/(fromIntegral $ length $ xs) is fine for the mean, That's probably my fault, out of ignorance. Do you know a good online resource about numeric

Re: [Haskell-cafe] Re: Math.Statistics

2007-09-26 Thread Henning Thielemann
On Wed, 26 Sep 2007, ChrisK wrote: ok wrote: There are a number of interesting issues raised by mbeddoe's Math.Statistics. data (Floating a, Ord a) = Simple_Continuous_Variate a = SCV [a] Int a a (Array Int a) list_to_variate xs = SCV xs n m s o where n = length

Re: [Haskell-cafe] Troubles understanding memoization in SOE

2007-09-26 Thread Henning Thielemann
On Wed, 26 Sep 2007, Don Stewart wrote: And don't forget these three games that got mentioned during the week. Octane Mech: http://berlinbrowndev.blogspot.com/2007/09/octane-mech-opengl-haskell-based-mech.html OpenGL Tetris:

Re: [Haskell-cafe] Packages and how to load them

2007-09-28 Thread Henning Thielemann
On Thu, 27 Sep 2007, bbrown wrote: If I have a set of haskell code and I create a directory with the source that has the following imports. (some_dir/MyLib.hs) module MyLib where And then I want to use that set of code at the top level directory, eg: MyTest.hs import MyLib How would I

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

2007-10-05 Thread Henning Thielemann
On 10/4/07, Don Stewart [EMAIL PROTECTED] wrote: It was raised at CUFP today that while Python has: Python is a dynamic object-oriented programming language that can be used for many kinds of software development. It offers strong support for integration with other languages and

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

2007-10-05 Thread Henning Thielemann
On Fri, 5 Oct 2007, Albert Y. C. Lai wrote: Granted, perhaps your perspective is, if every other company is shouting customers are number one, then ours must too, and who actually lives up to it is the non-sequitur here. You're in the buzzword war, not the evidence war. OK, then make sure

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

2007-10-05 Thread Henning Thielemann
On Fri, 5 Oct 2007, Laurent Deniau wrote: Henning Thielemann wrote: Productivity, robustness, maintainability: purity, type system, etc. Parallelism! 'type system' is something where C derivatives and scripting languages are weak - but their users count this as advantage. Rarely

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

2007-10-05 Thread Henning Thielemann
On Fri, 5 Oct 2007, Laurent Deniau wrote: Henning Thielemann wrote: I know that C programmers also like the concise/cryptic/inconsistent syntax. Syntax is often a matter of taste. Every languages look cryptic for unfamiliar people. Haskell has itself some conventions in notation which

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

2007-10-08 Thread Henning Thielemann
On Mon, 8 Oct 2007, Alistair Bayley wrote: I posed the question: do we want to attract this kind of programmer? My personal opinion, which some of you obviously don't share, is yes. It isn't about whether or not the Haskell community needs those sorts of programmers. It's whether or not those

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

2007-10-08 Thread Henning Thielemann
On Mon, 8 Oct 2007, Alistair Bayley wrote: On 08/10/2007, Henning Thielemann [EMAIL PROTECTED] wrote: You cannot turn any programmer into a disciplined programmer just by giving him a well designed language. I you try so, they will not like to use that language, will leave that language

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

2007-10-09 Thread Henning Thielemann
On Mon, 8 Oct 2007, Derek Elkins wrote: On Mon, 2007-10-08 at 20:54 +1000, Thomas Conway wrote: I must say, I get that! but at the same time, of course, the high level abstraction is exactly what *we* love about Haskell. Then they should teach assembly not Python. In fact, I'd recommend

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

2007-10-09 Thread Henning Thielemann
On Tue, 9 Oct 2007, Alex Tarkovsky wrote: Brent Yorgey wrote: Aren't you going to make one featuring a catamorphism? =) Done, thanks for the contribution! ;) I wish concat or concatMap :-) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] pi

2007-10-10 Thread Henning Thielemann
On Wed, 10 Oct 2007, Yitzchak Gale wrote: Dan Piponi wrote: The reusability of Num varies inversely with how many assumptions you make about it. A default implementation of pi would only increase usability, not decrease it. As the others have shown, you can compute PI in many ways. Which

Re: [Haskell-cafe] Re: pi

2007-10-10 Thread Henning Thielemann
On Wed, 10 Oct 2007, David Roundy wrote: On Wed, Oct 10, 2007 at 12:29:07PM +0200, [EMAIL PROTECTED] wrote: ChrisK writes: There are two things in Floating, the power function (**) [ and sqrt ] and the transcendental functions (trig functions,exp and log, and constant pi). Floating could be

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

2007-10-10 Thread Henning Thielemann
On Tue, 9 Oct 2007, Seth Gordon wrote: Henning Thielemann wrote: In my experience only the other way round works: Let people use C, Perl and Python until they find their programs unmaintainable. Then they will become interested in style and discipline and programming languages which

Re: [Haskell-cafe] Re: pi

2007-10-10 Thread Henning Thielemann
On Wed, 10 Oct 2007, Henning Thielemann wrote: (**) should not exist, because there is no sensible definition for many operands for real numbers, and it becomes even worse for complex numbers. The more general the exponent, the more restricted is the basis and vice versa in order to get

Re: [Haskell-cafe] Re: pi

2007-10-10 Thread Henning Thielemann
On Wed, 10 Oct 2007, David Roundy wrote: On Wed, Oct 10, 2007 at 08:53:22PM +0200, Henning Thielemann wrote: On Wed, 10 Oct 2007, David Roundy wrote: It seems that you're arguing that (**) is placed in the correct class, since it's with the transcendental functions, and is implemented

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

2007-10-11 Thread Henning Thielemann
On Wed, 10 Oct 2007, Seth Gordon wrote: Aha! Instead of the lambda surrounded by mathematical stuff as the haskell.org logo, we need a picture of a medicine bottle. Haskell. Fewer headaches. No side effects. Alternatively, a picture of a red pill with an embossed lambda... A snake

Re: [Haskell-cafe] Re: Type Synonyms

2007-10-11 Thread Henning Thielemann
On Thu, 11 Oct 2007, Tom Davies wrote: Andrew Wagner wagner.andrew at gmail.com writes: If you change your type declarations to 'newtype' declarations, I believe you would get the effect that you want, depending on what you mean by 'equivalent'. In that case, Foo and Bar would essentially be

Re: [Haskell-cafe] do

2007-10-13 Thread Henning Thielemann
On Sat, 13 Oct 2007, PR Stanley wrote: Hi do, what's its role? I know a few uses for it but can't quite understand the semantics - e.g. do putStrLn bla bla So, what does do, do? It's syntactic sugar. http://www.haskell.org/onlinereport/exps.html#sect3.14

Re: [Haskell-cafe] Filesystem questions

2007-10-13 Thread Henning Thielemann
On Sat, 13 Oct 2007, Yitzchak Gale wrote: Andrew Coppin wrote: Is there a way to get rid of . and .. in the results? Brandon S. Allbery wrote: Manual filtering is always required, whether C, Perl, Haskell, etc. I dunno, maybe python filters them for you or something. Correct, Python

Re: [Haskell-cafe] do

2007-10-13 Thread Henning Thielemann
On Sat, 13 Oct 2007, Henning Thielemann wrote: On Sat, 13 Oct 2007, PR Stanley wrote: Hi do, what's its role? I know a few uses for it but can't quite understand the semantics - e.g. do putStrLn bla bla So, what does do, do? It's syntactic sugar. http://www.haskell.org/onlinereport

Re: [Haskell-cafe] Filesystem questions

2007-10-14 Thread Henning Thielemann
On Sun, 14 Oct 2007, Bryan O'Sullivan wrote: Yitzchak Gale wrote: I do think that it is much better to provide IO laziness using monad transformers (or whatever) rather than unsafe IO. That's fair enough. I think it would be great if you were to turn your ideas into a library and provide

RE: [Haskell-cafe] do

2007-10-15 Thread Henning Thielemann
On Mon, 15 Oct 2007, Peter Verswyvelen wrote: Actually I stopped bothering long ago about 'understanding monads'. I think that's a shame, because when I wrote the source code myself to get from a pure functional approach (passing the object from function to function as an extra argument) to

Re: [Haskell-cafe] Java - Haskell adjustment

2007-10-15 Thread Henning Thielemann
On Mon, 15 Oct 2007, Ryan Bloor wrote: Hi, its Ryan here... I've just come from an intensive course in java and have been thrown into the imperative world of haskell. The problem that I have is extremely simple in java but I am having trouble adjusting my old mindset. A multiset is a

Re: [Haskell-cafe] Haskell libraries for computer vision

2007-10-16 Thread Henning Thielemann
On Mon, 15 Oct 2007, Don Stewart wrote: http://alberrto.googlepages.com/easyvision An experimental Haskell system for fast prototyping of computer vision and image processing applications. Looks ridiculously cool. Image processing with Haskell - really interesting. I know of

Re: [Haskell-cafe] Strange subtract operator behavior

2007-10-17 Thread Henning Thielemann
On Tue, 16 Oct 2007, Peter Verswyvelen wrote: Concurrent Clean uses the ~ symbol for unary negation. That's also a way of fixing it. Personally I could also live with allowing no space between the minus sign and the number... If you leave a space, - becomes the subtract operator. Me

Re: [Haskell-cafe] Do you trust Wikipedia?

2007-10-19 Thread Henning Thielemann
On Fri, 19 Oct 2007, Jules Bean wrote: [EMAIL PROTECTED] wrote: *PLEASE*, show me untrustworthy Wikipedia pages. Any article on a disputed territory or open political dispute. Most articles on a controversial philosophy. Many articles on living people. Articles on controversal topics

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

2007-10-19 Thread Henning Thielemann
On Fri, 19 Oct 2007, 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] After all, sometimes all you need to know about a list is that all the elements support a common set of operations. If

Re: [Haskell-cafe] Re: How much of Haskell was possible 20 years ago?

2007-10-21 Thread Henning Thielemann
On Sun, 21 Oct 2007, [ISO-8859-1] Maurí­cio wrote: Of course. But I think of somethink like a Intel 386 with 4MB of memory. According to The History of Haskell http://www.haskell.org/haskellwiki/History_of_Haskell (early versions of) Haskell could be used on such machines.

Re: [Haskell-cafe] XML parser recommendation?

2007-10-22 Thread Henning Thielemann
On Mon, 22 Oct 2007, Ketil Malde wrote: I'm wondering what approach others use for non-toy XML data. Is the problem due to some error I have made, or should I just ignore the XML, and just parse it manually by dissecting bytestrings, or will another XML library serve better? HXT uses

Re: [Haskell-cafe] ANN: Math.OEIS 0.1

2007-10-22 Thread Henning Thielemann
On Mon, 22 Oct 2007, Brent Yorgey wrote: Hi all, I'm pleased to announce the release of a somewhat silly -- yet perhaps somewhat useful -- library module, Math.OEIShttp://hackage.haskell.org/cgi-bin/hackage-scripts/package/oeis-0.1, intended for the enjoyment of combinatorial dilettantes,

Re: [Haskell-cafe] Local Search Module - Renaissance polyphony

2007-10-22 Thread Henning Thielemann
On Mon, 22 Oct 2007, David F. Place wrote: BTW, the problem I am working on is an automated approach to lifting pieces of Renaissance polyphony from 3-limit to 5-limit Just Intonation. I don't understand this sentence, but it sounds like Music processing, which I'm interested in. (See

Re: [Haskell-cafe] Binary constants in Haskell

2007-10-25 Thread Henning Thielemann
On Thu, 25 Oct 2007, Don Stewart wrote: claus.reinke: how about using ghc's new overloaded strings for this? 10111011::Binary there used to be a way to link to ghc head's docs, but i can't find it right now. the test is

Re: [Haskell-cafe] Binary constants in Haskell

2007-10-25 Thread Henning Thielemann
On Thu, 25 Oct 2007, Stefan O'Rear wrote: On Thu, Oct 25, 2007 at 02:40:36PM +0200, Josef Svenningsson wrote: On 10/24/07, Neil Mitchell [EMAIL PROTECTED] wrote: You can get pretty close with existing Haskell though: (bin 100010011) where bin :: Integer - Integer, and is

Re: [Haskell-cafe] Binary constants in Haskell

2007-10-25 Thread Henning Thielemann
On Thu, 25 Oct 2007, Stefan O'Rear wrote: On Thu, Oct 25, 2007 at 09:41:27PM +0200, Henning Thielemann wrote: Total functions, full laziness, and compile time evaluation of finite non-bottom CAFs... If I write a program that approximates a big but fixed number of digits of Pi - how

Re: [Haskell-cafe] Haskell to math

2007-10-26 Thread Henning Thielemann
On Fri, 26 Oct 2007, Peter Verswyvelen wrote: Some packages like Open Office and Microsoft Word contain a math expression writer. The same can be done with Maple, etc. Standard formats such as MathML, LaTex etc exist. Now what I would like to do, is to create a mathematical expression in

Re: [Haskell-cafe] placing modules in the module hierarchy

2007-10-29 Thread Henning Thielemann
On Mon, 29 Oct 2007, Dimitry Golubovsky wrote: So, I'd suggest for the Grapefruit library: whatever is specific to this library, goes under Graphics.UI.Grapefruit. Whatever may be commonly used elsewhere (say some useful data structures) might go under Data. So, if FRP signals are usable

[Haskell-cafe] Letting the darcs test fail, if QuickCheck tests fail

2007-10-30 Thread Henning Thielemann
When following the description on http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program#Add_some_automated_testing:_QuickCheck then darcs will run the QuickCheck tests on each 'darcs record', but the new patch is also accepted by darcs if one of the tests fail. What is the most

Re: [Haskell-cafe] Type inference problem with division (/)

2007-10-31 Thread Henning Thielemann
On Tue, 30 Oct 2007, noa wrote: I have the following function: theRemainder :: [String] - [String] - Double theRemainder xs xt = sum( map additional (unique xs) ) where additional x = poccur * (inf [ppos,pneg]) --inf takes [Double] where xsxt = zip

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-10-31 Thread Henning Thielemann
On Wed, 31 Oct 2007, Dan Piponi wrote: But every day, while coding at work (in C++), I see situations where true partial evaluation would give a big performance payoff, and yet there are so few languages that natively support it. Of course it would require part of the compiler to be present

Re: [Haskell-cafe] using an external application

2007-11-02 Thread Henning Thielemann
On Fri, 2 Nov 2007, Petr Hoffmann wrote: Hi, I'm solving the following problem - I need to use an external application - give it the input data and receive its output. However, when multiple calls are made, the results are not as expected. The simplified version of the problem is given

Re: [Haskell-cafe] using an external application

2007-11-02 Thread Henning Thielemann
On Fri, 2 Nov 2007, Felipe Lessa wrote: On 11/2/07, Stuart Cook [EMAIL PROTECTED] wrote: The solution would be to use a version of readFile that works in a stricter way, by reading the file when it's told to, but I don't have an implementation handy. I guess this does the job:

[Haskell-cafe] Efficient and type safe flag sets

2007-11-04 Thread Henning Thielemann
We have http://www.haskell.org/haskellwiki/EnumSet_EnumMap Is there also an efficient implementation for bit sets that fit into a machine word? This would be useful for foreign function interfaces. E.g. where C defines #define SND_SEQ_PORT_CAP_READ (10) /** readable from this port

Re: [Haskell-cafe] package maintainers: updating your packages to work with GHC 6.8.1

2007-11-04 Thread Henning Thielemann
On Mon, 5 Nov 2007, Duncan Coutts wrote: If you maintain a Haskell package this is for you. So now that GHC 6.8.1 is out you'll want to test your package with it. We'd especially like maintainers of packages that are distributed on hackage.haskell.org to test their packages and update them

Re: [Haskell-cafe] package maintainers: updating your packages to work with GHC 6.8.1

2007-11-05 Thread Henning Thielemann
Splitting of the base package seems to have invalidated the links from HaskellWiki into the Library documentation. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Is there a module for multivariate linear regression?

2007-11-06 Thread Henning Thielemann
On Mon, 5 Nov 2007, Lihn, Steve wrote: I am looking for a Haskell module that will do multivariate linear regression. Does someone know which module will do it? That is, the equivalent of Perl's Statistics::Regression.pm.

  1   2   3   4   5   6   7   8   9   10   >