Re: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-07 Thread Matthew Roberts
I don't think this is publishable research, there is too much other 
stuff already out there.


matt

On 06/06/2005, at 5:58 PM, Gracjan Polak wrote:


Matthew Roberts wrote:
I have a project (for an early research student) waiting for an 
interested student to take on.  It is called Programming patterns 
for OO-like programming in Haskell.  The basic idea is to identify 
how to achieve OO-like organisation of your code in vanilla haskell.  
Hopefully the student can come to a deep understanding of OO and 
haskell programming in the process.


If this could count as graduate student project and could spawn 
publication then I would be interested. :)


Sounds like exactly what you need.  Shame no-one has taken it up yet. 
 Perhaps next semester :)  Anyone out there want to come to Sydney 
and take it on?


As I see you did not cc the list, so currently I'm the only one that 
received this message. :)



Matt
On 06/06/2005, at 3:55 AM, Gracjan Polak wrote:

Cédric Paternotte wrote:
 Hi. This is my first message here so Hello to everyone.

 I'm just starting to learn Haskell and I really think it's a cool 
language.


Me too :)

 I know OO and inheritance is not really the point of Haskell and 
that

 other mechanisms are provided to somewhat achieve reuse. But it's a
 way of programming I've been so used to that I feel lost without 
it.
 You might think I'm heading in the wrong direction. My mistake I 
have

 to agree. Let's take it as a learning exercise then.

Me too :)

 5. With this : 
http://www.cs.utexas.edu/ftp/pub/techreports/tr01-60/tr01-60.pdf



I've been thinking about slight generalization of this lately. Here 
are my semi-backed thoughts as of now.


First of all, in Haskell there will be strict separation between 
interfaces and data, so almost every method will be declared twice. 
This is not so strange to anybody programing in Java, but for C++ 
programmers can be. Inheritance relation is specified after data. 
There is also separation between two concepts: what interfaces each 
piece of data implements and which intefaces given interface 
inherits. So:


{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

module Main where

-- general inheritance relation
class Inherits b x where
get_super :: x - b

-- declare interface with one method
class IA a where
get_a :: a - Int

-- define data with one field
data DA = DA { da_field :: Int }

-- say how data DA conforms to interface IA
instance IA DA where
get_a x = da_field x

-- declare some other interface IB
-- note: IB is unrelated to IA
class IB a where
get_b :: a - String

-- data that inherits fields of DA and adds one another field
data DB = DB { db_super :: DA, db_field :: String }

-- DB inherits fields and methods of DA
instance Inherits DA DB where
get_super x = db_super x

-- data DB implements interface IB
instance IB DB where
get_b x = db_field x

-- some other random data
data DC = DC { dc_super :: DA }

-- DC implements interface IB
instance IB DC where
get_b x = show (get_a x)

-- and inherits DA
instance Inherits DA DC where
get_super x = dc_super x

-- now the tricky part: state that every data x inheriting DA
-- implements all interfaces of DA (repeat for each interface)
instance (Inherits DA x) = IA x where
get_a w = da_field (get_super w)

main = do
let db = DB (DA 123) zzz
let dc = DC (DA 123)
putStrLn $ show (get_a db)
putStrLn $ show (get_a dc)
putStrLn $ show (get_b db)
putStrLn $ show (get_b dc)

As you see there is much more writting as in Java. But this gives 
better control over inheritance and subsumption because everything 
must be stated explicitly. Multiple inheritance is allowed :) Also 
it is private inheritance (as in C++) by default.


There are some problems left: how to update a field? or how to make 
inheritance transitive. I don't know it yet :)



 I guess my question now is this : Are there other ways to achieve
 inheritance in Haskell ?

Me too:)

My proposal (above) is about the level of 'OO' things done in 
procedural languages (example: C with GTK+ library). There must be a 
better way. Any comments?


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


RE: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-07 Thread Ralf Lammel
There are tons of good research questions readily waiting.

Such as:

- What would we want to explore in OOish Haskell so that we, once more,
can provide interesting input for mainstream language development? More
specifically: what sorts of type inference would make a difference in
Java 1.5+, C# 2.0+?

- How would Haskell's type-class type system need to evolve in order to
provide completely satisfying programmer experience for the uses of
type classes in the various existing styles of OOish Haskell
programmning?

- We have Template Haskell but we are *still* rather lame when doing
(OOish) language extensions. Macro systems with syntax extensions
perhaps really open up a wormhole but nevertheless: *how* can we get a
more experimental Haskell environment where language experiments make a
good impression at the level of syntactic sugar, debugging, error
messages, and all that?

- How is it possible that Haskell lacks true extensible functions
(modulo the kind of encoding I sent around earlier)? This is one of the
big immediate benefits of OO mainstream programming. Seeing Haskell
not providing them, makes me feel sad. It is also amazing that Haskell
scores with complicated modes of extensibility (cf. monad transformers),
but has no watertight answer when it comes to silly extensible datatypes
(or classes) and functions (or methods) defined upon those.

- ...

Let's go to Sydney :-)
(Or at the very least, let's meet at the Haskell Workshop!)

Ralf

 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Matthew Roberts
 Sent: Tuesday, June 07, 2005 12:15 AM
 To: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] [Newbie] Quest for inheritance
 
 I don't think this is publishable research, there is too much other
 stuff already out there.
 
 matt
 
 On 06/06/2005, at 5:58 PM, Gracjan Polak wrote:
 
  Matthew Roberts wrote:
  I have a project (for an early research student) waiting for an
  interested student to take on.  It is called Programming patterns
  for OO-like programming in Haskell.  The basic idea is to identify
  how to achieve OO-like organisation of your code in vanilla
haskell.
  Hopefully the student can come to a deep understanding of OO and
  haskell programming in the process.

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


Re: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-07 Thread Gracjan Polak

Ralf Lammel wrote:

Cédric Paternotte wrote:
...

 5. With this :
http://www.cs.utexas.edu/ftp/pub/techreports/tr01-60/tr01-60.pdf


Gracjan Polak wrote:

I've been thinking about slight generalization of this lately. Here are
my semi-backed thoughts as of now.



I should have mentioned 
http://homepages.cwi.nl/~ralf/OOHaskell/src/PoorMens2/

(again *not* using OOHaskell)


From the quick skim of code:
.?. -- apply function to upcast object
.!. -- apply modification function to upcast object and substitute 
returned value (new object), basically update


Is there any description avaliable what is PoorMens2 all about?



A more general and preliminary observation:
the entire approach is potentially more about
object *composition* (and perhaps delegation) 
rather than inheritance. Many OO evangelists 
consider inheritance as a concept that was used

too much in early OO times, while object composition
is often more appropriate and flexible. So one *might*
say that this approach does not encode a Java-inheritance
solution but it does an inheritance-to-object-composition
migration on the fly. So what Gracjan calls Inherits
(and I call subtyping or substitution) is perhaps more a
delegates.


Yes, I agree with this statement. The OP question was: how to simulate 
inheritance in Haskell? One of the answers: using delegation :)




Ralf


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


RE: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-07 Thread Ralf Lammel
Hi Gracjan,

  http://homepages.cwi.nl/~ralf/OOHaskell/src/PoorMens2/
  (again *not* using OOHaskell)
 
  From the quick skim of code:
 .?. -- apply function to upcast object
 .!. -- apply modification function to upcast object and substitute
 returned value (new object), basically update

Absolutely.

 Is there any description avaliable what is PoorMens2 all about?

Let me try.
It's just a variation on Chris' encoding of the shape example,
while trying to improve code reuse, while trying to highlight
the commonalities in the data parts of the objects in the inheritance
hierarchy. The approach ends up being similar to yours in so far
that getters (and setters) can be made work for derived types once
they are defined on the base type. 

I just notice that there is a short (because non-monadic) version:

http://homepages.cwi.nl/~ralf/OOHaskell/src/PoorMens/

Ralf

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


[Haskell-cafe] class Ref...

2005-06-07 Thread Gracjan Polak


Hi,

I the paper of Magnu Carlsson I noticed small, interesting class:

class Monad m = Ref m r | m - r where
newRef :: a - m (r a)
readRef :: r a - m a
writeRef :: r a - a - m ()

He defined it locally, but it seems to be very useful generalization of 
IORef and STRef. Is there something like this in standard libraries? I 
couldn't find it... :( Is there any reason why isn't it included?


Another question: priority queue. In libraries bundled with ghc we have 
Data.Queue, but I couldn't find PriorityQueue. Is there somewhere an 
implementation that everybody uses, but is not in the library?


Thanks!

--
Gracjan

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


Re: [Haskell-cafe] foldl and space problems

2005-06-07 Thread Gracjan Polak

Bernard Pope wrote:


A more practical solution is to force the compiler to generate more
strict code. 


I tried to put strictness annotation in every place I could think of. 
Without result :(




You might also find GHood useful:

http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/GHood/


Thanks for the pointer.



Cheers,
Bernie.


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


Re: [Haskell-cafe] foldl and space problems

2005-06-07 Thread Bernard Pope
On Tue, 2005-06-07 at 12:35 +0200, Gracjan Polak wrote:
 Bernard Pope wrote:
  
  A more practical solution is to force the compiler to generate more
  strict code. 
 
 I tried to put strictness annotation in every place I could think of. 
 Without result :(

Did you try Data.List.foldl' ?

Perhaps you could post the definition of the state type? Or even better,
a small example of code that runs badly.

Cheers,
Bernie.

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


Re: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-07 Thread Cédric Paternotte
 I just notice that there is a short (because non-monadic) version:
 
 http://homepages.cwi.nl/~ralf/OOHaskell/src/PoorMens/

I have to say that this version of the Shape example is my favourite so far.
Good compromise between complexity, typing and usefulness.

May I just suggest an improvement that could further improve the code re-use ?

I noticed that both Rectangle and Circle need to redefine the
operators because of the different names of their respective delegate
to Shape, namely rectangle2shape and circle2shape.

I we were to give these fields the same name ('parent', or 'super') in
both Rectangle and Circle, could it be that we can avoid to redefine
the operators by moving their definition upwards (and thus requiring
only one definition for both classes) ?

I guess that would also mean that we restrict ourselves to
single-inheritance since we rely on the uniqueness of the name
'parent' throughout. But since single inheritance is IMO enough to fit
most needs I don't see it as a problem.

Would it then be a problem if we further subclass Rectangle in, say,
two subclasses Square and NonSquareRectangle ? Would that still work
or would there be a collision between the multiple 'parent' fields ?


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


Re: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-07 Thread Bulat Ziganshin
Hello Cédric,

Sunday, June 05, 2005, 5:52:13 PM, you wrote:

CP What interested me in this was the mechanism they used to model
CP inheritance (described on page 16  19), based on data types instead
CP of classes. The idea being that all constructors of the Employee
CP datatype have a same parameter, 'inCommon', of type
CP 'CommonOfEmployees'.
CP The conclusion I drew from my quick  early findings is that the
CP latest method is the simplest way to get inheritance in my programs.

OO approach is only one technology of divide and conquer, just very
popular in last 20 years. moreover, in OO world all the other possible
programming techniques are gone to be modelled via this uniform
mechanism. as a result, programmers with strong OO-only backgound tend
to search solution for any programming problem in terms of classes and
inheritance between them

FP provides your another basic programming block - function call,
or parameterized computation. quick comparision with OO basic block -
class will tell you that function call is a more simple, basic element
while class interface consists of several such function calls. so,
simplest analogy of class interface is just tuple of functions:

createCircle x y r = let draw = ...
 move x y = ...
 changeColor c = ...
 in (draw, move, changeColor)

createRectangle x y w h = let draw = ...
  move x y = ...
  changeColor c = ...
 in (draw, move, changeColor)

such types of interfaces cover 90% of situations where you must use
classes in C++ (well, only 30%. another 60% covered by even simpler
construction:

data Shape = Circle x y r
   | Rectangle x y w h

draw (Circle x y r) = ...
draw (Rectangle x y w h) = ...



imho, FP programming require that you think in terms what operations
i need for this object and what data each this operation will need
instead of OO's what is a class hierarchy. code reusing is reached
by creating general functions which receive divergent subfunctions as
their parameters:

calcCRC (fOPEN,fREAD,fCLOSE) = do
  h - fOPEN
  crc - newIORef 0
  buf - mallocBytes 65536
  let go = do len - fREAD h buf 65536
  crc - updateCRC crc buf len
  when (len0) go
  go
  fCLOSE h
  readIORef crc

calcFileCRC filename = calcCRC (hOpen filename, hGetBuf, hClose)

calcCompressedDataCRC file algorithm  = do
  calcCRC (startDecompression file algorithm,
   decompressBlock,
   finishDecompression)


You can find more examples of using such technique in my program
(http://freearc.narod.ru), see for example allocator/memoryAllocator,
ByteStream.createFile/createBuffered/create, read_file
  

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell-cafe] class Ref...

2005-06-07 Thread Gracjan Polak

Bulat Ziganshin wrote:

Hello Gracjan,

Tuesday, June 07, 2005, 2:25:50 PM, you wrote:
class Monad m = Ref m r | m - r where
GP  newRef :: a - m (r a)
GP  readRef :: r a - m a
GP  writeRef :: r a - a - m ()

may be the following will be even more interesting:



I like it very much!


import Control.Monad
import Data.IORef

infixl 0 =:, +=, -=, =::, =
ref = newIORef
val = readIORef
a=:b = writeIORef a b


Pretty shame := is already reserver :(. There is something alike 
Graphics.Rendering.OpenGL.GL.StateVar. The use $= for assignment. 
Generalizing variables (in respect to some monad) seems to be often 
reinvented idea :)


As I see this could be generalized to all Ref-like constructs 
(IO,ST,others?)



a+=b = modifyIORef a (\a- a+b)
a-=b = modifyIORef a (\a- a-b)
a=::b = ((a=:).b) = val a

Is this convoluted modify? Why doesn't it use modifyIORef? Or am I wrong?


for :: [a] - (a - IO b) - IO ()
for = flip mapM_


I like:

foreach = flip mapM
foreach_ = flip mapM_



newList = ref []
list = x   =  list =:: (++[x])

Is this append?


push list x  =  list =:: (x:)
pop list =  do x:xs-val list; list=:xs; return x

main = do
  sum - ref 0
  lasti - ref undefined
  for [1..5] $ \i - do
sum += i
lasti =: i
  sum =:: (\sum- 2*sum+1)
  print = val sum
  print = val lasti

  xs - newList
  for [1..3] (push xs)
  xs = 10
  xs = 20
  print = val xs



Haskell as ultimate imperative language :)




I use this module to simplify working with references in my program.
The first inteface can be used for IORef/STRef/MVar/TVar and second
for lists and Chan



Then we should create classes for those interfaces.

--
Gracjan

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


[Haskell-cafe] Infix operators naming conflicts (was: class Ref)

2005-06-07 Thread Dimitry Golubovsky
Gracjan Polak wrote:

 val = readIORef
 a=:b = writeIORef a b

Pretty shame := is already reserver :(. There is something alike 
Graphics.Rendering.OpenGL.GL.StateVar. The use $= for assignment. 
Generalizing variables (in respect to some monad) seems to be often 
reinvented idea :)

Indeed, has anyone tried to summarize possible conflicts between infix
operators as they are defined in many places to serve different
purpose?

e. g.

(!) :: Ix i = Array i e - i - e 
The value at the given index in an array.  (Data.Array)

(!) :: a - [HtmlAttr] - a (Text.Html)

so if a module imports both modules mentioned above simultaneously,
will the compiler complain about (!) and ask to use a qualified name?

I had the following experience: when trying to create a convenient
syntax to access fields of foreign C structures using appropriate Ptr
and field label, I tried to define a combinator for that, and to name
it (.) (dot, same as dot-composition defined in Prelude, to look
similarly to Java notation) Type signature for my (.) was totally
different than Prelude's (.), and semantically it is not composition
of functions. However the compiler (GHC) asked to use qualified name.

Finally I ended up with the name (--) which looks like C notation.
But who knows, whether someone wishes to use (--) for other purposes?

-- 
Dimitry Golubovsky

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


[Haskell-cafe] Usage of | in classes

2005-06-07 Thread Frank-Andre Riess
Hi,
(B
(BGracjan's question led me to another question:
(B
(B class Monad m = Ref m r | m - r where
(B  newRef :: a - m (r a)
(B  readRef :: r a - m a
(B  writeRef :: r a - a - m ()
(B
(BWhat's the meaning of the bar and the function type in this declaration. I've 
(Bseen something like that before (with state monads, I think), but couldn't 
(Bfind an explanation in the Haskell grammar (or anywhere else on haskell.org).
(B
(BThanks in advance,
(BFrank-Andre
(B___
(BHaskell-Cafe mailing list
(BHaskell-Cafe@haskell.org
(Bhttp://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Usage of | in classes

2005-06-07 Thread Arthur van Leeuwen
On Tue, Jun 07, 2005 at 03:54:06PM +0200, Frank-Andre Riess wrote:
 Hi,
 
 Gracjan's question led me to another question:
 
  class Monad m = Ref m r | m - r where
   newRef :: a - m (r a)
   readRef :: r a - m a
   writeRef :: r a - a - m ()
 
 What's the meaning of the bar and the function type in this declaration. I've 
 seen something like that before (with state monads, I think), but couldn't 
 find an explanation in the Haskell grammar (or anywhere else on haskell.org).

It is a functional dependency. That is, in this case, the choice of type r 
is uniquely determined by the choice for the type m. See also
http://haskell.org/hawiki/FunDeps and
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#functional-dependencies

 Thanks in advance,

My pleasure.

Doei, Arthur.

-- 
  /\/ |   [EMAIL PROTECTED]   | Work like you don't need the money
 /__\  /  | A friend is someone with whom | Love like you have never been hurt
/\/__ | you can dare to be yourself   | Dance like there's nobody watching
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Infix operators naming conflicts (was: class Ref)

2005-06-07 Thread Abraham Egnor
On 6/7/05, Dimitry Golubovsky [EMAIL PROTECTED] wrote:
 Gracjan Polak wrote:
 
  val = readIORef
  a=:b = writeIORef a b
 
 Pretty shame := is already reserver :(. There is something alike
 Graphics.Rendering.OpenGL.GL.StateVar. The use $= for assignment.
 Generalizing variables (in respect to some monad) seems to be often
 reinvented idea :)

Indeed; another example is
http://ofb.net/repos/attribute/src/Data/Attribute.hs.

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


Re: [Haskell-cafe] Re: Visual Hashell Studio.NET 2005

2005-06-07 Thread Krasimir Angelov
Hi Maurício,

VSHaskell has nothing to do with .NET or Mono. This isn't Haskell for
.NET compiler. We are just developing programming environment for
Haskell in Visual Studio. The environement uses the normal GHC
compiler.

Cheers,
 Krasimir


On 6/6/05, Maurício [EMAIL PROTECTED] wrote:
 Brian Smith wrote:
  Hi,
 
  When will VHS support the Visual Studio.NET 2005 Beta? I'd like to
  volunteer to test VHS.NET 2005 when it is available. (Also, MS is
  giving away the VS.NET 2005 beta for free, and VS.NET 2003 costs a
  whopping $15.00 from my school's bookstore).
 
  Thanks,
  Brian
 
   Can we use Haskell with mono?
 
   [...],
   Maurício
 
 ___
 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


Re: [Haskell-cafe] Visual Hashell Studio.NET 2005

2005-06-07 Thread Krasimir Angelov
Hi Brian,

Currently I have only VS.NET 2003 license and this is my main
development platform. I think it will not be much effort to upgrade
VSHaskell to VS.NET 2005 but I have no way to try it. I may try to
download Visual Studio.NET 2005 Beta but I am afraid that the download
will be too large.

Cheers,
  Krasimir

On 6/5/05, Brian Smith [EMAIL PROTECTED] wrote:
 Hi,
 
 When will VHS support the Visual Studio.NET 2005 Beta? I'd like to
 volunteer to test VHS.NET 2005 when it is available. (Also, MS is
 giving away the VS.NET 2005 beta for free, and VS.NET 2003 costs a
 whopping $15.00 from my school's bookstore).
 
 Thanks,
 Brian
 ___
 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


RE: [Haskell-cafe] [Newbie] Quest for inheritance

2005-06-07 Thread Ralf Lammel
Hi Cedric,

  http://homepages.cwi.nl/~ralf/OOHaskell/src/PoorMens/
 
 Good compromise between complexity, typing and usefulness.

[unfortunately also limited,
which is the reason that we came up with the monadic version:
PoorMens2.]

 I noticed that both Rectangle and Circle need to redefine the
 operators because of the different names of their respective delegate
 to Shape, namely rectangle2shape and circle2shape.
 
 I we were to give these fields the same name ('parent', or 'super') in
 both Rectangle and Circle, could it be that we can avoid to redefine
 the operators by moving their definition upwards (and thus requiring
 only one definition for both classes) ?

Won't work. ;-)
Haskell standard records are not polymorphic like this.
You can't write an operation that uses a record selector without committing to 
a specific record type. (With HList that underlies OOHaskell, of course, you 
can!!!)

This is *precisely* the reason that:
- Gracjan's code had a get_super.
- my code has the generic .?. operator.

We could try to give up on using normal records.
That is, we could use a tuple convention where the first projection
returns the data part of the base class, and the second projection
returns the contribution of the derivation. However, this won't get
us anywhere. We need the nominal types introduced by the new record
types in order to represent the inheritance hierarchy in the type
system (through the Inherits or Subtype classes).

 Would it then be a problem if we further subclass Rectangle in, say,
 two subclasses Square and NonSquareRectangle ? Would that still work
 or would there be a collision between the multiple 'parent' fields ?

Due to the abovementioned reasons, any sort of parent fields will not 
interfere. Repeated inheritance simply leads to nested data composition;
that's Ok. 

Ralf

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


Re: [Haskell-cafe] class Ref...

2005-06-07 Thread Tomasz Zielonka
On Tue, Jun 07, 2005 at 12:25:50PM +0200, Gracjan Polak wrote:
 Another question: priority queue. In libraries bundled with ghc we have 
 Data.Queue, but I couldn't find PriorityQueue. Is there somewhere an 
 implementation that everybody uses, but is not in the library?

You can use the new Data.Map module for this (old Data.FiniteMap too,
but a bit more clumsily), it has findMin, findMax, deleteFindMin,
deleteFindMax, deleteMin, deleteMax. All these operations should have
O(log N) cost.

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


[Haskell-cafe] Re: Quest for inheritance

2005-06-07 Thread Andre Pang

On 06/06/2005, at 3:47 PM, Cédric Paternotte wrote:



Manuel Chakravarty and I also wrote a paper titled Interfacing
Haskell to Object-Oriented Languages that you might find useful:



I've been reading it and from what I understood the technique you've
come up with is used to model foreign OO language hierarchies so that
Haskell can interface with them. My question is can you use it to code
in Haskell in a OO way or is it just meant to provide bridges to these
foreign OO objects ?



I don't think there's any real barrier to coding Haskell in an OO  
way, though my personal motivation for the paper was really to use it  
as a primitive bridging layer, and build a more functional interface  
on top of it.  wxHaskell is a good example of this: it provides a  
more Haskell-like interface on top of a basic layer to wxWidgets via  
a layer named wxCore.  Note that Mocha (which is discussed in the  
paper) has been succeeded by HOC: http://hoc.sf.net/, although  
that's probably of serious interest to you if you have a Mac.




I noticed most examples in the paper were related to the matters of
interfacing. Or is it more than that ? Could you, for instance, craft
a version of, say, the Shapes example with this approach ?



You could definitely craft up a Shapes example with the interfaces  
presented in the paper; if you think of an OO library that exports  
Shapes as a public API, then making an interface to this library vs  
crafting the Shapes example is the same thing.



--
% Andre Pang : trust.in.love.to.save  http://www.algorithm.com.au/



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


Re: [Haskell-cafe] class Ref...

2005-06-07 Thread ajb
G'day all.

Quoting Gracjan Polak [EMAIL PROTECTED]:

 class Monad m = Ref m r | m - r where
  newRef :: a - m (r a)
  readRef :: r a - m a
  writeRef :: r a - a - m ()
[...]

 Is there something like this in standard libraries?

No.

 Is there any reason why isn't it included?

Nobody could agree on the details.  For example, MVars are perfectly
respectable Refs on the IO monad.  So would it make sense to add an
instance for that?  If so, the functional dependency should go, which
introduces its own problems.

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


[Haskell-cafe] Re: [Haskell] Strictness question

2005-06-07 Thread Ben Lippmeier


 To gloss over details: it'll reduce x far enough so it knows that
 it's an Integer, but it won't nessesarally compute that integers
 value.

 No, Integers don't contain any lazy components.
 It statically knows that it's an integer.

I meant that it would reduce to the outermost constructor but 
nessesarally evaluate the rest of the object.


Ok, I actually looked up the implementation of Integer in GHC.

 -- | Arbitrary-precision integers.
 data Integer   
   = S# Int# -- small integers
 #ifndef ILX
   | J# Int# ByteArray#  -- large integers
 #else
   | J# Void BigInteger  -- .NET big ints

You were right and I was wrong, Integers contain no lazy components. 
Perhaps that just highlights the folly of guessing how much actually 
gets evaluated in a lazy language.. :)


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


Re[2]: [Haskell-cafe] class Ref...

2005-06-07 Thread Bulat Ziganshin
Hello Gracjan,

Tuesday, June 07, 2005, 4:52:50 PM, you wrote:

 a=:b = writeIORef a b

GP Pretty shame := is already reserver :(.

:=  reserved for infix data constructors, as any other symbols
starting with ':'

GP As I see this could be generalized to all Ref-like constructs
GP (IO,ST,others?)

i think so

 a+=b = modifyIORef a (\a- a+b)
 a-=b = modifyIORef a (\a- a-b)
 a=::b = ((a=:).b) = val a
GP Is this convoluted modify? Why doesn't it use modifyIORef? Or am I wrong?

a=::(*2)  doubles value of `a` and so on. i don't define this as
`modifyIORef` equivalent just because it's is a funnier definition :)
also i was interested to define all funcs via 2 primitives - `val` and
'=:` (which is like readRef/writeRef in your example); such
definitions will be more convenient for defining Ref as class:

class Ref a where
  val 
  (=:) ...

instance Ref (MVar a) where
  val=takeMVar
  (=:)=putMVar

where all other operations are defined via this two primitives. of
course, it's not the best way - adding `modifyRef` to Ref class with
default definition via 'val' and `=:' would be better


 newList = ref []
 list = x   =  list =:: (++[x])
GP Is this append?

it is adding one value to end of list, for Chan'nels it would be
`writeChan`


GP Haskell as ultimate imperative language :)

it may be better, though :)

 I use this module to simplify working with references in my program.
 The first inteface can be used for IORef/STRef/MVar/TVar and second
 for lists and Chan
 

GP Then we should create classes for those interfaces.

of course. i don't done it only because my own program use only IORefs


with help of this defines my code was significantly lightened. see for
example: 

crc   -  ref aINIT_CRC
origsize  -  ref 0
let update_crc (DataChunk buf len) =  do when (block_type/=DATA_BLOCK) $ do
 crc .- updateCRC buf len
 origsize += toInteger len
.
acrc   -  val crc == finishCRC
aorigsize  -  val origsize

you can imagine how this code looked before, using newIORef, readIORef
and so on...  ('.-' is `modifyIORef` in IO monad)

but of course i will prefer more direct support of imperative
programming. i have some proposal - translating

x := @x + @y + @@f 1 2

to

x1 - val x
y1 - val y
f1 - f 1 2
x =: x1+y1+f1

but i guess that number of True Imperative Programmers among GHC users
is not very large :)  in any case, there is an interesting STPP array
indexing preprocessor (http://www.isi.edu/~hdaume/STPP/stpp.tar.gz),
which decides nearly the same problem


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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