[Haskell] New Version of my Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson

I just posted a new version of FG, my Arrows GUI Library Based on GTK+.  
You can find it at http://kevin.atkinson.dhs.org/fg/.  I reworked how 
Events are handled which decreases the number of times a loop is 
traversed form 2^d to d + 1 where d is the depth of the inner most 
loop.  Furthermore only the loop which the event was fired in will need to 
be traversed multiple times.

You can find it at http://kevin.atkinson.dhs.org/fg/.

Feedback appreciated.

Here are some interesting parts from the documentation:

Description:

This module is a first attempt of using Arrows to create a GUI Library 
based on GTK+. A good understanding of how Arrows work is required in 
order to understand the interface. For more information on Arrows see 
http://www.haskell.org/arrows/.

It uses many ideas from Fruit (http://haskell.org/fruit/). However it is 
based on discrete events rather than a continuous signal. The interface is 
only updated during an Event. It also ideas from Fudgets 
(http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/), some of which 
were also used by Fruit. 

...

Implementation Notes:

Arrows essentially build up a huge tree like data structure representing 
the control flow between arrows. In the current implementation most of 
top-level structure has to be traversed when ever an event is fired -- 
even if absolutely no actions need to be taken. When a loop is used parts 
of this structure may be traversed multiple times. In particular the inner 
most loop where an event was fired from will be traversed d + 1 times 
where d is the depth of the loop. If an event was not fired inside a loop 
(or any of the sub loops) than the loop will only be traversed once.

Avoiding this problem of having to traverse most of tree for every event 
requires information that I'm not sure the compiler can give me. For 
example I need to know the difference between arr (x - x) and arr (_ - 
10). The first passes the input to the output the second throws the value 
away. All I am able to know is that arr was used. What exactly the 
function does is a black box. 

-- 
http://kevin.atkinson.dhs.org


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


[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson
On Sun, 20 Mar 2005 [EMAIL PROTECTED] wrote:

 On Sat, Mar 19, 2005 at 12:17:46PM -0700, Kevin Atkinson wrote:
  On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:
   I would also have expected loopFG to have been defined using fixIO.
  
  Could you be more specific.  Ie How?
 
 For the type definitions
 
   newtype FG' a b = FG' (Control - a - IO (Control, b))
   newtype FG a b = FG (FGState - IO (FG' a b, FGState))
   newtype Container a b = Container (FG ([WidgetP], a) b)
 
 the usual instances would be (give or take a ~):
 
   instance ArrowLoop FG' where
   loop (FG' f) = FG' $ \ c x - do
   (c', x', _) - mfix $ \ ~(_, _, y) - do
   ~(c', ~(x', y')) - f c (x, y)
   return (c', x', y')
   return (c', x')

I must admit that I am baffled by what this is doing.  But I don't think 
it has the semantics I want.  When I try substituting your 
code in I get Exception: loop.  I have reworked the way loops are 
handled.  Please have a look at the new code at 
http://www.haskell.org/arrows/.

-- 
http://kevin.atkinson.dhs.org

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


[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson
On Tue, 22 Mar 2005, Kevin Atkinson wrote:

 On Sun, 20 Mar 2005 [EMAIL PROTECTED] wrote:
 
  On Sat, Mar 19, 2005 at 12:17:46PM -0700, Kevin Atkinson wrote:
   On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:
I would also have expected loopFG to have been defined using fixIO.
   
   Could you be more specific.  Ie How?
  
  For the type definitions
  
  newtype FG' a b = FG' (Control - a - IO (Control, b))
  newtype FG a b = FG (FGState - IO (FG' a b, FGState))
  newtype Container a b = Container (FG ([WidgetP], a) b)
  
  the usual instances would be (give or take a ~):
  
  instance ArrowLoop FG' where
  loop (FG' f) = FG' $ \ c x - do
  (c', x', _) - mfix $ \ ~(_, _, y) - do
  ~(c', ~(x', y')) - f c (x, y)
  return (c', x', y')
  return (c', x')
 
 I must admit that I am baffled by what this is doing.  But I don't think 
 it has the semantics I want.  When I try substituting your 
 code in I get Exception: loop.  I have reworked the way loops are 
 handled.  Please have a look at the new code at 
 http://www.haskell.org/arrows/.

Make that http://kevin.atkinson.dhs.org/fg/.  Sorry need to pay attention 
when I paste URL's :(

-- 
http://kevin.atkinson.dhs.org

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


[Haskell-cafe] Re: Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson
[From haskell@ to [EMAIL PROTECTED]

On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:

 Some more minor suggestions:
 - I'd suggest making Container a newtype, so it could have an Arrow
   instance (it would be a reader arrow).  Then hbox and vbox could be
   used as arrow operators/combinators.

What will that give me?  Could you give me an example of how I would use 
it in such a manner?

-- 
http://kevin.atkinson.dhs.org

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


[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson
On Tue, 22 Mar 2005 [EMAIL PROTECTED] wrote:

 On Tue, Mar 22, 2005 at 09:52:04AM -0700, Kevin Atkinson wrote:
  I must admit that I am baffled by what this is doing.  But I don't think
  it has the semantics I want.  When I try substituting your
  code in I get Exception: loop.

 I could have made it a bit simpler:

 instance ArrowLoop FG' where
 loop (FG' f) = FG' $ \ c x - do
 (c', ~(x', _)) - mfix $ \ ~(_, ~(_, y)) - f c (x, y)
 return (c', x')

 This executes f once only, with y bound to the third component of the
 output of f.  This isn't available until f finishes, so any attempt
 to examine it while f is running will lead to loop, but f can pass
 it around, and store it in data structures; it can even create cyclic
 structures.  (Under the hood, the IO instance of mfix starts with y bound
 to an exception, and updates it when f finishes, a bit like what you're
 trying to do with IORef's, except that existing references to y then
 point at the updated thing.)  Your definition runs f once with undefined
 as the last argument to get a value for y to supply to a second run.
 Presumably the things you're doing with Control need to change too,
 and I don't understand all that, but I expect that the mfix version
 could be made to work, and would do less work.

I think I understand it more, but I am not sure it will do what I want.
For one thing f still needs to know when it can examine its input thus,
still needing an initializing pass.

Please have a look at the new code.  I have reworked how loops are handled
and no longer use Control.  Also the state variable is now needed in
separate functions.  Thus I am not sure I can use the mfix trick to hide
the state.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-19 Thread Kevin Atkinson
On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:

 On Fri, Mar 18, 2005 at 07:18:29PM -0700, Kevin Atkinson wrote:
  What follows is my first attempt of using Arrows to create a GUI Library 
  based on GTK+.  It uses many ideas from Fruit (http://haskell.org/fruit/). 
  However it is based on discrete events rather than a continuous signal. 
  The interface is only updated during an Event. It also ideas from Fudgets 
  (http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/), some of which 
  were also used by Fruit.  
 
 The implementation of Fruit is also based on discrete events,
 though the abstract description talks about continuous signals.

In FG there is no notation of continuous time.  Something only happens 
during a user event.  In Fruit the each Arrow revives input continuously 
(conceptually, in reality it us during fixed intervals).  In the paper they 
mention that they tried to make into the formal but ran into serious
problems with due to the way they implemented things.  I am not sure if it 
is fundamental to the fire

 
 Your module uses the arrow interface, but it's actually equivalent to
 monads.  

It is?  Than what would app look like?

 I don't know if this is the source of the multiple traversals,
 but you may wish to experiment with synchronous stream arrows like
 Automaton transformer in the experimental arrow transformer library
 linked from the arrows page, or an asynchronous Fudgets-like arrow
 (see John's original paper).

I will get back to you.  I can sort of see how it is Monad (but won't be 
convinced until I see an app implementation).  Has anyone tried to make 
Fudgets an instance of the Arrow class?

 Some more minor suggestions:

 - how about: data Event a = NoEvent | Event a

And what would a be?  For Now I only have one event.  I do need a more 
extensible Event system.

 - you don't really need mkAFunDef in AbstractFunction, and indeed you
   don't need AbstractFunction either -- you could just use Arrow, of
   which both (-) and FG are already instances.

But than can I make a function like tag which can either be used as an 
arrow or a function.  Ie:
  a - tag a  button [] - def
  b - tag b  button [] - def
  let e = a  b
  ...
OR
  a - button [] - def
  b - button [] - def
  let e = tag a a  tag b b
  ...

 - you could make FG, FG', EntryP newtypes instead of using the !
   annotation.

Yes your right.

 - I'd suggest making Container a newtype, so it could have an Arrow
   instance (it would be a reader arrow).  Then hbox and vbox could be
   used as arrow operators/combinators.

I will look into it.  I am still trying to fully understand Arrows.  Which 
is maybe why I may of inadvertently made a monad.

-- 
http://kevin.atkinson.dhs.org

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


Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-19 Thread Kevin Atkinson
On Sat, 19 Mar 2005, David Menendez wrote:

 Kevin Atkinson writes:
 
  
  What follows is my first attempt of using Arrows to create a GUI
  Library based on GTK+.  It uses many ideas from Fruit
  (http://haskell.org/fruit/). However it is based on discrete events
  rather than a continuous signal. The interface is only updated during
  an Event. It also ideas from Fudgets
  (http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/), some of
  which were also used by Fruit.
  
  To the best of my knowledge this has note been attempted before as
  Fruit is not based on an existing GUI.
 
 Are you familiar with wxFruit[1]? It adapts Fruit to run on wxHaskell.
 
 [1] http://zoo.cs.yale.edu/classes/cs490/03-04b/bartholomew.robinson/

No I was not originally aware of this.  I had a brief look at the paper.  
Unlike my module, it was written on top of the Yampa AFRP module.  It thus 
inherits some of the inherited problems of Yampa, the main one is that is 
that widgets are continuously being updated, even if there are no user 
actions.

The continuous updates avoided the problem of having to traverse the Arrow 
structure twice in the case of loops.  This is because the output of the 
underlying Arrow inside the loop will be feed back in during the next 
iteration.  I image that if they took away the continuous updates they would 
have the same problems that I have in implementing loops.

-- 
http://kevin.atkinson.dhs.org

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


Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-19 Thread Kevin Atkinson
On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:

 On Sat, Mar 19, 2005 at 07:48:09AM -0700, Kevin Atkinson wrote:

  Has anyone tried to make Fudgets an instance of the Arrow class?
 
 see the stream processors in John Hughes's original paper.

I will have a closer look.

   - how about: data Event a = NoEvent | Event a
  
  And what would a be?
 
 The thing you currently always pair with an Event, and ignore if it's
 NoEvent.

But that value may also be used even if there is not an event.  For 
example you may want to read the current value of an Entry or a 
ToggleButton.

   - you don't really need mkAFunDef in AbstractFunction, and indeed you
 don't need AbstractFunction either -- you could just use Arrow, of
 which both (-) and FG are already instances.
  
  But than can I make a function like tag which can either be used as an 
  arrow or a function.
 
 But functions are arrows: (-) is an instance of the Arrow class.

But of separate Arrow instances.  For example if I redefine tag from

  tag :: (AbstractFunction f) = b - f (Event, a) (Event, b)
  tag v = mkAFun (\(e, _) - (e, v)) 
to
  tag :: b - (Event, a) - (Event, b)
  tag v = \(e, _) - (e, v)

Than I couldn't do as I gave in my example:

  a - tag a  button [] - def

-- 
http://kevin.atkinson.dhs.org


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


[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-19 Thread Kevin Atkinson
On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:

 [moving to haskell-cafe, as this thread is getting long]
 
 On Fri, Mar 18, 2005 at 07:18:29PM -0700, Kevin Atkinson wrote:
  What follows is my first attempt of using Arrows to create a GUI Library 
  based on GTK+.  It uses many ideas from Fruit (http://haskell.org/fruit/). 
  However it is based on discrete events rather than a continuous signal. 
  The interface is only updated during an Event. It also ideas from Fudgets 
  (http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/), some of which 
  were also used by Fruit.  
 
 I would also have expected loopFG to have been defined using fixIO.

Could you be more specific.  Ie How?

-- 
http://kevin.atkinson.dhs.org


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


[Haskell] Arrows GUI Library Based on GTK+

2005-03-18 Thread Kevin Atkinson

What follows is my first attempt of using Arrows to create a GUI Library 
based on GTK+.  It uses many ideas from Fruit (http://haskell.org/fruit/). 
However it is based on discrete events rather than a continuous signal. 
The interface is only updated during an Event. It also ideas from Fudgets 
(http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/), some of which 
were also used by Fruit.  

To the best of my knowledge this has note been attempted before as Fruit 
is not based on an existing GUI.  As such I ran into a number of 
unique problems.  Some of which are discussed in the implementation notes 
below.  I plan on elaborating on the many issues I had to deal with 
latter.

You can find the code and documentation at: 
  http://kevin.atkinson.dhs.org/fg/.  

I am also intersting parts below (The whole file is two large).  Feedback 
appreciated.


-- FG.hs
-- Copyright (C) 2005 by Kevin Atkinson under the GNU LGPL license
-- version 2.0 or 2.1.  You should have received a copy of the LGPL
-- license along with this library if you did not you can find
-- it at http://www.gnu.org/

{-|

This module is a first attempt of using Arrows to create a GUI Library
based on GTK+.  A good understanding of how Arrows work is required in
order to understand the interface.  For more information on Arrows see
http://www.haskell.org/arrows/.

It uses many ideas from Fruit (http://haskell.org/fruit/).  However
it is based on discrete events rather than a continuous signal.  The
interface is only updated during an Event.  It also ideas from
Fudgets (http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/),
some of which were also used by Fruit.

Here is a complete working example to give you an idea of how to use FG:

  import FG

  -- A Widget with three buttons Inc, Dec and Reset.  Dec is
  -- disabled when the count is 0.   Does not actually display the count.
  -- The output value is the current value of the counter.
  counter :: Widget WidgetP Int
  counter = proc p - hbox [] (proc _ - do
  rec inc - tag (+1)  button [text Inc] - def
  dec - tag (+(-1))  button [text Dec] - [enabled (c  0)]
  reset - tag (const 0)  button [text Reset] - def
  cs@(_,c) - hold 0 - onEvent (\f - Just $ f c) Nothing
(inc  dec  reset)
  returnA - cs) - (p, ())
  
  -- The main FG.  Connects the value of the counter to a Label.
  mainFG :: Container () ()
  mainFG = vbox [spacing 2] $ proc _ - do
  (_,c) - counter - def
  label [] - [text $ show c]
  returnA - ()
  
  main :: IO ()
  main = runFG mainFG

-}

---
--
-- Basic Types
--

data FG a b = FG !(FGState - IO (FG' a b, FGState))

data Event = NoEvent | Event

---
--
-- Internal data types
--

data FG' a b = FG' !(Control - a - IO (Control, b))

data Control = Init | Pending !EventId | Handled !EventId | Done deriving Eq

type EventId = Int

data AbstrWidget = forall w. WidgetClass w = AbstrWidget w

data PendingCallback = PendingCallback !EventId !(Callback - IO ())

type Callback = IO ()

data FGState = FGState ![AbstrWidget]
   !EventId -- Last used callback id
   ![PendingCallback]

---
--
-- Arrow Implementation
--

instance Arrow FG where
arr = arrFG
() = combFG
first = firstFG

instance ArrowLoop FG 
where loop = loopFG

arrFG :: (a - b) - FG a b
arrFG f = FG $ \s - do
let f' c x = return (c, f x)
return (FG' f', s)

combFG :: FG a b - FG b c - FG a c
combFG (FG f1) (FG f2) = FG $ \s - do
(FG' f1, s) - f1 s
(FG' f2, s) - f2 s
let f c v = do (c, v) - f1 c v
   (c, v) - f2 c v
   return (c, v)
return (FG' f, s)

firstFG :: FG a b - FG (a,c) (b,c)
firstFG (FG f) = FG $ \s - do
(FG' f, s) - f s
let f' c (x, y) = do (c, x) - f c x
 return (c, (x, y))
return (FG' f', s)

loopFG :: FG (a, c) (b, c) - FG a b
loopFG (FG f) = FG $ \z - do
(FG' f, z) - f z
st - newIORef undefined
let f' Init v = do (Init, (v', s)) - f Init (v, undefined)
   writeIORef st s
   return (Init, v')
f' c v = do s - readIORef st
(c, (_, s)) - f c (v, s)
(c, (v', s)) - f c (v, s)
writeIORef st s
return (c, v')
return (FG' f', z)

---
--
-- ArrowDef
--

class ArrowDef a where
def :: a
-- ^Evaluates to a sensible default value.  When used as an Arrow,
-- ie on the RHS of a @-@, evaluates to 'init' which takes a
-- paramater for the default value, if this parameter is ommited
-- the default value is 'def'.

instance ArrowDef () where

Unique Types in haskell (was Re: OO in Haskell)

1999-10-12 Thread Kevin Atkinson

Lars Lundgren wrote:
 
 On Mon, 11 Oct 1999, Adrian Hey wrote:
 
  On Mon 11 Oct, Lars Lundgren wrote:
   I'm sure a lot of poeple have gotten this wrong. I would be surprised if
   not all the experienced haskellers has this view though.
 
  Probably so, but this view seems in complete contradiction to
  that of the Clean world. So I'm still confused :-)
 
 
 I just took a glance at Clean. (Glanced through "The Ins and Outs of Clean
 I/O" by Peter Achten and Rinus Plasmeijer.) I think their solution with
 unique types is really neat.
 
 One downside may be that they have made the type system more complex
 since it has to handle all the uniqness tags.
 
 They deal with side effects (IO) by tagging the values with * and calling
 them unique. Haskell deals with side effects (IO) by using an abstract
 data type IO a which denotes an action [with clean type *World -
 (a,*World) ]. In both cases, the compiler is notified that it is not ok to
 change order of evaluation.
 
 In the Related work section, they mention Monadic IO and writes "To our
 knowledge combining monads of different type is a rather tedious task..."
 
 I'm reluctant to say that I agree. I have written a few programs using
 monad transformers and while everything works in principle, it is, well -
 tedious...
 
 I also do not like the tendency to put more things in the IO monad (I'm
 thinking about the extensions with IORef). I like stToIO better, but
 somehow it still feels like a hack. Maybe some library support for monad
 transformers and maybe even some syntactig sugar would do the trick.
 
 They also wrote "[The monadic IO approach] over determines order of
 evaluation". I'm a bit puzzled about that statement. Is it true? Comments
 anyone?

I have been meaning to bring this up for quite some time.  I think
Haskell could really benefit from a uniqueness typing system as it would
really simplify many things, such as fast array updates.  Also it opens
the door for TONES of optimization opportunities if the compiler can
also mark standard types of being unique, even if the user did not. 
Eventually the compiler could become so good at uniqueness identifying
that the user will never have to explicitly mark anything as unique
except in the case where its communication to the outside work.  Ie IO
etc. Thus one can write non-destructive array updating programs that
would without an uniqueness type system be horribly inefficient (but
easy to verify as being correct) but with a uniqueness type system will
fast and easy to verify.  Can you ask for more?

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: Reverse composition

1999-10-08 Thread Kevin Atkinson

On Fri, 8 Oct 1999 [EMAIL PROTECTED] wrote:

 Some time ago there was a discussion about what to call reverse
 composition (I can't find it in the archive - needs a search option?)
 
 Just now I thought of .~ from . for composition and ~ (tilde, but
 commonly called twiddle) for twiddling the order about.
 
 Maybe we could adopt that as normal usage?

Interesting however I like (.| and $|) since it represents a unix pipe.
The ~ tilde is generally used for not.
My guess is that it is not in the standard becuase we can't agree on which
one is best.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: OO in Haskell

1999-10-07 Thread Kevin Atkinson

Marcin 'Qrczak' Kowalczyk wrote:
 
 Tue, 5 Oct 1999 14:10:26 -0400 (EDT), Kevin Atkinson [EMAIL PROTECTED] pisze:
 
  1) Dynamic types.  You can't cast up.  That is you can't recover the
  original type from an object in a existential collection.  You need to
  use a dynamic type library for that.  And the library proved with hugs
  and ghc leaves a lot to be desired.  In an OO langauge all classes
  automatically cary dynamic typing information.
 
 Please, no. Don't require existentials to carry dynamic type
 information. IMHO it's as ugly as Dynamic.
 

The types won't be required to carry dynamic type information.  It will
just be there if you need it.  It there will be a special function or
the like you can call to get information about the original object.  If
you don't won't to use it, you don't have to and you will NEVER know its
there.  Also if none of the code uses dynamic typing the compile will be
able to optimize away the dynamic type information.

 The concept of existentials works well without it. The essence of
 existential is that you don't care what type is inside as long as it
 has the stated properties. If you need it, I think this is either
 wrong design (e.g. the operation that would use the cast should be
 put inside the existential as a method) or some more fundamental lack
 in the Haskell's type system. Don't break existentials.
 
 If you like this, you must also like Dynamic, so simply require the
 type under the existential to be Typeable and cast it through Dynamic.
 The effect would be the same, without a penalty to those that don't
 use it.
 
 In simple cases where the set of types that need to be casted is
 fixed, there can be methods returning `Maybe ACastedType', with
 obvious semantics.
 
 Sorry that I really can't explain well why I think that this concept
 does not fit into Haskell. I must have heard that such "typecase"
 is most often a bad design.
 

I am not going to argue with you here but there are times where some
casting is unavoidable and I think haskell should provide a safe clean
way of allowing it and the Dynamic type library is not it.

  3) Encapsulation.  You can't have private and protected members.  Some
  of this can be done using modules.  However it is more work.
 
 Please, no. C++'s friends are symptoms that this does not work well.
 This belongs to the module system.
 
 Functions does not "belong" to the type of objects they act on, which
 is obvious when we consider functions working symmetrically on more
 than one argument: which does it belong to? And what about constants:
 in what sense does the emptySet belong to a Set type? I have never
 accepted the OO way, where the first argument is distinguished as
 the owner.
 
 When thinking about whether the implementation details of something are
 known to a function, it should be obvious that they are "more known"
 to a function in the same file acting on different types than to some
 function defined in other file, even acting on the same type.
 
 Haskell's modules, unlike Pascal's, can reexport entities imported
 from other modules, so there may be views of a family of entities
 with various levels of visibility of the inner details.

Perhaps.  However I have also think Haskell's module system is a bit to
simple.  One think I really think it needs is the ability to group a
collection of functions with a tag.  And then when importing a module
you can ask to only import that tag.  For example:

module A
  list: head tail foldr foldl
  array: index (!!) foldr foldl

...

import A(list)

which will make using modules a LOT more convent.  

Also, Haskell currently allows you to explicitly import one module with
another.  However, I think that this should be extended to be able to
import part of the module for example:

module Mod1(module Mod2 hiding foo, module Mod3(foo))

and the like.  Right now when ever a module uses a prelude function you
have to import it like so:

import Prelude hiding head
import Mod1

which can be VERY annoying when a module overrides a lot of the prelude
functions.

 
  4) Cleaner more natural syntax.
 
 I know no other language that has cleaner and more natural syntax
 than Haskell :-)
 
 In particular I dislike typical OO syntax: object.method(args).
 It's good that Haskell makes field selection functions look like
 normal functions, because they _are_ normal functions that could be
 defined elsewhere. Or else you could argue that fst and head should
 look like pair.fst and list.head. Please, no.

I guess its a matter of personal taste.


-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






RE: OO in Haskell

1999-10-06 Thread Kevin Atkinson

On Wed, 6 Oct 1999, Simon Peyton-Jones wrote:

 Kevin writes:
 
 | I strongly agree that Haskell can become a *much* more 
 | powerful language
 | with out losing any of clean syntax or semantics.  However, 
 | when ever I
 | bring up limitations of Haskell type system on this list I either get
 | ignorance or resistance.
 
 I strongly agree that Haskell could be better.  But it is not easy
 to come up with clean designs for the sort of extensions you would like.
 - True ad-doc polymorphism
 - Built in dynamic typing system.
 - State Encapsulation
 - A solution to the abilities arising from multi parameter type classes.
 - Syntactic sugar for supporting OO programming styles
 
 It is easier to identify the problem, that to identify a solution.
 It is easier to identify a solution than to describe that solution 
   completely and precisely.
 It is easier to describe the solution precisely than to implement it.
 
 I think some of the resistance Kevin feels may have something of
 the flavour of "lets wait to find a good solution, rather than 
 whip up a half-baked one".

What happens is that those few who think it is a good idea post one or
two messages expression they view points and perhaps giving a URL to
work they've done on the subject but don't really participate in the
discussion.  Meanwhile about a dozen other people post messages of why in
printable the idea is bad.  They don't say its a good idea but has
problems, they say how Haskell doesn't need it and they are happy with
the way things are.  So I reply to those dozen people and half the
time make a fool out of my self because I only half know what I am
taking about.  Thus because I received so much negative feedback I get
the impression that the Haskell community just doesn't *want* that
feature--even if those high up think is a good idea.

 Dynamic types is a good example.  There is a large design space of
 possible solutions, and it's not clear (to me) which is best.  I don't
 think any consensus has emerged.  
 
 Ad hoc polymorphism is another good example.  Carlos's System CT
 goes a way towards a fairly fully-described solution; Mercury implements
 another variant.  I don't know how the two compare.  It is controversial
 whether the interaction of ad-hoc polymorphism with type-class overloading
 makes the whole thing unmanageably complex.

I think it would be in Carlos interest to modify Marks sample
implantation of the type system to support this.  Then we can really
see if his system will indeed work with the rest of Haskell.

 On the MPTC issues, a good solution does indeed seem to be emerging,
 as Mark mentions.

Yes it does, and because of this I am going to take another shot at my
abstraction library.  With Mark's solution I should not one into any
of the major barriers I did before.

 None of this is to say that dynamic types or ad-hoc polymorphism
 is a bad thing.  But I think it's a misconception to interpret the
 feedback Kevin has received as closed-mindedness. It's just a lot of work
 to work out to describe and implement these sort of extensions; even
 laying aside the expressiveness vs simplicity tradeoff, which itself
 is a real issue.
 
 What can be done to hurry the process along?  One constructive thing
 would be for enthusiasts for a particular extension to move towards
 complete, precise descriptions of what they would like; and to 
 implement the feature in Mark's type checker (the one he's just released).
 Doing this doesn't guarantee that a feature will make it into Haskell,
 but it does make it more likely.  The way to guarantee that a feature
 will make it into a particular compiler is to implement it.  Both Hugs
 and GHC are open source, and work from a CVS repository you can get to
 over the network.
 
 Haskell belongs to you. (Sound of violins.)

Thanks for some feedback from someone who doesn't think I want to
undermine Haskell.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

On Tue, 5 Oct 1999, George Russell wrote:

 Perhaps I'm being stupid.  (It certainly wouldn't be the first time!)
 But what does OO give me that I can't get with existential types (in
 datatype definitions) and multiparameter type classes? The latter seem
 to me much more powerful, since I can add dancing and singing methods
 to objects without having to go back to the original class definition.

1) Dynamic types.  You can't cast up.  That is you can't recover the
original type from an object in a existential collection.  You need to
use a dynamic type library for that.  And the library proved with hugs
and ghc leaves a lot to be desired.  In an OO langauge all classes
automatically cary dynamic typing information.

2) More specific types, you can't _easilly_ call the more general type.
For example in OO this is very commen:

class Base
  virtual foo()
do stuff

class Derived, extends Base
  foo()
call Base::foo()
doo stuff

3) Encapsulation.  You can't have private and protected members.  Some
of this can be done using modules.  However it is more work.

4) Cleaner more natural syntax.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Limititions of Haskell Type System (was Re: OO in Haskell)

1999-10-05 Thread Kevin Atkinson

On Tue, 5 Oct 1999, Theo Norvell wrote:

 On Tue, 5 Oct 1999, Kevin Atkinson wrote:
 
  If there is enough interest I could repost this code as well as an
  explanation of the many "hacks" I had to due to get around ambiguity
  arising fro the use of multiple parameter classes and other
  limitations of Haskell.
 
 Rather than repost all the code, could you post just enough to show the
 source of the difficulty? 

Ok, here is the biggest one.

I have a generic mutable array class which has a few basic methods:

class MArray ... where
  newArray :: Int - m (mutArray st el)
  write :: mutArray st el - Int - el - m ()
  read :: mutArray st el - Int - m el
  freeze :: m mutArray st el - m array el 
  thaw ::  m array el - m mutArray st el

and it turns out that it is possible to create a full fledge
non-mutable array based on the mutable array class with the help of
this method:

  thawRunFreeze :: Array el 
- (m mutArray st el - m ())
- Array el

Which will, as the signature suggests and name suggest, thaw an array,
perform some actions on the mutable array, and then freeze it,
returning the new array.

The only problem is that it is impossible to have a generic
thawRunFreeze method in Haskell.  So I had to resort to some ugly code
generation.

If I have time I will put together a more detailed report of exactly
Why Haskell can't do it.  However in the mean time this should give
you an idea of the sharp limitations of Haskell current type system.

The original post can be found at
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01592.html.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

"Hamilton Richards Jr." wrote:
 
 One of the more clear-eyed (IMHO) and successful authors of C++ texts is
 Cay Horstmann. A feature of his text, "Mastering C++" (Wiley, 1991), which
 I like is the section, appearing at the end of each chapter, entitled
 "Pitfalls" (the idea comes from Andrew Koenig's book, "C Traps and
 Pitfalls").  Some of the pitfalls describe ordinary programming mistakes,
 but the majority are "gotchas" caused by shortcomings in C++'s design of
 (many of them faithful copies of mistakes in C). Horstmann gives a very
 entertaining lecture on the topic of C++ pitfalls; a full hour does not
 suffice to mention them all.

Yes I know C++ has many pitfalls I never said it was beautiful, however
it is powerful.  And this power is the reason I like C++ so.

 With time and patience, one can learn to think in C++, and it's quite
 possible to write beautiful and efficient code in it (I'm a bit partial to
 some of my own efforts). I believe, however, that one cannot fully
 appreciate a programming language's strengths amnd weaknesses until one has
 tried teaching it to a variety of students. Having done that, I'm here to
 attest that Haskell's syntax --to say nothing of its semantics-- is much
 cleaner, much simpler, and much easier to learn.

Yes Haskell syntax is MUCH nicer than just about ANY other language out
they.  That is what first drew me into Haskell.  Unfortunately Haskell,
like Java in some ways, is also a simple language.  I don't like
languages that try to stay simple because doing complex things in simple
languages in well, frustrating.  Can you agree with me here?

I strongly agree that Haskell can become a *much* more powerful language
with out losing any of clean syntax or semantics.  However, when ever I
bring up limitations of Haskell type system on this list I either get
ignorance or resistance.  I get the distant felling that most people on
this list like Haskell simplicity and fell that making it any more
powerful than it is will ruin it.  Well if that is truly how most people
fell I am just wasting my time with Haskell and should just go back to
using C++ with all its flaws, and never grace the presence of any
Haskell user again.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:

4) Cleaner more natural syntax.
  
   More like C++, you mean?
 
  Or Java.  Although many OO things can be done in Haskell C++ and Java
  syntax is more natural more doing OO.
 
 If I sound a tad skeptical about some of your suggestions, it may be
 because you do seem to have something of the running undercurrent
 in your posts that what Haskell _really_ needs to be is C++ with some
 functional bits and bobs added on, which instantly gets my defensive
 instincts going, as it sounds, without wanting to provoke Language
 Wars here, like a truly alarming prescription for a language design,
 and not one very compatible with Haskell as it's currently constituted.

I would like to be able to do the things in Haskell that I can do in C++
but currently Haskell's type system is too simple to allow me to do
them.  There are also some things I can't do in C++ but really wish I
could, I also wish I could do those things with Haskell.  I am not
saying C++ is an elegant language, however it is a powerful one.  I
would like to have that power in Haskell. 

 In short, I'm unaware of any way in which C++ syntax is 'more natural',
 other than in the sense of 'for a C++ programmer', or 'cleaner' -- at all.

For most things C++ is not.  However for representing OO in some areas
C++ is cleaner.  Java is an evern cleaner language for OO as that what
it is based around.   When I think of them I will send some examples to
this list.

Once again:

Haskell for *most* things has far cleaner syntax than just about any
other language out there.  However, OO is not one of them.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:
 
 Kevin Atkinson and I argue about C++'s 'Cleaner more natural syntax':
  I would like to be able to do the things in Haskell that I can do in C++
  but currently Haskell's type system is too simple to allow me to do
  them.  There are also some things I can't do in C++ but really wish I
  could, I also wish I could do those things with Haskell.  I am not
  saying C++ is an elegant language, however it is a powerful one.  I
  would like to have that power in Haskell.
 
 I concur that there are places, due to its desire to maintain
 strong typing properties that Haskell is 'less powerful' than C++.
 But the consensus seems to be that strong typing is worth the
 occassional pain (or at least we avoid the pain by not using Haskell
 if the task isn't well-suited, perhaps), and that we _don't_ want
 to abandon that in favour of C++'s inherent lack of type safety
 (or that if we do, we go and write C++ programs).  Yes, there
 are areas in which it appears to be possible to make Haskell-style
 typing more general, without any basic loss of typing properties,
 but as you say in a related context, it rapidly gets Rather
 Technical, so the issues aren't as simple as 'Haskell's type
 system should immediately be made to accept everything C++ would'.

I never, ever, said that I would like Haskell to be able to do
everything C++ can.  I also never said that I want Haskell to become a
more type unsafe language.  If it was implied I'm sorry.  What I did say
that I would like Haskell to support true ad-hoc overloading which you
seam to bitterly oppose to spite its many benefits. 

Also, I strongly belove that if Haskell's type system is made more
powerful it can be suited to a great number of tasks.  The only thing it
won't really be well suited for is low level system takes as those by
there very nature require unsafe casts of raw memory.  However with some
low level extensions to be able to read and write to raw
memory--probably encapsulate with in a state monad of course--Haskell
could also be suited to those tasks.  However that is not really what I
am interested in.

I am interested in using Haskell to come up with a really generic set of
containers and libraries.   Haskell type system in its current state is
not well suited for this task at all.  However, I fell that once it can
do this task it will be able to do it better than any other language out
there due to its type class system.


  Haskell for *most* things has far cleaner syntax than just about any
  other language out there.  However, OO is not one of them.
 
 "OO" is such a open-ended term, with such a lack of any simple
 definition that I think it'd be best to avoid it entirely (I mean in
 this sort of discussion, though 'ever' wouldn't be a bad plan either),
 in favour of more specific, albeit more open-ended, features of same,
 whether those be message-passing, ad hoc polymorphism, subtyping,
 inheritance, state encapulation -- et cetera, et cetera.  Haskell takes
 a decidedly 'cafeteria' approach to that shopping list, so blanket
 statements like 'Haskell is good/bad for OOP' obscure more than they
 reveal, IMO.

Ok here is my partial list.

- True ad-doc polymorphism
- Built in dynamic typing system.
- State Encapsulation
- A solution to the abilities arising from multi parameter type classes.
- Syntactic sugar for supporting OO programming styles

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:
 
 Kevin Atkinson:
  I never, ever, said that I would like Haskell to be able to do
  everything C++ can.
 
 No, that was my inference from the general drift of your comments.
 
   I also never said that I want Haskell to become a
  more type unsafe language.  If it was implied I'm sorry.  What I did say
  that I would like Haskell to support true ad-hoc overloading which you
  seam to bitterly oppose to spite its many benefits.
 
 Hardly 'bitterly'.  I just wish to observe that it:  involves a
 considerable technical complication, at least, if one wishes to
 preserve sensible typing properties;  adds no actual power to the
 language, whatsoever;  is a _highly questionable_ practice from
 a human factors POV;  and, well, what were the benefits, again?

I listed some of them in previous posts which you chose to ignore.

 I think it should be eminently possible to write a good generic
 container class without resorting to either dynamic typing, or to
 ad hoc polymorphism.  (I don't see how these would really help,
 actually.)  

Neither of them will.  Sorry if I implied a connection.  What I DO need
is a solution is a better solution to multi parameter classes. 

 There are likely still 'issues' with doing this properly
 with MPCs, I can well believe that:  the 'exploring the design
 space' document, and some other papers, examine relaxing/generalising
 the rules for class defaults and overlapping instances, in many
 reasonable-seeming, though also technically tricky, directions.
 It may be worth looking at least, if you're certain existing MPC
 implentations don't allow everything you want to do with containers.

Yes MPC is too limiting.  I have tried.  See my post "Limititions of
Haskell Type System (was Re: OO in Haskell)".

  Ok here is my partial list.
 
  - True ad-doc polymorphism
  - Built in dynamic typing system.
  - State Encapsulation
  - A solution to the abilities arising from multi parameter type classes.
  - Syntactic sugar for supporting OO programming styles
 
 You should try C++ sometime, some people _highly_ recommend it
 for the above. ;-)

I take it what you really want me to do is just shut up and leave and
to  stop trying to change the Haskell language into something you think
its not.    
  
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:
 
 Kevin Atkinson, replying to me...
 
- True ad-doc polymorphism
- Built in dynamic typing system
- State Encapsulation
- A solution to the abilities arising from multi parameter type classes.
- Syntactic sugar for supporting OO programming styles

...

  I take it what you really want me to do is just shut up and leave and
  to  stop trying to change the Haskell language into something you think
  its not.
 
 No, I want you to try and change it into something that it might
 plausibly become.  Your 'partial' list would appear, from a initial
 inspection, to leave little left of either type safety or referential
 transparency. 

Could explain how they could.  There is a very nice paper written up on
True ad-hoc polymorphism.  By a build in build in dynamic type system I
mean being able to safely recover types from an existential collection
using a runtime check.  I can not see how State encapsulation will
weaken any type system. And a better solution to MPC is the one thing I
think we all agree on.

 Either you, or someone of a like agenda, have a very
 large number of technical tricks up your sleeve, or those will go
 down like the proverbial lead balloon at the next (first?) committee
 meeting on Haskell II, I would predict with a degree of confidence
 you're at liberty to not share.  It's not clear from the above agenda,
 though, that it wouldn't be easier to define (C++)++ (the second ++ being
 lazy evaluation, HOFs, partial ap., GC).  Which don't get me wrong,
 would be an entirely good thing, IMO.

God NO, I like C++ because it is powerful but adding more features on an
already ugly (but powerful languge) will make matters worse my making it
more powerful but so ugly with so many pitfalls that no one will want to
use it.

Haskell on the other hand is a modern language which is not based on
something which came out of the 70's (C) which got it popularity because
it was easy to implement and good for system programming as it has
virtual no type safety.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

"Manuel M. T. Chakravarty" wrote:
 
 Kevin Atkinson [EMAIL PROTECTED] wrote,
 
  I take it that you are happy with names such as:
 
 [long list of names deleted]
 
  I *hate* languages that try to keep things too simple.  Which is one of
  the reasons I *hate* java.  Please don't make me *hate* Haskell for the
  same reason.
 
 The problem with excessive overloading is that

The key word here is excessive.   If you are confusing your self by
using the same name for everthing than you need to use seperate function
names.  So you are saying that haskell should avoid all featurs that can
be abused. 
 
 (1) it is often cute in small programs, but bites you when
 software gets more complex, and

I have never yet hade this problem with my C++ functions and
overloading.  I only use overloading when it will be clear my the
context what it means.

 (2) it makes it harder for beginners.
 
 Re (1): Consider the usage of different function names as a
 form of additional documentation.

Yes but many times excessively long function names can make code harder
to read.
 
 Re (2): There was some overloading in Haskell 1.4, which was
 taken out in Haskell 98 exactly for this reason (usage of
 list comprehensions for other monads than list and the
 overloading of map and (++)).

That is a shame.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

On Mon, 4 Oct 1999, Manuel M. T. Chakravarty wrote:

 Kevin Atkinson [EMAIL PROTECTED] wrote,
 
  The key word here is excessive.   If you are confusing your self by
  using the same name for everthing than you need to use seperate function
  names.  So you are saying that haskell should avoid all featurs that can
  be abused. 
 
 Excessive by my definitions if the use of one function name
 for `union' and `unionBy'.  What's the harm in using two
 function names here?  Where overloading makes sense `union'
 uses it already.  If you have to use `unionBy', this is
 because the elements of the set are not part of `Eq' or you
 want to use something else than standard equality.  In other
 words, there is a good reason for using `unionBy' contained
 in the algorithm or at least the structure of your program
 (otherwise, you have probably already made a mistake in your
 class definitions).  As there is such a reason, you should
 document it by using `unionBy' instead of `union' -
 everything else is, frankly speaking, careless software
 engineering.


I am not going to argue with you any more.  We have a different
definitions of what is easy to read.  To me:

  union fun list1 list2

makes perfect sense to me.  To you it may not.  The union and unionBy
is not so much what I object to as having to write two definitions for
union when I should only really have to write one using a generic
comparison function.

Also I hate not being able to have emulations such as

  data Bool = True | False
  data Bool2 = True | False | DontCare

which true adhoc overloading will allow.

Also, sense Haskell does not support objects in the form 
  object-function parms
you have to use
  function object parms

Unfortunately this means that two different objects can not have the same
"method" name unless that method is a type class.  And type classes won't
always work.

Also I hate long complicated system calls with lots of parameters which
you have to explicitly specify in the order given.  True adhoc
overloading will allow me to write an open function such as.

open HANDLE filename ReadOnly
open HANDLE filename Append
open HANDLE filename Write (Overwrite := False)

true adhoc overloading will allow me to do this.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

On Mon, 4 Oct 1999, Joe English wrote:

 Kevin Atkinson wrote:
 
  "Generic comparison function" is not really what I mean here.  What I
  mean is a single generic union which will have its
  comparison function default to (==) if one is not specified.
 
  It COULD be written something like
 
  union (cmp = (==)) l1 l2
...
  where
union l1 l2
  means
union (==) l1 l2
 
 I don't quite see what algorithm you're using
 to decide how many arguments are passed
 to the function.

Neither do I.  I meant to express a general idea.  Perhaps that is not the
best way to do it but that is what I would like to be able to do.

 What would you get if you typed:
 
 foo = foldr union []

since foldr expects the function to have the signature
(a-b-b) it will use the union which matches it, which
will be the union :: [a] - [a] - [a] and not
union :: ( a - a - Bool) - [a] - [a] - [a].

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Kevin Atkinson

Arthur Gold wrote:
 
 Though I am _not_ exactly a Haskell expert, I could not avoid
 commenting...
 
 Kevin Atkinson wrote:
 
  Here is a laundry list of things I think Haskell still needs.  By
  Haskell here I mean Haskell plus extension that are found in both hugs
  and ghc.
 
  1) Support for true ad-hoc overloading.  I am a *strong* believer that
  if the context is clear for a human than it should be clear to the
  computer.  This also includes support for default parameters as found in
  C++.

 "True ad-hoc overloading?" Unless you restrict it to dispatch on the
 first argument, this would imply muliple-dispatch generic functions. In
 fact, this is really what multiple parameter type-classes are all about.
 So it's in there (well in the extensions, anyway).

Yes but often putting things in type classes is tedious to do.  I also
want to be able to overload not only on the TYPE of parameters but also
on the NUMBER of parameters.  It IS possible to do these things and it
DOES make sense in a curing system.

 Default parameters just don't make sense in a language that supports
 currying.

If overloading based on the NUMBER of parameters makes sense so does
default parameters as default parameters will just be syntactic sugar.

See http://www.dcc.ufmg.br/~camarao.

  2) Support for TRUE OO style programming.
 What is "TRUE" OO style programming? If you mean objects with mutable
 state, you're violating one of the most basic tenets of FP.

No. I mean being able to do things such as.

Have a collection of object of a common base class AND be able to up
cast them when necessary.

Be able to override methods and ALSO be able for the overriding methods
to call there parent methods.  

I believe Haskell CAN do these things however the solutions are anything
but elegant.

  4) Being able to write
do a - getLine
   b - getLine
   proc a b
  as
proc getLine getLine
  and the like.  I don't know the number of times that I get REALLY sick
  of having to explicitly bind everything to a variable.  Monads do a very
  good job of supporting imperative style.  Now lets make them less
  tedious to use.

 ACK! For one thing this would mean that arguments would _always_ have to
 be evaluated left-to-right...which is completely incompatible with a
 non-strict language.

NO. NO. NO.  

proc getLine getLine will be interpreted as the do notion above.  With a
powerful enough type system it WILL be possible.  I will go into details
later if anyone is interested.

 (actually, I've never been too happy with the 'do' notation myself, as
 it to often obscures what's really going on...and I think what's really
 going on is _important_)

Maybe however it CAN be tedious.

 Further, if you're going to mess with referential transparency, what's
 the point? You might as well just use C++ (or, if things like pattern
 matching are what draws you to Haskell, take a look at Pizza or GJava.

Your missing the point.

 A note on referential transparency:

 One of the great potential benfits of an rt language--and one that at
 least I believe will be more significant as time goes on--is the
 potential for exposing parallelism. There have been some pretty cool
 papers on the subject, and as multiple processor machines become more
 and more common (as they no doubt will) the ability to parallelize at
 run-time (because you needn't do extensive code analysis) will become
 _terribly_ valuable.

I agree with you here.  You just need to get the word out as WAY to many
people don't release it (with half of those people not even knowing what
a functional programming language is)

  So what do you Haskell experts think.

 Perhaps (and please take this as neither flame nor flame-bait) pure-lazy
 FP just ain't for you! (just as it certainly isn't the right tool for
 certain cllases of tasks).

But with some work it CAN be.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Kevin Atkinson

"Frank A. Christoph" wrote:
 
  Here is a laundry list of things I think Haskell still needs.  By
  Haskell here I mean Haskell plus extension that are found in both hugs
  and ghc.
 ...
  4) Being able to write
do a - getLine
   b - getLine
   proc a b
  as
proc getLine getLine
  and the like.  I don't know the number of times that I get REALLY sick
  of having to explicitly bind everything to a variable.  Monads do a very
  good job of supporting imperative style.  Now lets make them less
  tedious to use.
 
 You could define proc':
 
 proc' act1 act2 = do
   v1 - act1
   v2 - act2
   proc v1 v2
 
 so you can write:
 
  proc' getLine getLine

I know.

 When proc returns a value rather than a computation, i.e., proc :: a - b -
 c, and c is not monadic, then you can just write Monad.liftM2 proc getLine
 getLine.
 
 You could define a higher-order version of proc' above in the same vein:
 
 liftM2' :: (a - b - m c) - (m a - m b - m c)
 liftM2' proc m1 m2 = do
   v1 - m1
   v2 - m2
   proc v1 v2

Yes I also know.

 
 In simpler cases where proc takes only one argument, you can avoid thinking
 up new names by currying:
 
   getLine = proc

Yes I also know.
 
 I find that if you make liberal use of higher-order constructs and
 modularize your code, then the need to do explicit binding is not so much of
 a problem. Then again, I am the sort of person who uses "let" and "where"
 whenever he can to name subexpressions as well...

But the point is I would like the type system to AUTOMATICALLY do this
for me so that I don't have to memorize/lookup a bunch of higher order
functions.  True ONCE you know them all they are not difficult to use
but to a new programmer all these (seemly unnecessary) high functions
can make doing the simplest task quite difficult.  So the new programmer
will just use the do

This is why I belive in true adhoc overloading.

1) so that you don't have to make up names just reuse the old ones
2) make using standard library functions easier to use because there
will be a lot fewer names to lookup/memorize.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Kevin Atkinson

On Mon, 27 Sep 1999, George Russell wrote:

 Kevin Atkinson wrote:
 [snip]
  1) Support for true ad-hoc overloading.
 [snip] 
  2) Support for TRUE OO style programming.
 [snip]
  4) Being able to write
do a - getLine
   b - getLine
   proc a b
  as
proc getLine getLine
 [snip]
 AAARRRGGH no.  I don't like overloading.  For one thing it makes it a bore
 working out what any given function call means.  Haskell takes it about as
 far as it goes, but I don't want to go any further.  For example, I would much
 prefer to maintain
   do a - getLine
  b - getLine
  proc a b
 since all the action is clearly written out.  I don't have to know that
 getLine is an IO something and deduce automatic coercion.
 
 If anything we should be trying to simplify Haskell's type system, not
 complicate it.  I would welcome a better way of doing multi-parameter
 type classes, but that seems to be something of a research problem
 right now.

Perhapes an implicit coercion is going two far. But i would DEFENTLY
like to say something like.

lift proc getLine getLine
lift proc "A line." getLine
lift proc "A line." "Another line."

The lift in this case makes it clear what is going on.   With current
haskell I would have had to use a seperate lift function for each case.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







OO in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-27 Thread Kevin Atkinson

On Mon, 27 Sep 1999, Alex Ferguson wrote:

 Kevin Atkinson, replying to me:
 
   If I understand you correctly, then the best way of doing this would be
   with existentially (boundedly) quantified data types, currently a
   non-standard extention present in hbc (and I think, ghc, these days, not
   sure if it's with the same generality.)
  
  existentially (boundedly) quantified data types can not cast up.
 
 'Cast up' to what?  If you can't write a class context that descibes
 the relatedness of everything you want to put in a heterogenous collection,
 then I'm inclined to doubt if it isn't more heterogenous than is
 sensible.

You have a collection of Shapes.  Some of these shapes are circles,   
however, others are rectangle.  Occasionally you will need to extract
these specific shapes form the collection of generic shapes as there is no   
way to find the length and width of a generic shape, only its area and
circumference.  So I need to cast the objects in shapes that are *really*
rectangles back up to rectangles.

1) test for the true type of the object
2) cast it back up to its true type

  In order to do that you would ALSO need to use the dramatic typing
  extensions found in the GHC/Hugs library.
 
 I don't see how this relates to anything other than heterogenous collections;
 perhaps an example?

A collection of objects with existential types very often is a
heterogeneous collections.

  The point that class hierarchy isn't precisely _type_ hierarchy is
  exactly the point I am trying to get gate Haskell needs to also be able to
  support a class hierarchy if it is to really support OO style programming.
 
 I'm aware that Haskell doesn't precisely ape that sorts of 'OOP
 style' that the likes of C++ admits  What I've yet to see is any
 argument that this is anything other than the wisest possible decision...

And by this you mean...

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Kevin Atkinson

On Mon, 27 Sep 1999, Alex Ferguson wrote:

2) Support for TRUE OO style programming.
 
  No. I mean being able to do things such as.
  
  Have a collection of object of a common base class AND be able to up
  cast them when necessary.
 
 If I understand you correctly, then the best way of doing this would be
 with existentially (boundedly) quantified data types, currently a
 non-standard extention present in hbc (and I think, ghc, these days, not
 sure if it's with the same generality.)

existentially (boundedly) quantified data types can not cast up.  In order
to do that you would ALSO need to use the dramatic typing extensions found  
in the GHC/Hugs library.  Unfortunately the dramatic typing library leaves
a lot to be desired.

  Be able to override methods and ALSO be able for the overriding methods
  to call there parent methods.  
 
 If by that you mean a more flexible and general means of specifying
 defaults, I'd agree.  Method definitions don't have a strict 'parent'
 in the usual OO sense, since the class hierarchy isn't precisely a
 _type_ hierarchy (and a good thing too, IMO), so I'm not entirely
 confident about what you mean by parent method, though.

The point that class hierarchy isn't precisely _type_ hierarchy is
exactly the point I am trying to get gate Haskell needs to also be able to
support a class hierarchy if it is to really support OO style programming.

  proc getLine getLine will be interpreted as the do notion above.  With a
  powerful enough type system it WILL be possible.  I will go into details
  later if anyone is interested.
 
 Please do.  This is something that it would be nice to do, on one level:
 occassionally one has to 'monadise' part of one's program, and due to
 the above effect, end up driving a coach and four through the rest of
 one's code.

It has already been done to some extent in other threads.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Ad-hoc overloading in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-27 Thread Kevin Atkinson

On Tue, 28 Sep 1999, Fergus Henderson wrote:

  That's far from clear.  Certainly, I don't think it's likely to be
  reasonably possible a conversative extension.
 
 I think it could be.
 However, whether it is in "the spirit of Haskell" is another question.
 
 Mercury supports both type classes and ad-hoc overloading.
 You can define two different symbols with the same name in
 different modules and import them into another module
 and the compiler will use your type declarations to disambiguate.
 You can define the same symbol with different arities (number of parameters)
 within a single module, and the compiler will use the types and the
 context to disambiguate.
 
 Ad-hoc overloading and type inference don't mix so well, because
 you can easily get ambiguities which the compiler cannot resolve.
 However, the user can add explicit type annotations where necessary
 to resolve the ambiguities.  And I find this preferable to making
 the explicit type annotations part of the symbol names, which is
 what I currently tend to do when writing Haskell.
 

I am glad that SOMEONE agrees with me.  Anyone else

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: OO in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-27 Thread Kevin Atkinson

Alex Ferguson wrote:
 
 Kevin Atkinson:
  You have a collection of Shapes.  Some of these shapes are circles,
  however, others are rectangle.  Occasionally you will need to extract
  these specific shapes form the collection of generic shapes as there is no
  way to find the length and width of a generic shape, only its area and
  circumference.  So I need to cast the objects in shapes that are *really*
  rectangles back up to rectangles.
 
  1) test for the true type of the object
  2) cast it back up to its true type
 
 There's no need for a 'cast' here, as Shape can be represented as a
 class.  The trickier part is putting different types into a heterogenous
 collection, and then manipulating according to their _individual_ types.
 Unless you want to restrict yourself to a particular set of possible
 types (in which case it's straightforward, anyway), this seems to me
 like it _is_ a case of dynamic programming.

Yes but it is ALSO a case of typical things one does with OO.  Except
with OO it is very natural as you just stick them all into a container
of Shapes.  When you need to access the identical type of an object you
use simply case up once you are sure what the REAL type of the object
is.  Also in OO you can
have a class heritage like this.

Shape
  Circler
Oval
Circle
  Polygon

Now than suppose the Circler has a method to find the maxim and minimum
radius of its shape.  Now you have a collection of Shapes.  For all
those that are Circler you would like to find this information.  In
these situation it is NOT necessary to recover the complete type of the
object, but merely to cast it up one level to Circler so that you can
find the this information.  Can dynamic programming handle this?  And
how?

   I'm aware that Haskell doesn't precisely ape that sorts of 'OOP
   style' that the likes of C++ admits  What I've yet to see is any
   argument that this is anything other than the wisest possible decision...
 
  And by this you mean...
 
 That C++ has a very poor type system.

You are going to have to justify it as I thing C++ and Java has a VERY
good type system minus the implicit typing system. In fact I *like*  the
C++ typeing system better than I do Haskell's in many cases.

Do you not like OO at all?
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






What *I* thinks Haskell Needs.

1999-09-26 Thread Kevin Atkinson

Here is a laundry list of things I think Haskell still needs.  By
Haskell here I mean Haskell plus extension that are found in both hugs
and ghc.

1) Support for true ad-hoc overloading.  I am a *strong* believer that
if the context is clear for a human than it should be clear to the
computer.  This also includes support for default parameters as found in
C++.

2) Support for TRUE OO style programming.

3) A better solution to all the unresolved overloading that comes up due
to multi parameter type classes.

4) Being able to write
  do a - getLine
 b - getLine
 proc a b
as 
  proc getLine getLine
and the like.  I don't know the number of times that I get REALLY sick
of having to explicitly bind everything to a variable.  Monads do a very
good job of supporting imperative style.  Now lets make them less
tedious to use.

5) A rich set of standard libraries such as provided by the STL is C++.

And the points that are brought up so much that I don't even what to get
into.

6) speed.

7) less memory. 

So what do you Haskell experts think.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: Is their a *good* online tutorial and reference for Haskell?

1999-08-11 Thread Kevin Atkinson

Byron Hale wrote:

 In my experience, people, talking as the "Coward" did, are engaged in a
 turf war. Nothing that you do will satisfy them, because their apparent
 objective is not their real one. However, the appearance criticism may be
 something to actually be addressed.

 Here in Silicon Valley, the turf wars are very apparent. There was a Java
 investment fund of $100,000,000 USD, whether real or apparent. There has
 been an attempt to brainwash consumers (100% pure Java code). Propoganda
 tactics have been used by marketing communications companies to create fear
 of code that would run outside a sandbox. The sandbox, however, was quietly
 abandoned.'

Please restate this in english.

I know that The University of Maryland is starting to incorporate Java
in its curriculum.

 
 Java has not caught on, generally. In fact, the last I heard, there was no
 Java for Linux!

Just what do you mean by this.  The java runtime system has been
available for linux for a very long time. 

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Is their a *good* online tutorial and reference for Haskell?

1999-08-10 Thread Kevin Atkinson

Keith Wansbrough wrote:
 
  looked all I could find were pointers to books and links to Amazon.Com. Oh
  yes, and some moldy academic papers in postscript format. I think it would
 
 It would be a good idea for tutorial papers to be available in PDF
 format as well (and maybe even HTML if it doesn't look too ugly)...

May I add to this by strongly suggesting you run the original LaTeX
formats through latex2html.  Some of the documents might need some work,
however, before they will go through.  I tried to run Edison through
latex2html however it did not do well at all.  One of the problems I
believe is that the document used math mode in a lot of places where
they won't strictly needed such as for "O(n)"; an italicized font would
have done just fine in my view--even if it wasn't 100% "correct". 
However that wasn't not the only thing giving latex2html a hard time.  I
don't know latex too well as I use LyX most of the time so I wan't sure
where the exact program was.  It could be that he used a little bit of
raw TeX...

Also is there some reason the latex source to documents is hardly ever
released?
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Is their a *good* online tutorial and reference for Haskell?

1999-08-09 Thread Kevin Atkinson

In responce to a slashdot article on "All-Purpose Distributed Computing"
(http://slashdot.org/article.pl?sid=99/08/09/1214204) I wrote:

I hate to break this to you but some purely functional programming
languages can already do this [automatically execute programs in   
parallel]. Haskell is a Lazy, Purely Functional programming language with
strict typing. More information on Haskell can be found at
www.haskell.org. The GHC compiler is capapable of executing
Haskell programs in parallel with out any additional work on the 
programmers part. However, it is not very efficent right now. 

Then an Anonymous Coward replyed:

Is their a good online tutorial and reference for Haskell? Last time I
looked all I could find were pointers to books and links to Amazon.Com. Oh
yes, and some moldy academic papers in postscript format. I think it would
behoove those in the communities of less well know languages to provide
good online instruction and reference material. I'm not going to pop 60
bucks to learn another language that may or may not meet my needs. Try 
before you buy.

So is there?

That could be _one_ of the reasons Java did so well.


--
KevinA








Re: Rule question.

1999-07-08 Thread Kevin Atkinson

Simon Peyton-Jones wrote:

 Sorry it's taken me a long time to look at this.
 Two things are going on here.

No problem

   module KevinB where
 
   data Arr ix el = Arr Int [(ix,el)] deriving Show
 
   replaceMany :: [(ix,el)] - Arr ix el - Arr ix el
   replaceMany = error "In Replace Many"
 
   {-# RULES
  "rule1" forall f,l,a. replaceMany (map f l) a = replaceManyMap f l a
#-}
 
   replaceManyMap :: (v - (ix,el)) - [(ix,el)] - Arr ix el - Arr ix el
   replaceManyMap = error "In Replace Many Map"
 
   arr s l = let a = Arr s [] in
 replaceMany l a
 
 If you compile this, replaceMany will be inlined in arr's defn,
 which means that anyone importing KevinB won't see the version
 of arr that has replaceMany in it.  So
 
 module KevinA where
 import KevinB
 arr2 s l = arr s (map (\(i,e)-(i+2,e)) l)
 
 will not fire the rule.
 
 Solution: add an INLINE pragma to 'arr'.   This has the
 effect of *preventing* inlining in arr's RHS, and causing
 'arr' to be inlined at every call site.
 
 This is an annoying gotcha when using RULES, but I don't see an
 easy fix.

Whats wrong with simply keeping track of all the functions used in the
LHS of a rule and if one of these functions appears in the RHS of a
definition add an implicate INLINE pragma.

PS: Have you had a chance to look at the rule in my "Generator" post the
the haskell mailing list.  The rule is being fired up but the compiler
is not optimizing as well as it could.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: Calling Haskell from C

1999-07-07 Thread Kevin Atkinson

Kevin Atkinson wrote:
 
 Marcin 'Qrczak' Kowalczyk wrote:
 
  Tue, 06 Jul 1999 14:21:11 -0400, Kevin Atkinson [EMAIL PROTECTED] pisze:
 
As I can't build ghc from sources and fix the problem myself, is
there any workaround?
  
   Why can't you build ghc from source?
 
  Because it mysteriously fails to compile some files (PerlBase.lhs)
  without any error message. I reported it on glasgow-haskell-bugs;
  I've seen other people reporting similar problems some time ago.
 
  I'll try to compile it again using the glibc-fixed compiler. It
  takes half a day crazily swapping because I have only 32 MB of RAM
  (I think I'll buy some more soon...), so it's even hard to experiment.
 
 I believe your unlit is crashing as I had the same problem. I posted the
 patch to haskell-bugs.  The CVS version has this problem fixed if you
 care to mess with that.  (I assume Simon P-J got the tree in a working
 state again.)  There are some binary packages available at
 http://www-i2.informatik.rwth-aachen.de/Software/Haskell/ which might
 interest you.

But before you do that do a gdb -c core in the directory ghc/lib/std/ to
figure out what is really crashing.  My unlit might of been crashing
because I had the header files for glibc2.0 but the binaries for
glibc2.1 installed.  It could make a bit of a difference ;)  Anyway
examining the core file could save you a lot of trouble.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



One function for foldr, foldl, zip, union, etc...

1999-07-07 Thread Kevin Atkinson

As you probably know I am desperately trying to come up with a good STL
like abstraction (that is a collection of generically containers and
algorithms that can easily work together), however I hit a stumbling
block that I thought some of you Haskell experts can help me with.

I would like to know if there is one good efficient function (or way)
that will allow me to *effectually* walk through a container in a list
like manner.  On the surface I could just use lazy lists however, as
implemented in ghc, they carry a huge amount of overhead.  While it is
also possible define these all these functions (foldr, foldl, zip,
union, etc) in terms of foldl or foldr in really, as shown in a previous
post, this is horribly inefficient.  It seams like my Generator concept,
which I just posted 2 days ago, would be a good way to go because GHC is
able to optimize away any garbage collection when used with simple
things like integer, but I am not sure how well that will work for a
tree like structure.

So I am asking you: Is there one really efficient function (or way) I
can use to define all list like functions with such as foldr, foldl,
foldr1, foldl1, zip, zip3, union on sorted ranges,  etc on any sort of
container.  This function needs to be efficient enough so that when
other functions are defined in terms of it there will be nearly as
efficient (within 10% or so) as writing the function directly based on
the structure of the container.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Calling Haskell from C

1999-07-06 Thread Kevin Atkinson

Marcin 'Qrczak' Kowalczyk wrote:
 
 Tue, 06 Jul 1999 14:21:11 -0400, Kevin Atkinson [EMAIL PROTECTED] pisze:
 
   As I can't build ghc from sources and fix the problem myself, is
   there any workaround?
 
  Why can't you build ghc from source?
 
 Because it mysteriously fails to compile some files (PerlBase.lhs)
 without any error message. I reported it on glasgow-haskell-bugs;
 I've seen other people reporting similar problems some time ago.
 
 I'll try to compile it again using the glibc-fixed compiler. It
 takes half a day crazily swapping because I have only 32 MB of RAM
 (I think I'll buy some more soon...), so it's even hard to experiment.

I believe your unlit is crashing as I had the same problem. I posted the
patch to haskell-bugs.  The CVS version has this problem fixed if you
care to mess with that.  (I assume Simon P-J got the tree in a working
state again.)  There are some binary packages available at
http://www-i2.informatik.rwth-aachen.de/Software/Haskell/ which might
interest you.

--
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: Calling Haskell from C

1999-07-06 Thread Kevin Atkinson

Marcin 'Qrczak' Kowalczyk wrote:

 As I can't build ghc from sources and fix the problem myself, is
 there any workaround?

Why can't you build ghc from source?
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: A datatype for the text editor buffer?

1999-07-06 Thread Kevin Atkinson

Fergus Henderson wrote:

 I have heard that the latest versions of the SGI STL C++ library include a
 `rope' data type which is, I believe, based on the same kind of idea,
 but I don't know the details.

I belive it is a similar idea but it is based on a hash table.  URL
http://www.sgi.com/Technology/STL/index.html

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Using Generators to remove intermediate lists

1999-07-05 Thread Kevin Atkinson

This is a multi-part message in MIME format.
--EF4673DF4E1172F415EEF3AF
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Attached is my idea for removing intermediate lists using what I call
Generators.  I would be very interested if any one has tried something
like this.  I would also be interested in how it compares with Andrew
John Gill's idea presented in his Cheap Deforestation theses and as
currently implemented with CVS version of GHC.

For numeric instance calculations my idea seems to make a BIG
difference.

Ghc compiler writers: As usual, I am having some trouble getting rules
to behave.  Any help would be appreciated.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/
--EF4673DF4E1172F415EEF3AF
Content-Type: text/plain; charset=us-ascii;
 name="Opt.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="Opt.hs"


{-- Using so called Generators to remove intermediate lists. --}
{-- Kevin Atkinson, [EMAIL PROTECTED]--}

module Opt where

import Prelude hiding (foldr, foldl, map, filter, take, drop, iterate)
import Maybe (fromJust)

{- The basic idea behind my idea is the Generator type: -}

type Gen h t = (t - Maybe (h,t), -- generator function
t )   -- initial value

{- where the generator function takes in an initial state (say a list) 
   and returns a value (the head of a list for example) plus a new state 
   (the tail of the list) or Nothing if there is nothing to return (an
empty list).  It is the exact same type on function one
   would feed to the unfoldr (defined in the List module) and is very
   similar to an Ananorphism pair except that the generator and the 
   predicate function is wrapped into one function.  

   Now all functions which normal deal with lists will instead work 
   with nothing but generators. -}
   
foldrG :: (a - b - b) - b - Gen a t - b
foldrG f v (g,i) = f' i
where f' i = case g i of 
 Just (h,t) - f h (f' t)
 Nothing- v

foldr1G :: (a - a - a) - Gen a t - a
foldr1G f (g,i) = f' $ fromJust $ g i
where f' (h,t) = case g t of 
 Nothing - h
 Just v  - f h (f' v)

foldlG :: (b - a - b) - b - Gen a t - b
foldlG f v (g,i) = f' v i
where f' v i = case g i of
   Just (h, t) - f' (f v h) t
   Nothing - v


foldl1G :: (a - a - a) - Gen a t - a
foldl1G f (g,i) = foldlG f v (g,i') where (v,i') = fromJust$ g i

mapFst f (a,b) = (f a,b)
mapSnd f (a,b) = (a,f b)

mapG :: (h - i) - Gen h t - Gen i t 
mapG f (g,i) = ((\a-fmap (mapFst f) (g a)),i)
   
data TakeG v = TakeG !Int v

takeG :: Int - Gen h t - Gen h (TakeG t)
takeG num (g,i) = (g',TakeG 0 i) 
where g' (TakeG i v) | i == num  = Nothing
 | otherwise = fmap (mapSnd $ TakeG $ i+1) (g v)

filterG :: (h - Bool) - Gen h t - Gen h t
filterG f (g,i) = (g',i)
where g' i = case g i of
 Just (h,t) | f h   - Just (h,t)
| otherwise - g' t
 Nothing- Nothing

rangeG (a,z) = numRangeG (a, a+1, z)

numRangeG (a,b,z) = (g,a)
where g i | i  z = Nothing
  | otherwise = Just (i,i+(b-a))

iterateG f i = ((\i-Just (i,f i)),i)

headG (g,i) = fst$ fromJust$ g i
tailG (g,i) = snd$ fromJust$ g i

lastG = foldr1G (flip const)

{- And to work with normal lists the normal list functions will simply 
   convert the generator to and from a list as necessary  -}

fromG :: Gen a b - [a]
fromG = foldrG (:) [] 

toG   :: [a] - Gen a [a]
toG   l   = (g,l) 
where g (h:t) = Just (h,t)
  g _ = Nothing

foldr f v = foldrG f v . toG

foldl f v = foldlG f v . toG

map f = fromG . mapG f . toG

take n = fromG . takeG n . toG

filter f = fromG . filterG f . toG

intRange :: (Int, Int) - [Int]
intRange = fromG . rangeG

numRange :: (Ord a, Num a) = (a,a,a) - [a]
numRange = fromG . numRangeG

iterate f i = fromG $ iterateG f i

{- and finally use the rule: -}

{-# RULES
"toG/fromG"forall a.  toG (fromG a) = a
 #-}

{- to remove any intermediate conversion to list -}

{- the following inlines seam necessary to make rule work out -}

{-# INLINE fromG #-}
{-# INLINE toG #-}
{-# INLINE foldr #-}
{-# INLINE foldl #-}
{-# INLINE map #-}
{-# INLINE take #-}
{-# INLINE filter #-}
{-# INLINE intRange #-}
{-# INLINE numRange #-}
{-# INLINE iterate #-}

{- 

   Although I have not had a chance to look into Andrew John Gill's
   _Cheap Deforestation for Non-strict Functional Languages_ (1996) in 
   detail, as I see my approach semas to have two distinct advantages:

   1) Generators work with tail-recursive foldl.

   2) They are easier to generalize to other data structures (simply
  create a functions to convert the data structure to and from 
  a generator.

   For numeric instance calcul

Re: The cost of defining foldl w/ foldr and vis versa

1999-07-03 Thread Kevin Atkinson

Kevin Atkinson wrote:
 
 Even though it is possible to define foldl with foldr or vis versa it
 (with the current implantation of Haskell with ghc) not nearly as
 efficient.  To demonstrate this consider folding of a range.
 
 import System
 
 foldR f i (a,z) = g a
 where g a | a == z= i
   | otherwise = f a (g (a+1))
 
 foldL f v (a,z) = g v a
 where g v a | a == z= v
 | otherwise = g (f v a) (a+1)

After playing with it a little I released that these folds will not
include the last number in the range.  Well I never documented what they
did so consider it part of the desired behavior ;)

 
 foldL2 f z l = foldR (\ a h - \ b - h (b `f` a)) id l z
 
 foldR2 f z l = foldL (\ h a - \ b - h (a `f` b)) id l z
 
 main = do (c:_) - getArgs
   let zero  = 0::Double  -- Will overflow with Int, and Integer
  -- are not nearly as efficient
   range = (0,10)
   case c of
"L"  - print$ foldL  (+) zero range
"R"  - print$ foldR  (+) zero range
"L2" - print$ foldL2 (+) zero range
"R2" - print$ foldR2 (+) zero range
 
 ghc -O Main.hs
 ./a.out ? +RTS -sstderr -K4m
 
   Total Time  Allocated on Heap  GC   Memory
 L   0.02 s10,1320.0%1 Mb
 R   0.17   1,214,356   41.2%5 Mb
 L2  1.07   6,014,868   50.5%   11 Mb
 R2  1.19   4,409,236   61.3%   13 Mb
 
 ./a.out R2 +RTS -sstderr -K4m -A10m
 
   Total Time  Allocated on Heap  GC   Memory
 L   0.02 ssame  0.0%   10 Mb
 R   0.12 ssame  0.0%   14 Mb
 L2  0.41 ssame  0.0%   18 Mb
 R2  0.38 ssame  0.0%   18 Mb
 
 (I chose the best time from several tries)
 
 As you can see when I defined one in terms of the other I suffered a
 serious performance lost, both in memory and speed.
 
 As expected the direct foldL is the fastest because it is done in
 constant space.  The foldR has to build up a stack however it is fairly
 efficient.  The foldL2 I believe is building up both a stack and a huge
 lambda expression thus is horribly inefficient compared to foldL.  The
 foldR2 essentially does the same thing that foldR does however it is
 building up a huge lambda expression rather than a stack and thus is not
 nearly as efficient.  However, with proper Optimization I imagine that
 foldR2 could be as efficient as foldR.  I don't know about foldL2
 though.
 
 --
 Kevin Atkinson
 [EMAIL PROTECTED]
 http://metalab.unc.edu/kevina/

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: CVS Version of GHC has problems finding Instances

1999-07-01 Thread Kevin Atkinson

Simon Peyton-Jones wrote:
 
 Kevin
 
 Simon has built your library with the current GHC and it's happy.
 So at the moment we can't reproduce your problem.

Is it happy when you comment out the "import Eval" in Main.hs?

  Have you still
 got it? (After doing your cvs update.)

Updated tuesday morning.

After I commenting out import Eval:

Main.hs:63:
No instance for `Monad Eval.Eval'
arising from use of `elems' at Main.hs:63

ghc-4.02 does not have this problem.  Nor does hugs.

 
 Simon
 
  -Original Message-
  From: Kevin Atkinson
  Sent: Monday, June 28, 1999 8:10 AM
  To: [EMAIL PROTECTED]
  Subject: CVS Version of GHC has problems finding Instances
 
 
  It seams that the CVS version of ghc (June 27) has problems finding
  instances.   See the attached file Main.hs in a message I just sent to
  the Haskell mailing list with a subject of "Second attempt for an STL
  like library for Haskell".  If I don't import Eval it complains of not
  being able to find an instance of Monad for Eval.Eval.
 
  If this is not a known problem I have some additional examples I can
  provide.  Just let me known.
  --
  Kevin Atkinson
  [EMAIL PROTECTED]
  http://metalab.unc.edu/kevina/
 

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: Rule question.

1999-07-01 Thread Kevin Atkinson

Simon Peyton-Jones wrote:
 
 Hmm.  Your example relies on inlining 'arr' at its call site.
 My guess is that you aren't using -O.  In that case, there's no
 cross-module inlining, so 'arr' doesn't get inlined.
 
 Is that it?

No:

[kevina@kevins-linux Rules]$ make clean
rm -f *.o *.hi
[kevina@kevins-linux Rules]$ make
ghc -c T2.hs -fglasgow-exts -O
ghc: module version changed to 1; reason: no old .hi file
ghc -c Main.hs -fglasgow-exts -O
ghc: module version changed to 1; reason: no old .hi file
rm -f main
ghc -o main -fglasgow-exts -O Main.o T2.o
[kevina@kevins-linux Rules]$ ./main

Fail: In Replace Many

An INLINE arr did not help either.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/

module Main where
 
import T2

arr2 s l = arr s (map (\(i,e)-(i+2,e)) l)

main = print$ arr2 10 [(1::Int,10::Int),(2,20)]


module T2 where

data Arr ix el = Arr Int [(ix,el)] deriving Show

replaceMany :: [(ix,el)] - Arr ix el - Arr ix el
replaceMany = error "In Replace Many"

{-# RULES 
   "rule1" forall f,l,a. replaceMany (map f l) a = replaceManyMap f l a 
 #-}

replaceManyMap :: (v - (ix,el)) - [(ix,el)] - Arr ix el - Arr ix el
replaceManyMap = error "In Replace Many Map"

{-# INLINE arr #-}
arr s l =
let a = Arr s [] in
replaceMany l a





HC  = ghc
HC_OPTS = -fglasgow-exts $(EXTRA_HC_OPTS)

EXTRA_HC_OPTS = -O

SRCS = $(wildcard *.hs)
OBJ2 = $(SRCS:.hs=.o)
OBJS = $(OBJ2:.lhs=.o)

.SUFFIXES : .o .hi .lhs .hc .s

main : $(OBJS)
rm -f $@
$(HC) -o $@ $(HC_OPTS) $(OBJS)

clean :
rm -f *.o *.hi

realclean: clean
rm -f main main.* core

depend :
mkdependHS -- $(HC_OPTS) -- $(SRCS)

# Standard suffix rules
%.hi : %.o
@:

%.o : %.hs
$(HC) -c $ $(HC_OPTS)

%.o : %.lhs
$(HC) -c $ $(HC_OPTS)

























# DO NOT DELETE: Beginning of Haskell dependencies
Main.o : Main.hs
Main.o : ./T2.hi
T2.o : T2.hs
# DO NOT DELETE: End of Haskell dependencies



Layout rules. (was Re: Another bug in the 98 Report?)

1999-07-01 Thread Kevin Atkinson

Malcolm Wallace wrote:

 Mark P Jobes wrote: 

 | Something like the following can be used in Hugs 98:
 |
 |   f x = case x of
 | (a,b) - case a of
 | (c,d) - case b of
 | (e,f) - [c,d,e,f]
 
 You can't be serious!  This is a great example of mis-using layout to
 baffle and bemuse.

I belive he is as it is very similar to

 {- code -} = \(a,b) -
 {- code -} = \(c,d) -
 {- code -} = \(e,f) -  
 return [c,d,e,f]

Also how about.

mcompare x y = 
 do i - x ==~ y 
if i then return EQ else do 
i - x =~ y 
if i then return LT else do
return GT

with strictly increasing indentation iut would have to be something
like.

mcompare x y = 
 do i - x ==~ y 
if i then return EQ else do 
  i - x =~ y 
  if i then return LT else do
return GT

which is a bit uglier.


-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson

Mike Gunter wrote:

  Remember you may ONLY use the three functions given above and NOTHING
  else.  Creating a list with "foldr (:) []" is also not allowed.
 
 Only?  How do I construct a pair?  (I'm probably misunderstanding you.)

What I meant to say is that those three functions are the ONLY way to
manipulate the abstract container.  That is this container has no head,
tail , etc. defined for it.


-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson

Laszlo Nemeth wrote:
 
 Kevin Atkinson wrote:
 
  cons   :: a - c a - c a
  empty  :: c
  foldr  :: (a - b - b) - b - c a - b
 
 I am not an expert. I have a minor problem with this, the type of
 empty: if c stands for a type constructor then empty should have type
 (c a). 

Yes (c a) typo.

 Moreover, I don't understand why you use 'c' for lists (if you
 are hoping for polytypism, -- abstraction over type constructors --
 that is being able to zip trees etc, then this is not going to work)

Yes I mean ANY container that supports those 3 functions

 
 Now, if by zipping you mean the operation defined in the Prelude
 (slightly differently) as:
 
 zip :: [a] - [b] - [(a, b)]
 zip (x:xs) (y:ys) = (x,y):zip xs ys
 zip _  _  = []
 
 then (you still need pairing and case)
 
 foldr (\ a g ys - case ys of
 [] - empty
 (b:bs) - (a,b) `cons` g bs)
   (\ _ - [])

But only for lists.  As you are patern matching on ":".

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Kevin Atkinson

Lennart Augustsson wrote:


 No, it will not be as efficient.  foldr is not the right primitive for making
 functions on lists.  You want the more general
   recurse :: (a - c a - b - b) - b - c a - b

Could you give me some refrence on how that function is used as this is
the first time I herd of it.

What exactly does it do?  What would its defination for a list be.
How would you define a foldl, foldr, foldl1, foldr1, zip, etc.. with it.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Another rule guestion.

1999-06-30 Thread Kevin Atkinson

Simon Peyton-Jones wrote:

 The way it is now, ONE rule, the fold/build rule
 deals with fusion.  The others are all there to express things
 in terms of fold and build, AND THEN to return certain common
 patterns of usage for foldr to their familiar mapList and filterList
 forms.
 
 Does that help?

Tremendously.  I was thinking that those rules were there becuase the
rule "map f (map g xs) = map (f.g) xs" would simply not work.  Now back
to my orignal question:

Why doesn't my "replaceMany (map f l) a = replaceManyMap f l" rule--as
shown in the previous email titled "Rule Question"--behave as expected.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Another rule guestion.

1999-06-29 Thread Kevin Atkinson

I was looking through PrelBase.lhs and I can not make head or tails out
of the point in all the run around with build, mapFB, etc. is.

As I see it the simplification of  "(map f. map g) l" would go as
follows:

(map f . map g) xs

map f (map g xs)

build$ \c n - foldr (mapFB c f) n (map g xs)

build$ \c n - foldr (mapFB c f) n 
(build$ \c n - foldr (mapFB c g) n xs)

--with rule: foldr k z (build g) = g k z

build$ \c n - 
  (\c n - foldr (mapFB c g) n xs) (mapFB c f) n

build$ \c n - foldr (mapFB (mapFB c f) g) n xs

-- with rule: mapFB (mapFB c f) g = mapFB c (f.g)

build$ \c n - foldr (mapFB c (f.g)) n xs

(\c n - foldr (mapFB c (f.g)) n xs) (:) []

foldr (mapFB (:) (f.g)) [] xs

-- with rule: foldr (mapFB (:) f) [] = mapList f

mapList (f.g) xs

which seams like a hell of a lot of work when the rule "map f (map g xs)
= map (f.g) xs" should do the trick.

I am sure all this run-around is here for a good reason, but what is it?
I am also sure that understanding what all this run-around does is the
key to understanding why the rule "replaceMany (map f l) a =
replaceManyMap f l" is not behaving as expected.

Thanks in advance for any help with this.  I can see how the rule
rewriting mechanism can be very powerful; however, it is not very useful
if I can't figure out how it works...
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: PATCH: unlit.c

1999-06-28 Thread Kevin Atkinson

Kevin Atkinson wrote:
 
 I discovered that my problem was that unlit was crashing because stdout
 does not like to be closed.
 
 Anyway this patch fixes the problem.
 
 I will let you know how things go now that I solved that problem.  Next
 time I will actually take a look at the core file.  It would of saved my
 and Kirstin S. Reese a lot of trouble.

It turns out that unlit.c was the only think I needed to modify in order
to get the CVS version (June 27) to compile with the ghc 4.02 linux
binaries.  The fflush in RtsStartup had nothing to do with it.

Not being able to close stdout is defiantly a bug as the glibc info
pages has an example in which it does that very thing.  However
considering that the libc distributed with Redhat 6.0 has this problem I
strongly recommend you apply my patch as it does not do any real harm.

Special thanks to Kirstin S. Reese for helping me with this problem.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: PATCH: unlit.c

1999-06-28 Thread Kevin Atkinson

Simon Marlow wrote:

 Thanks Kevin - I've applied your patch.  Should be in tomorrow's CVS.
 

Your welcome.  

BTW: the ghc perl script could defiantly be dive better error messages. 
Like saying which program actually crashed instead of just returning
nothing but a bad return value.
-- 

Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



CVS Version of GHC has problems finding Instances

1999-06-28 Thread Kevin Atkinson

It seams that the CVS version of ghc (June 27) has problems finding
instances.   See the attached file Main.hs in a message I just sent to
the Haskell mailing list with a subject of "Second attempt for an STL
like library for Haskell".  If I don't import Eval it complains of not
being able to find an instance of Monad for Eval.Eval.

If this is not a known problem I have some additional examples I can
provide.  Just let me known.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Second attempt for an STL like library for Haskell

1999-06-28 Thread Kevin Atkinson

This is a multi-part message in MIME format.
--EBB527FEAD30E684DE2E6D05
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Here is begginings of my second attempt for an STL like library for
Haskell.  The only think this version has is Arrays however I plan to
add a lot more.  I am almost done with a mutable hash table and I plan
on adding incorporating in other containers such as Ordered Map, Sets,
and Bags, Queues, Dequeues and other similar stuff.  I also plan on
working on a general algorithm collection.  I will implement both purely
functional containers and truly mutable ones.

This version will compile under ghc 4.02 without optimization and the
June 27 CVS version of ghc with Optimizations.  It will also work
through hugs provided you run the files through hscpp.  Unlike Edition I
will strive to making sure that my library always makes it through the
latest version of Hugs.

The file Main.hs contains a small test script demonstrating how
PrimArrays can be faster than arrays with bound checking.  Although it
is difficult to tell, as the garbage collector gets in the way of my
benchmarks, accumPrimArray is about 50% to 33% faster than the normal
accumArray and my implementation of accumArray also seams to be a little
faster than GHC implantation.  I tried profiling the various accums
however I can't seam to get meaningful results form  the CVS version of
ghc.  (Is the profiler still not working correctly or is it me?).

I am very serious about hammering out a nice STL like library for
Haskell so I would be very interested in early feedback from some of you
Haskell experts out there.

I have attached some of the more interesting files from my library.  The
complete set can be found at http://metalab.unc.edu/kevina/abs.tar.

Once again feed back most welcome, especially from the Haskell experts
out on the list.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/
--EBB527FEAD30E684DE2E6D05
Content-Type: text/plain; charset=us-ascii;
 name="Container.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="Container.hs"

module Container where

import Prelude hiding (null)

{- Basic container functions. -}

class Name c where
name :: c - String

class Size c where
size :: c - Int

class Empty c where
empty:: c

class Null c where
null :: c - Bool
isEmpty  :: c - Bool

null = isEmpty
isEmpty = null

class Values c v where
values :: c v - [v]

class ValMap c v1 v2 where
valmap :: (v1 - v2) - c v1 - c v2

instance (Functor c) = ValMap c v1 v2 where
valmap = fmap

--EBB527FEAD30E684DE2E6D05
Content-Type: text/plain; charset=us-ascii;
 name="Assoc.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="Assoc.hs"


module Assoc where

{- 

Functions on Associated Containers (Assoc. C.).  A Simple Assoc. C.
is a container which is indexed based on the value of its
elements such as Sets and Bags.  A Pair Assoc. C. is a Finite Map.

-}

import Container (ValMap(..))
import Prelude hiding (lookup)
import Maybe

class Buckets c where
-- the number of buckets in a hash table
buckets :: c - Int

class Bounds c i e where
-- the bounds of an array
bounds :: c i e - (i,i)

class Assocs c i e where
-- convert a container to a list of ...
assocs  :: c i e - [(i,e)]
indices :: c i e - [i]
keys:: c i e - [i]
elems   :: c i e - [e]

-- minimal definition: assocs | indices  elems | keys  elems
-- keys and indices are assumed to do the same thing
   
assocs c = zip (indices c) (elems c)
indices = map fst . assocs
keys= indices
elems   = map snd . assocs

class Lookup c i e where
-- finds an elemant in a Pair. Assoc. C.  (!) will cause an error
-- if the element is not found
lookup  :: i - c i e - Maybe e
(!) :: c i e - i - e

-- monmal defination: lookup
  
c ! a = fromJust (lookup a c)

class Find c v where
find :: v - c v - Maybe v
findAll :: v - c v - [v]  
isMember :: v - c v - Bool
count :: v - c v - Int

-- minimal defination: find | findAll

find v c = listToMaybe$ findAll v c
findAll v c = maybeToList$ find v c
isMember v c = isJust$ find v c
count v c = length$ findAll v c

class Ixmap c i e j where
ixmap   :: (j,j) - (i - j) - c i e - c j e

class Keymap c i e j where
keymap   :: (i - j) - c i e - c j e

class Elmap c i e f where
elmap   :: (e - f) - c i e - c i f
map_:: ((i,e) - f) - c i e - c i f

-- minimal defination: map_

elmap f = map_ (\(_,e) - f e)

instance (Elmap c i e f) = ValMap (c i) e f where
valmap = elmap

class AssocsMap c i e j f where
assocsMap :: ((i,e) - (j,f)) - c i e - c j f

class Insert c v where
-- insert a new element in a Simple Assoc. C.  
-- the behavinor of i

Re: Second attempt for an STL like library for Haskell

1999-06-28 Thread Kevin Atkinson

This is a multi-part message in MIME format.
--D60EAED940B337DE04784023
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Kevin Atkinson wrote:
 
 The file Main.hs contains a small test script demonstrating how
 PrimArrays can be faster than arrays with bound checking.  Although it
 is difficult to tell, as the garbage collector gets in the way of my
 benchmarks, accumPrimArray is about 50% to 33% faster than the normal
 accumArray and my implementation of accumArray also seams to be a little
 faster than GHC implantation.  I tried profiling the various accums
 however I can't seam to get meaningful results form  the CVS version of
 ghc.  (Is the profiler still not working correctly or is it me?).

After modifying Main.hs to test each of the accums one at a time it
seams that my accum takes about as much time as ghc accum and the
accumPrimArray is twice as fast as the other two.

As I suspected the fancy indexes and bound checking come at a high
price.

I attached the modified Main.hs so that you can try it out for yourself.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/
--D60EAED940B337DE04784023
Content-Type: text/plain; charset=us-ascii;
 name="Main.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="Main.hs"


module Main (main, prim, norm, orig, expr) where

import Prelude hiding (null, lookup)

import Mutable
import Assoc
import Container

import MutPrimArray
import MutAltArray 
import STExtras

import Random
import System

import qualified Array
import Ix


import PrelBase
import PrelST
import PrimArrayDefn hiding (freeze', unsafeFreeze', thaw')

#ifdef __GLASGOW_HASKELL__

import Eval -- this should really not be necessary, however the CVS
-- version of ghc (June 27, 1999) requires it. 
-- I think it is a bug.

import CPUTime

num :: Int
num = 10

#define scc(n) _scc_ n

#else

getCPUTime :: IO Integer
getCPUTime = return 0

num :: Int
num = 1000

#define scc(n)

#endif

l :: [Int]
l = take num$ rs (mkStdGen 13)

rs g = case randomR (0,98) g of (x,g') - x : rs g'

main :: IO ()
main = do bench$ print$ scc("gen") seq (sum l) "Evaluating l"
  x - getArgs
  case head x of 
   "orig" - bench$ scc("orig") orig l
   "prim" - bench$ scc("prim") prim l
   "norm" - bench$ scc("norm") norm l

bench com = do s - getCPUTime
   com
   f - getCPUTime
   print$ (f-s) `div` (10^9)

prim l = do let a :: PrimArray Int Int
a = accumPrimArray (+) 0 100 $ zip l (repeat 1)
putStr "prim\n"
print$ elems a

norm l = do let a :: Array Int Int
a = accumArray (+) 0 (0,99) $ zip l (repeat 1)
putStr "norm\n"
print$ elems a

orig l = do let a :: Array.Array Int Int
a = Array.accumArray (+) 0 (0,99) $ zip l (repeat 1)
putStr "orig\n"
print$ Array.elems a

{-
expr l = do let els = do m - mlistPrimArray 100 (take 100 $ repeat 0)
 maccum (+) m (1,
 melems m
putStr "expr\n"
print$ runST els
-}

expr l = do let a :: PrimArray Int Int
a = accumPrimArray (+) 0 100 [(1,a!2),(2,a!3),(3,a!4),(4,100)]
putStr "expr\n"
print$ elems a

maccum' f (M m _) l = ST$ \s - (# z s l, () #)
where z s [] = s
  z s ((I# ix,el):t) = 
  case readArray# m ix s of
  (# s, x #) - let r = case x `f` el of r - seq r r 
in  case writeArray# m ix r s of
s - z s t

mcount' (M m _) l = ST$ \s - (# z s l, () #)
where z s [] = s
  z s ((I# ix):t) = 
  case readArray# m ix s of
  (# s, x #) - case writeArray# m ix (x+1) s of
s - z s t

--D60EAED940B337DE04784023--






PATCH: unlit.c

1999-06-26 Thread Kevin Atkinson

I discovered that my problem was that unlit was crashing because stdout
does not like to be closed.

Anyway this patch fixes the problem.

I will let you know how things go now that I solved that problem.  Next
time I will actually take a look at the core file.  It would of saved my
and Kirstin S. Reese a lot of trouble.


--- unlit.c~Sun Feb  7 17:06:27 1999
+++ unlit.c Fri Jun 25 17:45:30 1999
@@ -338,8 +338,8 @@
 
 unlit(file, istream, ostream);
 
-fclose(istream);
-fclose(ostream);
+if (istream != stdin)  fclose(istream);
+if (ostream != stdout) fclose(ostream);
 
 exit(errors==0 ? 0 : 1);
 }

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



UPDATE: CVS compile problems

1999-06-25 Thread Kevin Atkinson

Ok on the advice of Kirstin S. Reese who said:
 
 You are using a new version of glibc, and your newly compiled hsc is
 crashing.
 
 This problem is caused by the call to fflush(stdout) in shutdownHaskell in
 RtsStartup. The call to fflush is no longer needed.
 
 You cannot simply comment this out, however, as hsc is linked to your
 installed libraries while the new libraries are being compiled. The missing
 fflush prevents the images from being the same size.
 
 You will have to comment out the fflush, and bootstrap from the .hc files,
 as if no binary existed for your platform.

tar xfvz ghc-4.02-src.tar.gz
cd fptools
tar xfvz ../ghc-4.02-x86-hc.tar.gz
# went in and commented out fflush in ghc/rts/RtsStartup.c
./configure --enable-hc-boot
make boot
make all
./configure
cd ghc/lib
make boot

and everthing worked fine but when I did a make all

I got the same error.  I carefully went in and cleaed out ghc from 
/usr/local/bin|lib before starting anything:

[kevina@kevins-linux bin]$ ls -F 
Ted*   happy@   libtoolize*   texi2html~*
Xvnc@  happy-1.5*   miditext* txtplay*
aclocal*   hugs*netscape@ vncpasswd@
acroread@  ifnames* run-with-aspell*  vncserver@
aspell*java@runhugs*  vncviewer@
cpp@   javac@   soffice@  xwp*
drvmidi*   latex2html@  texi2html*xwp~*

[kevina@kevins-linux lib]$ ls -F 
aspell/  libaspell.la*libaspell.so.2.0.0*
happy-1.5/   libaspell.so@libclient.a
libaspell.a  libaspell.so.2@

I am using Redhat 6.0.

After looking through the bug archive I realized that I was having the
exact same problem that Giuliano P Procida had.  Is there a known fix
for this problem as commenting out the fflush did not seam to work.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: UPDATE: CVS compile problems

1999-06-25 Thread Kevin Atkinson

Kevin Atkinson wrote:
 
 Ok on the advice of Kirstin S. Reese who said:
 
  You are using a new version of glibc, and your newly compiled hsc is
  crashing.
 
  This problem is caused by the call to fflush(stdout) in shutdownHaskell in
  RtsStartup. The call to fflush is no longer needed.
 
  You cannot simply comment this out, however, as hsc is linked to your
  installed libraries while the new libraries are being compiled. The missing
  fflush prevents the images from being the same size.
 
  You will have to comment out the fflush, and bootstrap from the .hc files,
  as if no binary existed for your platform.
 
 tar xfvz ghc-4.02-src.tar.gz
 cd fptools
 tar xfvz ../ghc-4.02-x86-hc.tar.gz
 # went in and commented out fflush in ghc/rts/RtsStartup.c
 ./configure --enable-hc-boot
 make boot
 make all
 ./configure
 cd ghc/lib
 make boot
 
 and everthing worked fine but when I did a make all
 
 I got the same error.  

Here is what I got.  Sorry for leaving it out.


==fptools== make all -r;
 in /usr/local/src/fptools/ghc/lib/std

rm -f PrelBase.o ; if [ ! -d PrelBase ]; then mkdir PrelBase; else find
PrelBase -name '*.o' -print | xargs rm -f __rm_food ; fi ;
../../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing
-O -split-objs -odir PrelBase  -H10m  -c PrelBase.lhs -o PrelBase.o
-osuf o
make[1]: *** [PrelBase.o] Error 1
make: *** [all] Error 1


 I am using Redhat 6.0.
 
 After looking through the bug archive I realized that I was having the
 exact same problem that Giuliano P Procida had.  Is there a known fix
 for this problem as commenting out the fflush did not seam to work.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Layout Rules

1999-06-25 Thread Kevin Atkinson

Currently Hugs except the following piece of code but GHC does not:

mcompare x y = 
 do i - x ==~ y 
if i then return EQ else do 
i - x =~ y 
if i then return LT else do
return GT

However both except:

mcompare x y = 
 do i - x ==~ y 
if i then return EQ else do 
  i - x =~ y 
  if i then return LT else do
return GT

which is a bit uglier.

Is ghc correct in rejecting the original code segment?  Is this a bug in
ghc or the Haskell 98 report? I prefer hugs behavior over ghc.



-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





CVS compile problems

1999-06-24 Thread Kevin Atkinson

I am having some trouble compiling the CVS version of ghc which I
checked out Jun 23 21:51 EDT


==fptools== make all --no-print-directory -r;
 in /usr/local/src/fptools/ghc/lib/std

rm -f PrelBase.o ; if [ ! -d PrelBase ]; then mkdir PrelBase; else find
PrelBase -name '*.o' -print | xargs rm -f __rm_food ; fi ;
../../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing
-O -split-objs -odir PrelBase -fcompiling-prelude -static  -H12m  -c
PrelBase.lhs -o PrelBase.o -osuf o
make[3]: *** [PrelBase.o] Error 1
make[2]: *** [all] Error 1
make[1]: *** [all] Error 1
make: *** [all] Error 1

The PrelBase directory is empty.  I have the
ghc-4.02-i386-unknown-linux.tar.gz package installed.

I also had to add -optCrts-M128M to the parser/Parser_HC_OPTS in order
to get parser.lhc to compile (which by the way to over an Hour on my
machine to compile which is a Pentium 166MX with 96M of ram)

Any help would be greatly appreciated.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: Type Synonym where the kind is not *

1999-06-18 Thread Kevin Atkinson

Simon Peyton-Jones wrote:
 
 Thanks for reporting this.  I think we fixed already.  It's certainly ok in
 the
 current CVS snapshot.

When do you plan on releasing a new version of GHC with this bug fixed
as I rely on it pretty heavily?
 
 Simon
 
  -Original Message-
  From: Kevin Atkinson
  Sent: Wednesday, June 16, 1999 5:39 PM
  To: [EMAIL PROTECTED]
  Subject: Type Synonym where the kind is not *
 
 
  GHC version 4.02, patchlevel 0 does not allow type synonym where the
  kind is not *.  For example it does not allow
type List = []
  which is given an example in section 4.2.2 of the Haskell 98 Report.
 
  The latest version of hugs doesn't have any problems with it
 
  --
  Kevin Atkinson
  [EMAIL PROTECTED]
  http://metalab.unc.edu/kevina/
 

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Type Synonym where the kind is not *

1999-06-16 Thread Kevin Atkinson

GHC version 4.02, patchlevel 0 does not allow type synonym where the
kind is not *.  For example it does not allow
  type List = []
which is given an example in section 4.2.2 of the Haskell 98 Report.

The latest version of hugs doesn't have any problems with it

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/



Re: Overlapping instances?

1999-06-13 Thread Kevin Atkinson

Lars Henrik Mathiesen wrote:
 
  Date: Sun, 13 Jun 1999 01:51:06 -0400
  From: Kevin Atkinson [EMAIL PROTECTED]
 
  Could some one explain to me why [this is not OK]:
 
class T f r
 
instance T a   (d a)
instance T (c a b) (c a (d b))
 
 Because, just as Hugs says:

Thanks but why is this OK?

  class T f r

  instance T a   (a)
  instance T (c a b) (c a (b))

I mean the comman instance here is T (c a b) (c a (b)).
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Overlapping instances?

1999-06-13 Thread Kevin Atkinson

Could some one explain to me why this is OK:

  class T f r

  instance T a   (a)
  instance T (c a b) (c a (b))

but this is not:

  class T f r

  instance T a   (d a)
  instance T (c a b) (c a (d b))

as Hugs gives (with -98 +o)

  ERROR "T.hs" (line 4): Overlapping instances for class "T"
  *** This instance   : T (a b c) (a b (d c))
  *** Overlaps with   : T a (b a)
  *** Common instance : T (a b c) (a b (a b c))

and GHC gives

Duplicate or overlapping instance declarations
for `T a (d a)' at T.hs:3 and T.hs:4

Thanks in advance.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: How to murder a cat

1999-06-10 Thread Kevin Atkinson

"D. Tweed" wrote:

 
 I think it'd probably better software engineering to split the two tasks.
 Other than a rather nasty syntax, make does what it sets out to do quite
 well:  using specified dependencies and time-stamps on files to run
 `compilation-type' processes in an appropriate way. What would, as you
 say, be very nice is a tool which can be run periodically to auto-generate
 these dependencies. Especially nice would be if the source were available
 so people could have a go at adapting it to other languages, e.g., C++, or
 latex files, etc.

Um the gnu c preproccer can auto generate these dependencies with cpp
-M.  I believe ghc has tools to do the same.... 


-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: how to write a simple cat

1999-06-01 Thread Kevin Atkinson

Keith Wansbrough wrote:
 
 Sven Panne wrote:
 
   Don't fear! Mr. One-Liner comes to the rescue:;-)
  
  longerThan fn lenlim = readFile fn = lines .| filter (length .| (lenlim)) 
.| zip [1..] .| map (\(n,l) - shows n ") " ++ l) .| unlines .| putStr
 
 Friedrich wrote:
 
  Do you want to drive me away from learning Haskell? Who the hell can try
  to write such functions? Is readabilty not a concern in Haskell?
 
 I would have to agree, Sven does seem to be working hard to drive a
 beginner away from Haskell.  But he is illustrating an important
 coding style.  If we lay his function out on a few more lines, and
 replace his (|.) = flip (.) operator with the standard functional
 composition (.), we get the following:

Truthfully I think the forward composition ie (flip (.) ) makes the code
more natural to read as it can be read do this, than this, than this,
etc...  As opposed to do this to the result of this to the result of
this, etc...  The former can be read as a sequence of actions to
perform.

I just wish a standard operator is chosen for a) flip (.) and b) flip
($) instead of having everyone make up their own.  I don't really care
what it is.  I truthfully like . for flip (.) and # for flip ($) but I
can easily change.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Implementation of Nameable Type Parameters

1999-06-01 Thread Kevin Atkinson

Kevin Atkinson wrote:
 
 For those of you who may be interested:
 
 I am working on an implementation of Nameable Type Parameters written in
 Haskell.  I currently have them working in a so called Mini Haskell
 where all kind information is presented explicitly.  I had a few
 unification problems but I eventually got it all working out.   It even
 allows overlapping instances!  I will let you know when I have a
 finished product which includes complete kind inference.  If anyone is
 interest in seeing the preliminary product please let me know and I will
 send you a copy.

This "Mini Haskell" only has unification and kind inference. It is just
enough to demonstrate how Nameable Type Parameters work.  Sorry if
anyone though it was a complete Haskell like system.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Implementation of Nameable Type Parameters

1999-05-29 Thread Kevin Atkinson

For those of you who may be interested:

I am working on an implementation of Nameable Type Parameters written in
Haskell.  I currently have them working in a so called Mini Haskell
where all kind information is presented explicitly.  I had a few
unification problems but I eventually got it all working out.   It even
allows overlapping instances!  I will let you know when I have a
finished product which includes complete kind inference.  If anyone is
interest in seeing the preliminary product please let me know and I will
send you a copy.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Portability dreams

1999-05-28 Thread Kevin Atkinson

Sven Panne wrote:
 

* If you upgrade your version of GHC, its libraries change in such a
  way that you have to recompile all your code: A compiler-generated
  entity (ds42, lvl1, tpl60, ...) from one version can mean quite a
  different thing in the next. Compare this with C libs: You don't have
  to completely re-install your whole *nix after switching to another
  C compiler. I'm not sure if things are better with nhc13 or hbc, but
  I fear they are not.

This is also partly true for c++ compilers.  C compiles have a VERY
simple symbols which is simply a name.   More advanced languages have
complex symbols that store additional necessary information.  C++ stores
type information in the symbol to resolve overloading.  Ghc might do a
similar thing.  Than again Haskell overloading is nothing like C++
overloading so maybe not.

 
* Libraries differ vastly between systems, although there is some hope
  for Hugs/GHC.

The trick here is to have free portable libraries that can compile under
any valid Haskell compiler so that if you need something simply include
the library with your program.

 
 After these remarks here are my pleas:
 
* Implementors: Write a Haskell-aware preprocessor. Include details
  about it in the next language report. A preprocessor-free and at
  the same time evolving language is a dream, but nothing more. In
  the meantime, at least make your systems agree on the preprocessor
  constants (see above).

I have a better idea.  Have a pragma to allow the preprocessing to be
done my some arbitrary haskell function.  An optional module may be
specified.  The function should have the signature of 
String - String - [String] - String.  The First string is the actual
file, the second string is the name of the file being processed, the
third is a list of preprocess options from the command line and the
Output is the processed file.  The pragma should look something like
this 
{-# pre haskell function #-} or {-# prewModule module name haskell
function #-}.  Because the actual text may not a valid haskell program
it should look for this string anywhere within the first 5 lines of the
file.  The function naturally should be totally independent from the
rest of the file.  If no preprocess is specified use a default one. 
This will allow different styles of literate programing to be used with
out any additional fuss amoung other things.
 
* The Haskell 98 libraries are nice, but by no means sufficient.
  A quick(!) agreement on libs to include in every system is necessary,
  because languages live and die with libraries. Compare Scheme and Java:
  Scheme's approach to "get everything right the first time" has lead
  to a crawling development (How many changes between R^4RS and R^5RS?
  Any standardized and non-trivial libs out there?). The Java hype on
  the other hand can mainly be attributed to the enormous availability
  of standard libs.

See my above note.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Kind Question

1999-05-26 Thread Kevin Atkinson

I have a question for the Haskell experts on the list.  (Especially
Haskell compiler writers).

Is it possible to have a kind more complicated than:

kind   = kind' | kind' - kind
kind'  = * | ( kind'' )
kind'' = * | * - kind''

If so could you give me an example of a type which has a more
complicated kind as I sure can't find one.

Thanks in advance.  I look forward to a yes or no.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Please don't post

1999-05-26 Thread Kevin Atkinson

Kevin Atkinson wrote on Wed, 26 May 1999 03:05:17 -0400:
 
 I have a question for the Haskell experts on the list.  (Especially
 Haskell compiler writers).
 
 Is it possible to have a kind more complicated than:
 
 kind   = kind' | kind' - kind'

I made a mistake here.   Please don't post this one.  Post the one
sent 6 minutes latter (on Wed, 26 May 1999 03:11:31 -0400).

The latter one has the above line fixed to read:
  kind   = kind' | kind' - kind

 kind'  = * | ( kind'' )
 kind'' = * | * - kind''
 
 If so could you give me an example of a type which has a more
 complicated kind as I sure can't find one.
 
 Thanks in advance.  I look forward to a yes or no.
 --
 Kevin Atkinson
 [EMAIL PROTECTED]
 http://metalab.unc.edu/kevina/

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Kind Question

1999-05-26 Thread Kevin Atkinson

Lennart Augustsson wrote:
 
 Kevin Atkinson wrote:
 
  I have a question for the Haskell experts on the list.  (Especially
  Haskell compiler writers).
 
  Is it possible to have a kind more complicated than:
 
  kind   = kind' | kind' - kind
  kind'  = * | ( kind'' )
  kind'' = * | * - kind''
 
 Yes, kinds are generated by the grammar
 kind ::= * | kind - kind | (kind)
 
  If so could you give me an example of a type which has a more
  complicated kind as I sure can't find one.
 
 Your grammar does not seem to cover
 ((*-*) - *) - *
 which you could get (as the kind of D) e.g. from
 data D c = C (c [])
 

Thanks.

Now how would I use a type considering its constructor has a signature
of:

C :: a [] - D a

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Kind Question

1999-05-26 Thread Kevin Atkinson

Kevin Atkinson wrote:
 
 Lennart Augustsson wrote:
  Your grammar does not seem to cover
  ((*-*) - *) - *
  which you could get (as the kind of D) e.g. from
  data D c = C (c [])
 
 
 Now how would I use a type considering its constructor has a signature
 of:
 
 C :: a [] - D a

I answered my own question.

data D c = C (c [])
data E c = F (c Int)

a = C (F [10])

But what can such a type be used for?

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Kind Question

1999-05-26 Thread Kevin Atkinson

I have a question for the Haskell experts on the list.  (Especially
Haskell compiler writers).

Is it possible to have a kind more complicated than:

kind   = kind' | kind' - kind'
kind'  = * | ( kind'' )
kind'' = * | * - kind''

If so could you give me an example of a type which has a more
complicated kind as I sure can't find one.

Thanks in advance.  I look forward to a yes or no.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Draft Proposal: Nameable Type Parameters

1999-05-25 Thread Kevin Atkinson

This is a multi-part message in MIME format.
--9FB4D0D35F15A05DBD8B1B67
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Here is a slightly corrected version of my proposal.  It has a few
grammar fixes and since I am sending it as an attachment it shouldn't
have the formatting problems.

Feedback most welcome.  An html, and ps version of this report is
available at http://metalab.unc.edu/kevina/ntp.


-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/
--9FB4D0D35F15A05DBD8B1B67
Content-Type: text/plain; charset=us-ascii;
 name="ntp.txt"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="ntp.txt"


  Nameable Type Parameters
  
       Kevin Atkinson
 [EMAIL PROTECTED]
   
   
   The Basic Problem
   
   The basic problem with Haskell type system is that it is impossible to
   make both Array and a list of tuple pairs a member of a class to
   lookup elements based on an index. It is also impossible to make both
   lists and arrays a member of a map class where items in the array are
   treated as an associated pair. Although in practice this may not be a
   serious problem, it does put a serious hinder on coming up with a good
   clean abstraction of common data structures and algorithms in Haskell.
   It is probably also one of the reasons Haskell received a B while Ada
   received an A in support for reuse in a controlled experiment to judge
   the effectiveness of several different language for prototyping
   support.1
   
   One solution the this problem within Haskell is to use vague classes:
   
 class Find c i e where
   find :: i - c - e
 
 class Map a b c d where
   map :: (a - b) - c - d
 
 instance Eq i = Find [(i,e)] i e where ...
 instance Map a b [a] [b] where ...
 
 instance Find (Array i e) i e ...
 instance Map (i,e) (j, f) (Array i e) (Array j f) where...
 
   However this solution has several problems:
   
   1.
  When used with a function like show it will lead to an
  unresolved overloading because Haskell can't figure out the
  return type.
   2.
  The instance declaration are unnecessary ugly.
   3.
  The map functions does not promise to return a container of the
  same type based on the class declaration.
  
   Another solution within current Haskell is to make a new data type:
   
 data MyArray c (i,e) = MyArray c
 myarray :: Array i e - MyArray (Array i e) (i,e)
 myarray a = MyArray a
 
   which will solve the problem of vague classes but will introduce a new
   problem, mainly that writing the Map class such as
   
 class Map c a b where
   map :: (a - b) - c a - c b
 
   will not allow a map to be defined over a MyArray where the element
   types are not the same as the container type will also change.
   Defining the map instance for Array like so
   
 instance Map MyArray (Array i e) (i,e) (j,f) where ...
 
   will force j and f to be the same type of i and e respectfully. In
   order to allow the contents type to change the map function will have
   to have a signature of
   
 map :: ((i,e) - (j,f)) - (MyArray (Array i e)) (i,e)
 - (MyArray (Array j f)) (i,e)
 
   which is not allowed as (MyArray (Array i e)) is the container type
   and it changed when the content types changed. Thus the map function
   will have to have a vague signature such as in the original example.
   This defeats the whole purpose of defining a new type. Defining a new
   type also is not transparent to the end user which defeats the whole
   purpose of coming up with an abstraction.
   
   Nameable Type Parameters
   
   Nameable type parameters is simply a way to attach labels to existing
   types. These labels can then be used to resolve overloading in a much
   more flexible way than Haskell currently can.
   
   To attach the a label to a type simple define it using the syntax:
   
 assign ::= label atype = atype'
 label ::= valid uppercase Haskell identifier
 atype ::= valid Haskell type
 atype' ::= atype
 
   For example, the Array class can have an Inx, El, and Con type label
   attached to it with the commands:
   
 Inx Array i e = i
 El Array i e = e
 Con Array i e = (i,e)
 
   Multiple assign statements may be given for the same label. A type
   label is then used by extending the valid Haskell type syntax to:
   
 type ::= simple-type label-type
 simple-type ::= [single-type ]+
 label-type :: = [label: type']+
 single-type ::= type-name | type-var
 type-name ::= valid uppercase Haskell 

Draft Proposal: Nameable Type Parameters

1999-05-22 Thread Kevin Atkinson


  Nameable Type Parameters
  
   Kevin Atkinson
 [EMAIL PROTECTED]
   
   
   The Basic Problem
   
   The basic problem with Haskell type system that it is impossible to
   make both Array and a list of tuple pairs a member of a class to
   lookup elements based on an index. It is also impossible to make both
   lists and arrays a member of of map class where items in the array
are
   treated as an associated pair. Although in practice this may not be a
   serious problem, it does put a series hinder on combing up with a
good
   clean abstraction of common data structures and algorithms in
Haskell.
   It is probably also one of the reasons Haskell received a B while Ada
   received an A in support for reuse in a controlled experiment to
judge
   the effectiveness of several different language for prototyping
   support.1
   
   One solution within Haskell is to use vague classes:
   
 class Find c i e where
   find :: i - c - e
 
 class Map a b c d where
   map :: (a - b) - c - d
 
 instance Eq i = Find [(i,e)] i e where ...
 instance Map a b [a] [b] where ...
 
 instance Find (Array i e) i e ...
 instance Map (i,e) (j, f) (Array i e) (Array j f) where...
 
   However this solution has several problems:
   
   1.
  When used with a function like show it will lead to an
  unresolved overloading because Haskell can't figure out the
  return type.
   2.
  The instance declaration are unnecessary ugly.
   3.
  The map functions does not promise to return a container of
the
  same type based on the class declaration.
  
   Another solution within current Haskell is to make a new data type:
   
 data MyArray c (i,e) = MyArray c
 myarray :: Array i e - MyArray (Array i e) (i,e)
 myarray a = MyArray a
 
   which will solve the problem of vague classes but will introduce a
new
   problem, manly that writing the Map class such as
   
 class Map c a b where
   map :: (a - b) - c a - c b
 
   will not allow a map to be defined over a MyArray where the element
   types are not the same as the container type will also change.
   Defining the map instance for Array like so
   
 instance Map MyArray (Array i e) (i,e) (j,f) where ...
 
   will force j and f to be the same type of i and e respectfully. In
   order allow the contents type to change the map function will have to
   have a signature of
   
 map :: ((i,e) - (j,f)) - (MyArray (Array i e)) (i,e)
 - (MyArray (Array j f)) (i,e)
 
   which is not allowed as (MyArray (Array i e)) is the container type
   and it changed when the content types changed. Thus the map function
   will have to have have to have a vague signature such as in the
   original example. This defeats the whole purpose of defining a new
   type. Defining a new type also is not transparent to the end user
   which defeats the whole purpose of coming up with an abstraction.
   
   Nameable Type Parameters
   
   Nameable type parameters is simply a way to attach labels to existing
   types. These labels can then be used to resolve overloading in a much
   more flexible way than Haskell currently can.
   
   To attach the a label to a type simple define it using the syntax
   
 assign ::= label atype = atype'
 label ::= valid uppercase Haskell identifier
 atype ::= valid Haskell type
 atype' ::= atype
 
   For example the Array class can have an Inx, El, and Con type label
   attached to it with the commands:
   
 Inx Array i e = i
 El Array i e = e
 Con Array i e = (i,e)
 
   Multiple assign statements may be given for the same label. A type
   label is then used by extending the valid Haskell type syntax to:
   
 type ::= simple-type label-type
 simple-type ::= [single-type ]+
 label-type :: = [label: type']+
 single-type ::= type-name | type-var
 type-name ::= valid uppercase Haskell identifier
 type-var ::= valid lowercase Haskell identifier
 type' ::= type
 
   (Function, List and Tuple types will also work however for the
purpose
   of this explanation, they will be ignored as it should be easy to
   expand the grammar to support them.)
   
   If the kind of simple-type is * then look for an assign with a
   matching label, and a matching atype and bind type' to atype' if it
   can. If it can't it will keep searching. If the kind of simple-type
is
   * - * than look for either an assign with the same label in which
the
   atype has a kind of * - * or has at least two single-types. If the
   atype has two single-types drop the last single-type when trying to
   find a match. Once

Re: View on true ad-hoc overloading.

1999-05-21 Thread Kevin Atkinson

Fergus Henderson wrote:

 On first impression, having just read the paper "Type restrictions for
 overloading, without restrictions, declarations or annotations",
 I don't think I like system CT very much, because I think declaring
 interfaces is very important for software engineering reasons.
 Experience with C++ has shown that that the lack of declared interfaces
 with C++ templates causes major problems.  At first impression, it seems
 to me that a language based on system CT will suffer from the same kinds
 of problems.

And I agree.  I propose extending the CT system to allow constraints to
be made on how a function can be overloaded.  Functions will still be
allowed to be overloaded in other ways, but only by explicitly stating
that this function violates the rule.  These constraints for all intends
and purposed will act like type classes.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: View on true ad-hoc overloading.

1999-05-20 Thread Kevin Atkinson

Brian Boutel wrote:
 
 Of course it *can* be done, but *should* it be done?
 
 Uncontrolled overloading means that when you see a function application you can't
 immediately see what function is being applied - you see its name but not its 
semantics, because
 there may be many different functions with the same name.
 
 Obfuscating the program source in this way presents a risk of error, and is bad 
language engineering.
 
 What would be gained by allowing ad hoc overloading? If operations on different 
types have similar meaning
 there is a case for defining a new class. If you have existing different functions 
with similar names you can
 qualify them to avoid the ambiguity. When else would you want this feature?

1) Allowing operational parameters to be used.

2) Allow record names to be reused.  Most langauges have a special
syntak for record names but haskell does not.  Record names are just
treated as selector functions.

3) Allow really really clean systax for functions with compicated
parameters.  Try doing this within current haskell.

  array (range 1 to 10) ...
  array (range 1 to 10 skip 2) ...
  array (range 1 to 100 factor 2) ...

with true overlading you can do this my defining multiple range
functions.

data To ; to :: To; to = undefined
data Skip  ; skip :: Skip; skip = undefined
data Factor ; factor :: Factor; factor = undefined;

range :: a - To - a - ArrayRange
range x to y = ...
range :: ...
range x to y skip s = ...
range :: ..
range x to y factor 2 = ...

And with a little bit of syntactic sugar this can be made even shorter.

Try doing that with current haskell!

True ad-hoc overloading can lead to unreadable programs if it is
misused.  However it can make code more readable and concise if used
properly.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: View on true ad-hoc overloading.

1999-05-20 Thread Kevin Atkinson

Olaf Chitil wrote:
 
  1) Allowing operational parameters to be used.
 
 Sorry, I don't know what you mean by `operational parameters'. 

Sorry typo.  That should be optional.
 
  2) Allow record names to be reused.  Most langauges have a special
  syntak for record names but haskell does not.  Record names are just
  treated as selector functions.
 
 Yes, that's very useful. And the TREX extension (extensible records) of Hugs
 permits you to do that and much more.

I never looked into TREX but perhaps I will.
 
  3) Allow really really clean systax for functions with compicated
  parameters.  Try doing this within current haskell.
 
array (range 1 to 10) ...
array (range 1 to 10 skip 2) ...
array (range 1 to 100 factor 2) ...
 
 Reuse the existing list functions:
 
 array [1..10]
 array [1,3..10]
 array (takeWhile (=100) (iterate (*2) 1))

You misunderstood me.

It should be.

array (range 1 to 10) [(1,1), (1,2) ]
array (range 1 to 10 skip 2) [(1,1), (3,2) ...]
array (range 1 to 100 factor 2] [(1,1), (2,2), (4,3), (8,4) ...]

Perhapes range is not a good word to use.  Maybe indices instead.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Haskell Type System Nameable type parameters

1999-05-17 Thread Kevin Atkinson

Mark P Jones wrote:

 | 2) Does anyone care that this type of thing is not possible?
 
 Yes, they do.  That said, I've often found that people are usually happy
 simply to write something like:
 
newtype Assocs i e = MkAssocs [(i,e)]
 
 I know it's a bit of a pain to be forced to use the MkAssocs constructor,
 but this kind of thing usually works pretty well in practice.  I don't think
 you've explained why this solution isn't suitable for your purposes?

Ok.  In case you haven't figured out I am also the one who asked about
an STL like library for haskell and the one who is attempting to come up
with a good abstraction for Haskell.  While doing this abstraction I
have come up against many of the limitations of Haskell type system. 
Perhaps if I document the process and detail all the workarounds I had
to do to get around limitations of Haskell type system and the drawback
to those limitations I could give everyone a better idea of the
frustrations I am felling?
 
 | 3) Does any one have a solution to this problem?
 
 I believe that "parametric type classes", introduced by Chen, Hudak and
 Odersky at the Lisp and FP conference in 1992 (but as yet unimplemented)
 would provide a solution.  You can download their paper from Yale, but
 I'm afraid I don't have the URL to hand right now.  (My own paper on
 "Simplifying and Improving qualified types" from 1995 is also relevant,
 but is more abstracr and has also not been implemented as yet in any general
 form.)

Thanks for pointing the paper out. (A url with a copy of the paper is
(http://www.cis.unisa.edu.au/~cismxo/papers/ for those who are
interested) I have not taken a detail look at it but if I don't think it
would completely solve my problem.  For example would this be legal:

class c :: ToList a where
  toList :: c - [a]

instance Array a b :: ToList (a,b) where ...

 | 4) What did you think of my idea for getting around this problem (and a
 | lot more) in the post titled "Idea: Nameable type parameters"
 
 Well I think you'd need to spell out your idea in a lot more detail before
 anyone could give any firm conclusions.  All you have given us so far is
 an example.  What exactly are you proposing in more general terms, and how
 would it interact with type inference and modules?  

I have not thought of all the details I was more interested if it had
potential and if it is needed.

 I don't want to discourage
 you from fleshing out the proposal more fully, but I think you should pay
 particular attention to these last two points.  For example, the essence
 of your proposal seems to be a notation for defining functions on types,
 and I suspect that you will have problems making unification work properly
 in that setting.

Your right as I presented it there are some problem.  But I think I can
work them out.  However I would like to know if it is even worth
pursuing as I am doing this completely on my own time.

 
 I hope that this helps.

It does.  Thanks for responding.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Haskell Type System

1999-05-15 Thread Kevin Atkinson

Unlike most people I was drawn to Haskell not because it is a lazy
functional programming language but because it has an advanced type
system and very clean syntax.  Unfortunately as I am quickly discovering
Haskell type system, while being rather _advanced_, is not nearly as
flexible as C++ system which is probably one of the most _flexible_ type
systems out there.  I have made several inquiries about the type system
however I have gotten little reply.

The biggest one is that I would like to be able to make [(ix,el)], [Pair
ix el], and Array ix el all members of a Find class while should look
something like this:

  class Find c ix el where
find :: ix - c - Maybe el

without having to define a new type or introducing the possibility of
unresolved overloading when the return type isn't explicitly known.

I would _really_ like to know if

1) Am I correct in assuming this is not possible with current Haskell as
implemented in Hugs and GHC (ie not just Haskell 98)?

2) Does anyone care that this type of thing is not possible?

3) Does any one have a solution to this problem?

4) What did you think of my idea for getting around this problem (and a
lot more) in the post titled "Idea: Nameable type parameters"

I really look forward to an authorized answer to these questions.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Idea: Nameable type parameters

1999-05-10 Thread Kevin Atkinson

Kevin Atkinson wrote:
 
   -- If the kind of an object is Cont2_ - ie then its
   -- Ix type is the Fst type of ie  if  ie has a type Fst
   Ix (Cont2_ ie) = Fst ie
   -- If the kind of an object is Cont2_ - ie then its
   -- El type is the Snd type of ie  if  ie has a type Snd
   El (Cont2_ ie) = Snd ie
 

After thinking about it a bit I decided that the syntax for the two
above lines should be.

Ix (Cont2_ (ie Fst:ix)) = ix
El (Cont2_ (ie Snd:el)) = el

So that the syntax of a type assigning statement can be:
  Name type = type

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





An STL like Abstraction for Haskell

1999-05-09 Thread Kevin Atkinson

This is a multi-part message in MIME format.
--D94C6EDB5EF90419BD64FA07
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

When I asked if there was an STL like library available for Haskell the
short answer was no.  So I decided to create one.

Attached is a first draft of my attempt to come up with an abstraction. 
It currently encapsulates list and arrays.  I plan on encapsulates all
of Edison's data structures under this view once it come out.

It uses mutiparapter type classes and overlapping instances and at the
moment only compiles under "hugs -98 +o".  The main problem with GHC is
that it does not allow "type"s on partly applies types such as the
example given in the standard: "type List = []".

The module AltPrelude basically makes all of Haskell's standard list
functions methods and thus is expected to be used as the Standard
Prelude.  The rest of the modules are for the array abstraction.  The
file main.hs provides some simple examples.

Early feedback most welcome.  My intention is that something like this
will be used in Haskell 2.  If you know of a better way to do something
please tell me.

For those of you who don't know STL stands for Standard Template Library
and provided a very powerful collection of algorithms and containers for
C++.  Thrue the use of templates and iterators it provides an extremely
well thought out abstraction of many common containers and algorithms. 
An abstraction which I hope this Library will bring to Haskell.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/
--D94C6EDB5EF90419BD64FA07
Content-Type: text/plain; charset=us-ascii;
 name="AltPrelude.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="AltPrelude.hs"


module AltPrelude
 (
-- Normal prelude
Bool(False, True),
Maybe(Nothing, Just),
Either(Left, Right),
Ordering(LT, EQ, GT),
Char, String, Int, Integer, Float, Double, Rational, IO,
--  List type: []((:),]
--  Tuple types: (,), (,,), etc.
--  Trivial type: ()
--  Functions: (-)
(:),
Eq((==), (/=)),
Ord(compare, (), (=), (=), (), max, min),
Enum(succ, pred, toEnum, fromEnum, enumFrom, enumFromThen,
 enumFromTo, enumFromThenTo),
Bounded(minBound, maxBound),
Num((+), (-), (*), negate, abs, signum, fromInteger),
Real(toRational),
Integral(quot, rem, div, mod, quotRem, divMod, toInteger),
Fractional((/), recip, fromRational),
Floating(pi, exp, log, sqrt, (**), logBase, sin, cos, tan,
 asin, acos, atan, sinh, cosh, tanh, asinh, acosh, atanh),
RealFrac(properFraction, truncate, round, ceiling, floor),
RealFloat(floatRadix, floatDigits, floatRange, decodeFloat,
  encodeFloat, exponent, significand, scaleFloat, isNaN,
  isInfinite, isDenormalized, isIEEE, isNegativeZero, atan2),
Monad((=), (), return, fail),
Functor(fmap),
mapM, mapM_, sequence, sequence_, (=), 
maybe, either,
(), (||), not, otherwise,
subtract, even, odd, gcd, lcm, (^), (^^), 
fromIntegral, realToFrac, 
fst, snd, curry, uncurry, id, const, (.), flip, ($), until,
asTypeOf, error, undefined,
seq, ($!),

ReadS, ShowS,
Read(readsPrec, readList),
Show(showsPrec, showList),
reads, shows, show, read, lex,
showChar, showString, readParen, showParen,

FilePath, IOError, ioError, userError, catch,
putChar, putStr, putStrLn, print,
getChar, getLine, getContents, interact,
readFile, writeFile, appendFile, readIO, readLn,

iterate, repeat, replicate, cycle,
lines, words, unlines, unwords, 
zip, zip3, zipWith, zipWith3, unzip, unzip3,

-- redefined and new classes and functions
Name(), Size(), Empty(), Null(),
Reverse(), Map(), DMap(), 
Fold1(), Fold(), 
Concat(), ConcatL(), 
Filter(), TakeDrop(), TakeDropWhile(), 
Elem(), IndexLookup(), Lookup(), 
Ixmap(), DIxmap(), IxmapB(), DIxmapB(), Elmap(), DElmap(),
ToList(), Assocs(), Bounds(), ToRevList(),
FrontSeq(), BidirSeq(), 
FromList(), FromListB(), FromElemList(), FromElemListB(),
AccumFromList(), AccumFromListB(), Accum(),
Insert(), Replace(), Remove(), Cons(), Snoc(), 
and, or, any, all) where

import qualified Prelude
import Prelude hiding (map, foldr, foldl, foldr1, foldl1, head, tail, filter,
   length, null, take, drop, splitAt, takeWhile, 
   dropWhile, span, break, last, init, reverse, 
   elem, notElem, lookup, scanr, scanl, scanr1, scanl1,
   (!!), (++), concat, and, or, any, all)
import Ix

infixl 1 #
a # f = f a


{- 

poly. types naming convetions:

  c,d   - in/out container  
  a,b   - in/out contents of container and or single type
  e,f   - in/out elements  
  i,j   - in/out indixes
  cc,dd - in/out containers of containers

Class names in general are the name of the prinisable m

Re: More Bulk types in Context Implicit Conversions

1999-05-09 Thread Kevin Atkinson

Kevin Atkinson wrote:

 ... However, there should be some way to get the return type with out having to 
explicitly store it in the object as a bulk type.

Another solution I thought of is to be able to have auxiliary types in
class
such as

class Listable c, a where
  toList :: c - [a]  

instance Listable [a], a where
  toList a = a

which is saying only try to resolve an overload using _c_.  Once the
overload is resolved _a_ automatically has a type based on the instance
declaration.  For example:
  toList [10,20,30}
would resolve just find because c is [Int].  a will automatically have
the type Int because that is what the instance declaration says.  If the
type Int is incompatible with with what the return type needs to be then
there is a type error.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: More Bulk types in Context Implicit Conversions

1999-05-09 Thread Kevin Atkinson

"D. Tweed" wrote:
 
 On Wed, 5 May 1999, Kevin Atkinson wrote:
 
  Normally given the class.
 
  class Listable c b where
   toList :: c - [b]
 
  to list will never be able to be resolved unless the signature is given
  when toList is called because there is no way to derive the type of b
 from the function call.  However when given an instance declaration of
 
  instance Listable [a] a where
toList c = c
 
  the compiler should be able to resolve toList [1,2,3] however it
  currently doesn't.
 
 Is this inference valid since you might also have somewhere in your
 script
 
 instance Listable [Int] Char where
   toList xs = map chr xs

Obviously there are complex issues with it.  However, there should be
some way to get the return type with out having to explicitly store it
in the object as a bulk type.

In C++ you can get type information about an object by using speculation
of templates.  For example to find out the difference type of a pointer
you can use the syntax.

  iterator_traitsdouble *::diffrence_type d

And the code to make this work:

  // declares a generic template class with nothing in it
  template typename Itr
  class iterator_traits {};

  // a speculation of iterator_traits for int *
  template 
  class iterator_traitsdouble * {
typedef int diffrence_type;
  };

Now the type "double *" i no way stores the diffrence_type as part of
its definition.  Only classes can do that, and double * is a basic type
and not a class.  The line: 

  iterator_traitsdouble *::diffrence_type d

says make a new object d that is the type  diffrence_type in the class
iterator_traitsdouble *.

There out to be a way to do a similar thing in haskell.  So you can say
something like

class Listable c where
  toList :: c - [ContinentsType c]

type_class ContinentsType c

type_instance ContinentsType [c] where 
  type :: c

type_instance ContinentsType Array ix el where
  type :: (ix,el)

or something to that nature.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: More Bulk types in Context Implicit Conversions

1999-05-05 Thread Kevin Atkinson

Ok I think I found a solution to my problem however it requires a new
data type thus the is not completely transparent to the end user. 
However using implicit conversion (which to my knowledge haskell does
not have) it can be made completely transparent.

import qualified Array

data Array_ c ix el ixel = MkArray c

type Array ix el = Array_ (Array.Array ix el) ix el (ix,el)
type Array' ix el = Array_ (Array.Array ix el) ix el

class Listable c a where
  toList :: c a - [a]

class Find c a b where
  find   :: a - c (a,b) - Maybe b

instance Listable [] a where
  toList c = c

instance (Eq a, Listable c (a,b)) = Find c a b where
  find a c = lookup a (toList c)

instance Ix ix = Listable (Array' ix el) (ix,el) where
  toList (MkArray c) = Array.assocs c

instance Ix ix = Find (Array' ix el) ix el where
  find a (MkArray c) = Just ((Array.!) c a)

-- now I rename the array functions

array :: Ix ix = (ix, ix) - [(ix,el)] - Array ix el
array a b = MkArray (Array.array a b)

listArray :: Ix ix = (ix, ix) - [el] - Array ix el
listArray a b = MkArray (Array.listArray a b)

-- etc...

-- However this will not work for exiting functions that I don't know
about.
-- For these the user will have to explitly convert to and from our new
-- Array structure to the orignal one:

toNewArray :: Array.Array ix el - Array ix el
toNewArray a = MkArray a

fromNewArray :: Array ix el - Array.Array ix el
fromNewArray (MkArray a) = a

-- A better solution (in my view) would be to have an implicit
conversion
-- which could have a syntax like:
--
--implicit :: Array.Array ix el - Array ix el
--implicit a = MkArray a
--
--implicit :: Array ix el - Array.Array ix el
--implicit (MkArray a) = a
--
-- Now whenever a function is given an Array_ but is expecting 
-- an Array.Array (or vise versa) it will automatically perform the 
-- conversion function.  For example if a is an Array_
--   assocs a
-- will be interpreted as
--   assocs ((\(MkArray a) - a) a)
-- and if a is an Array.Array
--   toList a
-- will be interpreted as 
--   toList (MkArray a)
--
-- Thus the fact that toList really takes an Array_ will be completely
-- transparent to the end user
-- The renaming functions will also not be needed

So I was wondering if they any plans for bringing implicit conversions
into Haskell?

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: More Bulk types in Context Implicit Conversions

1999-05-05 Thread Kevin Atkinson

I should point out that cleaner solution is possible is the Overloaded
resolutions rules are modified a bit.

Normally given the class.

class Listable c b where
  toList :: c - [b]

to list will never be able to be resolved unless the signature is given
when toList is called because there is no way to derive the type of b
from the function call.  However when given an instance declaration of 

instance Listable [a] a where
  toList c = c

the compiler should be able to resolve toList [1,2,3] however it
currently doesn't.

So if the compiler is modified to work a little harder before reporting
an unresolved Overloaded resolution the solution could be written as:

import Array

class Listable c b where
  toList :: c - [b]

class Find c a b where
  find   :: a - c - Maybe b

instance Listable [a] a where
  toList c = c

instance (Eq a, Listable [(a,b)] (a,b)) = Find [(a,b)] a b  where
  find a c = lookup a (toList c)

instance Ix ix = Listable (Array ix el) (ix,el) where
  toList  c = assocs c

instance Ix ix = Find (Array ix el) ix el where
  find a c | inRange (bounds c) a = Just (c!a)
   | otherwise= Nothing

With out any fancy tricks.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: STL Like Library For Haskell

1999-04-29 Thread Kevin Atkinson

Bjorn Lisper wrote:
 
 There is another good reason to have a total order: it makes reduction
 operations (folds) over the structure well-defined.

But how important is having a fold well defined.  For many common
numerical operations such as summing a list, taking the product of a
list, etc. The order in which the elements get folded does not matter. 
All that matters is that each element gets represented exactly once.

 
 The main point though is that the total order exists, and is a sorting
 order separate from the Ord derivation.
 
 Then Haskell uses this to implement sets and maps by using C++ STL style
 balanced trees. As Haskell already has generic variables, just as in the
 case of lists, it needs only be implemented once.
 
 We have been working for a while on a related topic: support for generic and
 convenient collection-oriented programming over indexed structures. In order
 to achieve this, we have designed something called "data fields" which can
 be seen as arrays generalized to more arbitrary index sets than the
 "rectangular" ones given by array bounds. So we have a data type "Bounds a"
 which provide representations of sets of elements of type a, and some
 abstract set operations. Bounds be either "dense" (array-like bounds),
 "sparse" (general finite sets), or cartesian products.  Data fields are
 created from bounds in Bounds a and functions a - b.
 
 We require that there is a function enumerate :: Bounds a - [a] which
 provides a total order of the elements in any bound defining a finite
 set. This is exactly to make operations like folds well-defined for any
 finite data field regardless of the "shape" of its bound. We assume a
 predefined total order on elements of non-product data types (we require
 that these belong to the class Ix), and if a is a product data type then we
 use the lexicographical ordering on tuples. We use balanced trees to
 represent "sparse" bounds. So in some sense we seem to be quite close to
 what you ask for.

Do strings fall within the requirements?

 
 Our implementation is a somewhat rehacked version of nhc from
 Gothenburg/York. It has been "almost finished" for a while now (some minor
 things to polish) and we will make it available on the net as soon as this
 is done.
 
 Just a final comment on total orders on sets: this makes sense, as regards
 operations where the order is important for the semantics, only if the
 elements of the set are drawn from an enumerable set. It would not be very
 sensible to, for instance, try to impose a total order on a set of
 functions. A total order of the objects representing the functions would of
 course be possible and could be used to have the balanced trees, but it
 would not be possible to, say, have a well-defined fold over that kind of
 set (or any indexed structure using this set as index set).

Well that depends on how you define well defined.  For most cases simply
having a a list of functions appear in the same order through out the
execution of the program should be enough.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: STL Like Library For Haskell

1999-04-28 Thread Kevin Atkinson

Simon Peyton-Jones wrote:
 
 Chris Okasaki is working on just such a thing.
 He'll be ready soon...

Could you give me a link to a working URL?  The one off of the haskell
library page is dead and the links to the doc. and source code off of
http://www.cs.columbia.edu/~cdo/edison/ also don't work.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: STL Like Library For Haskell

1999-04-27 Thread Kevin Atkinson

Hans Aberg wrote:
 
 Has anyone done any work on comings up with an STL like collection of
 Containers and Algorithms for Haskell.
 
 In partially I would like to see the following containers:
 
 Hash map, set, and bags which behave like arrays do.
 Truly mutable hash map set and bags.
 Truly mutable arrays and references.
 Ordered map, set, and bags with efficient purely functional updates as
 well as array style updates for efficiently updating a bunch of elements
 at once.
 
 Is not mutable taboo in Haskell, which is supposed to be dogmatically pure?

I thought that is was generally accepted that using trully mutable data
structures is OK as long as it is wrapped in a monade.

 However, however experimenting with C++ STL programming with a generic
 (dynamic) variable, I found that there is an interesting implementation of
 sets and maps, which may be suitable for a language like Haskell:
 
 So one defines a global total order on the elements of all classes and
 instances, which then can be used to create maps and sets which are
 balanced trees, just as in C++ STL. This total order is normally different
 from any derivation of Ord, and is just used for sorting purposes.

How is this different.  Do you mean that some times the ordering is just
an ordering and as no meanings to humans like an alphabet order does?
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





STL Like Library For Haskell

1999-04-26 Thread Kevin Atkinson

Has anyone done any work on comings up with an STL like collection of
Containers and Algorithms for Haskell.

In partially I would like to see the following containers:

Hash map, set, and bags which behave like arrays do.
Truly mutable hash map set and bags.
Truly mutable arrays and references.
Ordered map, set, and bags with efficient purely functional updates as
well as array style updates for efficiently updating a bunch of elements
at once.

queue and deque implanted with both amortized and constant time updates.

And all of this should me implanted in a consistent fashion with a nice
class heritage.

I release that bits and pieces exist however I have not seen a nice
collection with clean abstraction.  That is one that has a heritage
similar to the heritage of the STL.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/





Re: Dynamic binding and heterogeneous lists

1999-04-24 Thread Kevin Atkinson

"Frank A. Christoph" wrote:
 
  Lennart Augustsson wrote:
  
   Kevin Atkinson wrote:
  
I am sorry for the naive question but how do you fell about adding
dynamic binding to Haskell to make it possible to have heterogeneous
lists with out having to use a nasty union type which has a number of
problems.
   
  
   What you want(?) is existential types.  Most implementations support
   this.
 
  Maybe?  What exactly are they.  I have not been able to find a good
  guide which explains the forall and exists qualifier concepts.
 
 There is a short explanation and an example or two in the GHC manual
 (section 5.7).

After reading it through several times I finally was able to get it.  It
would be nice if there was a more gentile guide.

 
  What I want to be able to do is store a bunch of objects with a common
  base class in a list.  And I also want to be able to add types to this
  heritage without having to modify a single line of the existing code.
 
 The first is trivially possible; with existential types you can put any
 object of whatever type into a list with other objects. It's not clear to me
 exactly what you mean by the second.

Don't worry about it.  Its not important.

 This is explained in slightly more detail in the GHC manual. There are also
 papers about implementing existential types in functional languages (e.g.,
 Laufer  Odersky), and these usually include motivating examples, and papers
 about using existential types to represent OO-style objects (e.g., Pierce 
 Turner). Mail me if you want a full reference.

Thanks for the explanation.  I will see if I can track the papers down.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/