RE: Haskell Implemetors Meeting

2001-02-08 Thread Simon Peyton-Jones

GHC transforms Haskell into "Core", which is roughly 
the second-order lambda calculus,
augmented with let(rec), case, and constructors.  This is an
a small explicitly-typed intermediate language, in contrast
to Haskell which is a very large, implicitly typed language.
Getting from Haskell to Core is a lot of work, and it might
be useful to be able to re-use that work.

Andrew's proposal (which he'll post to the Haskell list)
will define exactly what "Core" is.

Simon

| -Original Message-
| From: Timothy Docker [mailto:[EMAIL PROTECTED]]
| Sent: 05 February 2001 22:16
| To: [EMAIL PROTECTED]
| Subject: Haskell Implemetors Meeting
| 
| 
| 
|  > We agreed that it would be a Jolly Good Thing if GHC could
|  > be persuaded to produce GHC-independent Core output,
|  > ready to feed into some other compiler.  For example,
|  > Karl-Filip might be able to use it. 
|  > ANDREW will write a specification, and implement it.
| 
| A quick question. What is meant by  "Core output"? Subsequent posts
| seem to suggest this is some "reduced Haskell", in which full Haskell
| 98 can be expressed. Am I completely off beam here?
| 
| Tim Docker
| 
| ___
| Haskell-Cafe mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/haskell-cafe
| 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Brian Boutel

William Lee Irwin III wrote:
> 
> 
> The Standard Prelude serves its purpose well and accommodates the
> largest cross-section of users. Perhaps a Geek Prelude could
> accommodate the few of us who do need these sorts of schenanigans.
> 
>

Amen.

--brian

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Tom Pledger

Marcin 'Qrczak' Kowalczyk writes:
 | On Thu, 8 Feb 2001, Tom Pledger wrote:
 | 
 | > nice answer: give the numeric literal 10 the range type 10..10, which
 | > is defined implicitly and is a subtype of both -128..127 (Int8) and
 | > 0..255 (Word8).
 | 
 | What are the inferred types for
 | f = map (\x -> x+10)
 | g l = l ++ f l
 | ? I hope I can use them as [Int] -> [Int].

f, g :: (Subtype a b, Subtype 10..10 b, Num b) => [a] -> [b]
Yes, because of the substitution {Int/a, Int/b}.

 | > x + y + z -- as above
 | > 
 | > --> (x + y) + z   -- left-associativity of (+)
 | > 
 | > --> realToFrac (x + y) + z-- injection (or treating up) done
 | >   -- conservatively, i.e. only where needed
 | 
 | What does it mean "where needed"? Type inference does not proceed
 | inside-out.

In the expression

(x + y) + z

we know from the explicit type signature (in your question that I was
responding to) that x,y::Int and z::Double.  Type inference does not
need to treat x or y up, because it can take the first (+) to be Int
addition.  However, it must treat the result (x + y) up to the most
specific supertype which can be added to a Double.

 | What about this?
 | h f = f (1::Int) == (2::Int)
 | Can I apply f

h?

 | to a function of type Int->Double?

Yes.

 | If no, then it's a pity, because I could inline it (the comparison
 | would be done on Doubles).  If yes, then what is the inferred type
 | for h? Note that Int->Double is not a subtype of Int->Int, so if h
 | :: (Int->Int)->Bool, then I can't imagine how h can be applied to
 | something :: Int->Double.

There's no explicit type signature for the result of applying f to
(1::Int), so...

h :: (Subtype a b, Subtype Int b, Eq b) => (Int -> a) -> Bool

That can be inferred by following the structure of the term.  Function
terms do seem prone to an accumulation of deferred subtype
constraints.

Regards,
Tom

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: GHC Core Language

2001-02-08 Thread Andrew Tolmach

[moving to haskell-cafe]

> From: matt hellige [mailto:[EMAIL PROTECTED]]
> a quick question re: ghc's Core language... is it still very similar
> to the abstract syntax given in, for example, santos' "compilation by
> transformation..." (i think it was his dissertation?) and 
> elsewhere, or
> has it changed significantly in the last couple of years? i only ask
> because i know the language used in that paper is somewhat 
> different from
> the Core language given in peyton jones and lester's 
> "implementing functional 
> languages" from 92, and includes type annotations and so on.
> 
> m
> 
The current Core language is still quite similar to what is described in
Santos'
work; see

SL Peyton Jones and A Santos,
"A transformation-based optimiser for Haskell,"
Science of Computer Programming 32(1-3), pp3-47, September 1998.
http://research.microsoft.com/Users/simonpj/papers/comp-by-trans-scp.ps.gz

