Tuples or Record

2003-08-18 Thread Frederic BELLOC
Hello,
When I have started my project, I use a Tuples but i would know if it
is possible to create a record such C or Ocaml provide. I mean creating
a structure  where variables are accessible by a '.' or something
like that.
-- 
BELLOC Frederic
EPITA 2005 STUDENT
C, socks and sun !

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


Re: Tuples or Record

2003-08-18 Thread Keith Wansbrough
 Hello,
 When I have started my project, I use a Tuples but i would know if it
 is possible to create a record such C or Ocaml provide. I mean creating
 a structure  where variables are accessible by a '.' or something
 like that.

Yes.  Like this:

  data Tree a = Node { key :: Int,
   val :: a,
   left, right :: Tree a }
  | Nil deriving Show
  
  inorder :: Tree a - [(Int,a)]
  inorder (Node {key = k, val = v, left = l, right = r})
= inorder l ++ [(k,v)] ++ inorder r
  inorder Nil
= []
  
  inorder' :: Tree a - [(Int,a)]
  inorder' n@(Node {}) = inorder' (left n) ++ [(key n,val n)] ++ inorder' (right n)
  inorder' Nil = []
  
  insert :: Tree a - (Int,a) - Tree a
  insert Nil (k,v)
= Node { key = k, val = v, left = Nil, right = Nil }
  insert n@(Node {}) (k,v)
= if k  key n then
n { left = insert (left n) (k,v) }
  else
n { right = insert (right n) (k,v) }
  
  t :: Tree String
  t = foldl insert Nil [(3,three),(1,one),(4,two),(5,five)]

Note that field access is by key n, rather than by n.key as in
other languages.  key is just a function, like any other: it has
type Tree a - Int.  Records can be constructed directly, as in the
Nil case of insert, or based on another record with changes specified,
as in the Node case of insert.  Pattern-matching can match none, some,
or all of the fields, in any order.

Because field names become functions, they live in the global name
space.  This means you can't use the same field name in two different
data types - so it is usual to prefix the field name with an
abbreviation of the data type name, such as

  data BinTree a = BinTree { btKey :: Int }

But you can use the same field in multiple constructors of the *same*
data type, as in:

  data Shape a = Point   { loc :: (Int,Int) }
   | Square  { loc :: (Int,Int),
   size :: Int }
   | Circle  { loc :: (Int,Int),
   size :: Int }
   | Ellipse { loc :: (Int,Int),
   size :: Int,
   eccentricity :: Float
 }

HTH.

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


Re: More type design questions

2003-08-18 Thread Andre Pang
On Tuesday, August 19, 2003, at 03:33  AM, Konrad Hinsen wrote:

On Monday 18 August 2003 19:10, Andre Pang wrote:

This seems to work (with -fglasgow-exts):

module Foo where

class Vect v where
   (+) :: v - v - v
data Vector a = Vector a a a
   deriving (Show, Eq)
instance Floating a = Vect (Vector a) where
   (+) (Vector x1 y1 z1) (Vector x2 y2 z2)
  = Vector (x1+x2) (y1+y2) (z1+z2)
instance Floating a = Vect [Vector a] where
   (+) l1 l2 = zipWith (+) l1 l2
*Foo (Vector 5 6 7) + (Vector 1 2 3)
Vector 6.0 8.0 10.0
*Foo [Vector 1 2 3, Vector 10 20 30] + [Vector 100 200 300, Vector 
4
5 6]
[Vector 101.0 202.0 303.0,Vector 14.0 25.0 36.0]

... or does example not do something which you want it to do?
Well, yes, because my original example was cut down to illustrate the 
problem
I had.  The full version of the class Vect is

class Vect v a where
  (+) :: Floating a = v a - v a - v a
  (-) :: Floating a = v a - v a - v a
  (*) :: Floating a = a - v a - v a
I need the parametrization on a in order to be able to define the type 
of
scalar multiplication.

I do have the choice of class Vect v or class Vect v a, both seem 
to do
the same in this context, but in both cases v has the role of a type
constructor.
Ah.  What about the code I gave above, and in addition to that:

class (Floating a, Vect v) = VectMult v a where
  (*) :: a - v - v
instance VectMult (Vector Float) Float where
  (*) n (Vector x y z) = Vector (n*x) (n*y) (n*z)
?

--
% Andre Pang : trust.in.love.to.save
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: More type design questions

2003-08-18 Thread Konrad Hinsen
On Monday 18 August 2003 19:26, Brandon Michael Moore wrote:
 I think what you want are functional dependencies.
...

Bingo! That's what I needed. I had tried something like that before, but I had 
started from a fundamental misunderstanding: I had assumed that

class Vect v a where...

would automatically make 'v' a type constructor, and all my experiments using 
that assumption plus dependencies produced rather useless results.

What I have now satisfies all my needs (at least my current needs...), and it 
works with GHC. Hugs hangs in some places, but I guess that's another problem 
entirely.

 The GHC users guide, the Haskell Wiki, and the paper Type Classes:
 Exploring the Design Space are all good places for more information.

Thanks, I'll look at all that...

Konrad.

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


Re: More type design questions

2003-08-18 Thread Remi Turk
On Mon, Aug 18, 2003 at 07:33:47PM +0200, Konrad Hinsen wrote:
 Well, yes, because my original example was cut down to illustrate the problem 
 I had.  The full version of the class Vect is
 
 class Vect v a where
   (+) :: Floating a = v a - v a - v a
   (-) :: Floating a = v a - v a - v a
   (*) :: Floating a = a - v a - v a
 
 I need the parametrization on a in order to be able to define the type of 
 scalar multiplication.

Would this suffice?

module Foo where

class Vect v a | v - a where
(+), (-):: Floating a = v - v - v
(*)   :: Floating a = a - v - v

data Vector a   = Vector a a a deriving (Show)

instance Vect (Vector a) a where
(+)   = fzipWith (+)
(-)   = fzipWith (-)
(*)   = fmap . (*)


instance Vect [Vector a] a where
(+)   = zipWith (+)
(-)   = zipWith (-)
(*)   = fmap . (*)

instance Functor Vector where
fmap f (Vector x y z)
= Vector (f x) (f y) (f z)

class Functor z = Ziptor z where
fzipWith:: (a - b - c) - z a - z b - z c

instance Ziptor Vector where
fzipWith f (Vector x1 y1 z1) (Vector x2 y2 z2)
= Vector (f x1 x2) (f y1 y2) (f z1 z2)

Hm, did anyone else ever want a Ziptor class? (I didn't, until now ;))

Happy hacking,

Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgp0.pgp
Description: PGP signature


Re: Tuples or Record

2003-08-18 Thread Derek Elkins
On Mon, 18 Aug 2003 16:21:46 +0100
Keith Wansbrough [EMAIL PROTECTED] wrote:

  Hello,
  When I have started my project, I use a Tuples but i would know if
  it is possible to create a record such C or Ocaml provide. I mean
  creating a structure  where variables are accessible by a '.' or
  something like that.
 
 Yes.  Like this:
 
   data Tree a = Node { key :: Int,
val :: a,
left, right :: Tree a }
   | Nil deriving Show
   

hmm, maybe I shouldn't say this, but record syntax does not preclude
positional syntax.  You can still pattern match and construct Node as
if it was defined Node Int a (Tree a) (Tree a), i.e. 
Node 1 foo Nil Nil
or f (Node 0 _ _ _) = ...
Of course, this brings back all the issues of positional notation, so
you may not want to use this... um, ever.
However, one issue with records is that it's possible (or rather easier)
to make partially defined records.  E.g. Node { key = 5 } is legal, and
any attempt to use val/left/right will cause a run-time error.  So this
might be a use for the alternate positional syntax.  Code that uses the
positional syntax to build records will break when fields are added to
the record rather than go on creating broken records (of course, GHC at
least, produces a warning for uninitialized fields).

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