Re: [Haskell-cafe] extensible data types in Haskell?

2008-07-08 Thread Pablo Nogueira
I prefer Bruno's approach, though. It allows meta-level type-checking
of expressions and there's the possibility of closing the extension
with a wrapper:
(References: Generics as a Library and his PhD thesis)

- GADT as a type class (or encode the type as it's fold):

 class Exp e where
 lit  :: TyRange a = a - e a
 plus :: e Int - e Int - e Int
 and  :: e Bool - e Bool - e Bool

- Notice we cannot construct an ill-typed expression, the Haskell
type-checker complains.

- |TyRange| is the class of indices:

class TyRange a
instance TyRange Int
instance TyRange Bool

- The behaviour is given by instances:

newtype Eval a = Eval {eval :: a}

instance Exp Eval where
 lit   = Eval
 plus x y  = Eval (eval x + eval y)
 and  x y  = Eval (eval x  eval y)

Extension is easy:

class Exp e = ExpIf e where
   ifOp :: TyRange a = e Bool - e a - e a - e a

instance ExpIf Eval where
   ifOp c t e = Eval (if (eval c) then (eval t) else (eval e))

class Exp e = ExpMult e where
mult :: e Int - e Int - e Int

instance ExpMult Eval where
mult x y = Eval (eval x * eval y)

- Adding new meta-level types is easy:

instance TyRange a = TyRange [a]
instance TyRange Char

class Exp e = ExpConcat e where
conc :: e [Char] - e [Char] - e [Char]

instance ExpConcat Eval where
conc x y = Eval (eval x ++ eval y)

- Closing expressions is also easy:  wrap around a type and provide
new functions:

data TyRange a = Wrap a = Wrap (forall e. (Exp e, ExpIf e, ExpMult e,
ExpConcat e) = e a)

 evalExp :: TyRange a = Wrap a - a
 evalExp (Wrap x) = eval x

- Some expresions:

Compare:

exp1 :: Exp e = e Int
exp1 = plus (lit 3) (lit 3)
val1 = eval exp1

With:

exp1' :: Eval Int
exp1' = plus (lit 3) (lit 3)
va1'  = eval exp1
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] extensible data types in Haskell?

2008-07-08 Thread David Walker
thanks for everyone's help -- it seems the simplest solution is to use
the Typeable class, existential types and type-safe cast.

Cheers,
Dave

On Sun, Jul 6, 2008 at 9:18 PM, Don Stewart [EMAIL PROTECTED] wrote:
 princedpw:
 Hi all,

 SML conveniently contains the type exn which is an instance of an
 extensible data type.  In other words, unlike normal data types that
 are closed (can't admit new constructors once defined), SML's exn
 type is open, allowing programmers to keep adding new alternatives
 as often as they choose.  Like normal datatypes, the elimination form
 for an extensible data type is a case statement (or match function).

 Friends have told me that Haskell doesn't have extensible data types.
 However, it seems fairly straightforward to code them up using type
 classesthough the solution I'm thinking of has a little bit of
 boilerplate I'd like to scrap (you have to define a new type
 declaration *and* an instance of a type class with a match method)
 and matching occurs through a string comparison (which can lead to
 silly programmer errors if there is accidentally a typo in the
 string).

 You should probably use Typeable here, for the type matching, rather
 than a custom matcher. class Typeable a = Extensible a, this leads to a
 fairly straighforward extensible data type, where the open instance
 definition lets you add variants on the fly.

 Anyway, it's possible with some thought I could come up with a better
 solution, but before worrying about it, I figured I'd ask if anybody
 else already has a package that does this.  It seems like a pretty
 natural feature to want to have.

 There's a number of ways to do this, including fully statically via type
 classes and existential types, or via the Dynamic type.

 Googling for expression problem Haskell will turn up some things. Some
 implementions of open data types in use can be found in xmonad, and the
 extensible exceptions proposal here,


 http://209.85.173.104/search?q=cache:xeXhle5KAqkJ:www.haskell.org/~simonmar/papers/ext-exceptions.pdf

 -- Don

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


Re: [Haskell-cafe] extensible data types in Haskell?

2008-07-07 Thread Ryan Ingram
I like the approach the Data Types a la Carte paper takes to solve
this problem.

There's a small discussion here:
http://wadler.blogspot.com/2008/02/data-types-la-carte.html

Summary: if you model your data types as functors, typeclass machinery
lets you combine them into an extensible whole, while maintaining type
safety.  You then create an interpretation class which allows data
to choose how it interacts with a particular computation.

The biggest weakness is that you need a type annotation at the point
of calling the interpretation function.  An example (leaving out the
library bits):

class Functor a = EvalSimple a where
evalSimple :: a Int - Int
instance (EvalSimple a, EvalSimple b) = EvalSimple (a :+: b) where
evalSimple (Inl a) = evalSimple a
evalSimple (Inr b) = evalSimple b

-- foldExpr :: Functor e = (e a - a) - Expr e - a
-- eval :: EvalSimple e = Expr e - Int
eval e = foldExpr evalSimple e

newtype Val a = Val Int -- trivial functor
instance Functor Val where fmap _ (Val x) = (Val x)
instance EvalSimple Val where evalSimple (Val x) = x
val x = inject (Val x)
-- inject :: a :: e = a (Expr e) - Expr e
-- val :: Val :: e = Int - Expr e


data Add a = Add a a -- pair functor
instance Functor Add where fmap f (Add a b) = Add (f a) (f b)
add a b = inject (Add a b)
instance EvalSimple Add where evalSimple (Add a b) = a + b

-- here is where we need the type annotation
sample :: Expr (Val :+: Add)
sample = add (add (val 1) (val 2)) (val 3)

sampleResult = eval sample  -- is 6

On 7/6/08, David Walker [EMAIL PROTECTED] wrote:
 Hi all,

 SML conveniently contains the type exn which is an instance of an
 extensible data type.  In other words, unlike normal data types that
 are closed (can't admit new constructors once defined), SML's exn
 type is open, allowing programmers to keep adding new alternatives
 as often as they choose.  Like normal datatypes, the elimination form
 for an extensible data type is a case statement (or match function).

 Friends have told me that Haskell doesn't have extensible data types.
 However, it seems fairly straightforward to code them up using type
 classesthough the solution I'm thinking of has a little bit of
 boilerplate I'd like to scrap (you have to define a new type
 declaration *and* an instance of a type class with a match method)
 and matching occurs through a string comparison (which can lead to
 silly programmer errors if there is accidentally a typo in the
 string).

 Anyway, it's possible with some thought I could come up with a better
 solution, but before worrying about it, I figured I'd ask if anybody
 else already has a package that does this.  It seems like a pretty
 natural feature to want to have.

 Thanks in advance,
 Dave
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] extensible data types in Haskell?

2008-07-06 Thread David Walker
Hi all,

SML conveniently contains the type exn which is an instance of an
extensible data type.  In other words, unlike normal data types that
are closed (can't admit new constructors once defined), SML's exn
type is open, allowing programmers to keep adding new alternatives
as often as they choose.  Like normal datatypes, the elimination form
for an extensible data type is a case statement (or match function).

Friends have told me that Haskell doesn't have extensible data types.
However, it seems fairly straightforward to code them up using type
classesthough the solution I'm thinking of has a little bit of
boilerplate I'd like to scrap (you have to define a new type
declaration *and* an instance of a type class with a match method)
and matching occurs through a string comparison (which can lead to
silly programmer errors if there is accidentally a typo in the
string).

Anyway, it's possible with some thought I could come up with a better
solution, but before worrying about it, I figured I'd ask if anybody
else already has a package that does this.  It seems like a pretty
natural feature to want to have.

Thanks in advance,
Dave
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] extensible data types in Haskell?

2008-07-06 Thread Don Stewart
princedpw:
 Hi all,
 
 SML conveniently contains the type exn which is an instance of an
 extensible data type.  In other words, unlike normal data types that
 are closed (can't admit new constructors once defined), SML's exn
 type is open, allowing programmers to keep adding new alternatives
 as often as they choose.  Like normal datatypes, the elimination form
 for an extensible data type is a case statement (or match function).
 
 Friends have told me that Haskell doesn't have extensible data types.
 However, it seems fairly straightforward to code them up using type
 classesthough the solution I'm thinking of has a little bit of
 boilerplate I'd like to scrap (you have to define a new type
 declaration *and* an instance of a type class with a match method)
 and matching occurs through a string comparison (which can lead to
 silly programmer errors if there is accidentally a typo in the
 string).

You should probably use Typeable here, for the type matching, rather
than a custom matcher. class Typeable a = Extensible a, this leads to a
fairly straighforward extensible data type, where the open instance
definition lets you add variants on the fly.

 Anyway, it's possible with some thought I could come up with a better
 solution, but before worrying about it, I figured I'd ask if anybody
 else already has a package that does this.  It seems like a pretty
 natural feature to want to have.

There's a number of ways to do this, including fully statically via type
classes and existential types, or via the Dynamic type.

Googling for expression problem Haskell will turn up some things. Some
implementions of open data types in use can be found in xmonad, and the
extensible exceptions proposal here,


http://209.85.173.104/search?q=cache:xeXhle5KAqkJ:www.haskell.org/~simonmar/papers/ext-exceptions.pdf

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


Re: Extensible data types?

2000-10-20 Thread José Romildo Malaquias

Hello.

I am back with the issue of extensible union types. Basically
I want to extend a data type with new value constructors.
Some members of the list pointed me to the paper

   "Monad Transformers and Modular Interpreters"
   Sheng Liang, Paul Hudak and Mark Jones

The authors suggest using a type constructor to express
the disjoint union of two other types:

   data Either a b = Left a | Right b

which indeed is part of the Haskell 98 Prelude. Then they introduce
a subtype relationship using multiparameter type classes:

   class SubType sub sup where
  inj :: sub - sup -- injection
  prj :: sup - Maybe sub   -- projection

The Either data type consructor is then used to express
the desired subtype relationshipe:

   instance SubType a (Either a b) where
  inj   = Left
  prj (Left x)  = Just x
  prj _ = Nothing

   instance SubType a b = SubType a (Either c b) where
  inj   = Right . inj
  prj (Right x) = prj x
  prj _ = Nothing

The authors implemented their system in Gofer, due to
restrictions in the type class system of Haskell.
But now that there are Haskell extensions to support
multiparametric type classes, that could be implemented
in Haskell.

The above code fails to type check due to instances
overlapping. Hugs gives the following error message:

   ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType"
   *** This instance   : SubType a (Either b c)
   *** Overlaps with   : SubType a (Either a b)
   *** Common instance : SubType a (Either a b)

(I did not check Gofer, but is there a way to solve these
overlapping of instances in it?)

So this is scheme is not going to work with Haskell (extended
with multiparameter type classes).

I would like hear any comments from the Haskell comunity on
this subject. Is there a workaround for the overlapping instances?

Regards.

Romildo
-- 
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Re: Extensible data types?

2000-10-20 Thread Jose Emilio Labra Gayo

 
 The above code fails to type check due to instances
 overlapping. Hugs gives the following error message:
 
In Hugs, there is a flag that you can set to allow overlapping instances

:s +o

In GHC, you can also set

-fallow-overlapping-instances

BTW, I use extensible union types in a "Language prototyping System" that
I am implementing and which compiles with GHC and Hugs (it is based
on Liang, Hudak and Jones paper). 
You can download the source code from 
  "http://lsi.uniovi.es/~labra/LPS/LPS.html"

Best regards, Jose Labra
http://lsi.uniovi.es/~labra




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



Re: Extensible data types?

2000-10-20 Thread S. Doaitse Swierstra

It is exactly for reasons like these that we developped our small
attribute grammar system:

http://www.cs.uu.nl/groups/ST/Software/UU_AG/index.html

Doaitse Swiesrtra

At 7:21 AM -0200 10/20/00, José Romildo Malaquias wrote:
Hello.

I am back with the issue of extensible union types. Basically
I want to extend a data type with new value constructors.
Some members of the list pointed me to the paper

"Monad Transformers and Modular Interpreters"
Sheng Liang, Paul Hudak and Mark Jones

The authors suggest using a type constructor to express
the disjoint union of two other types:

data Either a b = Left a | Right b

which indeed is part of the Haskell 98 Prelude. Then they introduce
a subtype relationship using multiparameter type classes:

class SubType sub sup where
   inj :: sub - sup   -- injection
   prj :: sup - Maybe sub -- projection

The Either data type consructor is then used to express
the desired subtype relationshipe:

instance SubType a (Either a b) where
   inj   = Left
   prj (Left x)  = Just x
   prj _ = Nothing

instance SubType a b = SubType a (Either c b) where
   inj   = Right . inj
   prj (Right x) = prj x
   prj _ = Nothing

The authors implemented their system in Gofer, due to
restrictions in the type class system of Haskell.
But now that there are Haskell extensions to support
multiparametric type classes, that could be implemented
in Haskell.

The above code fails to type check due to instances
overlapping. Hugs gives the following error message:

ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType"
*** This instance   : SubType a (Either b c)
*** Overlaps with   : SubType a (Either a b)
*** Common instance : SubType a (Either a b)

(I did not check Gofer, but is there a way to solve these
overlapping of instances in it?)

So this is scheme is not going to work with Haskell (extended
with multiparameter type classes).

I would like hear any comments from the Haskell comunity on
this subject. Is there a workaround for the overlapping instances?

Regards.

Romildo
--
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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

--
__
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
   P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
   Mail:  mailto:[EMAIL PROTECTED]
   WWW:   http://www.cs.uu.nl/
   PGP Public Key: http://www.cs.uu.nl/people/doaitse/
   tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

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



Re: Extensible data types?

2000-09-28 Thread Peter Achten

At 12:55 26-9-00 -0300, Prof. José Romildo Malaquias wrote:

[...skip...]
This solution works great for the data type, but, at least
to me, it seems to make it too dificult to write functions
over ExprExt.

Consider for example the original version of the addition
operation (somehow simplified) on the original Expr data type

 data Fn = Sum | Pro | Pow

 data Expr = Int Integer | Cte String | Var String | App Fn
[Expr]

 add :: Expr - Expr - Expr
 add (Int x) (Int y) = Int (x + y)
 add (Int 0) x = x
 add x (Int 0) = x
 add x
y = App Sum [x,y]
[...skip...]

The problem with this function definition is that it, if you would
transform it using the scheme as I suggested earlier, returns results of
different types depending on the *value* of the first argument. You can
see this in the first two alternatives of add. If both arguments are of
type INT, then the result is of type INT. If the first argument has value
(INT 0) then the result has the same type as the second argument (which
can be CTE, VAR, or APP). Basically, it is the same problem as giving a
type to a function f which result type depends on its argument
value:

f 0 = Zero
f 1 = 1.0
f 2 = '2'

I don't think this can be solved readily in Haskell. It sounds as if you
need something like dynamic typing. I have added a reference [1] below
(for Clean; anybody out here with refs to dynamics in Haskell?). In any
case, that will not help you *right now*.

Finally, you remark:
The use of an existentialy quantified
variable
would solve this,

 data Expr
=
Int Integer

|
Cte String

|
Var String
 |
forall a . (FnExt fn) = App fn Expr

but would make it to difficult to extend the
data type with new value constructors.
I am not sure if this will really help you. This will bring you back to
your initial problem: namely to extend constructors. In addition, the
solution also relies on the class member functions of FnExt.

Regards,
Peter

--
[1] Pil, M.R.C. (1999), Dynamic types and type
dependent functions, In Proc. of Implementation of
Functional Languages (IFL '98), London, U.K., Hammond, Davie and
Clack Eds., Springer-Verlag, Berlin, Lecture Notes in Computer Science
1595, pp 169-185. 



RE: Extensible data types?

2000-09-28 Thread Chris Angus

How about defining a Datatype Fn which defines all functions
and building in terms of this

data Expr = Int Integer
  | Cte String
  | Var String
  | App Fn [Expr] deriving (Show)

data Fn = Fn String
| Combiner String
| Compose Fn Fn deriving (Show)

class (Show a) = Fns a where
 mkFn :: a - Fn
 mkFn x = Fn (show x)
data Basic = Negate deriving (Show)
data Combining = Sum | Prod deriving (Show)
data Trig  = Sin | Cos | Tan deriving (Show)

instance Fns Trig
instance Fns Basic
instance Fns Combining where
 mkFn x = Combiner (show x)

sine= mkFn Sin
cosine  = mkFn Cos
tangent = mkFn Tan
neg  = mkFn Negate

compose :: Fn - Fn - Fn
compose x y = Compose x y

match (Fn x) (Fn y) = x == y
match (Combiner x) (Combiner y) = x == y
match (Compose x y) (Compose a b) = match x a  ma
match _ _ = False

diff :: Fn - Fn
diff fn | match fn sine   = cosine
diff fn | match fn cosine = neg `compose` cosine




 -Original Message-
 From: Jose Romildo Malaquias [mailto:[EMAIL PROTECTED]]
 Sent: 25 September 2000 12:14
 To: Chris Angus
 Cc: [EMAIL PROTECTED]
 Subject: Re: Extensible data types?
 
 
 On Mon, Sep 25, 2000 at 11:37:24AM +0100, Chris Angus wrote:
  I've not seen this before,
  
  out of interest, why would you want/need such a thing?
   
   Is there any Haskell implementation that supports
   extensible data types, in which new value constructors
   can be added to a previously declared data type,
   like
   
 data Fn = Sum | Pro | Pow
 ...
 extend data Fn = Sin | Cos | Tan
   
   where first the Fn datatype had only three values,
   (Sum, Pro and Pow) but later it was extended with
   three new values (Sin, Cos and Tan)?
 
 I want this to make a system I am workin on flexible.
 Without it, my system is going to be too rigid.
 
 I am working on an Computer Algebra system to transform
 mathematic expressions, possibly simplifing them. There
 is a data type to represent the expressions:
 
   data Expr = Int Integer
   | Cte String
   | Var String
   | App Fn [Expr]
 
 An expression may be an integer, a named constante (to
 represent "known" contantes like pi and e), a variable
 or an application. An application has a functor (function
 name) and a list of arguments. The functor is introduced
 with
 
   data Fn = Sum | Pro | Pow
 
 meaning the application may be a sum, a product or a
 power.
 
 The project should be modular. So there are modules to
 deal with the basic arithmetic and algebraic transformations
 involving expressions of the type above. But there are
 optional modules to deal with trigonometric expressions,
 logarithms, vectors, matrices, derivatives, integrals,
 equation solving, and so on. These should be available as
 a library where the programmer will choose what he
 needs in his application, and he should be able to
 define new ones to extend the library. So these modules
 will certainly need to extend the bassic types above.
 
 If it is really impossible (theoriticaly or not implemented)
 then I will have to try other ways to implement the idea.
 
 The functions manipulating the expressions also should be
 extensible to accomodate new algorithms. The extensions
 is in a form of hooks (based on the Fn component of an
 application function) in the main algorithms.
 
 Romildo
 -- 
 Prof. José Romildo Malaquias [EMAIL PROTECTED]
 Departamento de Computação
 Universidade Federal de Ouro Preto
 Brasil
 




Re: Extensible data types?

2000-09-28 Thread Jose Romildo Malaquias

On Thu, Sep 28, 2000 at 12:00:11PM +0100, Chris Angus wrote:
 How about defining a Datatype Fn which defines all functions
 and building in terms of this
 
 data Expr = Int Integer
   | Cte String
   | Var String
   | App Fn [Expr] deriving (Show)
 
 data Fn = Fn String
 | Combiner String
 | Compose Fn Fn deriving (Show)
 
 class (Show a) = Fns a where
  mkFn :: a - Fn
  mkFn x = Fn (show x)
 data Basic = Negate deriving (Show)
 data Combining = Sum | Prod deriving (Show)
 data Trig  = Sin | Cos | Tan deriving (Show)
 
 instance Fns Trig
 instance Fns Basic
 instance Fns Combining where
  mkFn x = Combiner (show x)
 
 sine= mkFn Sin
 cosine  = mkFn Cos
 tangent = mkFn Tan
 neg  = mkFn Negate
 
 compose :: Fn - Fn - Fn
 compose x y = Compose x y
 
 match (Fn x) (Fn y) = x == y
 match (Combiner x) (Combiner y) = x == y
 match (Compose x y) (Compose a b) = match x a  ma
 match _ _ = False

Your solution should work, but the match operation, would be
too common in my system (it would be needed in order to
check the class of applications) and as it is based on
string (list of characters) equality, it would made the
system inefficient. If it was easy to keep this
structure, but obtain an unique integer (instead of
string) for each functor, this solution would be good enough
for me, as integer comparisons are much more efficient
than string comparison.

 diff :: Fn - Fn
 diff fn | match fn sine   = cosine
 diff fn | match fn cosine = neg `compose` cosine

You forgot to differentiate the arguments of the function:

  data Diff = Diff deriving Show

  instance Fns Diff

  diffE :: Expr - Expr - Expr
  diffE (Int _) _ = Int 0
  diffE (Cte _) _ = Int 0
  diffE (Var x) (Var y)
 | x == y= Int 1
 | otherwise = Int 0
  diffE (App fn xs) (Var y) = App (diff fn) (map diffE xs)
  diffE x y = App Diff [x,y]

would be better (yeat too simplistic).

Romildo
-- 
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




Re: Extensible data types?

2000-09-26 Thread Peter Achten

At 11:18 25-9-00 -0300, Prof. José Romildo Malaquias wrote:

[...skip...]
And then how would I define data types based on Fn ? The math expressions
my system has to deal is expressed as something like

 data Expr = Int
   | App Fn [Expr]

I cannot just define

 data (FnExt fn) = Expr fn = Int
| App fn [Expr fn]

because the second value constructor would not be general enough
and the values of the second form would be all sums, or all products,
and so on.

[...skip...]

Anny comments?


The trick is to construct all of your recursive data structures also in an 
overloaded fassion. I have worked out your example (and checked it with GHC 
4.08.1). See below.

The first part is what I said in my last e-mail. The second part handles 
extensible expressions. You go through the same routine: (1) define an 
extensible type constructor class for Expr (ExprExt), (2) split your Expr 
data alternatives into separate type constructors (INT, CTE, VAR, and APP), 
and (3) define these types as instances of ExprExt.

The interesting case is obviously (APP fn expr). As you can see below, you 
express to what type constructor classes the parameters should belong.

In addition, we have found it to be convenient in the Object I/O Library to 
have a number of additional type constructors that are declared to be 
instances, namely to construct lists (List) and pairs (Pair). See also below.

Regards,

Peter

==
-- (1) for Fn
class FnExt a where
  -- Define your class member functions here
-- (2)
data Sum = Sum
data Pro  = Pro
data Pow  = Pow
-- (3)
instance FnExt Sum where fn x = x
instance FnExt Pro where fn x = x
instance FnExt Pow where fn x = x

-- (1) for Expr
class ExprExt a where
  -- Define your class member functions here
-- (2)
data INT = INT Integer
data CTE = CTE String
data VAR = VAR String
data APP fn expr = APP fn expr
-- (3)
instance ExprExt INT where ...
instance ExprExt CTE where ...
instance ExprExt VAR where ...
instance (FnExt fn,ExprExt expr) = ExprExt (APP fn expr) where ...

-- Convenient types when constructing lists and pairs:

data List expr  -- Lists for convenience when you do have expressions 
of same type
 = List [expr]
infixr 9 :^:-- This is basically a tuple, but you can leave out 
brackets
data Pair expr1 expr2
 = expr1 :^: expr2

instance (ExprExt e) = ExprExt (List e) where ...
instance (ExprExt e1,ExprExt e2) = ExprExt (Pair e1 e2) where ...





Re: Extensible data types?

2000-09-26 Thread Jose Romildo Malaquias

On Mon, Sep 25, 2000 at 02:42:20PM +0200, John Hörnkvist wrote:
 If you use Hugs -- and possibly GHC -- you might be able to use the  
 "Either" constructor for subtyping. I first saw this pattern in  
 "Modular Monadic Interpreters" (or something like that) by Jones,  
 Liang and Hudak.
 [...]

Thanks for the sugestions. For now I will try the solution posted by
Peter Achten, but yours will be in my bag for futre consideration,
when I should decide the design.

Regards,

Romildo
-- 
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




Re: Extensible data types?

2000-09-26 Thread Jose Romildo Malaquias

On Tue, Sep 26, 2000 at 09:56:18AM -0700, Peter Achten wrote:
 At 11:18 25-9-00 -0300, Prof. José Romildo Malaquias wrote:
 
 [...skip...]
 And then how would I define data types based on Fn ? The math expressions
 my system has to deal is expressed as something like
 
  data Expr = Int
| App Fn [Expr]
 
 I cannot just define
 
  data (FnExt fn) = Expr fn = Int
 | App fn [Expr fn]
 
 because the second value constructor would not be general enough
 and the values of the second form would be all sums, or all products,
 and so on.
 
 [...skip...]
 
 Anny comments?
 
 
 The trick is to construct all of your recursive data structures also in an 
 overloaded fassion. [...]
 
 The interesting case is obviously (APP fn expr). As you can see below, you 
 express to what type constructor classes the parameters should belong.
 [...]
 ==
 -- (1) for Fn
 class FnExt a where
   -- Define your class member functions here
 -- (2)
 data Sum = Sum
 data Pro  = Pro
 data Pow  = Pow
 -- (3)
 instance FnExt Sum where fn x = x
 instance FnExt Pro where fn x = x
 instance FnExt Pow where fn x = x
 
 -- (1) for Expr
 class ExprExt a where
   -- Define your class member functions here
 -- (2)
 data INT = INT Integer
 data CTE = CTE String
 data VAR = VAR String
 data APP fn expr = APP fn expr
 -- (3)
 instance ExprExt INT where ...
 instance ExprExt CTE where ...
 instance ExprExt VAR where ...
 instance (FnExt fn,ExprExt expr) = ExprExt (APP fn expr) where ...
 
 -- Convenient types when constructing lists and pairs:
 
 data List expr  -- Lists for convenience when you do have expressions 
 of same type
  = List [expr]
 infixr 9 :^:-- This is basically a tuple, but you can leave out 
 brackets
 data Pair expr1 expr2
  = expr1 :^: expr2
 
 instance (ExprExt e) = ExprExt (List e) where ...
 instance (ExprExt e1,ExprExt e2) = ExprExt (Pair e1 e2) where ...

This solution works great for the data type, but, at least
to me, it seems to make it too dificult to write functions
over ExprExt.

Consider for example the original version of the addition
operation (somehow simplified) on the original Expr data type

  data Fn = Sum | Pro | Pow

  data Expr = Int Integer | Cte String | Var String | App Fn [Expr]

  add :: Expr - Expr - Expr
  add (Int x) (Int y) = Int (x + y)
  add (Int 0) x   = x
  add x   (Int 0) = x
  add x   y   = App Sum [x,y]

The problem now is how to code the above algorithm using
the overloaded version of the data Expr data type.
Clearly the type of add should be

  add :: (ExprExt a, ExprExt b, ExprExt c) = a - b - c

I could not see how to implement it. I could define a
class

  class (ExprExt a, ExprExt b, ExprExt c) = AddOp a b c where
add :: a - b - c

But how the instances should be defined? One rule for
each possible combination of INT, CTE, VAR and APP for
a, b and c:

  instance AddOp INT INT INT where
add (Int x) (Int y) = Int (x + y)

  instance AddOp INT CTE ? where
add (Int 0) x = x
add x   y = App Sum (x :^: y)

  instance AddOp INT VAR ? where
add (Int 0) x = x
add x   y = App Sum (x :^: y)

  instance AddOp INT APP APP where
add (Int 0) x = x
add x   y = App Sum (x :^: y)

  instance AddOp CTE INT ? where
add (Int 0) x = x
add x   y = App Sum (x :^: y)

  ...

Some of these definitions will not type check.

Any clues?

The use of an existentialy quantified variable
would solve this,

  data Expr =  Int Integer
|  Cte String
|  Var String
| forall a . (FnExt fn) = App fn Expr

but would make it to difficult to extend the
data type with new value constructors.

Romildo
-- 
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




Extensible data types?

2000-09-25 Thread Jose Romildo Malaquias

Hello.

Is there any Haskell implementation that supports
extensible data types, in which new value constructors
can be added to a previously declared data type,
like

data Fn = Sum | Pro | Pow
...
extend data Fn = Sin | Cos | Tan

where first the Fn datatype had only three values,
(Sum, Pro and Pow) but later it was extended with
three new values (Sin, Cos and Tan)?

What are the pointers to documentation on such
kind of extensions to Haskell?

Thanks.

Romildo
-- 
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




Re: Extensible data types?

2000-09-25 Thread S.J.Thompson

Erik Poll ([EMAIL PROTECTED]) did some nice theoretical work on 
this a couple of years ago. I took a quick look on his web site
but couldn't see anything on it there. Maybe he can help?


Simon






Re: Extensible data types?

2000-09-25 Thread Peter Ljunglof


Perhaps the subtyping of O'Haskell is interesting:

http://www.cs.chalmers.se/~nordland/ohaskell/


/Peter Ljunglöf




On Mon, 25 Sep 2000, Jose Romildo Malaquias wrote:

 Is there any Haskell implementation that supports
 extensible data types, in which new value constructors
 can be added to a previously declared data type,
 like
 
   data Fn = Sum | Pro | Pow
   ...
   extend data Fn = Sin | Cos | Tan
 
 where first the Fn datatype had only three values,
 (Sum, Pro and Pow) but later it was extended with
 three new values (Sin, Cos and Tan)?





Re: Extensible data types?

2000-09-25 Thread Axel Simon

On Mon, 25 Sep 2000, Jose Romildo Malaquias wrote:

 Is there any Haskell implementation that supports
 extensible data types, in which new value constructors
 can be added to a previously declared data type?

I think this is what the TREX (extensible records) in Hugs are about. Take
a look at

http://www.cse.ogi.edu/PacSoft/projects/Hugs/pages/hugsman/exts.html

section 7.2.

Axel.







Re: Extensible data types?

2000-09-25 Thread Jose Romildo Malaquias

On Mon, Sep 25, 2000 at 11:37:24AM +0100, Chris Angus wrote:
 I've not seen this before,
 
 out of interest, why would you want/need such a thing?
  
  Is there any Haskell implementation that supports
  extensible data types, in which new value constructors
  can be added to a previously declared data type,
  like
  
  data Fn = Sum | Pro | Pow
  ...
  extend data Fn = Sin | Cos | Tan
  
  where first the Fn datatype had only three values,
  (Sum, Pro and Pow) but later it was extended with
  three new values (Sin, Cos and Tan)?

I want this to make a system I am workin on flexible.
Without it, my system is going to be too rigid.

I am working on an Computer Algebra system to transform
mathematic expressions, possibly simplifing them. There
is a data type to represent the expressions:

data Expr = Int Integer
  | Cte String
  | Var String
  | App Fn [Expr]

An expression may be an integer, a named constante (to
represent "known" contantes like pi and e), a variable
or an application. An application has a functor (function
name) and a list of arguments. The functor is introduced
with

data Fn = Sum | Pro | Pow

meaning the application may be a sum, a product or a
power.

The project should be modular. So there are modules to
deal with the basic arithmetic and algebraic transformations
involving expressions of the type above. But there are
optional modules to deal with trigonometric expressions,
logarithms, vectors, matrices, derivatives, integrals,
equation solving, and so on. These should be available as
a library where the programmer will choose what he
needs in his application, and he should be able to
define new ones to extend the library. So these modules
will certainly need to extend the bassic types above.

If it is really impossible (theoriticaly or not implemented)
then I will have to try other ways to implement the idea.

The functions manipulating the expressions also should be
extensible to accomodate new algorithms. The extensions
is in a form of hooks (based on the Fn component of an
application function) in the main algorithms.

Romildo
-- 
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




Re: Extensible data types?

2000-09-25 Thread Jose Romildo Malaquias

On Mon, Sep 25, 2000 at 01:01:25PM +0200, Axel Simon wrote:
 On Mon, 25 Sep 2000, Jose Romildo Malaquias wrote:
 
  Is there any Haskell implementation that supports
  extensible data types, in which new value constructors
  can be added to a previously declared data type?
 
 I think this is what the TREX (extensible records) in Hugs are about. Take
 a look at
 
 http://www.cse.ogi.edu/PacSoft/projects/Hugs/pages/hugsman/exts.html
 
 section 7.2.

The TREX extension enable the addition of new fields to a record type.
What I am looking for is a way of extending a data type with
new forms of values, and not a given value form with new "fields".

The TREX extension would allow something like (with an inventend syntax):

data T = V { field1 :: Integer
   , field2 :: Double
   }
...
extend data T = V  { field3 :: Char
   , field4 :: [Integer]
   , field5 :: Bool
   }

which would extend the value constructor V for the data type T
introducing new fields.

This does not help me in my project.

Romildo
-- 
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




Re: Extensible data types?

2000-09-25 Thread Ch. A. Herrmann

Hi,

Jose I am working on an Computer Algebra system to transform
Jose mathematic expressions, possibly simplifing them. There is a
Jose data type to represent the expressions:

Jose data Expr = Int Integer | Cte String | Var String | App Fn [Expr]

Jose An expression may be an integer, a named constante (to
Jose represent "known" contantes like pi and e), a variable or an
Jose application. An application has a functor (function name) and
Jose a list of arguments. The functor is introduced with

Jose   data Fn = Sum | Pro | Pow

Jose meaning the application may be a sum, a product or a power.

...

Jose The functions manipulating the expressions also should be
Jose extensible to accomodate new algorithms. The extensions is in
Jose a form of hooks (based on the Fn component of an application
Jose function) in the main algorithms.

I've encountered the same problem and I'm interested to get to know a
highly productive way which at the same time can be considered
a good way of software engineering.
Not enough ... it should pass the Haskell typechecker and be compatible
with the class concept.

At the moment, I know only one "right way": to define several different 
types and define functions on each of these types individually.
That's too much work for me ...

However, the only fast but awful style I know is something like:

data FunctorType = Sum | Pro | Pow | Sin | Trace | UnsafeInput 
 | ... whatever you like

data AllMyExpressions = SingleConstructor { functor:   FunctorType,
arguments: [AllMyExpressions] }
-- 
 Christoph Herrmann
 E-mail:  [EMAIL PROTECTED]
 WWW: http://brahms.fmi.uni-passau.de/cl/staff/herrmann.html





Re: Extensible data types?

2000-09-25 Thread Rob MacAulay

There is an interesting paper which includes a method of 
performing this extension in Gofer:

"Monad Transformers and Monad Interpreters"

by Liang, Hudak and Jones

I think this should be available from Mark Jones'  web site at OGI.

Rob MacAulay


  
   Is there any Haskell implementation that supports
   extensible data types, in which new value constructors
   can be added to a previously declared data type?
  
  I think this is what the TREX (extensible records) in Hugs are about. Take
  a look at
  
  http://www.cse.ogi.edu/PacSoft/projects/Hugs/pages/hugsman/exts.html
  
  section 7.2.
 
 The TREX extension enable the addition of new fields to a record type.
 What I am looking for is a way of extending a data type with
 new forms of values, and not a given value form with new "fields".
 
 The TREX extension would allow something like (with an inventend syntax):
 
   data T = V { field1 :: Integer
, field2 :: Double
}
   ...
   extend data T = V  { field3 :: Char
, field4 :: [Integer]
, field5 :: Bool
}
 
 which would extend the value constructor V for the data type T
 introducing new fields.
 
 This does not help me in my project.
 
 Romildo
 -- 
 Prof. Jos Romildo Malaquias [EMAIL PROTECTED]
 Departamento de Computao
 Universidade Federal de Ouro Preto
 Brasil
 


Rob MacAulay 
Techinical DirectorVulcan Machines

email : [EMAIL PROTECTED]   
http  : www.vulcanmachines.com
Tel   +[44] 1763 247624  (direct)
Tel   +[44] 1763 248163  (office)
Fax   +[44] 1763 241291  




Re: Extensible data types?

2000-09-25 Thread Axel Simon


   Is there any Haskell implementation that supports
   extensible data types, in which new value constructors
   can be added to a previously declared data type?
  
  I think this is what TREX (extensible records) in Hugs are about. Take
  a look at
  
  http://www.cse.ogi.edu/PacSoft/projects/Hugs/pages/hugsman/exts.html

 The TREX extension enable the addition of new fields to a record type.
 What I am looking for is a way of extending a data type with
 new forms of values, and not a given value form with new "fields".
 
Yes, ok. I agree. But couldn't you say something like

data Expr = Int Integer
  | Cte String
  | Var String
  | App (Rec ())

and extend the record in the last constructor by a label sum::
(Expr,Expr), pro::(Expr,Expr) etc.?

Axel.






RE: Extensible data types?

2000-09-25 Thread Chris Angus

Just wondering if you'd seen the dynamic
datatype which basically gives you an "Any"
in ghc/hugs



 -Original Message-
 From: Jose Romildo Malaquias [mailto:[EMAIL PROTECTED]]
 Sent: 25 September 2000 12:14
 To: Chris Angus
 Cc: [EMAIL PROTECTED]
 Subject: Re: Extensible data types?
 
 
 On Mon, Sep 25, 2000 at 11:37:24AM +0100, Chris Angus wrote:
  I've not seen this before,
  
  out of interest, why would you want/need such a thing?
   
   Is there any Haskell implementation that supports
   extensible data types, in which new value constructors
   can be added to a previously declared data type,
   like
   
 data Fn = Sum | Pro | Pow
 ...
 extend data Fn = Sin | Cos | Tan
   
   where first the Fn datatype had only three values,
   (Sum, Pro and Pow) but later it was extended with
   three new values (Sin, Cos and Tan)?
 
 I want this to make a system I am workin on flexible.
 Without it, my system is going to be too rigid.
 
 I am working on an Computer Algebra system to transform
 mathematic expressions, possibly simplifing them. There
 is a data type to represent the expressions:
 
   data Expr = Int Integer
   | Cte String
   | Var String
   | App Fn [Expr]
 
 An expression may be an integer, a named constante (to
 represent "known" contantes like pi and e), a variable
 or an application. An application has a functor (function
 name) and a list of arguments. The functor is introduced
 with
 
   data Fn = Sum | Pro | Pow
 
 meaning the application may be a sum, a product or a
 power.
 
 The project should be modular. So there are modules to
 deal with the basic arithmetic and algebraic transformations
 involving expressions of the type above. But there are
 optional modules to deal with trigonometric expressions,
 logarithms, vectors, matrices, derivatives, integrals,
 equation solving, and so on. These should be available as
 a library where the programmer will choose what he
 needs in his application, and he should be able to
 define new ones to extend the library. So these modules
 will certainly need to extend the bassic types above.
 
 If it is really impossible (theoriticaly or not implemented)
 then I will have to try other ways to implement the idea.
 
 The functions manipulating the expressions also should be
 extensible to accomodate new algorithms. The extensions
 is in a form of hooks (based on the Fn component of an
 application function) in the main algorithms.
 
 Romildo
 -- 
 Prof. José Romildo Malaquias [EMAIL PROTECTED]
 Departamento de Computação
 Universidade Federal de Ouro Preto
 Brasil
 




Re: Extensible data types?

2000-09-25 Thread John Hörnkvist

If you use Hugs -- and possibly GHC -- you might be able to use the  
"Either" constructor for subtyping. I first saw this pattern in  
"Modular Monadic Interpreters" (or something like that) by Jones,  
Liang and Hudak. [Apologies if I didn't get the attribution right.]

data Expr a = Int Integer
  | Cte String
  | Var String
  | App a [Expr a]

type ArithFn = Either Sum (Either Pro Pow)

data Sum = Sum
data Pro = Pro
data Pow = Pow

You may find these handy:
class SubType a b where
inj :: a - b
prj :: b - Maybe a

instance SubType a (Either a b) where
inj a = Left a
prj (Left a) = a
prj (_) = Nothing

instance SubType Pow (Either Pro Pow)
inj a = Right a
prj (Right Pow) = Pow

type TrigFun = Either Sin (Either Cos (Either Tan FirstFun)

data Sin = Sin
...

I don't remember if you can do
type TrigFn a = Either Sin (Either Cos (Either Tan a))
type Fun = TrigFn ArithFn

Next, define classes for the

class Application a where
app :: a - Expr - M Value

instance (Application a, Application b) = Application (Either a b) where
app (Left a) e = app a e
app (Right b) e = app b e

IIRC, you also need to do this for the "inner" value
instance Application (Either Pro Pow) where
app (Left a) e = app a e
app (Right b) e = app b e

instance Application Sum where
app Sum [] = return bottom -- ?
app Sum (x:xs) = do
v1 - (eval x)
 v2 - (Sum xs)
return (v1+v2)

...

eval :: Expr a - M Value
eval (App fn e) = app fn e
eval Cte "pi" = pi
eval Var s = get s
...

Note that a user of the libraries can pick components at will;
type MyFn = Either Sin (Either Pro Pow)
type MyExpr = Expr MyFn

I haven't run the above through the type checker, so it may not work. 

Hugs extended type system is very useful. You'll need to run hugs  
with +o -98 to enable it.

Regards,
John Hornkvist


--
ToastedMarshmallow, the perfect Cocoa companion
http://www.toastedmarshmallow.com




Re: Extensible data types?

2000-09-25 Thread Peter Achten

At 07:46 25-9-00 -0300, Prof. José Romildo Malaquias wrote:

Hello.

Is there any Haskell implementation that supports
extensible data types, in which new value constructors
can be added to a previously declared data type,
like

 data Fn = Sum | Pro | Pow
 ...
 extend data Fn = Sin | Cos | Tan

where first the Fn datatype had only three values,
(Sum, Pro and Pow) but later it was extended with
three new values (Sin, Cos and Tan)?

What are the pointers to documentation on such
kind of extensions to Haskell?

In the Clean Object I/O library we encountered a similar challenge and 
solved it using type constructor classes. The solution can also be used in 
Haskell. The basic idea is as follows:

(1) For each type constructor that has to be extensible you introduce a 
type constructor class;
(2) For each of the data constructors of such type constructors you 
introduce a new type constructor (reusing their name is very convenient);
(3) For each such new type constructor define it as an instance of the type 
constructor class that was created from its parent type constructor.

Example:

(1) From type constructor Fn you create:
class FnExt where
 ...   -- Define your class member functions here

(2) From the data constructors Sum | Pro | Pow you create:
data Sum = Sum
data Pro  = Pro
data Pow  = Pow

(3) For each newly defined type constructor in (2) you define an instance:
instance FnExt Sum
instance FnExt Pro
instance FnExt Pow


All of your functions that previously were defined on Fn are now overloaded 
functions:

fun :: ... Fn ... - ... Fn ...

becomes:

fun :: (FnExt fn) = ... fn ... - ... fn ...

I hope you find this scheme useful. I guess its applicability depends on 
your particular class member functions and program.

Regards,
Peter Achten

=
References: although the perspective in the Clean Object I/O library is on 
the data structures with generic interpretation functions, the technique is 
basically the same as described here.

In my PhD Thesis you can find an early reference:
* The reference:
Achten, P.M. Interactive Functional Programs - Models, Methods, and 
Implementation. PhD thesis, University of Nijmegen, 1996.
* The abstract at:
http://www.cs.kun.nl/~peter88/PeterThesisCh6.html
* The chapter at:
ftp://ftp.cs.kun.nl/pub/CSI/SoftwEng.FunctLang/papers/achp96-thesis6.ps.gz

A more modern version can be found here:
* The reference:
Achten, P.M. and Plasmeijer, M.J. Interactive Functional Objects in Clean. 
In Clack, C., Hammond, K., and Davie, T. eds., Proceedings 9th 
International Workshop Implementation of Functional Languages, IFL'97, 
St.Andrews, Scotland, UK, September 1997, selected papers, LNCS 1467, 
Springer, pp. 304-321.
* The abstract at:
ftp://ftp.cs.kun.nl/pub/Clean/papers/1998/achp97-InteractFuncObjects.abs
* The paper at:
ftp://ftp.cs.kun.nl/pub/Clean/papers/1998/achp97-InteractFuncObjects.ps.gz





RE: Extensible data types?

2000-09-25 Thread Chris Angus

Presumably this means differentiation/integeration would have to be typed as

diff :: (FnExt a,FnExt b) = a - b

Chris


 -Original Message-
 From: Peter Achten [mailto:[EMAIL PROTECTED]]
 Sent: 25 September 2000 23:34
 To: Jose Romildo Malaquias
 Cc: [EMAIL PROTECTED]
 Subject: Re: Extensible data types?
 
 
 At 07:46 25-9-00 -0300, Prof. José Romildo Malaquias wrote:
 
 Hello.
 
 Is there any Haskell implementation that supports
 extensible data types, in which new value constructors
 can be added to a previously declared data type,
 like
 
  data Fn = Sum | Pro | Pow
  ...
  extend data Fn = Sin | Cos | Tan
 
 where first the Fn datatype had only three values,
 (Sum, Pro and Pow) but later it was extended with
 three new values (Sin, Cos and Tan)?
 
 What are the pointers to documentation on such
 kind of extensions to Haskell?
 
 In the Clean Object I/O library we encountered a similar 
 challenge and 
 solved it using type constructor classes. The solution can 
 also be used in 
 Haskell. The basic idea is as follows:
 
 (1) For each type constructor that has to be extensible you 
 introduce a 
 type constructor class;
 (2) For each of the data constructors of such type constructors you 
 introduce a new type constructor (reusing their name is very 
 convenient);
 (3) For each such new type constructor define it as an 
 instance of the type 
 constructor class that was created from its parent type constructor.
 
 Example:
 
 (1) From type constructor Fn you create:
 class FnExt where
  ...   -- Define your class member functions here
 
 (2) From the data constructors Sum | Pro | Pow you create:
 data Sum = Sum
 data Pro  = Pro
 data Pow  = Pow
 
 (3) For each newly defined type constructor in (2) you define 
 an instance:
 instance FnExt Sum
 instance FnExt Pro
 instance FnExt Pow
 
 
 All of your functions that previously were defined on Fn are 
 now overloaded 
 functions:
 
 fun :: ... Fn ... - ... Fn ...
 
 becomes:
 
 fun :: (FnExt fn) = ... fn ... - ... fn ...
 
 I hope you find this scheme useful. I guess its applicability 
 depends on 
 your particular class member functions and program.
 
 Regards,
 Peter Achten
 
 =
 References: although the perspective in the Clean Object I/O 
 library is on 
 the data structures with generic interpretation functions, 
 the technique is 
 basically the same as described here.
 
 In my PhD Thesis you can find an early reference:
 * The reference:
 Achten, P.M. Interactive Functional Programs - Models, Methods, and 
 Implementation. PhD thesis, University of Nijmegen, 1996.
 * The abstract at:
 http://www.cs.kun.nl/~peter88/PeterThesisCh6.html
 * The chapter at:
 ftp://ftp.cs.kun.nl/pub/CSI/SoftwEng.FunctLang/papers/achp96-t
hesis6.ps.gz

A more modern version can be found here:
* The reference:
Achten, P.M. and Plasmeijer, M.J. Interactive Functional Objects in Clean. 
In Clack, C., Hammond, K., and Davie, T. eds., Proceedings 9th 
International Workshop Implementation of Functional Languages, IFL'97, 
St.Andrews, Scotland, UK, September 1997, selected papers, LNCS 1467, 
Springer, pp. 304-321.
* The abstract at:
ftp://ftp.cs.kun.nl/pub/Clean/papers/1998/achp97-InteractFuncObjects.abs
* The paper at:
ftp://ftp.cs.kun.nl/pub/Clean/papers/1998/achp97-InteractFuncObjects.ps.gz





Re: Extensible data types?

2000-09-25 Thread Keith Wansbrough

 In the Clean Object I/O library we encountered a similar challenge and 
 solved it using type constructor classes. The solution can also be used in 
 Haskell. The basic idea is as follows:
 

I didn't read your message in detail, but I wonder if this is related
to the trick TclHaskell / FranTk use to deal with configuration lists?

--KW 8-)





Re: Extensible data types?

2000-09-25 Thread Carl R. Witty

Jose Romildo Malaquias [EMAIL PROTECTED] writes:

 Hello.
 
 Is there any Haskell implementation that supports
 extensible data types, in which new value constructors
 can be added to a previously declared data type,
 like
 
   data Fn = Sum | Pro | Pow
   ...
   extend data Fn = Sin | Cos | Tan
 
 where first the Fn datatype had only three values,
 (Sum, Pro and Pow) but later it was extended with
 three new values (Sin, Cos and Tan)?


I don't know of any implementation that directly supports this.
Somebody else pointed you at TREX.  The theoretical underpinnings of
TREX are discussed in the following paper:

A Polymorphic Type System for Extensible Records and Variants,
Benedict R. Gaster and Mark P. Jones, Technical report NOTTCS-TR-96-3,
November 1996, Department of Computer Science, University of
Nottingham, University Park, Nottingham NG7 2RD, England.

(you can download a copy from http://www.cse.ogi.edu/~mpj/pubs.html).
As mentioned in the title of the paper, the type system described
supports both extensible records and extensible variants.  The TREX
extension only implemented the "extensible records" portion.  I've
often wished that the "extensible variants" were also implemented;
they seem more useful than extensible records to me.

Carl Witty