RE: Modeling multiple inheritance

2003-09-25 Thread Simon Peyton-Jones
When Mark Shields and I tackled this problem we came up with
Object-Oriented Style Overloading for Haskell

http://research.microsoft.com/~simonpj/Papers/oo-haskell/index.htm

It describes an (unimplemented) extension to Haskell, rather than
modelling it in Haskell itself, but you may find it interesting none the
less. 

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| Brandon Michael Moore
| Sent: 24 September 2003 22:22
| To: [EMAIL PROTECTED]
| Subject: Modeling multiple inheritance
| 
| I'm trying to build a nicer interface over the one generated by
| jvm-bridge. I'm using fancy type classes to remove the need to mangle
| method names. I would like methods to be automatcially inherited,
| following an inheritance hierarcy defined with another set of type
| classes.
| 
| My basic classes look like this
| class HasFooMethod cls args result | cls args - result where
|   foo :: cls - args - result
| 
| If I have classes A and B with foo methods like
|   foo_JA_Jint :: ClassA - Jint - Bool
|   foo_JB_Jboolean :: ClassB - Bool - Jint
| then I can make instances
|   instance HasFooMethod ClassA Jint Bool
|   instance HasFooMethod ClassB Bool Jint
| 
| Now I can just use foo everywhere. I would like to avoid declaring an
| instance for every class though. In java methods are inherited from a
| superclass, and I would like to inherit methods automatically as well.
In
| the bindings jvm-bridge generates a method is invoked with a function
| mangled after the highest ancestor that defined that particular
| overloading, so the implementation of HasFooMethod at a particular
| overloading is the same for any descendant.
| 
| So I defined a class to model the inheritance relationships
| 
| class SubType super sub | sub - super where
|   upCast :: sub - super
| 
| Now I can define a default instance of HasFooMethod:
| instance (HasFooMethod super args result,
|   SubClass super sub) =
|  HasFooMethod sub args result where
|   foo sub args = foo (upCast sub) args
| 
| This will propagate foo methods down the inheritance hierarcy. If a
new
| class C is derived from A, I just need to say
| 
| instance SubClass ClassA ClassC
| 
| and ClassC gets a foo method. (In the actually code I piggy-back on a
| transitive subclass relation jvm-bridge defines that already includes
an
| upcast method, so upCast has a default that should always be
acceptable).
| 
| The problem comes when interfaces are added to the mix. Interfaces are
| treated just like classes by jvm-bridge, and even though no
implementation
| is inherited from instances in Java, the method accessors generated by
| jvm-bridge should be inherited.
| 
| One problem is that the subclass relationship needs the functional
| dependency so that the default instance of HasFooMethod will respects
the
| functional dependencies of HasFooMethod, so I can't declare subclass
| instances for multiple inheritance. On the other hand, if I don't use
the
| functional dependency on HasFooMethod I end up needing to annotate
most of
| the return values in a program. I run into similar problems trying to
use
| numeric literals as arguments, because they are also overloaded.
| 
| Does anyone know of clever solutions that would model multiple
inheritance
| while preserving the functional dependencies (unsafe compiler flags
are
| fine too), or ways to reduce the pain of overloading resolution
without
| the functional dependency?
| 
| One alternative is generating seperate HasFooMethod instances for
every
| class in the system. The problem is that this would require alterating
the
| bit of jvm-bridge that uses JNI to find information on classes, which
| currently only reports newly defined methods. JNI is black magic to
me.
| 
| Thanks
| Brandon
| 
| ___
| Haskell-Cafe mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: Generating setMember functions for record structures

2003-09-25 Thread Peter Simons
Peter Gammie writes:

  Haskell Report, Sec 3.15.3

Great, that's exactly what I need.
Thanks a lot to all who replied!

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


RE: Database interface - would like advice on oracle library binding

2003-09-25 Thread oleg

The following code illustrates a _generic_ interface to low-level
database code. The left-fold iterator doQuery is completely generic
over any possible iterator -- no matter how many columns the query
returns, what are the types of these columns and what is the type of
the seed (accumulator). The code for doQuery remains the same. The
iterator allocates buffers for columns at the beginning and frees the
buffers at the very end. Again, this buffer handling is generic. There
is no longer need to write extraction/unmarshalling function for
specific types of rows. We only need fetching functions for specific
datatypes (not columns!). Again, the query and the row buffer
management code is completely generic. I guess I'm repeating
myself. The tests:

-- Query returns one column of type String
-- Never mind undefined: we return some static data in the buffers,
-- we don't have any oracle to bind to
test1 = doQuery undefined undefined iter1 ([]::[String])
  where
 iter1:: String - [String] - Either [String] [String]
 iter1 s acc = Right $ s:acc 


-- Query returns two columns of types String and Int
test2 = doQuery undefined undefined iter2 ([]::[(String,Int)])
  where
 iter2:: String - Int - [(String,Int)] - 
 Either [(String,Int)] [(String,Int)]
 iter2 s i acc = Right $ (s,i):acc 


-- Query returns three columns of types Int, String and Int
test3 = doQuery undefined undefined iter3 ([]::[(Int,String,Int)])
  where
 iter3:: Int - String - Int - [(Int,String,Int)] - 
 Either [(Int,String,Int)] [(Int,String,Int)]
 iter3 i1 s i2 acc = Right $ (i1,s,i2):acc 

Use the function runtests to run either of these tests.


The code follows. Compiler flags: 
-fglasgow-exts -fallow-overlapping-instances

-- DB column buffers

type BufferSize = Int
data BufferType = ORA_char | ORA_int
type Position = Int  -- column number of the result table

data Buffer = Buffer { bufptr :: String -- for this stub, just use String
 , nullindptr :: String -- likewise
 , retsizeptr :: String -- likewise
 , size:: BufferSize 
 , pos:: Position
 , ora_type:: BufferType }

-- understandably, below is just a stub ...
alloc_buffer (siz, typ) ps = 
  return $ Buffer { bufptr = show ps, pos = ps,  size = siz, ora_type = typ}
  
-- In this stub, don't do anything
free ptr = return ()


-- DB Column types

class DBType a where
  alloc_buffer_hints:: a - (BufferSize, BufferType)
  col_fetch:: Buffer - IO a

instance DBType String where
  alloc_buffer_hints _ = (2000, ORA_char)
  col_fetch buffer = return (bufptr buffer)

instance DBType Int where
  alloc_buffer_hints _ = (4, ORA_int)
  col_fetch buffer = return (read $ bufptr buffer)
  
-- need to add more ...

-- Row iteratees. Note, the folowing two instances cover ALL possible
-- iteratees. No other instances are needed

class SQLIteratee iter seed where
iter_apply:: [Buffer] - seed - iter - IO (Either seed seed)
alloc_buffers:: Position - iter - seed - IO [Buffer]

instance (DBType a) = SQLIteratee (a-seed-Either seed seed) seed where
iter_apply [buf] seed fn = col_fetch buf = (\v - return$ fn v seed)
alloc_buffers n _ _ = 
   sequence [alloc_buffer (alloc_buffer_hints (undefined::a)) n]

instance (SQLIteratee iter' seed, DBType a) = SQLIteratee (a-iter') seed 
 where
iter_apply (buf:others) seed fn = 
  col_fetch buf = (\v - iter_apply others seed (fn v))
alloc_buffers n fn seed = do
  this_buffer - alloc_buffer (alloc_buffer_hints (undefined::a)) n
  other_buffers - alloc_buffers (n+1) (fn (undefined::a)) seed
  return (this_buffer:other_buffers)

free_buffers = mapM_ free

-- The left fold iterator -- the query executor

data Session   -- not relevant for this example
data SQLStmt

db_execute session query = return ()

db_fetch_row buffers = return ()  -- use static data

doQuery:: (SQLIteratee iter seed) = Session - SQLStmt - iter - seed - IO seed

-- In this example, we just allocate buffers, fetch two rows and terminate
-- with a clean-up

doQuery session query iteratee seed = do
  buffers - alloc_buffers 0 iteratee seed
  db_execute session query
  db_fetch_row buffers
  (Right seed) - iter_apply buffers seed iteratee
  db_fetch_row buffers
  (Right seed) - iter_apply buffers seed iteratee
  free_buffers buffers
  return seed
  

-- Tests

-- Query returns one column of type String
test1 = doQuery undefined undefined iter1 ([]::[String])
  where
 iter1:: String - [String] - Either [String] [String]
 iter1 s acc = Right $ s:acc 


-- Query returns two columns of types String and Int
test2 = doQuery undefined undefined iter2 ([]::[(String,Int)])
  where
 iter2:: String - Int - [(String,Int)] - 
 Either [(String,Int)] [(String,Int)]
 iter2 s i acc = Right $ (s,i):acc 


-- Query returns three columns of types Int, String and Int
test3 = doQuery 

Haskell as specification language

2003-09-25 Thread Luc Taesch
out of curiosity, is haskell already been used as a specification language ?

i was thinking in a business term, rather than mathematical one. (i.e. one than  
normal mortal can read, even with a bit of training ;-)

I.e. one would specifiy a model, an application ( possibly run it on samples), and 
hand it over to 

developper, typically in other languages/environment...

I am aware of the contracts paper of SPJ, for instance... others you may think of ?

does a spec. always leads to a DSL , for instance ?

I imagine a specification for an application resulting in a DSL for the data model/ 
 process model  part, (which is the generic/ reusabel part, IMH) plus something more 
specific to the effective application targeted...

(I cannot resist explaining my long term view : if IT outsourcing really takes off one 
day, one key factor will be proper specification, which is in a dear state in the 
current practice nowadays in the field)

ref:  http://search.ft.com/search/article.html?id=030923007625
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: lexer puzzle

2003-09-25 Thread Brandon Michael Moore
Note I've replied to haskell-cafe. This post is a bit chatty and low on
solid answers.

On Thu, 25 Sep 2003, Sean L. Palmer wrote:

  A... should be split into A.. and .
  I found a compromise: let's make it a lexing error! :-)
  At least that agrees with what some Haskell compilers implement. No
  current Haskell compiler/interpreter agrees with what the report seems
  to say, that is that A... should be lexed as the two tokens A.. and
  ., and similarly, A.where should be lexed as A.wher followed by e.

 Hi.  I'm really new to Haskell, just learning it, and I must say I'm pretty
 overwhelmed by the large variety of constructs. (=, -, \ to name a few)

Would that be \ as in TREX row variable polymorphism? Just remember most
operators are just library functions. It's only =, -, =, -, :: that are
really part of the language, and {,},; for grouping. Did I miss any?


 But I'm just writing this to let you guys know (surely you know this
 already) that anyone from a C/C++/Java/Delphi background is going to
 completely misunderstand the meaning of A.anything in Haskell... it's
 completely nonintuitive to people with my background.  I kinda like dot
 notation because it ties together the symbols visually, for instance
 myrec.myfield is more of a unit than myrec myfield.  It stays together
 better when surrounded by other code, and would result in fewer parenthesis
 necessary.

A Python programmer would understand instantly: Python uses exactly the
same syntax for module access, though Python modules are usually in
lowercase. It also seems to be very much in the spirit of access a member
of this object of an OO language.

Or was that supposed to be composition of a constructor with a function, A
. f? Function composition, and higher order functions in general are
likely to confuse an imperative programmer, but I think there isn't much
syntax can do there.

Or are you talking about the field access syntax? Maybe the problem is
that dot has two to five different meanings, function composition, naming
module members, building hierarchial module names, being a decimal point,
and making elipses, and is commonly used for yet another purpose in OO
languages.

 Haskell to me seems to be a great language with a syntax problem, and a bad
 case of too many ways to do the same thing; thus every programmer does
 things their own way and it's difficult to grasp the language by looking at
 various programs, since they're all so very different.  As a small example,
 there's 'let' vs. 'where'.  Maybe a bit of pruning would be in order.

Do you mean the syntax is bad in places? Haskell is the cleanest language
I know of, but I'm sure it has some grungy bits. I've had problems with
unary minus (can't slice binary minus), and precedence of with irrefuatble
patterns and type ascription. I would be happy for any confusing syntax to
be improved. Any good ideas? Syntax change is a possibility: do notation
is a relatively recent addition, and arrow syntax is in the works.

I think you might instead mean the syntax cuts down our market share
because it isn't like common (C derived) languages. I don't think Haskell
could borrow any more syntax from C without actually making the language
worse. It's a problem, but not with the syntax. If someone is so solidly
into a C++/Java/OO mindset that the syntax would be a problem, the
semantics would probably be even more of a problem.

I would suggest Python if Haskell was too much of a jump for someone. It's
still OO, but it encourages more flexible and interesting programs, and
you don't have to live in a Java type system. Plus, it has more libraries,
bindings, and PR, so it's easier to get permission to use it in a company.

If someone is used to Python's layout rule and lack of type signatures,
and gets their head around some of the fun you can have dynamically
picking which members of an object to access, assigning to __dict__ and so
on, then Haskell should be much less of a jump in syntax, and less
imposing in semantics.

 That said, I still think it looks more promising than any other language
 I've looked at that actually is being actively used and maintained and has a
 decent installed base and good cross platform support.  So I will learn it.
 I just wish the transition was easier and that it took less time to learn.
 ;)

 Sean

I learned Haskell from the gentle introduction. It seemed gentle enough
to me but others disagree, so I'm probably not the best for advice for the
raw beginner. If you are interested in learning about monads though,
Jeff Newbern's monad tutorial seems accessible and as complete as anything
this side of Phil Wadler's paper.

I hope learning Haskell goes well.

Brandon

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


Modeling multiple inheritance

2003-09-25 Thread oleg

Brandon Michael Moore wrote:

 So I defined a class to model the inheritance relationships

 class SubType super sub | sub - super where
   upCast :: sub - super

 Now I can define a default instance of HasFooMethod:
 instance (HasFooMethod super args result,
   SubClass super sub) =
  HasFooMethod sub args result where
   foo sub args = foo (upCast sub) args

 This will propagate foo methods down the inheritance hierarcy. If a new
 class C is derived from A, I just need to say

 One problem is that the subclass relationship needs the functional
 dependency

 Does anyone know of clever solutions that would model multiple inheritance
 while preserving the functional dependencies (unsafe compiler flags are
 fine too), or ways to reduce the pain of overloading resolution without
 the functional dependency?

Yes. The code included. The solution is trivial: in case of a multiple
inheritance, a class has a _sequence_ of superclasses rather than a
single superclass. Like

instance SubClass (Object,()) ClassA
instance SubClass (Object,()) ClassB

-- Multiple inheritance (including the diamond!)
instance SubClass (ClassA,(ClassB,())) ClassC
instance SubClass (ClassA,(ClassB,(ClassC,( ClassD

And we need some intelligence to traverse the sequence. But even a
computer can do that. 

I would like to propose a different solution: a dual of
typeclasses in the value domain. Function foo is just a regular
function

foo:: Object - Int - Int
foo x y = y

We then need a class MApplicable fn args result with a method
mapply. The trick is that the method should take any object of a type
castable and cast it to the type of the first argument of fn. The cast
can be made safe and statically checkable, using the type
heap. Actually, we can use the type heap to model the dispatch table
(whose rows are functions and columns are object/classes). Given a
function and an object, we can search in many way for the applicable
combination.

And now, the code for the solution that works.
Compiler flags:
-fglasgow-exts -fallow-overlapping-instances -fallow-undecidable-instances

data Object = Object
data ClassA = ClassA
data ClassB = ClassB
data ClassC = ClassC
data ClassD = ClassD

class SubClass super sub | sub - super where
  upCast :: sub - super
  
instance SubClass (Object,()) ClassA
instance SubClass (Object,()) ClassB
-- Multiple inheritance (including the diamond!)
instance SubClass (ClassA,(ClassB,())) ClassC
instance SubClass (ClassA,(ClassB,(ClassC,( ClassD

class HasFooMethod cls args result where
  foo ::  cls - args - result

instance (SubClass supers sub, 
  HasFooMethod supers args result)
 = HasFooMethod sub args result where
  foo obj args = foo (upCast obj) args

instance (HasFooMethod cls args result) = HasFooMethod (cls,()) args result
  where
foo (x,()) = foo x

instance (HasFooMethod cls args result) = HasFooMethod (x,cls) args result
  where
foo (x,y) = foo y

instance HasFooMethod Object Int Int where
  foo _ x = x

test1::Int = foo Object (1::Int)
test2::Int = foo ClassA (2::Int)
test3::Int = foo ClassD (3::Int)

-- Likewise for another method:

class HasBarMethod cls args result where
  bar ::  cls - args - result
  
instance (SubClass supers sub, 
  HasBarMethod supers args result)
 = HasBarMethod sub args result where
  bar obj args = bar (upCast obj) args

instance (HasBarMethod cls args result) = HasBarMethod (cls,()) args result
  where
bar (x,()) = bar x

instance (HasBarMethod cls args result) = HasBarMethod (x,cls) args result
  where
bar (x,y) = bar y

instance HasBarMethod ClassB Bool Bool where
  bar _ x = x

test4::Bool = bar ClassB True
test5::Bool = bar ClassC True
test6::Bool = bar ClassD True
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe