Re: [Haskell-cafe] Features of Haskell

2006-06-04 Thread Dylan Thurston
On Sun, Jun 04, 2006 at 05:17:02PM -0700, Jared Updike wrote:
 stumped as to how I'm going to do this. I've got about 15-20 minutes,
 so I can only discuss the major features.
 
 I was always impressed with Autrijus Tang's presentation here:
   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
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-04-17 Thread Dylan Thurston
On Mon, Apr 10, 2006 at 12:13:55PM +0200, Andrew U. Frank wrote:
 there has been discussions on and off indicating problems with the structure
 of the number classes in the prelude. i have found a discussion paper by
 mechveliani but i have not found a concrete proposal on the haskell' list of
 tickets. i hope i can advance the process by making a concrete proposal for
 which i attach Haskell code and a pdf giving the rational can be found at
 ftp://ftp.geoinfo.tuwien.ac.at/frank/numbersPrelude_v1.pdf
 
 if i have not found other contributions, i am sorry and hope to hear about
 them. 
 
 i try a conservative structure, which is more conservative than the
 structure we have used here for several years (or mechveliani's proposal).
 It suggests classes for units (Zeros, Ones) and CommGroup (for +, -),
 OrdGroup (for abs and difference), CommRing (for *, sqr), EuclideanRing (for
 gdc, lcm, quot, rem, div...) and Field (for /). I think the proposed
 structure could be a foundation for mathematically strict approaches (like
 mechveliani's) but still be acceptable to 'ordinary users'.

I agree with Henning Thielemann about putting 'zero' in 'CommGroup'
and 'one' in 'CommRing'.  What is your thinking here?  I would also
argue for putting 'fromInteger' in 'CommRing', as discussed in the
NumPrelude proposal.  'EuclideanRing' is a misnomer; a Euclidean Ring
is a particular type of ring where GCD, etc. can be defined (see
http://planetmath.org/encyclopedia/EuclideanRing.html), but there are
other such rings, namely any Principal Ideal Domain or PID.
'IntegralDomain' is also a misnomer; I don't know what you're getting
at there, but there is a well-established mathematical term 'integral
domain' that means something different.

o On enforcing properties: there's not currently any way to enforce
properties (e.g., monad laws are not enforced); however, I believe
that expected properties should be documented.

o ^ and ^^ (which can actually be combined, see our proposal) are in
fact quite useful, and can be implemented considerably more
efficiently than a general exponentiation.  If you want a complete
proposal, you do need to go further.

o You do impose some additional burden by changing the name of the
'Num' class, and it is worth noting that.

o Mechvelliani's implementation could not be built on top of your
base, because he needs to have a sample argument to 'zero' to
determine, e.g., the right zero for modular arithmetic.  Henning
mentioned 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,
Dylan Thurston




signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-04-17 Thread Dylan Thurston
On Sat, Apr 08, 2006 at 10:16:53PM +0400, Serge D. Mechveliani wrote:
 I think that without  dependent types  for a Haskell-like language,  
 it is impossible to propose any adequate and in the same time plainly 
 looking algebraic class system.

Agreed.  Is there anything really wrong 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 signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
 
 genericLength :: Integral a = [b] - a
 
 if you have a different 'Integral' you can't call genericLength with it,
 or anything built up on genericLength. basically there would be no way
 for 'new' and 'old' polymorphic code to interact. 

I think the idea would be that the source for genericLength would
compile using either class hierarchy with no change.  For the case of
genericLength, this is true for the proposed alternate prelude Hennig
Theilemann pointed to.  It would be mostly true in general for that
proposal, with the exception that you would sometimes need to add Show
or Eq instances.

 the inability to evolve the class hierarchy is a serious issue, enough
 that it very well could be impractical for haskell' unless something
 like class aliases were widely adopted.

I think that as long as you're not defining classes source compatibility
would not be hard.  Of course you couldn't hope to link code written
with one hierarchy against another.

Peace,
Dylan Thursto


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 typing.  To wit, with records, you
give an example


data Pot = Pot
{
 pProfit :: !Word64,
 pAmounts :: ![Word64] -- Word16/
} deriving (Show, Typeable)

mkPot :: Pot
mkPot =
Pot
{
 pProfit = 333,
 pAmounts = []
}

and complain about having to explain to the customer how xyFoo is
really different from zFoo when they really mean the same thing.  I
wonder: if they really are the same thing, is there a way to get the
data types to faithfully reflect that?  Can you post a few more
snippets of your data structures?

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 line-by-line and doing the computation, it
 reads a whole bunch of lines (hundreds of megs worth, apparently) and
 only does away with them when a new header appears.
 
 Anyway, I uploaded a dead simple first-naive-implementation which is
 significantly faster (and more elegant):
 ...

The program is supposed to do reverse and complement.  The code you
posted just does complement.

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
  
   which clearly is not part of the current syntax, but I hope you get
   the picture. What are the elegant ways of doing this?
  
  How about
  f :: Real a = Extended a - Extended a
  
 Not quite what I had in mind. I'd like to have extended integers and
 extended rationals, and possibly extended dyadic numbers. So I can't
 have just a single type ExtendedRational (unless I'm prepared to do
 some ugly coersing).

You're missing the point.  Try:

 data Extended a = PlusInf | NegInf | Finite a

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 should be O(\n - n) (a remark by Simon Thompson in
The Craft of Functional Programming)
 
 I don't think this can be right.  Ken argued around this point, but
 here's a more direct argument: in
 
  f(x) = x + 1 + O(1/x)
 
 all the 'x's refer to the same variable; so you shouldn't go and
 capture the one inside the 'O'.
 
 I didn't argue, that textually replacing all O(A) by O(\n - A) is a 
 general solution. For your case I suggest
 
 (\x - f(x) - x - 1)   \in   O (\x - 1/x)

This kind of replacement on the top level is exactly what
continuations (which Ken was suggesting) can acheive.  If you think
carefully about exactly what the big-O notation means in general
expressions like this, you'll be led to the same thing.

 I haven't yet seen the expression 2^(O(n)). I would interpret it as 
 lifting (\x - 2^x) to sets of functions, then applying it to the function 
 set O(\n - n). But I assume that this set can't be expressed by an O set.

That's right; for instance, in your terminology, 3^n is in 2^(O(n)).

 But I see people writing f(.) + f(.-t) and they don't tell, whether this 
 means
 
   (\x - f x) + (\x - f (x-t))
 
 or
 
   (\x - f x + f (x-t))
 
 Have you really seen people use that notation with either of those
 meanings?
 
 In principle, yes.

I'm curious to see examples.

 That's really horrible and inconsistent.  I would have interpreted f(.) + 
 f(.-t) as
 
 \x \y - f(x) + f(y-t)
 
 to be consistent with notation like .*. , which seems to mean
 \x \y - x*y
 in my experience.
 
 The problems with this notation are: You can't represent constant 
 functions, which is probably no problem for most people, since they 
 identify scalar values with constant functions. But the bigger problem is 
 the scope of the dot: How much shall be affected by the 'functionisation' 
 performed by the dot? The minimal scope is the dot itself, that is . would 
 mean the id function. But in principle it could also mean the whole 
 expression.
  I think there are good reasons why such a notation isn't implemented for 
 Haskell. But I have seen it in SuperCollider.

I certainly don't want to defend this notation...

Now that you mention it, Mathematica also has this notation, with
explicit delimiters; for instance, `(#+2)' is the function of adding
two.

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 effects --
  see the third and fifth examples below.
 I can't imagine mathematics with side effects, because there is no order
 of execution.

Not all side effects require an order of execution.  For instance,
dependence on the environment is a side effect (in the sense that it
is related to a monad), but it does not depend on the order of
execution.  There are many other examples too, like random variables.

   O(n)
  which should be O(\n - n) (a remark by Simon Thompson in
  The Craft of Functional Programming)

I don't think this can be right.  Ken argued around this point, but
here's a more direct argument: in

  f(x) = x + 1 + O(1/x)

all the 'x's refer to the same variable; so you shouldn't go and
capture the one inside the 'O'.

This is established mathematical notation, it's very useful, and can
be explained almost coherently.  The one deficiency is that we should
interpret 'O' as an asymptotically bounded function of... but that
doesn't say what it is a function of and where we should take the
asymptotics.  But the patch you suggest doesn't really help.

 But what do you mean with 1/O(n^2) ? O(f) is defined as the set of
 functions bounded to the upper by f.  So 1/O(f) has no meaning at the
 first glance. I could interpret it as lifting (1/) to (\f x - 1 / f x)
 (i.e. lifting from scalar reciprocal to the reciprocal of a function) and
 then as lifting from a reciprocal of a function to the reciprocal of each
 function of a set. Do you mean that?

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 asymptotically bounded below by
1/kn^2 for some k.

 Hm, (3+) is partial application, a re-ordered notation of ((+) 3), which
 is only possible if the omitted value is needed only once. But I see
 people writing f(.) + f(.-t) and they don't tell, whether this means

   (\x - f x) + (\x - f (x-t))
 
 or
 
   (\x - f x + f (x-t))

Have you really seen people use that notation with either of those
meanings?  That's really horrible and inconsistent.  I would have
interpreted f(.) + f(.-t) as

 \x \y - f(x) + f(y-t)

to be consistent with notation like .*. , which seems to mean
 \x \y - x*y
in my experience.

 It seems to me that the dot is somehow more variable than variables, and a
 dot-containing expression represents a function where the function
 arguments are inserted where the dots are.

Right.  I don't know how to formalize this, but that doesn't mean it
can't be done.

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
 ([],_) - a
 (_, False) - a
 (b:bs', _) - foldlWhile f p (f a b) bs'
 
 foldl  does not seem to cover this.

Why not just

  foldlWhile f p a bs = takeWhile p $ foldl f a bs

?

 More `generic' variant:
 
   foldlWhileJust :: (a - b - Maybe a) - a - [b] - a 
   foldlWhileJustf  abs  =  case bs of
 
[]- a
b:bs' - case f a b of Just a' - foldlWhileJust f a' bs'
   _   - a

I don't know a short way to rewrite this one yet.

Peace,
Dylan


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


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
   (bs, p a)
   of
   ([],_) - a
   (_, False) - a
   (b:bs', _) - foldlWhile f p (f a b) bs'
 
  Why not just
foldlWhile f p a bs = takeWhile p $ foldl f a bs
 
 Quite different. The former stops a foldl when the accumulating parameter no 
 longer satisfies p, the later assumes the accumulating parameter of the foldl 
 is a list, and takes the portion of the list that does satisfy p.

Yes, this was a mistake.

 The following is closer to the original, but doesn't work when the whole list 
 is folded (i.e., p always satisfied):  
 foldlWhile f p a = head . dropWhile p . scanl f a

Serge's version returns the last 'a' that satisfies 'p', while yours
returns the first 'a' that does not satisfy 'p'.  This should be an
equivalent version:

  foldlWhile f p a = tail . takeWhile p . scanl f a

But what about the version with Maybe?  There ought to be a concise way
to write that too.

Peace,
Dylan


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


[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 unclear here, it would be nice if GHC, Hugs, and NHC98 agreed on 
 something.
 Can we agree on the special Rational values below?

I would be very careful of adding non-rationals to the Rational type.
For one thing, it breaks the traditional rule for equality
  a % b == c % d iffa*d == b*c
You'd need to look at all the instances for Ratio a that are defined.
For instance, the Ord instance would require at least lots of special
cases.  And when would you expect 'x/0' to give +Infinity and when
-Infinity?  For IEEE floats, there are distinct representations of +0
and -0, which lets you know when you want which one.  But for the
Rational type there is no such distinction.

The behaviour that '1 % 0' gives the error 'Ratio.% : zero
denominator' is clearly specified by the Library Report.

In the meantime, there are utility functions for dealing with IEEE
floats (isNaN, etc.)

Peace,
Dylan


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


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 are a number of choices to be made in making such an
implementation.  It would be handy, but it makes sense that it's more
than the Haskell designers wanted to specify initially.

It would make a nice library if you want to write it.

Peace,
Dylan


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


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 itself, your result lazy list will
 never get anywhere.  The calculation will keep trying to determine
 whether or not the result is less than 2, this being necessary to
 find the first number in the representation. But every finite prefix
 of the square root of 2 leaves uncertainty both below and above, so
 the determination will never be made.

Right, one way to think about this problem is that the representations
by continued fractions are unique, so there's no way to compute the
prefix of a representation for something right on the boundary.
Representing numbers by lazy strings of, say, decimal digits has the
same problem.

There are known solutions, but they lack the elegance of continued
fraction representations.  You fundamentally have to have non-unique
representations, and that causes some other problems.  One popular
version is to use base 2 with digits -1, 0, and +1.

Simon Peyton-Jones already posted the references.

These methods appear to lose out in practice to using a large fixed
precision and interval arithmetic, increasing the precision and
recomputing as necessary.

Peace,
Dylan


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


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/6.0/html/base/Data.PackedString.html

Peace,
Dylan


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


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 where
 zero  :: v
 add   :: v - v - v
 scale :: a - v - v

You might want to add a functional dependency, if you only have one
type of scalars per vertor space:

 class VectorSpace v a | v - awhere
zero  :: v
add   :: v - v - v
scale :: a - v - v

But then again, you might not.

  instance Num a = VectorSpace a a where
 zero  = 0
 add   = (+)
 scale = (*)
 
 Here the compiler complains the first time:
 
 VectorSpace.lhs:27:
 Illegal instance declaration for `VectorSpace a a'
 (There must be at least one non-type-variable in the instance head
  Use -fallow-undecidable-instances to permit this)
 In the instance declaration for `VectorSpace a a'

Well, you know how to fix this...

Another way to fix it is to add a dummy type constructor:

 newtype Vector a = Vector a

 instance Num a = VectorSpace (Vector a) a

Later:
  instance Num a = VectorSpace [a] a where

By the way, depending how you resolve the issue above, you might want
instead

 instance (RealFloat a, VectorSpace b a) = VectorSpace [b] a where
 ...


 Now I introduce a new datatype for a vector valued quantity.
 The 'show' function in this simplified example
 may show the vector with the magnitude separated
 from the vector components.
 ...
 The problem which arises here is that the type 'a' is used for
 internal purposes of 'show' only. Thus the compiler can't decide
 which instance of 'Normed' to use if I call 'show':

This is exactly what is fixed by adding the functional dependency
above.

Alternatively, if you want to consider varying the scalars, you can
add 'a' as a dummy type variable to 'Quantity':

 data Quantity v a = Quantity v

 instance (Show v, Fractional a, Normed v a) =
 Show (Quantity v a) where
show (Quantity v) =
let nv::a = norm v
in  (show (scale (1/nv) v)) ++ * ++
(show nv)

GHC still won't accept this without prompting, but now at least you
can provide a complete type:

*VectorSpace show (Quantity [1,2,3] :: Quantity [Double] Double)
[0.1,0.,0.5]*6.0

Note that this makes sense semantically: if you have a vector space
over both, say, the reals and the complexes, you need to know which
base field to work over when you normalize.

 So I tried the approach which is more similar
 to what I tried before with a single-parameter type class:
 I use a type constructor 'v' instead of a vector type 'v'
 ...

  data QuantityC v a = QuantityC (v a)
 
  instance (Fractional a, NormedC v a, Show (v a)) =
  Show (QuantityC v a) where
 show (QuantityC v) =
 let nv = normC v
 in  (show (scaleC (1/nv) v)) ++ * ++
 (show nv)
 
 It lead the compiler eventually fail with:
 VectorSpace.lhs:138:
 Non-type variables in constraint: Show (v a)
 (Use -fallow-undecidable-instances to permit this)
 In the context: (Fractional a, NormedC v a, Show (v a))
 While checking the context of an instance declaration
 In the instance declaration for `Show (QuantityC v a)'

Hmm, I don't know how to fix up this version.

Peace,
Dylan


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


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
 
 I haven't added context requirements like (Num a)
 to the signatures of 'zero', 'add', 'scale'
 because I cannot catch all requirements
 that instances may need.
 
 The problematic part is the 'scale' operation
 because it needs both a scalar value and a vector.
 Without the 'scale' operation
 'v' could be simply a type (*)
 rather than a type constructor (* - *).

Right.

I recommend you use multi-parameter type classes, with a type of the
scalars and the type of the vectors.  For the method you're using, you
need to add a 'Num a' context.  You say that you 'cannot catch all
requirements that instances may need', but certainly any instance will
need that context.

If you use multi-parameter type classes, then in your instance
declaration you can specify exactly what requirements you need.  For
instance:

 class VectorSpace v a where
   zero :: v
   add :: v - v - v
   scale :: a - v - v

 instance VectorSpace IntArray Int where ...

 instance (Num a) = VectorSpace (GenericArray a) a where ...

Peace,
Dylan


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


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.  Similarly 
 there are queues which contain lists of functions which respond to events.  
 (CreatureAttackEvent - WorldState - WorldState) 
 
 I'd like to be able to save the game state to disk so that it can be 
 reloaded.  Obviously, these closures are now a problem, as they can't be 
 stored. 

It seems like there are two things you want to do with these
functional closures: save them to disk, and run them as functions.
Why not combine these two into a type class?

Peace,
Dylan


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


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
distanceVector :: u - Vector a - Vector a - Vector a
  ...
 
  You need to use ghc with '-fglasgow-exts' for this.

 What is the general attitude in the Haskell community towards
 compiler-specific extensions? My past experience with Fortran and
 C/C++ tells me to stay away from them. Portability is an important
 criterion for me.

I think it depends on the extension.  I find multi-parameter type
classes genuinely very useful, and the functional dependencies
notation (the '| u - a' above) has been around for a while and seems
to be becoming standard.  Hugs, for instance, implements these same
extensions, and it seems very likely to me to be part of the next
Haskell standard.  On the other hand, some ghc extensions, like
generic Haskell, seem much more preliminary to me; if you want
portable code, I would stay away from them.

There was some discussion earlier about formalising some of these
extensions.  As far as I know, the FFI is the only one for which this
has been completed; but I think multi-parameter type classes would be
a natural next choice.

Peace,
Dylan



pgp0.pgp
Description: PGP signature


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, Floating a) = Universe u a | u - a where
distanceVector :: u - Vector a - Vector a - Vector a
  ...
 
 Actually, this is a nice way to represent vector spaces, too:
 
   class (Num v, Fractional f) = VectorSpace vs v f | vs - v f where
   scale :: vs - f - v - v
   innerProduct :: vs - v - v - f
 
 The reason why you may want to do this is that you may in general want
 different inner products on the same vectors, which result in different
 vector spaces.

Hmm, that's an interesting technique, which I'll have to try out; there
are several instances where you want different versions of the same
structure on some elements.  This is an interesting alternative to
newtype wrapping or some such.

However, I would be sure to distinguish between an inner product space
and a vector space.  A vector space has only the 'scale' operation above
(beyond the +, -, and 0 from Num); you will rarely want to have
different versions of the scale operation for a given set of vectors and
base field.  An inner product space has the 'innerProduct' operation you
mention; as you say, there is very frequently more than one interesting
inner product.

Peace,
Dylan


pgp0.pgp
Description: PGP signature


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.  When 'u' is 'OrthorhombicUniverse x', it
 doesn't know that this 'x' is supposed to be the same as the 'a'.  One
 way to fix this is to parameterize the Universe data type on the
 element, something like:
 
 class Universe u where
   distanceVector :: (RealFrac a, Floating a) = u a - (Vector a) -
 (Vector a) - (Vector a)
 ...

Another approach is to make Universe a multi-parameter type class:

class (RealFrac a, Floating a) = Universe u a | u - a where
  distanceVector :: u - Vector a - Vector a - Vector a
...

You need to use ghc with '-fglasgow-exts' for this.

Peace,
Dylan


pgp0.pgp
Description: PGP signature


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 defined separately for 
  each type, instance (...) = Num a doesn't work.
 
 It works in extended Haskell however, so I suspect it lays to rest the 
 question of needing some other language extension.

I disagree!  This method (putting each function in its own class) does
not address two related points:

a) Being able to declare default values for a method declared in a
superclass;

b) Being able to refine a type heirarchy without the users noticing
(and without explosion of the number of instance declarations
required).

Peace,
Dylan


pgp0.pgp
Description: PGP signature


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 handy if the subclass could define defaults for the superclass
 methods (e.g. Ord defining (==)), so that the superclass instance could
 be optional.

I agree, but this needs to be carefully thought out.  For instance,
remember to consider the case that there is more than one default
instance for a given method of a superclass.  I am reminded of
multiple inheritance considerations.

(These difficulties came up before when I was thinking about the
numeric heirarchy, and was the reason I proposed a heirarchy which was
much less fine-grained than, e.g., in Mechvelliani's proposal.)

Peace,
Dylan


pgp0.pgp
Description: PGP signature


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
 Okasaki, but I must have a typo somewhere, because I was having typing
 clashes that I couldn't easily clarify.  At least, when I loaded the
 BinomialHeap.hs into Hugs, it didn't complain, but when I tried to
 create an empty heap using the heapEmpty function, Hugs screamed at me.
 I got scared and fled the scene, retreating into the safety of lists.

I don't think you should worry about this now, but the problem was
problem that heapEmpty returns something like 'Heap a', for an
undetermined type variable 'a'; you may need to specify the type of
your empty heap in order for Hugs not to complain.

Peace,
Dylan


pgp0.pgp
Description: PGP signature


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 task is simply to look at a lengthy list of stock keeping units
 (SKUs -- what retailers call individual items), stores, dates that a
 promotion started, dates the promotion ended, and something like
 sales amount; we want to pull out the records where promotions
 overlap.  I will have dates in mmdd format, so there's probably
 no harm in treating them as Ints.

(Unless this is really a one-shot deal, I suspect using Ints for dates
is a bad decision...)

 My suggestion went something like this (I'm not at my desk so I
 don't have exactly what I typed):

I have a different algorithm, which should be nearly optimal, but I
find it harder to describe than to show the code (which is untested):

 import List(sortBy, insertBy)

 data PromotionRec  = PR {sku :: String, store :: String, startDate :: Int, endDate 
 :: Int, amount::Float}

 compareStart, compareEnd :: PromotionRec - PromotionRec - Ordering
 compareStart x y = compare (startDate x) (startDate y)
 compareEnd x y = compare (endDate x) (endDate y)

 overlap :: [PromoRec] - [[PromoRec]]
 overlap l = filter (lambda l. length l  1) 
(overlap' [] (sortBy compareStart l))

 overlap' _ [] = []
 overlap' active (x:xs) =
   let {active' = dropWhile (lambda y. endDate y  startDate x) active} in
   (x:active') : overlap' (insertBy compareEnd x active') xs

The key is that, by keeping a list of the currently active promotions
in order sorted by the ending date, we only need to discared an
initial portion of the list.

You could get a moderately more efficient implementation by keeping
the active list as a heap rather than a list.

Peace,
Dylan


pgp0.pgp
Description: PGP signature


Re: infinite (fractional) precision

2002-10-10 Thread Dylan Thurston

On Thu, Oct 10, 2002 at 02:25:59AM -0700, Ashley Yakeley wrote:
 At 2002-10-10 01:29, Ketil Z. Malde wrote:
 
 I realize it's probably far from trivial, e.g. comparing two equal
 numbers could easily not terminate, and memory exhaustion would
 probably arise in many other cases.
 
 I considered doing something very like this for real (computable) 
 numbers, but because I couldn't properly make the type an instance of Eq, 
 I left it. Actually it was worse than that. Suppose I'm adding two 
 numbers, both of which are actually 1, but I don't know that:
 
  1.0 +
  0.9
 ...

The solution to such quandries is to allow non-unique representation.
For instance, you might consider a binary system with allowed digits +1,
0, and -1, so that a number starting

  0.xx

can be anything between -1 and 1, and

  0.1x

can be anything between 0 and 1, etc.  It is then possible to guarantee
being able to output digits in a finite amount of time.  With a scheme
like this, the cases that blow up are ones you expect, like trying to
compute 1/0; there are ways around that, too.

As 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) of
Just n - Just (show n)
Nothing -
 case (nimber g) of
  Just n - Just (*++(show n))
  Nothing - Nothing

You could write (using GHC's pattern guards):

show g | Just n = number g   = Just (show n)
   | Just n = fraction g = Just (show n)
   | Just n = nimber g   = Just (*++show n)
   | Nothing = Nothing

Do I detect a program for analyzing combinatorial games being written?

--Dylan



msg02002/pgp0.pgp
Description: PGP signature


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
Prelude.fromInteger 3 - for any *module Prelude* which is in scope!
 
That is, one could say:
import Prelude ()
import MyPrelude as Prelude
IMHO it's very intuitive, contrary to -fno-implicit-prelude flag.

I don't agree with this, since the Haskell 98 standard explicitly
contradicts it.  I don't see what's wrong with a command line switch
that would do this, anyway.

 Presuming of course that defaulting would follow this path and refer
 to the new Prelude.

I never came up with a design that would allow this.  Defaulting seems
to be the one piece of the Haskell standard for which there is not yet
a general solution.

Although now that I think about it, if you could just specify which
fromInteger you wanted (i.e., give that fromInteger a more specific
type) the problem would go away.  Perhaps that's really the better
solution anyway: how often do people want to default to something
that's not the first on the defaulting list?  I think that might end
up being less surprising to programmers, anyway.  It might work as a
temporary hack for you, anyway.

(That is, add declarations like

fromInteger :: Integer - Int
fromRational :: Rational - Double

in your new Prelude.  This would work as long as users don't otherwise
use fromInteger.)

I don't know how you want to transform the types, but there are at
least two areas where there are still special types: List and Bool.
For List, I don't actually see any problem in principle with allowing
other implementations of list comprehensions and whatnot, but Simon
Peyton-Jones indicated that it would be difficult to actually
implement; with Bool, one would need to define additional functions
(like ifThenElse).

Best,
 Dylan



msg01816/pgp0.pgp
Description: PGP signature


Re: Replacing the Prelude

2002-05-14 Thread Dylan Thurston

On Sun, May 12, 2002 at 09:31:38PM -0700, Ashley Yakeley wrote:
 I have recently been experimenting writing code that replaces large 
 chunks of the Prelude, compiling with -fno-implicit-prelude. I notice 
 that I can happily redefine numeric literals simply by creating functions 
 called 'fromInteger' and 'fromRational': GHC will use whatever is in 
 scope for those names.
 
 I was hoping to do something similar for 'do' notation by redefining 
 (), (=) etc., but unfortunately GHC is quite insistent that 'do' 
 notation quite specifically refers to GHC.Base.Monad (i.e. Prelude.Monad, 
 as the Report seems to require). I don't suppose there's any way of 
 fooling it, is there? I was rather hoping 'do' notation would work like a 
 macro in rewriting its block, and not worry about types at all.
 
 I accept that this might be a slightly bizarre request. There are a 
 number of things I don't like about the way the Prelude.Monad class and 
 'do' notation are set up, and it would be nice to be able to experiment 
 with alternatives.

A while ago, there were extensive discussions about replacing the
Prelude on this list.  (Search for Prelude shenanigans.)  I started
to write up a design document for how to enable replacing the Prelude.
This boiled down to taking most of the syntactic sugar defined in
the report seriously, ignoring the types (as you say).

I'm surprised that ghc uses the fromInteger and fromRational that are
in scope; I thought there was general agreement that it should use the
Prelude.from{Integer,Rational} in scope.

As I recall, there were several relevant bits of syntactic sugar:

- Numeric types, including 'fromInteger', 'fromRational', and
  'negate'.  This all works fine, except that the defaulting mechanism
  is completely broken, causing a number of headaches.

- Monads.  The translation given in the report is clean, and it seems
  like it can be used without problems.

- Bools.  There was a slight problem here: the expansion of
  'if ... then ... else ...' uses a case construct referring to the
  constructors of the Bool type, which prevents any useful
  redefinition of Bool.  I would propose using a new function,
  'Prelude.ifThenElse', if there is one in scope.

- Enumerations.  Clean syntactic sugar.

- List comprehensions.  The report gives one translation, but I think
  I might prefer a translation into monads.

- Lists and tuples more generally.  At some point the translations
  start getting 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

(Redirected to haskell-cafe.)

On Mon, May 06, 2002 at 04:49:55PM -0700, [EMAIL PROTECTED] wrote:
 Problem: given an integer n within [0..maxn], design a scaling
 function sc(n) that returns an integer within [s..t], t=s.
 The function sc(n) must be 'monotonic': 
   0=a  b == sc(a) = sc(b)
 and it must map the ends of the interval:
   sc(0) - s and sc(maxn) - t.

Just an aside (which Oleg surely knows): for actual random number
generation, you often don't care about the monotonicity, and only care
about uniform generation.  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 end of the range [s..t].

--Dylan Thurston



msg01661/pgp0.pgp
Description: PGP signature


Re: sort inefficiency

2002-04-02 Thread Dylan Thurston

On Wed, Apr 03, 2002 at 09:35:51AM +0400, Serge D. Mechveliani wrote:
 The Standard library specifies only the  map  related to the name 
 `sort'. This map can be described, for example, via sort-by-insertion
 program.
 And the algorithm choice is a matter of each particular
 implementation. Implementation has right to change the algorithm.

Reading this, it occurred to me that if you're very picky the
implementation probably isn't allowed to pick the algorithm: you need to
assume that '' is actually a total order to have much leeway 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 call site:
 
   show {| Constr c t |} (Con x) = (name {| c |}) ++ show x
 
 I quite like the thought of being able to supply explicit type
 arguments
 but I don't konw how to speak about the order of type parameters.
 What order does map takes its two type parameters in?

Sorry, this seems like a non-sequitur to me?

'map' has type '(a-b) - [a] - [b]'; supplying explicit type
parameters would mean giving values to 'a' and 'b'.  If I wanted to
propose notation for this, I would suggest, e.g.,
  (map :: (String - Int) - [String] - [Int]) length [Hello, World]

'name' (above) has type 'String'; the '{| c |}' is not providing a type
parameter in the same sense.

What am I missing?

Best,
Dylan



msg01379/pgp0.pgp
Description: PGP signature


Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-15 Thread Dylan Thurston

On Mon, Oct 15, 2001 at 03:52:06PM +0200, Kent Karlsson wrote:
  Simon Peyton-Jones:
   Russell O'Connor suggests:
   | but sinh and cosh can easily be defined in terms of exp
   | sinh x = (exp(x) - exp(-x))/2
   | cosh x = (exp(x) + exp(-x))/2
...
   This looks pretty reasonable to me.  We should have default methods
   for anything we can.
 Mathematically, yes.  Numerically, no.  Even if 'exp' is implemented
 with high accuracy, the suggested defaults may return a very
 inaccurate (in ulps) result.  Take sinh near zero.  sinh(x) with x
 very close to 0 should return x.  With the above 'default' sinh(x)
 will return exactly 0 for a relatively wide interval around 0, which
 is the wrong result except for 0 itself.

Hmm, on these grounds the current default definition for tanh x is
even worse behaved:

tanh x = sinh x / cosh x

For moderately large floating point x, this will overflow.

Frankly, I don't think the whole discussion matters very much; nobody
who cares will use the default definitions.  But remember to think
about branch cuts.

And why not go further?

cos x = (exp (i*x) + exp (-i*x))/2  where i = sqrt (-1)

etc.

 In general, this is why LIA-2 (Language Independent Arithmetic, part
 2, Elementary numerical functions, ISO/IEC 10967-2:2001) rarely
 attempts to define one numerical operation in terms of other
 numerical operations.  That is done only when the relationship is
 exact (even if the operations themselves are inexact).  That is not
 the case for the abovementioned operations. But it is the case for
 the relationship between the complex sin operation and the complex
 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 somewhere?

Best,
Dylan Thurston

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



Re: UniCode

2001-10-05 Thread Dylan Thurston

On Fri, Oct 05, 2001 at 11:23:50PM +1000, Andrew J Bromage wrote:
 G'day all.
 
 On Fri, Oct 05, 2001 at 02:29:51AM -0700, Krasimir Angelov wrote:
 
  Why Char is 32 bit. UniCode characters is 16 bit.
 
 It's not quite as simple as that.  There is a set of one million
 (more correctly, 1M) Unicode characters which are only accessible
 using surrogate pairs (i.e. two UTF-16 codes).  There are currently 
 none of these codes assigned, and when they are, they'll be extremely
 rare.  So rare, in fact, that the cost of strings taking up twice the
 space that the currently do simply isn't worth the cost.

This is no longer true, as of Unicode 3.1.  Almost half of all
characters currently assigned are outside of the BMP (i.e., require
surrogate pairs in the UTF-16 encoding), including many Chinese
characters.  In current usage, these characters probably occur mainly
in names, and are rare, but obviously important for the people
involved.

 However, you still need to be able to handle them.  I don't know what
 the official Haskell reasoning is (it may have more to do with word
 size than Unicode semantics), but it makes sense to me to store single
 characters in UTF-32 but strings in a more compressed format (UTF-8 or
 UTF-16).

Haskell already stores strings as lists of characters, so I see no
advantage to anything other than UTF-32, since they'll take up a full
machine word in any case.  (Right?)  There's even plenty of room for
tags if any implementations want to use it.

 See also: http://www.unicode.org/unicode/faq/utf_bom.html
 
 It just goes to show that strings are not merely arrays of characters
 like some languages would have you believe.

Right.  In Unicode, the concept of a character is not really so
useful; most functions that traditionally operate on characters (e.g.,
uppercase or display-width) fundamentally need to operate on strings.
(This is due to properties of particular languages, not any design
flaw of Unicode.)

Err, this raises some questions as to just what the Char module
from the standard library is supposed to do.  Most of the functions
are just not well-defined:
  isAscii, isLatin1 - OK
  isControl - I don't know about this.
  isPrint - Dubious.  Is a non-spacing accent a printable character?
  isSpace - OK, by the comment in the report: The isSpace function
recognizes only white characters in the Latin-1 range.
  isUpper, isLower - Maybe OK.
  toUpper, toLower - Not OK.  There are cases where upper casing a
 character yields two characters.
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 real
Unicode library with an interface at the correct level?

Best,
Dylan Thurston

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



Re: always new instance?

2001-10-04 Thread Dylan Thurston

On Tue, Oct 02, 2001 at 01:09:28PM +0300, Cagdas Ozgenc wrote:
 Do I ALWAYS need to create a new instance if I want to modify the state of
 an instance? For example, if I design an index for a simple database with an
 recursive algebric Tree type, do I need to recreate the whole Tree if I
 insert or remove an element? How can I improve performance, what are common
 idioms in these situations?

For trees, if you want to change a node you typically have to recreate
the nodes along the path to the root; that is, all the ancestors of
the node.  If your tree is well-balanced, this is only logarithmic in
the size of your data, and automatically gives you other benefits,
like persistence.

(That is, you only need to change the nodes when the corresponding
subtree has actually changed, which makes some sense.)

I second Mark Carroll's recommendation for Okasaki'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

On Fri, Sep 28, 2001 at 05:31:20PM +0800, Saswat Anand wrote:
 I have a very large time-series data. I need to perform some operation on
 that. At any instant of time, I only need a window-full of data, size of
 window being known. Starting from the first point, I slide the window
 towards right and operate on the data that reside in the current window.

This sounds perfectly suited to Haskell's standard lazy lists.  If you
only keep a pointer to the beginning of the data you need to work on,
then Haskell will automatically read in exactly as much data as you
use and 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
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



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 2 [],Cons 3 []]]

 Anyway, is my instance declaration still a bit mucked up?

Hmm.  To try to deduce Show (S [] Integer), the type checker reduces
it by your instance declaration to Show [S [] Integer], which reduces
to Show (S [] Integer), which reduces to...

ghci or hugs could, in theory, be slightly smarter and handle this case.

 Also, could there be a way to give a definition of show for S [] a? 

Yes.  You could drop the generality:

 instance (Show a) = Show (S [] a) where
show Nil = Nil
show (Cons x y) = Cons  ++ show x ++   ++ show y

Really, the context you want is something like

 instance (Show a, forall b. Show b = Show (m b)) = Show (S m b) ...

if that were legal.

--Dylan

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



Re: Implict parameters and monomorphism

2001-05-04 Thread Dylan Thurston

On Fri, May 04, 2001 at 07:56:24PM +, Marcin 'Qrczak' Kowalczyk wrote:
 I would like to make pattern and result type signatures one-way
 matching, like in OCaml: a type variable just gives a name to the given
 part of the type, without constraining it any way - especially without
 negative constraining, i.e. without yielding an error if it will
 be known more than that it's a possibly constrained type variable...

I'm not sure I understand here.  One thing that occurred to me reading
your e-mail was that maybe the implicit universal quantification over
type variables is a bad idea, and maybe type variables should, by
default, have pattern matching semantics.  Whether or not this is a
good idea abstractly, the way I imagine it, it would make almost all
existing Haskell code invalid, so it can't be what you're proposing.

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

On Thu, May 03, 2001 at 04:25:45PM -0400, Alan Bawden wrote:
 Here's a macro I use in my Scheme code all the time.  I write:
 
   (assert ( x 3))
 
 Which macro expands into:
 
   (if (not ( x 3))
   (assertion-failed '( x 3)))
 
 Where `assertion-failed' is a procedure that generates an appropriate error
 message.  The problem being solved here is getting the asserted expression
 into that error message.  I don't see how higher order functions or lazy
 evaluation could be used to write an `assert' 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 than the literal
expression; the macro can't do the former.

--Dylan Thurston
  [EMAIL PROTECTED]


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



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' - c
 ...
 -- zipWith is similar to map, only more complicated:
 class ZipWith c1 a1 c2 a2 c a
 | c1 - a1, c2 - a2, c - a,
   c1 a - c, c a1 - c1, c2 a - c, c a2 - c2
 where
 zipWith :: (a1 - a2 - a) - c1 - c2 - c
 ...

You raise many interesting question, but let me ask about one: why the
specific choice of functional dependencies above?  Why is "c' a - c"
necessary for Map?  Why doesn't ZipWith include, e.g., "c1 a2 - c2"?

(I don't have a lot of experience with these functional
dependencies...)

___
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

On Fri, Feb 16, 2001 at 05:13:10PM +, Marcin 'Qrczak' Kowalczyk wrote:
 Fri, 16 Feb 2001 04:14:24 -0800, Simon Peyton-Jones [EMAIL PROTECTED] pisze:
  Here I think the right thing is to say that desugaring for boolean
  constructs uses a function 'if' assumed to have type
  if :: forall b. Bool - b - b - b
 
 What if somebody wants to make 'if' overloaded on more types than
 some constant type called Bool?
 
 class Condition a where
 if :: a - b - b - b

(Note that Hawk does almost exactly this.)

 Generally I don't feel the need of allowing to replace if, Bool and
 everything else with custom definitions, especially when there is no
 single obvious way.

Why not just let

  if x then y else z

be syntactic sugar for

  Prelude.ifThenElse x y z

when some flag is given?  That allows a Prelude hacker to do whatever
she wants, from the standard

  ifThenElse :: Bool - x - x - x
  ifThenElse True x _ = x
  ifThenElse True _ y = y

to something like

  class (Boolean a) = Condition a b where
 ifThenElse :: a - b - b - b

("if" is a keyword, so cannot be used as a function name.  Hawk uses
"mux" for this operation.)

Compilers are good enough to inline the standard definition (and
compile it away when appropriate), right?

Pattern guards can be turned into "ifThenElse" as specified in section
3.17.3 of the Haskell Report.  Or maybe there should be a separate
function "evalGuard", which is ordinarily of type
  evalGuard :: [(Bool, a)] - a - a
(taking the list of guards and RHS, together with the default case).

It's less clear that compilers 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-14 Thread Dylan Thurston

On Wed, Feb 14, 2001 at 08:10:39AM -0800, Andrew Kennedy wrote:
 To be frank, the poster that you cite doesn't know what he's talking
 about. He makes two elementary mistakes:

Quite right, I didn't know what I was talking about.  I still don't.
But I do hope to learn.

 (a) attempting to encode dimension/unit checking in an existing type
 system;

We're probably thinking about different contexts, but please see the
attached file (below) for a partial solution.  I used Hugs' dependent
types to get type inference. This makes me uneasy, because I know that
Hugs' instance checking is, in general, not decidable; I don't know if
the fragment I use is decidable.  You can remove the dependent types,
but then you need to type all the results, etc., explicitly.  This
version doesn't handle negative exponents; perhaps what you say here:

 As others have pointed out, (a) doesn't work because the algebra of
 units of measure is not free - units form an Abelian group (if
 integer exponents are used) or a vector space over the rationals (if
 rational exponents are used) and so it's not possible to do
 unit-checking by equality-on-syntax or unit-inference by ordinary
 syntactic unification. ...

is that I won't be able to do it?

Note that I didn't write it out, but this version can accomodate
multiple units of measure.

 (b) not appreciating the need for parametric polymorphism over
 dimensions/units.
 ...  Furthermore, parametric polymorphism is
 essential for code reuse - one can't even write a generic squaring
 function (say) without it.

I'm not sure what you're getting at here; I can easily write a
squaring function in the version I wrote.  It uses ad-hoc polymorphism
rather than parametric polymorphism.  It also gives much uglier
types; e.g., the example from your paper 
  f (x,y,z) = x*x + y*y*y + z*z*z*z*z
gets some horribly ugly context:
f :: (Additive a, Mul b c d, Mul c c e, Mul e c b, Mul d c a, Mul f f a, Mul g h a, 
Mul h h g) = (f,h,c) - a

Not that I recommend this solution, mind you.  I think language
support would be much better.  But specific language support for units
rubs me the wrong way: I'd much rather see a general notion of types
with integer parameters, which you're allowed to add.  This would be
useful in any number of places.  Is this what you're suggesting below?

 To turn to the original question, I did once give a moment's thought
 to the combination of type classes and types for units-of-measure. I
 don't think there's any particular problem: units (or dimensions)
 are a new "sort" or "kind", just as "row" is in various proposals
 for record polymorphism in Haskell. As long as this is tracked
 through the type system, everything should work out fine. Of course,
 I may have missed something, 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 nice basis for a free Abelian group with a few
distinguished elements.  Has any progress been made on that?

Best,
Dylan Thurston


module Dim3 where
default (Double)
infixl 7 ***
infixl 6 +++

data Zero = Zero
data Succ x = Succ x

class Peano a where
  value :: a - Int
  element :: a
instance Peano Zero where
  value Zero = 0 ; element = Zero
instance (Peano a) = Peano (Succ a) where
  value (Succ x) = value x + 1 ; element = Succ element

class (Peano a, Peano b, Peano c) = PeanoAdd a b c | a b - c
instance (Peano a) = PeanoAdd Zero a a
instance (PeanoAdd a b c) = PeanoAdd (Succ a) b (Succ c)

data (Peano a) = Dim a b = Dim a b deriving (Eq)

class Mul a b c | a b - c where (***) :: a - b - c
instance Mul Double Double Double where (***) = (*)
instance (Mul a b c, PeanoAdd d e f) = Mul (Dim d a) (Dim e b) (Dim f c) where
  (Dim _ a) *** (Dim _ b) = Dim element (a *** b)
instance (Show a, Peano b) = Show (Dim b a) where
  show (Dim b a) = show a ++ " d^" ++ show (value b)

class Additive a where
  (+++) :: a - a - a
  zero :: a
instance Additive Double where
  (+++) = (+) ; zero = 0
instance (Peano a, Additive b) = Additive (Dim a b) where
  Dim a b +++ Dim c d = Dim a (b+++d)
  zero = Dim element zero

scalar :: Double - Dim Zero Double
scalar x = Dim Zero x
unit = scalar 1.0
d = Dim (Succ Zero) 1.0

f (x,y,z) = x***x +++ y***y***y +++ z***z***z***z***z



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 in my programs.  What are
the chances that the usability issues will be addressed?  (The main
one is all the fromInteger's, I think.)

   class (Real a, Floating a) = RealFrac a where
   -- lifted directly from Haskell 98 Prelude
   properFraction   :: (Integral b) = a - (b,a)
   truncate, round  :: (Integral b) = a - b
   ceiling, floor   :: (Integral b) = a - b
 These should be SmallIntegral.

It could be either one, since they produce the type on output (it
calls fromInteger).  I changed it, on the theory that it might be less
confusing.  But it should inherit from SmallReal.  (Oh, except then
RealFloat inherits from SmallReal, which it shouldn't have to.  Gah.)

  For an instance of RealIntegral a, it is expected that a `quot` b
  will round towards minus infinity and a `div` b will round towards 0.
 The opposite.

Thanks.

   class (Real a) = SmallReal a where
   toRational :: a - Rational
   class (SmallReal a, RealIntegral a) = SmallIntegral a where
   toInteger :: a - Integer
 ...
 I find names of these classes unclear: Integer is not small integral,
 it's big integral (as opposed to Int)! :-)

I agree, but I couldn't think of anything better.  I think this end of
the heirarchy (that inherits from Real) could use some more work.

RealIntegral and SmallIntegral could possibly be merged, except that
it violates the principle of not combining semantically disparate
operations in a single class.

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-13 Thread Dylan Thurston

On Mon, Feb 12, 2001 at 12:26:35AM +, Marcin 'Qrczak' Kowalczyk wrote:
 I must say I like it. It has a good balance between generality and
 usefulness / convenience.
 
 Modulo a few details, see below.
 
   class (Num a, Additive b) = Powerful a b where
   (^) :: a - b - a
   instance (Num a) = Powerful a (Positive Integer) where
   a ^ 0 = one
   a ^ n = reduceRepeated (*) a n
   instance (Fractional a) = Powerful a Integer where
   a ^ n | n  0 = recip (a ^ (negate n))
   a ^ n = a ^ (positive n)
 
 I don't like the fact that there is no Powerful Integer Integer.
 Since the definition on negative exponents really depends on the first
 type but can be polymorphic wrt. any Integral exponent, I would make
 other instances instead:
 
 instance RealIntegral b  = Powerful Int   b
 instance RealIntegral b  = Powerful Integer   b
 instance (Num a, RealIntegral b) = Powerful (Ratio a) b
 instancePowerful Float Int
 instancePowerful Float Integer
 instancePowerful Float Float
 instancePowerful DoubleInt
 instancePowerful DoubleInteger
 instancePowerful DoubleDouble

OK, I'm slow.  I finally understand your point here.  I might leave
off a few cases, and simplify this to

instance Powerful Int Int
instance Powerful Integer Integer
instance (Num a, SmallIntegral b) = Powerful (Ratio a) b
instance Powerful Float Float
instance Powerful Double Double
instance Powerful Complex Complex

(where "SmallIntegral" is a class that contains toInteger; "small" in
the sense that it fits inside an Integer.)  All of these call one of 3
functions:
  postivePow :: (Num a, SmallIntegral b) = a - b - a
  integerPow :: (Fractional a, SmallIntegral b) = a - b - a
  analyticPow :: (Floating a) = a - a - a
(These 3 functions might be in a separate module from the Prelude.)
Consequences: you cannot, e.g., raise a Double to an Integer power
without an explicit conversion 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



Clean numeric system?

2001-02-12 Thread Dylan Thurston

On Mon, Feb 12, 2001 at 04:40:06PM +, Jerzy Karczmarczuk wrote:
 This is the way I program in Clean, where there is no Num, and (+), (*),
 zero, abs, etc. constitute classes by themselves. ...

I've heard Clean mentioned before in this context, but I haven't found
the Clean 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?

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-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 Integer and have everything else work.
 No, because it overlaps with Powerful a Integer (the constraint on a
 doesn't matter for determining if it overlaps).

Point.  Thanks.  Slightly annoying.

   Then the second argument of (^) is always arbitrary RealIntegral,
  
  Nit: the second argument should be an Integer, not an arbitrary
  RealIntegral.
 
 Of course not. (2 :: Integer) ^ (i :: Int) makes perfect sense.

But for arbitrary RealIntegrals it need not make sense.

Please do not assume that
  toInteger :: RealIntegral a = a - Integer
  toInteger n | n  0 = toInteger negate n
  toInteger 0 = 0
  toInteger n | n  0 = 1 + toInteger (n-1)
(or the more efficient version using 'even') terminates (in principle)
for all RealIntegrals, at least with the definition as it stands in my
proposal.  Possibly toInteger should be added; then (^) could have the
type you suggest.  For usability issues, I suppose it should.  (E.g.,
users will want to use Int ^ Int.)

OK, I'm convinced of the necessity of toInteger (or an equivalent).
I'll fit it in.

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-12 Thread Dylan Thurston

On Sun, Feb 11, 2001 at 09:17:53PM -0800, William Lee Irwin III wrote:
 Consider taking of the residue of a truly infinite member of Z[[x]]
 mod an ideal generated by a polynomial, e.g. 1/(1-x) mod (1+x^2).
 You can take the residue of each term of 1/(1-x), so x^(2n) - (-1)^n
 and x^(2n+1) - (-1)^n x, but you end up with an infinite number of
 (nonzero!) residues to add up and hence encounter the troubles with
 processes not being finite that I mentioned.

Sorry, isn't (1+x^2) invertible in Z[[x]]?

 I think it's nice to have the Cauchy principal value versions of things
 floating around.  I know at least that I've had call for using the CPV
 of exponentiation (and it's not hard to contrive an implementation),
 but I'm almost definitely an atypical user. (Note, (**) does this today.)

Does Cauchy Principal Value have a specific definition I should know?
The Haskell report refers to the APL language report; do you mean that
definition?

For the Complex class, that should be the choice.

 I neglected here to add in the assumption that (=) was a total relation,
 I had in mind antisymmetry of (=) in posets so that element isomorphism
 implies equality. Introducing a Poset class where elements may be
 incomparable appears to butt against some of the bits where Bool is
 hardwired into the language, at least where one might attempt to use a
 trinary logical type in place 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, Feb 11, 2001 at 10:56:29PM -0500, Dylan Thurston wrote:
  But to define = in terms of meet and join you already need Eq!
  
x = y === meet x y == y
 
 I don't usually see this definition of (=), and it doesn't seem like
 the natural way to go about defining it on most machines. The notion
 of the partial (possibly total) ordering (=) seems to be logically
 prior to that of the meet to me. The containment usually goes:

It may be logically prior, but computationally it's not...  Note that
the axioms for lattices can be stated either in terms of the partial
ordering, or in terms of meet and join.

(In a completely fine-grained ordering heirarchy, I would have the
equation I gave above as a default definition for =, with the
expectation that most users would want to override it.  Compare my
fromInteger default definition.)

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,
Dylan Thurston


Revisiting the Numeric Classes
--
The Prelude for Haskell 98 offers a well-considered set of numeric
classes which cover the standard numeric types (Integer, Int,
Rational, Float, Double, Complex) quite well.  But they offer limited
extensibility and have a few other flaws.  In this proposal we will
revisit these classes, addressing the following concerns:

(1) The current Prelude defines no semantics for the fundamental
operations.  For instance, presumably addition should be
associative (or come as close as feasible), but this is not
mentioned anywhere.

(2) There are some superfluous superclasses.  For instance, Eq and
Show are superclasses of Num.  Consider the data type

 data IntegerFunction a = IF (a - Integer)

One can reasonably define all the methods of Num for
IntegerFunction a (satisfying good semantics), but it is
impossible to define non-bottom instances of Eq and Show.

In general, superclass relationship should indicate some semantic
connection between the two classes.

(3) In a few cases, there is a mix of semantic operations and
representation-specific operations.  toInteger, toRational, and
the various operations in RealFloating (decodeFloat, ...) are the
main examples.

(4) In some cases, the hierarchy is not finely-grained enough:
operations that are often defined independently are lumped
together.  For instance, in a financial application one might want
a type "Dollar", or in a graphics application one might want a
type "Vector".  It is reasonable to add two Vectors or Dollars,
but not, in general, reasonable to multiply them.  But the
programmer is currently forced to define a method for (*) when she
defines a method for (+).

In specifying the semantics of type classes, I will state laws as
follows:
  (a + b) + c === a + (b + c)
The intended meaning is extensional equality: the rest of the program
should behave in the same way if one side is replaced with the
other.  Unfortunately, the laws are frequently violated by standard
instances; the law above, for instance, fails for Float:

  (1.0 + (-1.0)) + 1.0 = 1.0
  1.0 + ((-1.0) + 1.0) = 0.0

Thus these laws should be interpreted as guidelines rather than
absolute rules.  In particular, the compiler is not allowed to use
them.  Unless stated otherwise, default definitions should also be
taken as laws.

This version is fairly conservative.  I have retained the names for
classes with similar functions as far as possible, I have not made
some distinctions that could reasonably be made, and I have tried to
opt for simplicity over generality.  The main non-conservative change
is the Powerful class, which allows a unification of the Haskell 98
operators (^), (^^), and (**).  There are some problems with it, but I
left it in because it might be of interest.  It is very easy to change
back to the Haskell 98 situation.

I sometimes use Simon Peyton Jones' pattern guards in writing
functions.  This can (as always) be transformed into Haskell 98
syntax.

 module NumPrelude where
 import qualified Prelude as P
 -- Import some standard Prelude types verbatim verbandum
 import Prelude(Bool(..),Maybe(..),Eq(..),Either(..),Ordering(..),
Ord(..),Show(..),Read(..),id)

 infixr 8  ^
 infixl 7  *
 infixl 7 /, `quot`, `rem`, `div`, `mod`
 infixl 6  +, -

 class Additive a where
 (+), (-) :: a - a - a
 negate   :: a - a
 zero :: a

  -- Minimal definition: (+), zero, and (negate or (-1))
 negate a = zero - a
 a - b= a + (negate b)

Additive a encapsulates the notion of a commutative group, specified
by the following laws:

  a + b === b + a
   (a + b) + c) === a + (b + c)
   zero + a === a
 a + (negate a) === 0

Typical examples include integers, dollars, and vectors.

 class (Additive a) = Num a where
 (*) :: a - a - a
 one :: a
 fromInteger :: Integer - a

   -- Minimal definition: (*), one
 fromInteger 0 = zero
 fromInteger n | n  0 = negate (fromInteger (-n))
 fromInteger n | n  0 = reduceRepeat (+) one n

Num encapsulates the mathematical structure of a (not necessarily
commutative) ring, with the laws

  a * (b * c) === (a * b) * c
  one * a === a
  a * one === a
  a * (b + c) === a * b + a * c

Typical examples include integers, matrices, and quaternions.

"reduceRepeat op a n" is an auxiliary function that, for an
associative operation "op", computes the same value as

  reduceRepeat op a n = foldr1 op (repeat n a)

bu

Re: A sample revised prelude for numeric classes

2001-02-11 Thread Dylan Thurston

Thanks for the comments!

On Mon, Feb 12, 2001 at 12:26:35AM +, Marcin 'Qrczak' Kowalczyk wrote:
 I don't like the fact that there is no Powerful Integer Integer.

Reading this, it occurred to me that you could explictly declare an
instance of Powerful Integer Integer and have everything else work.

 Then the second argument of (^) is always arbitrary RealIntegral,

Nit: the second argument should be an Integer, not an arbitrary
RealIntegral.

   class (Real a, Floating a) = RealFrac a where
   -- lifted directly from Haskell 98 Prelude
   properFraction   :: (Integral b) = a - (b,a)
   truncate, round  :: (Integral b) = a - b
   ceiling, floor   :: (Integral b) = a - b
 
 Should be RealIntegral instead of Integral.

Yes.  I'd actually like to make it Integer, and let the user compose
with fromInteger herself.

 Perhaps RealIntegral should be called Integral, and your Integral
 should be called somewhat differently.

Perhaps.  Do you have suggestions for names?  RealIntegral is what
naive users probably want, but Integral is what mathematicians would
use (and call something like an integral domain).

   class (Real a, Integral a) = RealIntegral a where
   quot, rem:: a - a - a   
   quotRem  :: a - a - (a,a)
  
 -- Minimal definition: toInteger
 
 You forgot toInteger.

Oh, right.  I actually had it and then deleted it.  On the one hand,
it feels very implementation-specific to me, comparable to the
decodeFloat routines (which are useful, but not generally
applicable).  On the other hand, I couldn't think of many examples
where I really wouldn't want that operation (other than monadic
numbers, that, say, count the number of operations), and I couldn't
think of a better place to put it.

You'll notice that toRational was similarly missing.

My preferred solution might still be the Convertible class I mentioned
earlier.  Recall it was
  class Convertible a b where
  convert :: a - b
maybe with another class like
  class (Convertible a Integer) = ConvertibleToInteger a where
  toInteger :: a - Integer
  toInteger = convert
if the restrictions on instance 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



Re: A sample revised prelude for numeric classes

2001-02-11 Thread Dylan Thurston
al 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



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: 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: '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 instance contexts must
  constrain only type variables, which ensures that context reduction
  terminates (but is sometimes overly restrictive). There is ghc's
  flag -fallow-undecidable-instances which relaxes this restriction,
  at the cost of undecidability.
 
 Ah!  Thanks for reminding me; I've been using Hugs, which allows these
 instances.  Is there no way to relax this restriction while
 maintaining undecidability?

After looking up the Jones-Jones-Meijer paper and thinking about it
briefly, it seems to me that the troublesome cases (when "reducing" a
context gives a more complicated context) can only happen with type
constructructors, and not with simple types.  Would this work?  I.e.,
if every element of an instance context is required to be of the form
  C a_1 ... a_n,
with each a_i either a type variable or a simple type, is type
checking decidable?  (Probably I'm missing something.)

If this isn't allowed, one could still work around the problem:
  class (Convertible Integer a) = ConvertibleFromInteger a
at the cost of sticking in nuisance instance declarations.

Note that this problem arises a lot.  E.g., suppose I have
  class (Field k, Additive v) = VectorSpace k v ...
and then I want to talk about vector spaces over Float.

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



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



(no subject)

2001-02-07 Thread Dylan Thurston



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



Re: Revamping the numeric classes

2001-02-07 Thread Dylan Thurston

Other people have been making great points for me.  (I particularly
liked the example of Dollars as a type with addition but not
multiplication.)  One point that has not been made: given a class
setup like

class Additive a where
  (+) :: a - a - a
  (-) :: a - a - a
  negate :: a - a
  zero :: a

class Multiplicative a where
  (*) :: a - a - a
  one :: a

class (Additive a, Multiplicative a) = Num a where
  fromInteger :: Integer - a

then naive users can continue to use (Num a) in contexts, and the same
programs will continue to work.[1]

(A question in the above context is whether the literal '0' should be
interpreted as 'fromInteger (0::Integer)' or as 'zero'.  Opinions?)

On Wed, Feb 07, 2001 at 06:27:02PM +1300, 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.

Why doesn't your argument show that 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.



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