But there have been some noticeable changes; for example, 
function arguments are no longer required to be atomic.
A more recent version of Core is partially described (omitting types) in 

SL Peyton Jones & S Marlowe, 
"Secrets of the Glasgow Haskell Compiler Inliner,"
IDL'99.
http://research.microsoft.com/Users/simonpj/papers/inline.ps.gz

 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: GHC Core output

2001-02-08 Thread Erik Meijer

I would *really* love to see GHC componetized (TM); it would even be better
if it would become easier to use the pieces. I would like to do experiments
on smaller bits of the compiler using Hugs (ideally the whole thing!). When
I was working on the Java/.NET backend I had to rebuild the whole compiler
just to test a few hundred lines of code that translated Core to Java which
is a major pain in the butt; I don't get a kick out of dealing with
installing Cygnus, recursive multi-staged makefiles, cpp, etc.

Erik "do you get a kick out of runnning the marathon with a ball and chain
at your feet?" Meijer

- Original Message -
From: "Andrew Tolmach" <[EMAIL PROTECTED]>
To: "'Timothy Docker'" <[EMAIL PROTECTED]>; <[EMAIL PROTECTED]>
Sent: Tuesday, February 06, 2001 2:53 AM
Subject: RE: GHC Core output


> Timothy Docker [mailto:[EMAIL PROTECTED]] writes:
> >
> >  > We agreed that it would be a Jolly Good Thing if GHC could
> >  > be persuaded to produce GHC-independent Core output,
> >  > ready to feed into some other compiler.  For example,
> >  > Karl-Filip might be able to use it.
> >  > ANDREW will write a specification, and implement it.
> >
> > A quick question. What is meant by  "Core output"? Subsequent posts
> > seem to suggest this is some "reduced Haskell", in which full Haskell
> > 98 can be expressed. Am I completely off beam here?
> >
> Not at all.
> "Core" is an intermediate language used internally by the GHC compiler.
> It does indeed resemble a reduced Haskell (but with explicit higher-order
> polymorphic types) and GHC translates full Haskell 98 into it.
> Currently Core has no rigorously defined external representation, although
> by setting certain compiler flags, one can get a (rather ad-hoc) textual
> representation to be printed at various points in the compilation process.
> (This is usually done to help debug the compiler).
>
> What we hope to do is:
>
> - provide a formal definition of Core's external syntax;
>
> - give a precise definition of its semantics (both static and dynamic);
>
> - modify GHC to produce external Core files, if so requested, at one or
more
> useful points in the compilation sequence -- e.g., just before
optimization,
> or just after.
>
> - modify GHC to accept external Core files in place of Haskell
> source files, again at one or more useful points.
>
> The first three facilities will let one couple GHC's front-end (parser,
> type-checker, etc.), and optionally its optimizer, with new back-end
tools.
> Adding the last facility will let one implement new Core-to-Core
> transformations in an external tool and integrate them into GHC. It will
> also
> allow new front-ends to generate Core that can be fed into GHC's optimizer
> or
> back end; however, because there are many (undocumented)
> idiosynracies in the way GHC produces Core from source Haskell, it will be
> hard
> for an external tool to produce Core that can be integrated with
> GHC-produced core
> (e.g., for the Prelude), and we don't aim to support this.
>
>
>
>
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: GHC Core output

2001-02-08 Thread Andrew Tolmach

Timothy Docker [mailto:[EMAIL PROTECTED]] writes:
> 
>  > We agreed that it would be a Jolly Good Thing if GHC could
>  > be persuaded to produce GHC-independent Core output,
>  > ready to feed into some other compiler.  For example,
>  > Karl-Filip might be able to use it. 
>  > ANDREW will write a specification, and implement it.
> 
> A quick question. What is meant by  "Core output"? Subsequent posts
> seem to suggest this is some "reduced Haskell", in which full Haskell
> 98 can be expressed. Am I completely off beam here?
> 
Not at all.
"Core" is an intermediate language used internally by the GHC compiler.
It does indeed resemble a reduced Haskell (but with explicit higher-order
polymorphic types) and GHC translates full Haskell 98 into it.
Currently Core has no rigorously defined external representation, although 
by setting certain compiler flags, one can get a (rather ad-hoc) textual
representation to be printed at various points in the compilation process.
(This is usually done to help debug the compiler).

What we hope to do is:

- provide a formal definition of Core's external syntax; 

- give a precise definition of its semantics (both static and dynamic);

- modify GHC to produce external Core files, if so requested, at one or more
useful points in the compilation sequence -- e.g., just before optimization,
or just after.

- modify GHC to accept external Core files in place of Haskell 
source files, again at one or more useful points.

The first three facilities will let one couple GHC's front-end (parser,
type-checker, etc.), and optionally its optimizer, with new back-end tools.
Adding the last facility will let one implement new Core-to-Core 
transformations in an external tool and integrate them into GHC. It will
also
allow new front-ends to generate Core that can be fed into GHC's optimizer
or 
back end; however, because there are many (undocumented)
idiosynracies in the way GHC produces Core from source Haskell, it will be
hard
for an external tool to produce Core that can be integrated with
GHC-produced core 
(e.g., for the Prelude), and we don't aim to support this.




___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread William Lee Irwin III

On Thu, Feb 08, 2001 at 08:30:31PM +, Marcin 'Qrczak' Kowalczyk wrote:
> Signum doesn't require Ord.
> signum z = z / abs z
> for complex numbers.

I'd be careful here.

\begin{code}
signum 0 = 0
signum z = z / abs z
\end{code}

This is, perhaps, neither precise nor general enough.

The signum/abs pair seem to represent direction and magnitude.
According to the line of reasoning in some of the earlier posts in this
flamewar, the following constraints:

(1) z = signum z <*> abs z where <*> is appropriately defined
(2) abs $ signum z = 1

should be enforced, if possible, by the type system. This suggests
that for any type having a vector space structure over Fractional
(or whatever the hierarchy you're brewing up uses for rings with
a division partial function on them) that the result type of signum
lives in a more restricted universe, perhaps even one with a different
structure (operations defined on it, set of elements) than the argument
type, and it seems more than possible to parametrize it on the argument
type. The abs is in fact a norm, and the signum projects V^n -> V^n / V.
Attempts to define these things on Gaussian integers, p-adic numbers,
polynomial rings, and rational points on elliptic curves will quickly
reveal limitations of the stock class hierarchy.

Now, whether it's actually desirable to scare newcomers to the language
into math phobia, wetting their pants, and running screaming with
subtleties like this suggests perhaps that one or more "alternative
Preludes" may be desirable to have. There is a standard Prelude, why not
a nonstandard one or two? We have the source. The needs of the geek do
not outweigh the needs of the many. Hence, we can cook up a few Preludes
or so on our own, and certainly if we can tinker enough to spam the list
with counterexamples and suggestions of what we'd like the Prelude to
have, we can compile up a Prelude for ourselves with our "suggested
changes" included and perhaps one day knock together something which can
actually be used and has been tested, no?

The Standard Prelude serves its purpose well and accommodates the
largest cross-section of users. Perhaps a Geek Prelude could
accommodate the few of us who do need these sorts of schenanigans.


Cheers,
Bill
-- 
 Excel/Spreadsheet Q: What is the formula for finding
out the time passed between two dates and or two times in the same day?
 excel/spreadsheet? Hmm, this is math? Is there a GTM on
excel or maybe an article in annals about spreadsheets or maybe
there's a link from wolfram to doing your own computer work, eh?
 jeeem, haven't you seen "Introduction to Algebraic Excel"?
 or "Spreadsheet Space Embeddings in 2-Manifolds"
 i got my phd in spreadsheet theory
 i did my thesis on the spreadsheet conjecture

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-08 Thread Brian Boutel

Patrik Jansson wrote:
>
> On Wed, 7 Feb 2001, Brian Boutel wrote:
> > * Haskell equality is a defined operation, not a primitive, and may not
> > be decidable. It does not always define equivalence classes, because
> > a==a may be Bottom, so what's the problem? It would be a problem,
> > though, to have to explain to a beginner why they can't print the result
> > of a computation.
> 
> The fact that equality can be trivially defined as bottom does not imply
> that it should be a superclass of Num, it only explains that there is an
> ugly way of working around the problem. Neither is the argument that the
> beginner should be able to print the result of a computation a good
> argument for having Show as a superclass.
> 

There is nothing trivial or ugly about a definition that reflects
reality and bottoms only where equality is undefined.

Of course, if you do not need to apply equality to your "numeric" type
then having to define it is a waste of time, but consider this:

- Having a class hierarchy at all (or making any design decision)
implies compromise.
- The current hierarchy (and its predecessors) represent a reasonable
compromise that meets most needs.
- Users have a choice: either work within the class hierarchy and accept
the pain of having to define things you don't need in order to get
the things that come for free, or omit the instance declarationsand
work outside the hierarchy. In that case you will not be able to use the
overloaded operator symbols   of the class, but that is just a matter of
concrete syntax, and ultimately unimportant.

--brian

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

Thu, 08 Feb 2001 11:24:49 +, Jerzy Karczmarczuk <[EMAIL PROTECTED]> pisze:

> The implicit coercion of numeric constants: 3.14 -=->>  (fromDouble
> 3.14) etc. is sick.

What do you propose instead?

(BTW, it's fromRational, to keep arbitrarily large precision.)

> Now, signum and abs seem to be quite distincts beasts. Signum seem
> to require Ord (and a generic zero...).

Signum doesn't require Ord.
signum z = z / abs z
for complex numbers.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

Thu, 8 Feb 2001 21:41:56 +1100, Fergus Henderson <[EMAIL PROTECTED]> pisze:

> Should this define an instance for `foo T'?
> (I think not.)
> 
> How about if the instance declaration is changed to
> 
> instance bar T where
>   f = 41
>   -- no definition for f2
>   b = 42
> 
> ?
> (In that case, I think it should.)

I don't like the idea of treating the case "no explicit definitions
were given because all have default definitions which are OK"
differently than "some explicit definitions were given".

When there is a superclass, it must have an instance defined, so if
we permit such thing at all, I would let it implicitly define all
superclass instances not defined explicitly, or something like that.
At least when all methods have default definitions. Yes, I know that
they can be mutually recursive and thus all will be bottoms...

So maybe there should be a way to specify that default definitions
are cyclic and some of them must be defined? It is usually written
in comments anyway, because it is not immediately visible in the
definitions. If not formally in the language (now any method definition
can be omitted even if it has no default!), then perhaps the compiler
could detect most cases when methods are defined in terms of one
another and give a warning.

Generally the compiler could warn if the programmer has written bottom
in an unusual way. For example
f x = g some_expression
g x = f some_expression
is almost certainly a programmer error.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

Thu, 8 Feb 2001 10:51:58 -0500, Peter Douglass <[EMAIL PROTECTED]> pisze:

> The first part of my question (not contained in your reply) is
> whether it is feasible to disable a developer's access to the
> "unsafe" numerical operations.

import Prelude hiding (quot, rem, (/) {- etc. -})
import YourPrelude -- which defines substitutes

You can "disable" it now. You cannot disable them entirely - anyone can
define present functions in terms of your functions if he really wants.

> Whether or not an individual developer chooses to do so is another
> matter.

Why only quot? There are many other ways to write bottom:
head []
(\(x:xs) -> (x,xs)) []
let x = x in x
log (-1)
asin 2
error "foo"

> If you "know" the value is non-zero before run-time, then that is
> statically determined.

I know but the compiler does not know, and I have no way to convince it.

> It is possible that the developer writes a function which returns a
> nonZeroNumeric value which actually has a value of zero.  However,
> the value of requiring division to have a nonZeroNumeric denominator
> is to catch at compile time the "error" of failing to scrutinize
> (correctly or incorrectly) for zero.

IMHO it would be more painful than useful.

> For most commercial software, the quality of run-time error messages
> is far less important than their absence.

It would not avoid them if the interface does not give a place to
report the error:
average xs = sum xs / case checkZero (length xs) of
Just notZero -> notZero
Nothing  -> error "This should never happen"
is not any more safe than
average xs = sum xs / length xs

and I can report bad input without trouble now:
average xs = case length xs of
0 -> Nothing
l -> Just (sum xs / l)

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

Thu, 08 Feb 2001 15:11:21 +0100 (CET), Elke Kasimir <[EMAIL PROTECTED]> pisze:

> However, what is missing for me is something like:
> 
> type Comfortable a = (Show a, Eq a, Num a) => a
> 
> or
> 
> class (Show a, Read a, Eq a) => Comfortable a
> instance (Show a, Read a, Eq a) => Comfortable a 

I agree and think it should be easy to add.

The latter syntax is nice: obvious what it means, not legal today.
This instance of course conflicts with any other instance of that
class, so it can be recognized and treated specially as a "class
synonym".

> For Haskell, I could imagine (without having having much thought
> about) in addition to the things mentioned in the beginning,
> several things making supporting the  "locally, fast and easy",
> including a mean to define classes with implied memberships, for
> example declarations saying that "Foo is the class of all types in
> scope for which somefoo :: ... is defined", or declarations saying
> that "class Num is locally restricted to all instances of global
> Num which also belong to Eq".

Here I would be more careful. Don't know if local instances or local
classes can be defined to make sense, nor if they could be useful
enough...

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
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

(Superficially irrelevant digression:)

Simon Peyton-Jones came here today and talked about his combinator
library for financial applications, as in his paper "Composing
Contracts".  One of the points he made was that a well-designed
combinator library for financial traders should have combinators that
work on a high level; then, when they want to start writing their own
contracts, they can learn about a somewhat smaller set of building
blocks inside that; then eventually they might learn about the
fundamental building blocks.  (Examples of different levels from the
paper: "european"; "zcb"; "give"; "anytime".)

One theory is that a well-designed class library has the same
property.  But standard Haskell doesn't allow this; that is why I like
the proposal to allow a single instances to simultaneously declare
instances of superclasses.  One problem is how to present the
information on the type hierarchy to users.  (This is a problem in
Haskell anyway; I find myself referring to the source of the Prelude
while writing programs, which seems like a Bad Thing when extrapolated
to larger modules.)

On Thu, Feb 08, 2001 at 09:41:56PM +1100, Fergus Henderson wrote:
> One point that needs to be  resolved is the interaction with default methods.
> 
> Consider
> 
> class foo a where
> f :: ...
>   f = ...
> f2 :: ...
>   f2 = ...
> 
> class (foo a) => bar a where
> b :: ...
>  
> instance bar T where
>   -- no definitions for f or f2
>   b = 42
> 
> Should this define an instance for `foo T'?
> (I think not.)

Whyever not?  Because there is 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:

class Foo a where
   f :: ...

class (Foo a) => Bar a where
   b :: ...
   b = ...
   f = ...

Best,
Dylan Thurston

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Dylan Thurston

On Thu, Feb 08, 2001 at 11:24:49AM +, Jerzy Karczmarczuk wrote:
> First, a general remark which has nothing to do with Num.
> 
> PLEASE WATCH YOUR DESTINATION ADDRESSES
> People send regularly their postings to haskell-cafe with
> several private receiver addresses, which is a bit annoying
> when you click "reply all"...

Yes, apologies.  The way the lists do the headers make it very easy to
reply to individuals, and hard to reply to the list.

> And, last, but very high on my check-list:
> 
> The implicit coercion of numeric constants: 3.14 -=->>  (fromDouble
> 3.14)
> etc. is sick. (Or was; I still didn't install the last version of GHC,
> and with Hugs it is bad). The decision is taken by the compiler
> internally,
> and it doesn't care at all about the fact that in my prelude 
> I have eliminated the 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 Prelude.Num, with no operations defined except Prelude.fromInteger?

> Dylan Thurston terminates his previous posting about Num with:
> 
> > 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.
> 
> Now, signum and abs seem to be quite distincts beasts. Signum seem to
> require Ord (and a generic zero...).
> 
> Abs from the mathematical point of view constitutes a *norm*. Now,
> frankly, I haven't the slightest idea how to cast this concept into
> Haskell class hierarchy in a sufficiently general way...

This was one thing I liked with the Haskell hierarchy: the observation
that "signum" of real numbers is very much like "argument" of complex
numbers.  abs and signum in Haskell satisfy an implicit law:
   abs x * signum x = x  [1]
So signum can be defined anywhere you can define abs (except that it's
not a continuous function, so is not terribly well-defined).  A
default definition for signum x might read
   signum x = let a = abs x in if (a == 0) then 0 else x / abs x
(Possibly signum is the wrong name.  What is the standard name for
this operation for, e.g., matrices?)  [Er, on second thoughts, it's
not as well-defined as I thought.  Abs x needs to be in a field for
the definition above to work.]

> I'll tell you anyway that if you try to "sanitize" the numeric
> classes, if you separate additive structures and the multiplication,
> if you finally define abstract Vectors over some field of scalars,
> and if you demand the existence of a generic normalization for your
> vectors, than *most probably* you will need multiparametric classes
> with dependencies. 

Multiparametric classes, certainly (for Vectors, at least).
Fortunately, they will be in Haskell 2 with high probability.  I'm not
convinced about dependencies yet.

> Jerzy Karczmarczuk
> Caen, France

Best,
Dylan Thurston

Footnotes: 
[1]  I'm not sure what I mean by "=" there, since I do not believe
these should be forced to be instances of Eq.  For clearer cases,
consider the various Monad laws, e.g.,
   join . join = join . map join
(Hope I got that right.)  What does "=" mean there?  Some sort of
denotational equality, I suppose.



___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: Revamping the numeric classes

2001-02-08 Thread Peter Douglass

Marcin Kowalczyk wrote:
> Wed, 7 Feb 2001 16:17:38 -0500, Peter Douglass 
> <[EMAIL PROTECTED]> pisze:
> 
> >  What I have in mind is to remove division by zero as an untypable
> > expression.  The idea is to require div, /, mod to take 
> NonZeroNumeric
> > values in their second argument.  NonZeroNumeric values 
> could be created by
> > functions of type: 
> >   Number a => a -> Maybe NonZeroNumeric
> > or something similar.
> 
> IMHO it would be impractical.
> 

The first part of my question (not contained in your reply) is whether it is
feasible to disable a developer's access to the "unsafe" numerical
operations.  Whether or not an individual developer chooses to do so is
another matter.  

> Often I know that the value is non-zero, but it is not
> statically determined,

If you "know" the value is non-zero before run-time, then that is statically
determined.  Otherwise, you don't "know" that.

> so it would just require uglification by
> doing that conversion and then coercing Maybe NonZeroNumeric to
> NonZeroNumeric.

  Ugliness is in the eye of the beholder I suppose.  For some applications,
every division should be preceded by an explicit test for zero, or the
denominator must be "known" to be non-zero by the way in which it was
created.  Forcing a developer to extract a NonZeroNumeric value from a Maybe
NonZeroNumeric value seems equivalent to me.

> It's bottom anyway when the value is 0, but bottom
> would come from Maybe coercion instead of from quot, so it only gives
> a worse error message.
> 

 It is possible that the developer writes a function which returns a
nonZeroNumeric value which actually has a value of zero.  However, the value
of requiring division to have a nonZeroNumeric denominator is to catch at
compile time the "error" of failing to scrutinize (correctly or incorrectly)
for zero. 
 
  For most commercial software, the quality of run-time error messages is
far less important than their absence.

> It's so easy to define partial functions that it would not buy much
> for making it explicit outside quot.
> 
> Haskell does not have subtypes so a coercion from NonZeroNumeric to
> plain Numbers would have to be explicit as well, even if logically
> it's just an injection. 

If one is aiming to write code which cannot fail at run-time, then extra
work must be done anyway.  The only question is whether the language will
support such a discipline.

> Everybody assumes that quot has a symmetric
> type as in all other languages, but in your proposal quot's arguments
> come from completely disjoint worlds.

If it is optional but not required that a developer may disable unsafe
division, then developers who expect arithmetic to work in the usual way
will not be disappointed.
 
> Moreover, 1/0 is defined on IEEE Doubles (e.g. in ghc): infinity.

This solution doesn't always help with code safety.

Thanks for the response.
--PeterD

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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

2001-02-08 Thread Elke Kasimir

On 07-Feb-2001 Patrik Jansson wrote:

(interesting stuff deleted)

> As far as I remember from the earlier discussion, the only really visible
> reason for Show, Eq to be superclasses of Num is that class contexts are
> simpler when (as is often the case) numeric operations, equality and show
> are used in some context.
> 
> f :: Num a => a -> String  -- currently
> f a = show (a+a==2*a)
> 
> If Show, Eq, Num were uncoupled this would be
> 
> f :: (Show a, Eq a, Num a) => a -> String
> 
> But I think I could live with that. (In fact, I rather like it.)

Basically I'm too.

However, what is missing for me is something like:

type Comfortable a = (Show a, Eq a, Num a) => a

or

class (Show a, Read a, Eq a) => Comfortable a
instance (Show a, Read a, Eq a) => Comfortable a 

I think here is a point where a general flaw of class hierachies as a mean
of software design becomes obvious, which consists of forcing the programmer
to arbitrarily prefer few generalizations to all others in a global, 
context-independent design decision.

The oo community (being the source of all the evil...) usually relies on the 
rather problematic ontological assumption that, at least from a certain point
of view (problem domain, design, implemention), the relevant concepts form in
a natural way a kind a generalization hierarchy, and that this generalization 
provides a natural way to design the software (in our case, determine the
type system in some a-priory fashion).

Considering the fact that a concept, for which (given a certain point of view)  
n elementary predicates hold a-priory, n! possible generalizations exist 
a-priory, this assumption can be questioned. 

In contrary to the given assumption, I have made the experience that, when 
trying to classify concepts,  even a light shift in the situation being 
under consideration can lead to a severe change in what appears to be the 
"natural" classification.  

Besides this, as is apparent in Show a => Num a, it is not always a priory 
generalizations that are really needed. Instead, the things must be fit
into the current point of view with a bit force, thus changing 
concepts or even inventing new ones.

(For example, in the oo community, which likes (or is forced?) to "ontologize" 
relationships into "objects", has invented "factories" for different things, 
ranging from GUI border frames to database connection handles. 
Behind such an at first glance totally arbitary conceptualization might stand
a more rational concept, for example applying a certain library design principle
called "factory" to different types of things. However one can't always wait 
until the rationale behind a certain solution is clearly recognized.)
 
In my experience, both class membership and generalization relationships are 
often needed locally and post hoc, and they sometimes even express empirical 
(a-posteriory) relations between concepts instead of true analytical (a-priory) 
generalization relationships.

As a consequence, for my opinion, programming languages should make it
possible and easy to employ post-hoc and local class membership declarations and
post-hoc and local class hierarchy declarations (or even re-organizations).

There will of course be situations where a global a-priory declaration of 
generalization nevertheless still make completely sense.

For Haskell, I could imagine (without having having much thought about) in 
addition to the things mentioned in the beginning, several things making 
supporting the  "locally, fast and easy", including a mean to define classes 
with implied memberships, for example declarations saying that "Foo is the class
of all types in scope for which somefoo :: ... is defined", or declarations  
saying that "class Num is locally restricted to all instances of global Num 
which also belong to Eq".

Elke.

---
Elke Kasimir
Skalitzer Str. 79
10997 Berlin (Germany)
fon:  +49 (030) 612 852 16
mail: [EMAIL PROTECTED]>  
see: 

for pgp public key see:


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Fergus Henderson

On 08-Feb-2001, Ketil Malde <[EMAIL PROTECTED]> wrote:
> Would it be a terribly grave change to the language to allow leaf
> class instance declarations to include the necessary definitions for
> dependent classes?  E.g.
> 
> class foo a where
> f :: ...
> 
> class (foo a) => bar a where
> b :: ...
> 
> instance bar T where
> f = ...
> b = ...

I think that proposal is a good idea.

It means that the user of a class which inherits from some complicated
class hierarchy doesn't need to know (or to write code which depends on)
any of the details of that class hierarchy.  Instead, they can just
give instance declarations for the classes that they want to use,
and provide definitions all of the relevant members.

It means that the developer of a class can split that class into two
or more sub-classes without breaking (source level) backwards compatibility.


One point that needs to be  resolved is the interaction with default methods.

Consider

class foo a where
f :: ...
f = ...
f2 :: ...
f2 = ...

class (foo a) => bar a where
b :: ...
 
instance bar T where
-- no definitions for f or f2
b = 42

Should this define an instance for `foo T'?
(I think not.)

How about if the instance declaration is changed to

instance bar T where
f = 41
-- no definition for f2
b = 42

?
(In that case, I think it should.)

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: Please help me

2001-02-08 Thread Chris Angus

Faizan,

A clue is to use list comprehensions (which are very like ZF set notation)

First think how you would define a cartesian product in set notation

X x Y x Z = {(x,y,z) | ...}

and then think how this is written in list comprehension notation

Chris

> -Original Message-
> From: FAIZAN RAZA [mailto:[EMAIL PROTECTED]]
> Sent: 08 February 2001 13:49
> To: [EMAIL PROTECTED]
> Subject: Please help me
> 
> 
> Hello
> 
> 
> Please help me to solve this questions
> 
> 
> Question
> 
> Cartesian Product of three sets, written as X x Y x Z is 
> defined as the set
> of all ordered triples such that the first element is a 
> member of X, the
> second is member of Y, and the thrid member of set Z. write a Haskell
> function cartesianProduct which when given three lists  (to 
> represent three
> sets) of integers returns a list of lists of ordered triples.
> 
> For examples,  cartesianProduct [1,3][2,4][5,6] returns
> [[1,2,5],[1,2,6],[1,4,5],[1,4,6],[3,2,5],[3,2,6],[3,4,5],[3,4,6]]
> 
> 
> 
> Please send me reply as soon as possible
> 
> Ok
> 
> I wish you all the best of luck
> 
> 
> 
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Jerzy Karczmarczuk

First, a general remark which has nothing to do with Num.

PLEASE WATCH YOUR DESTINATION ADDRESSES
People send regularly their postings to haskell-cafe with
several private receiver addresses, which is a bit annoying
when you click "reply all"...


Brian Boutel after Dylan Thurston:

> > Why doesn't your argument show that all types should by instances of
> > Eq and Show?  Why are numeric types special?
> 
> Why do you think it does? I certainly don't think so.
> 
> The point about Eq was that a objection was raised to Num being a
> subclass of Eq because, for some numeric types, equality is undecidable.
> I suggested that Haskell equality could be undecidable, so (==) on those
> types could reflect the real situation. One would expect that it could
> do so in a natural way, producing a value of True or False when
> possible, and diverging otherwise. Thus no convincing argument has been
> given for removing Eq as a superclass of Num.
> 
> In general, if you fine-grain the Class heirarchy too much, the picture
> gets very complicated. If you need to define separate subclases of Num
> for those types which have both Eq and Show, those that only Have Eq,
> those than only have Show and those that have neither, not to mention
> those that have Ord as well as Eq and those that don't, and then for all
> the other distinctions that will be suggested, my guess is that Haskell
> will become the preserve of a few mathematicians and everyone else will
> give up in disgust. Then the likely result is that no-one will be
> interested in maintaining and developing Haskell and it will die.

Strange, but from the objectives mentioned in the last part of this 
posting (even if a little demagogic [insert smiley here if you wish])
I draw opposite conclusions.

The fact that the number of cases is quite large suggests that Eq, Show
and arithmetic should be treated as *orthogonal* issues, and treated
independently. 

If somebody needs Show for his favourite data type, he is free to
arrange
this himself. I repeat what I have already said: I work with functional
objects as mathematical entities. I want to add parametric surfaces, to
rotate trajectories. Also, to handle gracefully and legibly for those
simpletons who call themselves 'theoretical physicists', the arithmetic
of un-truncated lazy streams representing power series, or infinitely
dimensional differential algebra elements. Perhaps those are not 
convincing arguments for Brian Boutel. They are certainly so for me.

Num, with this forced marriage of (+) and (*) violates the principle
of orthogonality. Eq and Show constraints make it worse.

===

And, last, but very high on my check-list:

The implicit coercion of numeric constants: 3.14 -=->>  (fromDouble
3.14)
etc. is sick. (Or was; I still didn't install the last version of GHC,
and with Hugs it is bad). The decision is taken by the compiler
internally,
and it doesn't care at all about the fact that in my prelude 
I have eliminated the Num class and redefined fromDouble, fromInt, etc. 

+

Dylan Thurston terminates his previous posting about Num with:

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

Now, signum and abs seem to be quite distincts beasts. Signum seem to
require Ord (and a generic zero...).

Abs from the mathematical point of view constitutes a *norm*. Now,
frankly, I haven't the slightest idea how to cast this concept into
Haskell class hierarchy in a sufficiently general way...

I'll tell you anyway that if you try to "sanitize" the numeric
classes, if you separate additive structures and the multiplication,
if you finally define abstract Vectors over some field of scalars,
and if you demand the existence of a generic normalization for your
vectors, than *most probably* you will need multiparametric classes
with dependencies. 


Jerzy Karczmarczuk
Caen, France

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Please help me

2001-02-08 Thread Ashley Yakeley

At 2001-02-08 02:04, Ashley Yakeley wrote:

>That's easy. Just define 'product' as a function that finds the cartesian 
>product of any number of lists, and then once you've done that you can 
>apply it to make the special case of three items like this:
>
>cartesianProduct a b c = product [a,b,c]
>
>At least, that's how I would do it.

eesh, 'product' is something else in the Prelude. Better call it 
'cartprod' or something.

-- 
Ashley Yakeley, Seattle WA


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Revamping the numeric classes

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

On Thu, 8 Feb 2001, Tom Pledger wrote:

> nice answer: give the numeric literal 10 the range type 10..10, which
> is defined implicitly and is a subtype of both -128..127 (Int8) and
> 0..255 (Word8).

What are the inferred types for
f = map (\x -> x+10)
g l = l ++ f l
? I hope I can use them as [Int] -> [Int].

> x + y + z -- as above
> 
> --> (x + y) + z   -- left-associativity of (+)
> 
> --> realToFrac (x + y) + z-- injection (or treating up) done
>   -- conservatively, i.e. only where needed

What does it mean "where needed"? Type inference does not proceed
inside-out. What about this?
h f = f (1::Int) == (2::Int)
Can I apply f to a function of type Int->Double? If no, then it's a
pity, because I could inline it (the comparison would be done on Doubles).
If yes, then what is the inferred type for h? Note that Int->Double is not
a subtype of Int->Int, so if h :: (Int->Int)->Bool, then I can't imagine
how h can be applied to something :: Int->Double.

-- 
Marcin 'Qrczak' Kowalczyk


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Please help me

2001-02-08 Thread Ashley Yakeley

At 2001-02-08 13:49, FAIZAN RAZA wrote:

>write a Haskell
>function cartesianProduct which when given three lists  (to represent three
>sets) of integers returns a list of lists of ordered triples.

That's easy. Just define 'product' as a function that finds the cartesian 
product of any number of lists, and then once you've done that you can 
apply it to make the special case of three items like this:

cartesianProduct a b c = product [a,b,c]

At least, that's how I would do it.

-- 
Ashley Yakeley, Seattle WA


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe