Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-27 Thread Andreas Rossberg

[EMAIL PROTECTED] wrote:


When you type class Foo in Java or C++, it does three things:

1. It declares a new type called Foo.

2. It declares a _set_ of types (i.e. a class).

3. It declares that the type Foo (and all of its subtypes) is a member
of the set of types Foo.


I would add:

4. Define a namespace, also called Foo, for a set of values (and 
probably nested classes).



In Haskell, these three operations are distinct.

1. You declare a new type using data or newtype.

2. You declare a new set of types using class.

3. You declare that a type is a member of a class using instance.


4. You define a new namespace using module.

Cheers,
- Andreas

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


[Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Thomas Nelson
I'm brand new to haskell and I'm having trouble using classes.  The basic idea 
is I want two classes, Sine and MetaSine, that are both instances of ISine. 
This way I can use the act method and recurse through the metasines and sines. 
Here's my code:


module Main
where

class ISine a where
period :: a - Integer
offset :: a - Integer
threshold :: a - Integer
act :: (ISine b) = Integer - a - b
on :: Integer - a - Bool
--on needs offset, period, threshold
on time self = (mod (time-(offset self)) (period self))  (threshold self)

data Sine =
Sine {
period :: Integer,
offset :: Integer,
threshold :: Integer,
letter :: String
}

instance Sine ISine where
act time (Sine self)
|on time self = [letter self]
|otherwise = []


data MetaSine =
MetaSine {
period :: Integer,
offset :: Integer,
threshold :: Integer,
sines :: (ISine a) = [a]
}

instance MetaSine ISine where
act time (MetaSine self)
|on time self  = foldr (++) (map (act time) (sines self))
|otherwise = []

The errors I get involve multiple declarations of period, offset, and 
threshold.


Any help would be greatly appreciated.
-Thomas

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


Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Albert Y. C. Lai
All record fields are in the same namespace, and furthermore this is 
also the same namespace of functions and class methods. In other words 
you cannot have two record types containing the same field name, and you 
cannot have a record field and a function using the same name, and you 
cannot have a record field and a class method using the same name. You 
have to choose some other names for the fields of Sine, and yet some 
other names for the fields of MetaSine.


In instance Sine ISine where ..., you must implement the methods 
period, offset, and threshold, not just act. Similarly for 
instance MetaSine ISine where 


The implementations of method act are syntactically wrong as well as 
semantically wrong. I do not know what is a right implementation. 
Actually given the overly general signature


  act :: (ISine b) = Integer - a - b

I do not think there is any possible implementation at all. I submit 
that you have set a goal too ambitious and too magical.

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


Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread Aaron McDaid

On 2/26/07, Thomas Nelson [EMAIL PROTECTED] wrote:

I'm brand new to haskell and I'm having trouble using classes.  The basic idea
is I want two classes, Sine and MetaSine, that are both instances of ISine.


'class' in Haskell doesn't mean the same as 'class' in C++ or Java. I
found it easier at first to thing of them as:
  A Haskell 'class' is more like a Java interface.
  Haskell types are more like what you might think of as 'class'es.
  Haskell 'instance' means Java 'implement'
  There is no word that means that same as 'instance' from Java/C++
terminology. I suppose we would call them 'values' or something.
Somebody more knowledgeable can describe the etymology of the terms,
but these 3 observations should help.


data Sine =
 Sine {  period :: Integer, offset :: Integer, threshold :: Integer,  
letter :: String}

instance Sine ISine where
 act time (Sine self)
 |on time self = [letter self]
 |otherwise = []


To be honest, I'm not sure what you're trying to do here, so beware of
my advice...
You might want to do this instead:

data Sine = Sine Integer Integer Integer String
instance ISine Sine where   -- note that ISine should come before Sine
 period (Sine p _ _ _ _) = p
 period (Sine _ o _ _ _) = o
-- and so on ...

There can only be a single function called period, which will take a
thing of any type which is an instance of ISine and return an Integer.
So every time you tell Haskell this type is to be an implementation
of ISine you have to write the period function for it as I have done
for Sine here.


-Thomas


Aaron
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread ajb
G'day all.

Quoting Aaron McDaid [EMAIL PROTECTED]:

 'class' in Haskell doesn't mean the same as 'class' in C++ or Java. I
 found it easier at first to thing of them as:
A Haskell 'class' is more like a Java interface.
Haskell types are more like what you might think of as 'class'es.
Haskell 'instance' means Java 'implement'
There is no word that means that same as 'instance' from Java/C++
 terminology. I suppose we would call them 'values' or something.
 Somebody more knowledgeable can describe the etymology of the terms,
 but these 3 observations should help.

When you type class Foo in Java or C++, it does three things:

1. It declares a new type called Foo.

2. It declares a _set_ of types (i.e. a class).

3. It declares that the type Foo (and all of its subtypes) is a member
of the set of types Foo.

In Haskell, these three operations are distinct.

1. You declare a new type using data or newtype.

2. You declare a new set of types using class.

3. You declare that a type is a member of a class using instance.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with record syntax and classes

2007-02-26 Thread ajb
G'day all.

Oh, one more thing.

Quoting Aaron McDaid [EMAIL PROTECTED]:

 Somebody more knowledgeable can describe the etymology of the terms,
[...]

You can think of a type as a set of values.  For example, Bool is the
set { False, True }.  A class, then, is a set of types.

The distinction between set and class comes from the various set
theories (Goedel-Bernays-von Neumann set theory being the most common)
which try to avoid Russell's Paradox.

For those who are don't know about Russell's Paradox, take a look at the
Wikipedia entry before going on:

http://en.wikipedia.org/wiki/Russell%27s_paradox

The idea behind GBN set theory is to distinguish between sets, which
are always well-behaved, and classes, which are not necessarily so
well-behaved.  Russell's Paradox is resolved by setting up your axioms
such that the paradoxical set of all sets with property X is not,
itself, a set, but a class.

By analogy, we call a set of types, or a set of sets, a class.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe