Overloading

2000-09-25 Thread Carlos Camarao de Figueiredo


Myself and Lucilia ([EMAIL PROTECTED]) have modified Mark Jones'
program, "Typing Haskell in Haskell",
(http://www.cse.ogi.edu/~mpj/thih) to support system CT (paper
available at http://www.dcc.ufmg.br/~camarao/ct.ps.gz). (Thanks Mark.)

The implementation is a prototype of system CT, mainly an adaptation
of system CT to deal with (possibly mutual) recursion in binding
groups. The source code is available at
http://www.dcc.ufmg.br/CT/CTinH.tar.gz . We would be very pleased to
receive comments, suggestions etc.

-- Overview of System CT

   System CT extends ML-like type inference for supporting
   overloading, with no special constructs for coping with
   overloading. Types are inferred, with no mandatory type annotations
   and no restrictions.

-- Abstract data are abstract

   No conflict arises then between data abstraction and types of
   overloaded symbols: constraints on types of terms (using
   overloaded symbols or not) are automatically inferred. Types must
   not be "determined" a priori by programmers, according to which
   overloading symbols are used (an implementation-dependent issue).

In Haskell:
  _
  | class Collection c where  |
  |   ... |
  |   member:: Eq a => a -> Set a -> Bool |
  |   ... |
  | instance Collection Set where |
  |   ... |
  |   member ...  |
  |   ... |
  |___|
  

  In CT:
  __ 
  | ...| - No class and instance declarations required
  | member ... | - No constraints required in type annotations
  | ...| - No mandatory type annotation
  || - More importantly:

 No obligation to a priori "determine" (and specify) the types and
 constraints of classes and their members (there are many possible
 ways of implementing collections)

-- Generality

   Support of overloading of constants and functions, including
   functions defined over different type constructors, with no
   restriction on the syntactic form and number of parameters of
   types. No monomorphism restriction.

   For example, using (predefined map on lists and) map on trees
   enabled by:

  __
  | map f Leaf = Leaf  |
  | map f (Node a b) = Node (map f a) map f b) |
  ||

  Overloading is possible in any let binding, and even inside lambda
  abstractions. This does not mean that these should be supported in a
  language, but difficulties introduced by overloading in expressions
  such as in the following example have been studied:

   (let o = ...
o = ... in e) (let o = ...
   o = ... in e')

-- Simple and informative types

  Overloading in a closed world means that types are inferred
  according to visible definitions. This enables the inference of more
  informative types (and issuing more informative error messages).

  For example, overloading and using "first" on pairs and triples:

   In Haskell
  __
  | class First p a where   |
  |   first:: p -> a|
  | |
  | instance First (a,b) a where|
  |   first = fst   |
  | instance First (a,b,c) where|
  |   first (a,b,c) = a |
  | |
  | f x y = first (x,y) |
  | main = print ((f::Bool->Int->Bool) True 10) |
  |_|

In CT
  
  | fst (a,b,c) = a  |  Type inferred for f:
  |  |in CT: a -> b -> a
  | f = curry fst|in Haskell:
  | main = print (f True 10) |  First (a,b) c => a -> b -> c
  |__|

  Constraints on types are maintained intenally but, since they are
  inferred, in interaction with programmers in system CT can
  use only simple (unconstrained) types.

-- Open World and Autonomous Software Components (somewhat ortogonal
   issue, not yet implemented in this prototype)

  Support for the use of type annotations, instead of import clauses,
  extends the open world approach for supporting the construction of
  autonomous software components (and mutually recursive modules).

  For example, one could use, instead of

  import Monad

  the following: 

  assume (return:: a -> m a, 
  (>>=) :: m a -> (a -> m b) -> m b)

  or equivalently:

 assume MonadInterface


Yours,

Carlos




Re: SAX, XML, Haskell

2000-09-25 Thread Joe English


Chris Angus wrote:
>
> I looked at HaXml a while ago
> and it seemed to offer a very Dom-like interface.


You could say that it's DOM-like in that it deals
with trees instead of an event stream, but it's actually
somewhere in between SAX and DOM.

The main difference between HaXML and DOM is that
in the DOM, nodes have object identity and it's
possible to access parent and sibling nodes (which
implies access to the entire tree tree starting from
any node).  With HaXML, you can only get to the subtree
rooted at a particular node.

[HaXML also encapsulates a lot of the plumbing and is relatively
cruft-free, which makes it considerably more pleasant to use
than the DOM in my opinion, but that's a secondary issue.]


> I was wondering if anyone had thought of making a Sax-like
> interface based on lazy evaluation. where tokens are
> processed and taken from a (potentially) infinite stream

The HaXML combinators actually have very nice laziness properties.
HaXML as a whole (at least the last time I looked at it)
is stricter than it needs to be -- because the XML parser
processes the entire input document before returning the
root node -- but a combination of the HaXML combinators
and Ketil Malde's parser would give the best of both worlds.


--Joe English

  [EMAIL PROTECTED]




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




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-)





How to force evaluation entirely?

2000-09-25 Thread Michael Marte

Hello,

I am trying to process a huge bunch of large XML files in order
to extract some data. For each XML file, a small summary (6 integers)
is created which is kept until writing a HTML page displaying the
results.

The ghc-compiled program behaves as expected: It opens one XML file after
the other but does not read a lot. After some 50 files, it bails out due
to lack of heap storage.

To overcome the problem, I tried to force the program to compute summaries
immediately after reading the corresponding XML file. I tried some eager
application ($!), some irrefutable pattern, and some strictness flags, but
I did not succeed. It seems to me that as long as something is not really
used, the implementation cannot be forced to evaluate it completely. I
resorted to printing the summary to /dev/null right after reading the XML
file. This works fine. Is there a more elegant solution?

Thank you.

Michael Marte









Correction: Re: Extensible data types?

2000-09-25 Thread John Hörnkvist

I wrote:
> 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

This should be:
instance SubType a (Either a b) where
inj a = Left a
prj (Left a) = a
prj (Right b) = prj b

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

Regards,
John Hörnkvist




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




Re: Extensible data types?

2000-09-25 Thread Jose Romildo Malaquias

On Mon, Sep 25, 2000 at 03:33:54PM -0700, Peter Achten wrote:
> 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.

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.

An existentialy quantified variable would solve this

data Expr =  Int
  | forall fn . (fn :: FnExt) => App fn [Expr]

But I have to think the its consequences to the system.

Anny comments?

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 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 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 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 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 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 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 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 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: SAX, XML, Haskell

2000-09-25 Thread Ketil Malde

Chris Angus <[EMAIL PROTECTED]> writes:

> I was wondering if anyone had thought of making a Sax-like 
> interface based on lazy evaluation. where tokens are
> processed and taken from a (potentially) infinite stream 

Sure.  While barely able to follow discussions about monadic parser
combinators, and with a background in numerical analysis, I went ahead 
and rolled my own non-validating XML parser nonetheless. (I needed to
rip some information from web pages, and this seemed like the most fun
way to do it :-)

Basically, I abandoned doing it the traditional way (returning a list
of parses, along with the rest of the stream), since I didn't get
the result lazy enough, and it's probably inefficient for other
reasons (e.g. the monads vs arrows paper by John Hughes). 

What I ended up with, was three layers:  a tokenizer that takes a
character stream and turns it into tokens (i.e. STAGO, TAGC [SGML
lingo], and so on, or simple characters).  Then, a "tagizer" that
recognizes the different types of tags (i.e STAG, ETAG, comments,
CDATA sections, whathaveyou) - and that's basically where SAX is,
IIRC.   And then a top layer, providing elements.  Here's my parser:

readXML = xmlize . tagize . tokenize

:-)  All the steps are as lazy as I can get them, so that

readXML "bar"

will return Element "xml" [ Element "foo" [PCDATA "bar" before giving
an error.  (Again IIRC, it's been shelved for a while now.)

Anyway, for HTML, which is invariably produced with hair-raisingly
broken tools, I had to substitute and interleave other functions, so
it's not quite as clean.  But it worked out all right for my purposes.

(It's probably not general/beautiful/complete enough to be part of a
real library, but if you (or anybody) wants the code, drop me a mail)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants




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 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 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 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






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




If you like Copper

2000-09-25 Thread simondudley2000


 
If you like copper, you will love DRC Resources: 
 
 
***





SAX, XML, Haskell

2000-09-25 Thread Chris Angus

Hi,

I looked at HaXml a while ago
and it seemed to offer a very Dom-like interface.

I was wondering if anyone had thought of making a Sax-like 
interface based on lazy evaluation. where tokens are
processed and taken from a (potentially) infinite stream 

Chris




test

2000-09-25 Thread root

1 2 3