Semantics of signum

2001-02-10 Thread Dylan Thurston

On Sat, Feb 10, 2001 at 07:17:57AM +, Marcin 'Qrczak' Kowalczyk wrote:
 Sat, 10 Feb 2001 14:09:59 +1300, Brian Boutel [EMAIL PROTECTED] pisze:
 
  Can you demonstrate a revised hierarchy without Eq? What would happen to
  Ord, and the numeric classes that require Eq because they need signum? 
 
 signum doesn't require Eq. You can use signum without having Eq, and
 you can sometimes define signum without having Eq (e.g. on functions).
 Sometimes you do require (==) to define signum, but it has nothing to
 do with superclasses.

Can you elaborate?  What do you mean by signum for functions?  The 
pointwise signum?  Then abs would be the pointwise abs as well, right?
That might work, but I'm nervous because I don't know the semantics
for signum/abs in such generality.  What identities should they
satisfy?  (The current Haskell report says nothing about the meaning
of these operations, in the same way it says nothing about the meaning
of (+), (-), and (*).  Compare this to the situation for the Monad class,
where the fundamental identities are given.  Oddly, there are identities
listed for 'quot', '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,
Dylan Thurston

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



Re: Semantics of signum

2001-02-10 Thread Marcin 'Qrczak' Kowalczyk

Sat, 10 Feb 2001 11:25:46 -0500, Dylan Thurston [EMAIL PROTECTED] pisze:

 Can you elaborate?  What do you mean by signum for functions?
 The pointwise signum?

Yes.

 Then abs would be the pointwise abs as well, right?

Yes.

 That might work, but I'm nervous because I don't know the semantics
 for signum/abs in such generality.

For example signum x * abs x == x, where (==) is not Haskell's
equality but equivalence. Similarly to (x + y) + z == x + (y + z).

If (+) can be implicitly lifted to functions, then why not signum?

Note that I would lift neither signum nor (+). I don't feel the need.
It can't be uniformly applied to e.g. () whose result is Bool and
not some lifted Bool, so better be consistent and lift explicitly.

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


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



Re: Semantics of signum

2001-02-10 Thread William Lee Irwin III

On Sat, Feb 10, 2001 at 11:25:46AM -0500, Dylan Thurston wrote:
 Can you elaborate?  What do you mean by signum for functions?  The 
 pointwise signum?  Then abs would be the pointwise abs as well, right?
 That might work, but I'm nervous because I don't know the semantics
 for signum/abs in such generality.  What identities should they
 satisfy?  (The current Haskell report says nothing about the meaning
 of these operations, in the same way it says nothing about the meaning
 of (+), (-), and (*).  Compare this to the situation for the Monad class,
 where the fundamental identities are given.  Oddly, there are identities
 listed for 'quot', 'rem', 'div', and 'mod'.  For +, -, and * I can guess
 what identities they should satisfy, but not for signum and abs.)

Pointwise signum and abs are common in analysis. The identity is:

signum f * abs f = f

I've already done the pointwise case. As I've pointed out before,
abs has the wrong type for doing anything with vector spaces, though,
perhaps, abs is a distinct notion from norm.

On Sat, Feb 10, 2001 at 11:25:46AM -0500, Dylan Thurston wrote:
 (Note that pointwise abs of functions yields a positive function, which
 are not ordered but do have a sensible notion of max and min.)

The ordering you're looking for needs a norm. If you really want a
notion of size on functions, you'll have to do it with something like
one of the L^p norms for continua and the \ell^p norms for discrete
spaces which are instances of Enum. There is a slightly problematic
aspect with this in that the domain of the function does not entirely
determine the norm, and furthermore adequately dealing with the
different notions of measure on these spaces with the type system is
probably also intractable. The sorts of issues raised by trying to
define norms on functions probably rather quickly relegate it to
something the user should explicitly define, as opposed to something
that should appear in a Prelude standard or otherwise. That said,
one could do something like

instance Enum a = Enum (MyTree a) where
... -- it's tricky, but possible, you figure it out

instance (Enum a, RealFloat b) = NormedSpace (MyTree a - b) where
norm f = approxsum $ zipWith (*) (map f . enumFrom $ toEnum 0) weights
where
weights = map (\x - 1/factorial x) [0..]
approxsum [] = 0
approxsum (x:xs)| x  1.0e-6 = 0
| otherwise = x + approxsum xs

and then do the usual junk where

instance NormedSpace a = Ord a where
f  g = norm f  norm g
...


Cheers,
Bill

___
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-10 Thread Brian Boutel

Marcin 'Qrczak' Kowalczyk wrote:
 
 Sat, 10 Feb 2001 14:09:59 +1300, Brian Boutel [EMAIL PROTECTED] pisze:
 
  Can you demonstrate a revised hierarchy without Eq? What would happen to
  Ord, and the numeric classes that require Eq because they need signum?
 
 signum doesn't require Eq. You can use signum without having Eq, and
 you can sometimes define signum without having Eq (e.g. on functions).
 Sometimes you do require (==) to define signum, but it has nothing to
 do with superclasses.
 

Let me restate my question more carefully:

Can you demonstrate a revised hierarchy without Eq? What would happen to
Ord and the numeric classes with default class method definitions that
use (==) either explicitly or in pattern matching against numeric
literals? Both Integral and RealFrac do this to compare or test the
value of signum.

In an instance declaration, if a method requires operations of another
class which is not a superclass of the class being instanced, it is
sufficient to place the requirement in the context, but for default
class method definitions, all class methods used must belong to the
class being defined or its superclasses.


--brian

___
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-10 Thread Brian Boutel

Fergus Henderson wrote:
 
 On 09-Feb-2001, Brian Boutel [EMAIL PROTECTED] wrote:
  Patrik Jansson wrote:
  
   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.
 ...
 
  There is nothing trivial or ugly about a definition that reflects
  reality and bottoms only where equality is undefined.
 
 I disagree.  Haskell is a statically typed language, and having errors
 which could easily be detected at compile instead being deferred to
 run time is ugly in a statically typed language.

There may be some misunderstanding here. If you are talking about type
for which equality is always undefined, then I agree with you, but that
is not what I was talking about. I was thinking about types where
equality is defined for some pairs of argument values and undefined for
others - I think the original example was some kind of arbitrary
precision reals. My remark about "a definition that reflects reality and
bottoms only where equality is undefined" was referring to this
situation.

Returning to the basic issue, I understood the desire to remove Eq as a
superclass of Num was so that people were not required to implement
equality if they did not need it, not that there were significant
numbers of useful numeric types for which equality was not meaningful. 

Whichever of these was meant, I feel strongly that accomodating this and
other similar changes by weakening the constraints on what Num in
Haskell implies, is going too far. It devalues the Class structure in
Haskell to the point where its purpose, to control ad hoc polymorphism
in a way that ensures that operators are overloaded only on closely
related types, is lost, and one might as well abandon Classes and allow
arbitrary overloading.

--brian





--brian

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



Re: Show, Eq not necessary for Num

2001-02-10 Thread Dylan Thurston

On Sun, Feb 11, 2001 at 01:37:28PM +1300, Brian Boutel wrote:
 Let me restate my question more carefully:
 
 Can you demonstrate a revised hierarchy without Eq? What would happen to
 Ord and the numeric classes with default class method definitions that
 use (==) either explicitly or in pattern matching against numeric
 literals? Both Integral and RealFrac do this to compare or test the
 value of signum.

I've been working on writing up my preferred hierarchy, but the short
answer is that classes that are currently derived from Ord often do
require Eq as superclasses.

In the specific cases: I think possibly divMod and quotRem should be
split into separate classes.  It seems to me that divMod is the
more fundamental pair: it satisfies the identity
  mod (a+b) b === mod a b
  div (a+b) b === 1 + div a b
in addition to
  (div a b)*b + mod a b === a.
This identity is not enough to specify divMod competely; another
reasonable choice for Integers would be to round to the nearest
integer.  But this is enough to make it useful for many applications.
quotRem is also useful (although it only satisfies the second of
these), and does require the ordering (and ==) to define sensibly, so
I would make it a method of a subclass of Ord (and hence Eq).  So I
would tend to put these into two separate classes:

class (Ord a, Num a) = Real a

class (Num a) = Integral a where
  div, mod  :: a - a - a
  divMod :: a - a - (a,a)

class (Integral a, Real a) = RealIntegral a where
  quot, rem :: a - a - a
  quotRem :: a - a - (a,a)

I haven't thought about the operations in RealFrac and their semantics
enough to say much sensible, but probably they will again require Ord
as a superclass.

In general, I think a good approach is to think carefully about the
semantics of a class and its operations, and to declare exactly the
superclasses that are necessary to define the semantics.

Note that sometimes there are no additional operations.  For instance,
declaring a class to be an instance of Real a should mean 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


___
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-10 Thread Fergus Henderson

On 11-Feb-2001, Brian Boutel [EMAIL PROTECTED] wrote:
 Fergus Henderson wrote:
  
  On 09-Feb-2001, Brian Boutel [EMAIL PROTECTED] wrote:
   Patrik Jansson wrote:
   
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.
  ...
  
   There is nothing trivial or ugly about a definition that reflects
   reality and bottoms only where equality is undefined.
  
  I disagree.  Haskell is a statically typed language, and having errors
  which could easily be detected at compile instead being deferred to
  run time is ugly in a statically typed language.
 
 There may be some misunderstanding here. If you are talking about type
 for which equality is always undefined, then I agree with you, but that
 is not what I was talking about. I was thinking about types where
 equality is defined for some pairs of argument values and undefined for
 others - I think the original example was some kind of arbitrary
 precision reals.

The original example was treating functions as a numeric type.  In the
case of functions, computing equality is almost always infeasible.
But you can easily define addition etc. pointwise:

f + g = (\ x - f x + g x)

 Returning to the basic issue, I understood the desire to remove Eq as a
 superclass of Num was so that people were not required to implement
 equality if they did not need it, not that there were significant
 numbers of useful numeric types for which equality was not meaningful. 

The argument is the latter, with functions as the canonical example.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.

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