Re: [Haskell-cafe] Features of Haskell

2006-06-04 Thread Dylan Thurston
Audrey > I think he managed to explain very effectively what made Haskell ^^ she Peace, Dylan Thurston signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org htt

Re: [Haskell-cafe] Re: Proposal for restructuring Number classes

2006-04-17 Thread Dylan Thurston
with the Kiselyov-Shan approach to dependent types? Does it look too bizarre? http://okmij.org/ftp/Haskell/types.html#Prepose http://okmij.org/ftp/Haskell/number-parameterized-types.html Peace, Dylan Thurston signature.asc Description: Digital

Re: [Haskell-cafe] Proposal for restructuring Number classes

2006-04-17 Thread Dylan Thurston
ntioned this in his response. To implement modular arithmetic with these signatures, as far as I know, you need to either separate Zero constructors or do something like the Kiselyov-Shan paper. (See, e.g., Frederick Eaton's linear algebra library recently posted to the Haskell list.) Peace,

Re: [Haskell-cafe] Re: Positive integers

2006-03-27 Thread Dylan Thurston
On Mon, Mar 27, 2006 at 05:02:20AM -0800, John Meacham wrote: > well, in interfaces you are going to end up with some specific class or > another concretely mentioned in your type signatures, which means you > can't interact with code that only knows about the alternate class. like > > genericLeng

Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Dylan Thurston
On Wed, Jan 04, 2006 at 03:02:29AM +0100, Sebastian Sylvan wrote: > I took a stab at the rev-comp one due to boredom. It's not a space > leak, believe it or not, it's *by design*... > > My god, I think someone is consciously trying to sabotage Haskell's > reputation! > > Instead of reading input

Re: [Haskell-cafe] Project postmortem II /Haskell vs. Erlang/

2006-01-03 Thread Dylan Thurston
On Sun, Jan 01, 2006 at 11:12:31PM +, Joel Reymont wrote: > Simon, > > Please see this post for an extended reply: > > http://wagerlabs.com/articles/2006/01/01/haskell-vs-erlang-reloaded Looking at this code, I wonder if there are better ways to express what you really want using static typi

Re: [Haskell-cafe] Functions with side-effects?

2005-12-26 Thread Dylan Thurston
On Wed, Dec 21, 2005 at 11:43:42AM +, Daniel Carrera wrote: > Hi all, > > I'm a Haskell newbie and I don't really understand how Haskell deals > with functions that really must have side-effects. Like a rand() > function or getLine(). > > I know this has something to do with monads, but I d

Re: [Haskell-cafe] Data types and Haskell classes

2005-05-18 Thread Dylan Thurston
On Tue, May 17, 2005 at 01:13:17PM +0200, Jens Blanck wrote: > > > How would I introduce number classes that are extended with plus and > > > minus infinity? I'd like to have polymorphism over these new classes, > > > something like a signature > > > > > > f :: (Real a, Extended a b) => b -> b > >

Re: [Haskell-cafe] Re: mathematical notation and functional programming

2005-02-05 Thread Dylan Thurston
On Fri, Feb 04, 2005 at 03:08:51PM +0100, Henning Thielemann wrote: > On Thu, 3 Feb 2005, Dylan Thurston wrote: > > >On Fri, Jan 28, 2005 at 08:16:59PM +0100, Henning Thielemann wrote: > > > >>>>O(n) > >>>> which sho

Re: [Haskell-cafe] Re: mathematical notation and functional programming

2005-02-05 Thread Dylan Thurston
of a set. Do you mean that? > > On Thu, Feb 03, 2005 at 08:16:49PM -0500, Dylan Thurston wrote: > > I think this is the only reasonable generalization from the > > established usage of, e.g., 2^(O(n)). In practice, this means that > > 1/O(n^2) is the set of functions

Re: [Haskell-cafe] Re: mathematical notation and functional programming

2005-02-04 Thread Dylan Thurston
(Resurrecting a somewhat old thread...) On Fri, Jan 28, 2005 at 08:16:59PM +0100, Henning Thielemann wrote: > On Fri, 28 Jan 2005, Chung-chieh Shan wrote: > > But I would hesitate with some of your examples, because they may simply > > illustrate that mathematical notation is a language with side

Re: [Haskell-cafe] foldlWhile

2004-11-20 Thread Dylan Thurston
On Sat, Nov 20, 2004 at 03:48:23PM +, Jorge Adriano Aires wrote: > > On Sat, Nov 20, 2004 at 12:47:58PM +0300, Serge D. Mechveliani wrote: > > > foldlWhile :: (a -> b -> a) -> (a -> Bool) -> a -> [b] -> a > > > foldlWhilefp abs = > > > case > > >

Re: [Haskell-cafe] foldlWhile

2004-11-20 Thread Dylan Thurston
On Sat, Nov 20, 2004 at 12:47:58PM +0300, Serge D. Mechveliani wrote: > Is such a function familia to the Haskell users? > > foldlWhile :: (a -> b -> a) -> (a -> Bool) -> a -> [b] -> a > foldlWhilefp abs = > case > (bs, p a) > of > ([],

Re: [Haskell-cafe] Re: Double -> CDouble, realToFrac doesn't work

2004-11-05 Thread Dylan Thurston
On Fri, Nov 05, 2004 at 02:53:01PM +, MR K P SCHUPKE wrote: > >My guess is because irrationals can't be represented on a discrete computer > > Well, call it arbitrary precision floating point then. Having built in > Integer support, it does seem odd only having Float/Double/Rational... There

[Haskell-cafe] Re: Double -> CDouble, realToFrac doesn't work

2004-11-05 Thread Dylan Thurston
On Thu, Nov 04, 2004 at 08:32:52PM +0100, Sven Panne wrote: > It's an old thread, but nothing has really happened yet, so I'd like to > restate and expand the question: What should the behaviour of toRational, > fromRational, and decodeFloat for NaN and +/-Infinity be? Even if the report > is uncle

Re: [Haskell-cafe] strictness and the simple continued fraction

2004-10-12 Thread Dylan Thurston
On Mon, Oct 11, 2004 at 09:53:16PM -0400, Scott Turner wrote: > Evenutally I realized that calculating with lazy lists is not as > smooth as you might expect. For example, the square root of 2 has a > simple representation as a lazy continued fraction, but if you > multiply the square root of 2 by

Re: [Haskell-cafe] Strings - why [Char] is not nice

2004-09-20 Thread Dylan Thurston
On Mon, Sep 20, 2004 at 01:11:34PM +0300, Einar Karttunen wrote: > Size > > Handling large amounts of text as haskell strings is currently not > possible as the representation (list of chars) is very inefficient. You know about the PackedString functions, right? http://www.haskell.org/ghc/docs/

Re: [Haskell-cafe] Context for type parameters of type constructors

2004-04-05 Thread Dylan Thurston
On Mon, Apr 05, 2004 at 01:59:18PM +0200, Henning Thielemann wrote: > In addition I separated a class VectorSpacePure from the VectorSpace > class that contains the operations that don't need the scalar type 'a', > i.e. 'zero' and 'add'. I called this class 'Additive' in my old proposal to revam

Re: [Haskell-cafe] Context for type parameters of type constructors

2004-04-03 Thread Dylan Thurston
On Sat, Apr 03, 2004 at 01:35:44PM +0200, Henning Thielemann wrote: > (I like to omit -fallow-undecidable-instances >before knowing what it means) There's a nice section in the GHC user's manual on it. I can't add anything to that. > > -- a classical linear space > > class VectorSpace v a

Re: [Haskell-cafe] Context for type parameters of type constructors

2004-03-29 Thread Dylan Thurston
On Mon, Mar 29, 2004 at 06:00:57PM +0200, Henning Thielemann wrote: > Thus I setup a type constructor VectorSpace > in the following way: > > > module VectorSpace > >where > > > > class VectorSpace v where > >zero :: v a > >add :: v a -> v a -> v a > >scale :: a -> v a -> v a >

Re: [Haskell-cafe] Storing functional values

2004-02-01 Thread Dylan Thurston
On Fri, Jan 30, 2004 at 09:21:58AM -0700, [EMAIL PROTECTED] wrote: > Hi, > > I'm writing a game in Haskell. The game state includes a lot of closures. > For example, if a game object wants to trigger an event at a particular > time, it adds a function (WorldState -> WorldState) to a queue. S

Re: Type design question

2003-07-29 Thread Dylan Thurston
On Mon, Jul 28, 2003 at 03:23:30PM +1000, Andrew J Bromage wrote: > G'day all. > > On Sun, Jul 27, 2003 at 10:36:46PM -0400, Dylan Thurston wrote: > > > However, I would be sure to distinguish between an inner product space > > and a vector space. > > That&#x

Re: Type design question

2003-07-28 Thread Dylan Thurston
On Mon, Jul 28, 2003 at 03:42:11PM +0200, Konrad Hinsen wrote: > On Friday 25 July 2003 21:48, Dylan Thurston wrote: > > > Another approach is to make Universe a multi-parameter type class: > > > > class (RealFrac a, Floating a) => Universe u a | u -> a where > &g

Re: Type design question

2003-07-27 Thread Dylan Thurston
On Mon, Jul 28, 2003 at 11:59:48AM +1000, Andrew J Bromage wrote: > G'day all. > > On Fri, Jul 25, 2003 at 03:48:15PM -0400, Dylan Thurston wrote: > > > Another approach is to make Universe a multi-parameter type class: > > > > class (RealFrac a, Floatin

Re: Type design question

2003-07-25 Thread Dylan Thurston
On Fri, Jul 25, 2003 at 08:31:26AM -0700, Hal Daume wrote: > However, once we fix this, we can see the real problem. Your Universe > class has a method, distanceVector, of type: > > | distanceVector :: Universe u, Floating a => u -> Vector a -> Vector a > -> Vector a > > And here's the problem.

Re: Arrow Classes

2003-07-15 Thread Dylan Thurston
On Tue, Jul 15, 2003 at 01:07:12AM -0700, Ashley Yakeley wrote: > In article <[EMAIL PROTECTED]>, > Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > > > It doesn't provide instances of Num for anything which is already an instance > > of the other classes. And in Haskell 98 they must be de

Costs of a class hierarchy

2003-07-10 Thread Dylan Thurston
On Thu, Jul 10, 2003 at 02:33:25PM +0100, Ross Paterson wrote: > Subclasses in Haskell cover a range of relationships, including this > sense where things in the subclass automatically belong to the superclass. > Other examples include Eq => Ord and Functor vs Monad. In such cases it > would be ha

Re: Naive question on lists of duplicates

2003-06-08 Thread Dylan Thurston
On Sat, Jun 07, 2003 at 08:24:41PM -0500, Stecher, Jack wrote: It sounds like you're on the right track... > > You could get a moderately more efficient implementation by keeping > > the active list as a heap rather than a list. > > I had thought about that, and took the BinomialHeap.hs file from

Re: Naive question on lists of duplicates

2003-06-07 Thread Dylan Thurston
On Thu, Jun 05, 2003 at 08:09:02AM -0500, Stecher, Jack wrote: > I have an exceedingly simple problem to address, and am wondering if > there are relatively straightforward ways to improve the efficiency > of my solution. Was there actually a problem with the efficiency of your first code? > The

Re: infinite (fractional) precision

2002-10-10 Thread Dylan Thurston
s Jerzy Karczmarczuk mentioned, there is really extensive literature on this. It's beautiful stuff. Part of my motivation for revising the numeric parts of the Prelude was to make it possible to implement all this elegantly in Haskell. --Dylan Thurston msg02082/pgp0.pgp Description: PGP signature

Re: Monad Maybe?

2002-09-21 Thread Dylan Thurston
On Sat, Sep 21, 2002 at 12:56:13PM -0700, Russell O'Connor wrote: > -BEGIN PGP SIGNED MESSAGE- > Hash: SHA1 > > [To: [EMAIL PROTECTED]] > > Is there a nicer way of writing the following sort of code? > > case (number g) of > Just n -> Just (show n) > Nothing -> > case (fraction g) o

Re: replacing the Prelude (again)

2002-07-13 Thread Dylan Thurston
On Sat, Jul 13, 2002 at 07:58:19PM +1000, Bernard James POPE wrote: > ... > I'm fond of the idea proposed by Marcin 'Qrczak' Kowalczyk: > >May I propose an alternative way of specifying an alternative Prelude? >Instead of having a command line switch, let's say that 3 always means >Pr

Re: Replacing the Prelude

2002-05-14 Thread Dylan Thurston
tting too hairy; I think I decided that lists and tuples were too deeply intertwined into the language to change cleanly. I'll dig up my old notes and write more, and then maybe write a complete design document and get someone to implement it. --Dylan Thurston msg01674/pgp0.pgp Description: PGP signature

Re: Proper scaling of randoms

2002-05-07 Thread Dylan Thurston
ation. In this case, there is a very simple algorithm: work modulo (s-t+1). scm(n) = (n `rem` (s-t+1)) + s Warning: some, broken, random number generators do not behave well when used like this. Also, although this is as uniform as possible, there is a systematic skew towards the lower

Re: sort inefficiency

2002-04-02 Thread Dylan Thurston
at all. (Suppose, e.g., that comparing two particular elements yields an exception.) It seems to me this is a problem with providing code as specification: you probably fix the details more than you want. Best, Dylan Thurston msg01575/pgp0.pgp Description: PGP signature

Re: Survival of generic-classes in ghc

2002-02-20 Thread Dylan Thurston
On Wed, Feb 20, 2002 at 01:15:36PM -0800, Simon Peyton-Jones wrote: > Another possiblity would be to make the ConCls class look like this > class ConCls c where > name :: String > arity :: Int > ...etc... > > Now we'd have to give an explicit type argument at the ca

Re: newtype/datatype (was efficiency)

2002-01-17 Thread Dylan Thurston
in this setup, the CPO [()->()] has four elements, in a totally ordered CPO; in increasing order, they are undefined const undefined id const () Is it really clear the first two ('undefined' and 'const undefined') are different? Ken says they are observationally equivalent. --Dylan Thurston msg01191/pgp0.pgp Description: PGP signature

Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-15 Thread Dylan Thurston
> sinh operation, for instance. (Complex will be covered by LIA-3.) This sounds like a very interesting standard. I am constantly annoyed by ISO's attempts to hide their standards; one might wonder what the purpose is of having unavailable "standards". Is the content available

Re: UniCode

2001-10-05 Thread Dylan Thurston
. etc. Any program using this library is bound to get confused on Unicode strings. Even before Unicode, there is much functionality missing; for instance, I don't see any way to compare strings using a localized order. Is anyone working on honest support for Unicode, in the form of a r

Re: always new instance?

2001-10-04 Thread Dylan Thurston
kasaki's book. Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: streching storage manager

2001-09-28 Thread Dylan Thurston
GC it away after you are done with it. The downside is that accessing elements within the window will take time O(window size). Are the windows large enough that this is a concern? Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAI

Re: Funny type.

2001-05-27 Thread Dylan Thurston
On Sun, May 27, 2001 at 10:46:37PM -0500, Jay Cox wrote: > >data S m a = Nil | Cons a (m (S m a)) >... > >instance (Show a, Show (m (S m a))) => Show (S m a) where > > show Nil = "Nil" > > show (Cons x y) = "Cons " ++ show x ++ " " ++ show y ... > >show s > >s = Cons 3 [Cons 4 [], Cons 5 [Cons

Re: Implict parameters and monomorphism

2001-05-04 Thread Dylan Thurston
. Are you proposing that variables still be implicitly quantified in top-level bindings, but that elsewhere they have pattern-matching semantics? Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Interesting: "Lisp as a competitive advantage"

2001-05-03 Thread Dylan Thurston
rt' that behaves like this. This is a good example, which cannot be implemented in Haskell. "Exception.assert" is built in to the ghc compiler, rather than being defined within the language. On the other hand, the built in function gives you the source file and line number rather tha

Re: Question about typing

2001-04-08 Thread Dylan Thurston
On Sun, Apr 08, 2001 at 11:34:45AM +, Marcin 'Qrczak' Kowalczyk wrote: > ... > I found a way to express map and zipWith, but it's quite ugly. I would > be happy to have a better way. > > class Map c' a' c a | c' -> a', c -> a, c' a -> c, c a' -> c' where > map :: (a' -> a) -> c' -

Re: Linearity Requirement for Patterns

2001-03-16 Thread Dylan Thurston
rrect? (As opposed to built-in equality for data constructors and characters.) --Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Literate Programming in Haskell?

2001-03-02 Thread Dylan Thurston
let me know. >From my cursory glance, it looked quite interesting, but I was disturbed by the changes required in the TeX source that didn't refer to Haskell at all. Is there any way to improve that situation? Best, Dylan Thurston ___

Re: Primitive types and Prelude shenanigans

2001-02-28 Thread Dylan Thurston
n't honestly say I would use it much (other than for the numeric types) in the near future. Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Primitive types and Prelude shenanigans

2001-02-27 Thread Dylan Thurston
ilers would be able to produce good code in this case. But this would have to be changed: An alternative of the form pat -> exp where decls is treated as shorthand for: pat | True -> exp where decls Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Typing units correctly

2001-02-19 Thread Dylan Thurston
nal and integral exponents, or I want Z/2 torsion? How do I create a new dimension? Is there some function that creates a dimension from a string or some such? What is its type? Can I prevent dimensions from unrelated parts of the program from interfering? Best, Dylan Thurston

Re: Scalable and Continuous

2001-02-17 Thread Dylan Thurston
h one > you want for each type; i.e.: > >instance Fractional MyFraction where > (^) = fractionalPow This is another option. It has the advantage of being explicit and allowing you to choose easily in cases of ambiguity. It is more conservative, but possibly less convenient

Re: Revised numerical prelude, version 0.02

2001-02-14 Thread Dylan Thurston
On Wed, Feb 14, 2001 at 09:53:16PM +, Marcin 'Qrczak' Kowalczyk wrote: > Tue, 13 Feb 2001 18:32:21 -0500, Dylan Thurston <[EMAIL PROTECTED]> pisze: > > Here's a revision of the numerical prelude. > I like it! I'd like to start using something like this

Re: Typing units correctly

2001-02-14 Thread Dylan Thurston
in which case I'd be very interested to > know about it. Incidentally, I went and read your paper just now. Very interesting. You mentioned one problem came up that sounds interesting: to give a nice member of the equivalence class of the principal type. This boils down to picking a nic

Revised numerical prelude, version 0.02

2001-02-13 Thread Dylan Thurston
Added SmallIntegral, SmallReal * wrote skeleton VectorSpace, PowerSeries * Added framework to make it run under hugs. There are some usability issues. Any comments welcome! Best, Dylan Thurston Revisiting the Numeric Classes -- The Prelude for Haskell 98 offers a wel

Re: A sample revised prelude for numeric classes

2001-02-13 Thread Dylan Thurston
onversion or calling a different function (or declaring your own instance). Is this acceptable? I think it might be: after all, you can't multiply a Double by an Integer either... You then have one instance declaration per type, just as for the other classes. Opinions? I'm still not very happy. Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Typing units correctly

2001-02-12 Thread Dylan Thurston
, > and SDL and UML for control parts. The result is likely to be a mess, in > particular when these specifications are to be combined into full system > descriptions. My hope is that you wouldn't need a special version of Haskell. Best, Dylan Thurston __

Re: A sample revised prelude for numeric classes

2001-02-12 Thread Dylan Thurston
of Bool to denote the result of an > attempted comparison. I'm still agnostic on the Poset issue, but as an aside, let me mention that "Maybe Bool" works very well as a trinary logical type. "liftM2 &&" does the correct trinary and, for instance. > On Sun

Re: A sample revised prelude for numeric classes

2001-02-12 Thread Dylan Thurston
On Mon, Feb 12, 2001 at 07:24:31AM +, Marcin 'Qrczak' Kowalczyk wrote: > Sun, 11 Feb 2001 22:27:53 -0500, Dylan Thurston <[EMAIL PROTECTED]> pisze: > > Reading this, it occurred to me that you could explictly declare an > > instance of Powerful Integer Intege

Clean numeric system?

2001-02-12 Thread Dylan Thurston
an numeric class system described yet. Can you send me a pointer to their class system, or just give me a description? Does each operation really have its own class? That seems slightly silly. Are the (/) and 'recip' equivalents independent, and independent of (*) as well? Be

Re: A sample revised prelude for numeric classes

2001-02-12 Thread Dylan Thurston
cannot define, even within the revised Class system, all the > common and useful operations on these types. This is the same situation > as with Haskell as it stands. The question is whether the (IMHO) > marginal increase in flexibility is worth the cost. I believe that with this structure as base, the other common and useful operations can easily be added on top. But I should go ahead and do it. Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: A sample revised prelude for numeric classes

2001-02-11 Thread Dylan Thurston
> ...and Ord defines a partial order > (and hence induces Eq) on a type. I think that "Ord" should define a total ordering; it's certainly what naive users would expect. I would define another class "Poset" with a partial ordering. > (e.g. > instance Ord a => Eq a where > x == y = x <= y && y <= x > ) But to define <= in terms of meet and join you already need Eq! x <= y === meet x y == y Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: A sample revised prelude for numeric classes

2001-02-11 Thread Dylan Thurston
nce contexts remain. Convertible a b should indicate that a can safely be converted to b without losing any information and maintaining relevant structure; from this point of view, its use would be strictly limited. (But what's relevant?) I'm still undecided here. Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

A sample revised prelude for numeric classes

2001-02-11 Thread Dylan Thurston
I've started writing up a more concrete proposal for what I'd like the Prelude to look like in terms of numeric classes. Please find it attached below. It's still a draft and rather incomplete, but please let me know any comments, questions, or suggestions. Best,

Re: Show, Eq not necessary for Num

2001-02-10 Thread Dylan Thurston
that the ordering (from Ord) and the numeric structure (from Num) are compatible. Note also that we cannot require Eq to state laws (the '===' above); consider the laws required for the Monad class to convince yourself. Best, Dylan Thurston __

Semantics of signum

2001-02-10 Thread Dylan Thurston
27;, 'rem', 'div', and 'mod'. For +, -, and * I can guess what identities they should satisfy, but not for signum and abs.) (Note that pointwise abs of functions yields a positive function, which are not ordered but do have a sensible notion of max and min.) Best,

Re: In hoc signo vinces (Was: Revamping the numeric classes)

2001-02-09 Thread Dylan Thurston
d 'one', which do obviously fit (they are the additive and multiplicative units): fromInteger n | n < 0 = negate (fromInteger (-n)) fromInteger n = foldl (+) zero (repeat n one) (Of course, one could use the algorithm in integer exponentiation to make this efficient.) Best, Dy

Re: 'Convertible' class?

2001-02-09 Thread Dylan Thurston
On Fri, Feb 09, 2001 at 12:05:09PM -0500, Dylan Thurston wrote: > On Thu, Feb 08, 2001 at 04:06:24AM +, Marcin 'Qrczak' Kowalczyk wrote: > > You can put Num a in some instance's context, but you can't > > put Convertible Integer a. It's because instan

Re: 'Convertible' class?

2001-02-09 Thread Dylan Thurston
You make some good arguments. Thanks. Let me ask about a few of them. On Thu, Feb 08, 2001 at 04:06:24AM +, Marcin 'Qrczak' Kowalczyk wrote: > Wed, 7 Feb 2001 15:43:59 -0500, Dylan Thurston <[EMAIL PROTECTED]> pisze: > > > class Convertible a b where > >

Re: Show, Eq not necessary for Num [Was: Revamping the numeric c

2001-02-09 Thread Dylan Thurston
gh really they should be part of a more general mechanism for dealing with instances explicitly. Agreed that they might not be useful enough. Best, Dylan Thurston ___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Instances of multiple classes at once

2001-02-08 Thread Dylan Thurston
no textual mention of class Foo in the instance for Bar? Think about the case of a superclass with no methods; wouldn't you want to allow automatic instances in this case? One might even go further and allow a class to declare default methods for a superclass:

Re: Revamping the numeric classes

2001-02-08 Thread Dylan Thurston
Num class and redefined fromDouble, fromInt, etc. Can't you just put "default ()" at the top of each module? I suppose you still have the problem that a numeric literal "5" means "Prelude.fromInteger 5". Can't you define your types to be instances of Prelud

Re: Revamping the numeric classes

2001-02-07 Thread Dylan Thurston
On Wed, Feb 07, 2001 at 01:57:41PM -0500, Dylan Thurston wrote: > ... One point that has not been made: given a class > setup like > > then naive users can continue to use (Num a) in contexts, and the same > programs will continue to work. I take that back. Instance declaratio

Re: Revamping the numeric classes

2001-02-07 Thread Dylan Thurston
istorical: map already existed before Haskell was powerful enough to type fmap, and the decision was not to affect existing programs too much. Presumably Haskell 2 will have them merged. Best, Dylan Thurston ___ Haskell-Cafe mailing lis

Re: Revamping the numeric classes

2001-02-07 Thread Dylan Thurston
hat all types should by instances of Eq and Show? Why are numeric types special? Best, Dylan Thurston Footnotes: [1] Except for the lack of abs and signum, which should be in some other class. I have to think about their semantics before I can say where they belong. ___

(no subject)

2001-02-07 Thread Dylan Thurston
___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe