Compiling Haskell on an UltraSparc/NetBSD

2004-11-16 Thread Stephane Bortzmeyer
[Not subscribed to haskell-users so please copy me the answers.] To compile the revision control system Darcs (http://www.darcs.net/), I need Haskell but I'm not myself a Haskell user. My machine is an UltraSparc 10 running NetBSD 1.6.2 userland and 2.0 kernel. There is a package source for

RE: Compiling Haskell on an UltraSparc/NetBSD

2004-11-16 Thread Simon Marlow
On 15 November 2004 21:16, Stephane Bortzmeyer wrote: [Not subscribed to haskell-users so please copy me the answers.] To compile the revision control system Darcs (http://www.darcs.net/), I need Haskell but I'm not myself a Haskell user. My machine is an UltraSparc 10 running NetBSD

RE: [Haskell] package with ghc and ghci

2004-11-16 Thread Simon Marlow
[ moved to [EMAIL PROTECTED] ] On 16 November 2004 07:51, Fred Nicolier wrote: I have some packages for doing signal and image processing stuff. Here is a little test program : \begin{code} module Main where import Hips a = listSignal (1,10) [1..10] b = liftSignals (:+) a a c = fft

[Haskell] Re: Parameterized Show

2004-11-16 Thread George Russell
[EMAIL PROTECTED] wrote (snipped): The running example includes an ORD class -- which is like the Ord class but can be parameterized by a comparison function, so to speak. This is precisely the problem. Rather than being able to use the existing functions, you have to haul around an extra

Re: [Haskell] Re: Parameterized Show

2004-11-16 Thread George Russell
Ben Rudiak-Gould wrote (snipped): If more than one dictionary is allowed per type, this correspondence breaks down, and all hell breaks loose as a result. We've already seen this happen with implicit parameters. In a program with implicit parameters: * Beta conversion no longer preserves

Re: [Haskell] Re: Parameterized Show

2004-11-16 Thread Lennart Augustsson
George Russell wrote: Since it hasn't been mentioned yet I should also point people once again to Functional Pearl: Implicit Configurations by Oleg and Chung-chieh Shan, which ingeniously uses polymorphic recursion to construct type class instances at run time. If there's a safe and sane way to

Re: [Haskell] Re: Parameterized Show

2004-11-16 Thread Ben Rudiak-Gould
George Russell wrote: Sorry, but I like implicit parameters, I use them, and I'm not going to stop using them because beta conversion no longer preserves semantics. You'll find that many people here don't agree with this view in general (though there's been surprisingly little backlash against

[Haskell] Unnamed fields

2004-11-16 Thread Ian Lynagh
Hi all, Is there a good reason why I can't say data Bar = Bar { _ :: Int, _ :: Char, x :: Bool } ? (Or data Bar = Bar { Int, Char, x :: Bool } if you prefer, but that's susceptible to typos of the x, y, z :: Int syntax causing confusion). I have a large datastructure in which there is one

Re: [Haskell] Unnamed fields

2004-11-16 Thread Martin Sjögren
On Tue, 16 Nov 2004 15:04:02 +, Ian Lynagh [EMAIL PROTECTED] wrote: Hi all, Is there a good reason why I can't say data Bar = Bar { _ :: Int, _ :: Char, x :: Bool } ? (Or data Bar = Bar { Int, Char, x :: Bool } if you prefer, but that's susceptible to typos of the x, y, z ::

Re: [Haskell] Unnamed fields

2004-11-16 Thread Malcolm Wallace
On Tue, 16 Nov 2004 15:04:02 +, Ian Lynagh [EMAIL PROTECTED] wrote: Is there a good reason why I can't say data Bar = Bar { _ :: Int, _ :: Char, x :: Bool } Since you only want one field out of many, what is the difficulty in simply defining the projection/updating functions

Re: [Haskell] Unnamed fields

2004-11-16 Thread Ben Rudiak-Gould
Martin Sjögren wrote: On Tue, 16 Nov 2004 15:04:02 +, Ian Lynagh [EMAIL PROTECTED] wrote: Hi all, Is there a good reason why I can't say data Bar = Bar { _ :: Int, _ :: Char, x :: Bool } ? I agree that it would be useful, but wouldn't data Bar = Bar Int Char { x :: Bool } make more

[Haskell] Re: Parameterized Show

2004-11-16 Thread Chung-chieh Shan
George Russell [EMAIL PROTECTED] wrote in article [EMAIL PROTECTED] in gmane.comp.lang.haskell.general: Ken Shan's paper, the above and the following messages http://www.haskell.org/pipermail/haskell/2004-September/014515.html argue that Haskell already has the full power of Standard

Re: [Haskell] Unnamed fields

2004-11-16 Thread Ian Lynagh
On Tue, Nov 16, 2004 at 04:07:48PM +, Malcolm Wallace wrote: On Tue, 16 Nov 2004 15:04:02 +, Ian Lynagh [EMAIL PROTECTED] wrote: Is there a good reason why I can't say data Bar = Bar { _ :: Int, _ :: Char, x :: Bool } In case it wasn't clear, there is an x :: Bool in lots

Re: [Haskell-cafe] Pure Haskell Printf

2004-11-16 Thread Henning Thielemann
On Mon, 15 Nov 2004, John Goerzen wrote: Here are some examples: vsprintf Hello Hello vsprintf Hello, %s\n John Hello, John\n vsprintf %s, your age is %d\n John (10::Integer) John, your age is 10\n sprintfAL %(name)s, your age is %(age)d\n [(name, v John), (age, v

[Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Peter Simons
Henning Thielemann writes: Variable length argument lists are really a mess. Why are people so keen on them? One advantage is that you need to type fewer characters. It's, well, not _that_ important, I'll readily admit. :-) But vsnprintf i = %d;\tj = %s 12 test is more compact than any

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Henning Thielemann
On 16 Nov 2004, Peter Simons wrote: Henning Thielemann writes: Variable length argument lists are really a mess. Why are people so keen on them? One advantage is that you need to type fewer characters. I know memory is expensive, that's why only the last two digits of year numbers

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Keean Schupke
At the risk of getting off topic... the reason 'C' has printf is because it is not polymorphic. Printf is a hack to allow different types to be printed out, such that they did not need printInt, printFloat etc. Remember C is typesafe, so the only way they could do this was to pass the first

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Andreas Rossberg
Keean Schupke wrote: Remember C is typesafe In which parallel universe? -- Andreas Rossberg, [EMAIL PROTECTED] Let's get rid of those possible thingies! -- TB ___ Haskell-Cafe mailing list [EMAIL PROTECTED]

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Jon Fairbairn
On 2004-11-16 at 11:42+0100 Peter Simons wrote: Henning Thielemann writes: One advantage is that you need to type fewer characters. I know memory is expensive, that's why only the last two digits of year numbers are stored. :-] I understand what you're getting at -- and I find it

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Keean Schupke
Andreas Rossberg wrote: Keean Schupke wrote: Remember C is typesafe In which parallel universe? I of course meant strongly-typed, you cannot pass a pointer to an int where a pointer to a float is required ... modern C compilers require you to explicitly cast. Where it fell down was all that

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Keean Schupke
Actually it can be statically checked, as the string is a constant, we can lift it to a type (at the moment we would have to use template haskell - but there is no reason the compiler cannot be a little more aggresive in applying functions to constants at compile time, in which case we can use

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread David Roundy
On Tue, Nov 16, 2004 at 12:21:41PM +0100, Henning Thielemann wrote: The function MissingH.Printf.sprintf is probably the better choice, but one could even replace [Value] by [String]. The conversion from any type to String can be easily done using 'show' by the caller. Though it gives the

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Ben Rudiak-Gould
Keean Schupke wrote: At the risk of getting off topic... the reason 'C' has printf is because it is not polymorphic. Printf is a hack to allow different types to be printed out, such that they did not need printInt, printFloat etc. Many language have printf-like functions despite not satisfying

[Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Peter Simons
Jon Fairbairn writes: vsprintf %d, your age is %s\n John (10::Integer) is type incorrect, but won't be reported at compile time. Hmmm. Right. You'd need Template Haskell for that. I see. Peter ___ Haskell-Cafe mailing list [EMAIL PROTECTED]

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Matthew Walton
Ben Rudiak-Gould wrote: Keean Schupke wrote: At the risk of getting off topic... the reason 'C' has printf is because it is not polymorphic. Printf is a hack to allow different types to be printed out, such that they did not need printInt, printFloat etc. Many language have printf-like

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Andreas Rossberg
Keean Schupke wrote: I of course meant strongly-typed, you cannot pass a pointer to an int where a pointer to a float is required ... modern C compilers require you to explicitly cast. According to the C standard, void f(float *p) { *p + 1.0; } void g(void *p) { f(p); } void h(int n) {

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread MR K P SCHUPKE
Of course you can do intertationalisation with show... There is a paper on using type classes to define implicit confugurations, perhasps someone can provide the reference? This can be used to nicely redefine show... Ill see if I cant dig out an example. Keean.

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Scott Turner
On 2004 November 16 Tuesday 06:42, Jérémy Bobbio wrote: There is a probleme with ShowS though: it is not internationalizable at all. Strings like printf's or with any kind of variable substitution is required for proper internationalization / localization. Printf is not adequate for

[Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread John Goerzen
On 2004-11-16, Henning Thielemann [EMAIL PROTECTED] wrote: On 16 Nov 2004, Peter Simons wrote: Yes and no. It can't be checked statically if the number of placeholders matches the number of arguments. It can't be checked statically if the types of placeholders match the types of arguments. It

[Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread John Goerzen
On 2004-11-16, Peter Simons [EMAIL PROTECTED] wrote: I know memory is expensive, that's why only the last two digits of year numbers are stored. :-] I understand what you're getting at -- and I find it annoying, too, when people sacrifice robustness for comfort. In this particular case,

[Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread John Goerzen
On 2004-11-16, Jon Fairbairn [EMAIL PROTECTED] wrote: On 2004-11-16 at 11:42+0100 Peter Simons wrote: I'm not sure, though, whether this is the case here, because vsnprintf in Haskell still is type-safe. Not statically, though, surely? vsprintf %d, your age is %s\n John (10::Integer) is

Re: [Haskell-cafe] Re: Pure Haskell Printf

2004-11-16 Thread Keith Wansbrough
On 2004 November 16 Tuesday 06:42, Jérémy Bobbio wrote: There is a probleme with ShowS though: it is not internationalizable at all. Strings like printf's or with any kind of variable substitution is required for proper internationalization / localization. Printf is not adequate for