RE: hGetBuf (or something related) broken for 6.2 with sockets

2003-12-23 Thread Simon Marlow
 ... I've attached a working version which you can use instead of
 System.IO.hGetBuf ...

But that version had a bug in it too (sigh).  Here's another attempt...

Cheers,
Simon


HGetBuf.hs
Description: HGetBuf.hs
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: Running a final finaliser

2003-12-23 Thread Adrian Hey
On Monday 22 Dec 2003 10:13 am, Simon Marlow wrote:
  Thanks for your reply. I'm afraid it's left me even
  more confused about which way to go with this :-(
 
  If it's possible that future Haskell FFI's don't guarantee
  that all finalisers are run then this more or less rules
  out the use of the reference counting solution (which
  wasn't particularly attractive anyway because it needs to
  be done in C AFAICS :-). If users who want this behaviour
  are required to code it themselves, it seems to require that
  they maintain a global list of all allocated ForeignPtrs.
  But doing that naively will stop them being garbage collected
  at all, unless it's possible to do something clever using weak
  pointers. Perhaps it is possible (or maybe some tricks at the
  C level could be used) but I think it's a significant extra
  burden for FFI users.

 Yes, it would have to be a global list of weak pointers to ForeignPtrs.
 This topic has come up before, though not on this list.  See this
 message, and the rest of the thread:

 http://www.haskell.org/pipermail/cvs-ghc/2003-January/016651.html

 the thread also moved on to [EMAIL PROTECTED]:

 http://www.haskell.org/pipermail/ffi/2003-January/001041.html

 and be sure to check out the paper by Hans Boehm referenced in that
 message, it's a good summary of the issues involved.

Thanks, I'll take a look at the Boehm paper. I didn't keep up with
this discussion at the time, but now I see the relevance. 

Assuming the weak pointers solution is the way to go, I've been
re-aquainting myself with System.Mem.Weak and now I'm now wondering
what is an appropriate key for each ForeignPtr.

Would it be OK to use the ForeignPtr itself as it's own key?
(Seems OK to me, but this is a bit different from the memoisation
example so I thought I'd check.)

If so, then I guess the thing to do is to maintain a mutable doubly
linked list of Weak pointers to ForeignPtrs using IORef's and have
the finaliser for each weak pointer short out the corresponding
list cell. When the program terminates execute the finalisers
of all ForeignPtrs which remain in this list.

Hmm, this is getting awfully complicated, and I still have my
doubts about it for a couple of reasons..

1- Executing ForeignPtr finalisers directly (as in Krasimirs
   example) seems to be ghc specific.
2- If there is no guarantee whether or when ForeignPtr finalisers
   are run then it seems that it is possible that a Weak pointer
   finaliser has been run (thereby deleting the weak pointer
   reference from the list), but the corresponding ForeignPtr
   finaliser has *not* been run.

The solution to problem 2 would seem to be to not associate
any finaliser with with the ForeignPtr, but do all finalisation
in the Weak pointer finaliser. I guess that would cure problem
1 too.

What do folk think about this?   

 performGC doesn't do anything that you can rely on :-)

Oh, that's handy :-)

  Also, I could you explain what you mean by a suitable
  exception handler? I don't really understand this at all.
  I'd expected I may well end up using bracket or similar,
  but I'm not sure how exception handling is relevant to
  this problem.

 Start your program something like this:

   import Control.Exception (finally)

   main = my_main `finally` clean_up
   my_main = ... put your program here ...
   clean_up = ... all the cleanup code goes here ...

 You can additionally use finalizers to perform incremental cleanup
 during program execution, but the right way to clean up at the end is to
 use an exception handler as above.

Ah OK, I was hoping the whole thing would be something as simple
as this..

withLibXYX :: IO () - IO ()
withLibXYZ doit = finally (initialiseLibXYZ  doit)
  (performGC  shutdownLibXYZ)

Where initialiseLibXYZ and shutdownLibXYZ are simple foreign functions
imported from libXYZ. I think it's a real shame performGC or some other
similar function can't simply guarantee that all (garbage) ForeignPtr
finalisers have been run before calling shutdownLibXYZ :-(

Regards
--
Adrian Hey




___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Running a final finaliser

2003-12-23 Thread Adrian Hey
On Monday 22 Dec 2003 8:53 pm, Carl Witty wrote:
Thanks for your reply. I'm afraid it's left me even
  
   more confused about which way to go with this :-(

 Is your problem something you could handle with a C atexit() handler?

That's a good idea. With ghc I guess this will work, assuming..
1- ghc rts runs all ForeignPtr finalisers before it shutsdown.
2- ghc rts is shutdown before atexit handlers are executed. 

I both think 1  2 are true with ghc at present, but Simon M.
indicated that 1 might not be true in future for ghc (or other
Haskell implementations). That said, the current FFI spec
states at bottom of p.14..

There is no guarantee on how soon the finalizer is executed
after the last reference to the associated foreign pointer
was dropped; this depends on the details of the Haskell storeage
manager. The only guarantee is that the finalizer runs before
the program terminates.

So I'm still confused :-)

Actually, though I think it would work for me, it's probably
not as general as some folk might want (they might want to
shutdown the library and free up whatever resources it claimed
earlier in program execution, not just at exit).

Regards
--
Adrian Hey


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Running a final finaliser

2003-12-23 Thread Simon Marlow
 Assuming the weak pointers solution is the way to go, I've been
 re-aquainting myself with System.Mem.Weak and now I'm now wondering
 what is an appropriate key for each ForeignPtr.

Before we go down that route, I want to be sure that it's actually
necessary to use weak pointers.  It sounds like your application has the
following properties:

  - there is a library that can allocate some resources, where
each resource is represented by a ForeignPtr

  - a resource needs to be released when it is no longer referenced

  - at some point, we would like to free *all* outstanding resources
(either at the end of the program, or when the library is no
longer required).

If this is the case, I'd do it something like this:

  - keep a global list of the pointers still to be released, probably
a doubly-linked list.  Lock the whole thing with an MVar.  Elements
are Ptrs, not ForeignPtrs.

  - the finaliser on each ForeignPtr removes the corresponding Ptr from
the list.

  - the final cleanup routine explicitly releases all the remaining
Ptrs in the list, holding the MVar lock as it does so to avoid
race conditions with finalisers.

Weak pointers aren't required, AFAICT.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Running a final finaliser

2003-12-23 Thread Adrian Hey
Hello

On Tuesday 23 Dec 2003 9:27 am, Simon Marlow wrote:
  Assuming the weak pointers solution is the way to go, I've been
  re-aquainting myself with System.Mem.Weak and now I'm now wondering
  what is an appropriate key for each ForeignPtr.

 Before we go down that route, I want to be sure that it's actually
 necessary to use weak pointers.  It sounds like your application has the
 following properties:

   - there is a library that can allocate some resources, where
 each resource is represented by a ForeignPtr

Basically, but there are also some hardware resources (other than memory)
which are claimed just as a result of library initialisation (before any
library objects have been created).

   - a resource needs to be released when it is no longer referenced

Yes, that's right.

   - at some point, we would like to free *all* outstanding resources
 (either at the end of the program, or when the library is no
 longer required).

I want to free all heap space used by library objects, then free whatever
other hardware resources have been claimed by the library (by calling
the appropriate shutdown routine).

 If this is the case, I'd do it something like this:

   - keep a global list of the pointers still to be released, probably
 a doubly-linked list.  Lock the whole thing with an MVar.  Elements
 are Ptrs, not ForeignPtrs.

   - the finaliser on each ForeignPtr removes the corresponding Ptr from
 the list.

   - the final cleanup routine explicitly releases all the remaining
 Ptrs in the list, holding the MVar lock as it does so to avoid
 race conditions with finalisers.

 Weak pointers aren't required, AFAICT.

Maybe, I'd forgotten that I could get at the Ptr inside each ForeignPtr.
I guess I've still got to think about the consequences of ForeignPtr
finalisers being run after the final shutdown. (Making each
List cell an IORef (Maybe something) would do that I think).

The other complication I can see is that ForeignPtr finalisers can't
be Haskell. So I have to call the Haskell finalisation from C.
Is that safe? I'm afraid I still don't fully understand why Haskell
finalisers are unsafe or why (if) calling Haskell from a C finaliser
(which then called C land again) would be any safer. 

Thanks for the idea though. I'll play about with a few implementations
of these ideas after christmas and see what problems I encounter.

Regards
--
Adrian Hey

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Perspectives on learning and using Haskell

2003-12-23 Thread Graham Klyne
I've spent part of the past few months learning Haskell and developing a 
moderately sized application.  I came to this from a long background (20 
years or so) of conventional programming in a variety of languages (from 
Fortran and Algol W to Java and Python).  For me, learning Haskell has been 
one of the steepest learning curves of any new language that I have ever 
learned.  Before this project, I was aware of some aspects of functional 
programming, but had never previously done any in anger (i.e. for real).

Throughout this period, I've been accumulating some notes about some things 
that I found challenging along the way.  The notes are not organized in any 
way, and they're certainly not complete.  I've published them on my web 
site [1] in case the perspective might be useful to any old hands here.

[1] http://www.ninebynine.org/Software/Learning-Haskell-Notes.html

...

Also on the topic of perspectives:

In recent conversation with a colleague, he mentioned to me that the term 
functional programming has an image problem.  He suggested that the term 
conveys an impression of an approach that is staid, non-progressive or 
lacking novelty, and is prone to elicit a response of been there, done 
that from programmers who don't realize the full significance of the term 
functional.  I've also noticed that when I talk about functional 
programming, some people tend to think I'm talking about using techniques 
like functions in C or Pascal (which is course is very desirable, but old 
hat and not worthy of great excitement).

#g


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Perspectives on learning and using Haskell

2003-12-23 Thread Tomasz Zielonka
On Tue, Dec 23, 2003 at 05:26:20PM +, Graham Klyne wrote:
 Throughout this period, I've been accumulating some notes about some things 
 that I found challenging along the way.  The notes are not organized in any 
 way, and they're certainly not complete.  I've published them on my web 
 site [1] in case the perspective might be useful to any old hands here.
 
 [1] http://www.ninebynine.org/Software/Learning-Haskell-Notes.html

Thanks, that was a nice reading :)

I have some comments:

8. Your explanation of Functor excludes many useful Functors which are
   rather not collections. For example, every monad (like IO) can
   be a Functor if you take fmap = Monad.liftM. 
   
   For [] and Maybe this would give the same operation as in their
   normal instances.

11 and 18.
   If you define an instance of Monad for ((-) e) then

  return (putStrLn Hello!) 'x'

   is a proper IO () value. Probably still not sensible ;)

   Special treatment of 'return' could be helpful, but I am afraid that
   it could also make it look special, like a return keyword in C.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Haskell naming conventions

2003-12-23 Thread Sean L. Palmer



It occurs to me that Haskell would be quite a bit 
easier for OO and traditional programmers to grasp if Haskell would actually use 
the correct, or at least more commonly used, names for things.

For instance, 

data Maybe a = Nothing | Just 
a
Maybe is a type 
constructor and Nothing and Just are data constructors.

So it makes me wonder why the use of the datakeyword... wouldn't it make 
more sense to say:

type Maybe a = Nothing | Just 
a

? Either that or perhaps change the 
descriptions "type constructor" and "data constructor" to something that fits 
with the keywords used. 

Likewise with class, type class, and instance:

class Eq a where
  (==) :: a 
- a - Bool

That actually declares a type class, not a 
class. So why the use of the keyword class? Is it done merely to 
confuse C++ and Java programmers? The concept of type class in Haskell 
apparently roughly corresponds to the concept of "interface" in Java. So 
why not call it interface? 

Instance is also 
confusing:

instance EqInteger where  a 
== b = a `integerEq` b

That actually declares that Integer is a type, not 
an "instance" in the traditional use of the word. A C++ programmer would 
probably use the word "subclass" instead of "instance".

Then consider how different a meaning "return" has 
in Haskell than it does in C. ;)

Does anyone else think this is a problem? If 
so, is it fixable?

I guess from reading the many tutorials and FAQ's, 
that I'm in the same boat as everybody else. I consider myself a pretty 
bright boy, I've learned all kinds of other programming languages, from asm to 
forth to basic, pascal, C, C++, java, and C#... but this Haskell business, 
has me almost stumped. I mean, I understand the basic ideas pretty easily 
enough, but there seems to be such syntactical wierdness that to understand how 
to program in Haskell above the level of toy programs requires one to revisit 
every single design decision that went into making the language and its 
libraries, and grasp everything along the way, not only its function but also 
its peculiar nomenclature, and usually two different ways to say the same thing 
(maybe more). Only after following this long tortuous path will one ever 
be able to actually write useful programs. 

If Haskell (or any language of this style) is ever 
to gain a larger following, it would probably be wise to accomodate the existing 
programmer knowledge base a little more. I believe that the same core 
language, with cleaner design, different keywords, maybe different operators, 
would probably be readily accepted. 

There are many things that contribute to making 
Haskell less approachable, the above is just one.

I wonder if there are any tutorials out there that 
provide a 1:1 mapping of concepts and idioms from other common languages into 
Haskell; small snippets of examples of pure translations would make things 
easier to grasp for some people than any amount of longwinded explanation. 
Probably there are easier ways to do the same things in Haskell, but it would be 
useful for beginners to get aunedited translation, even if that means 
heavy use of do-notation. At least people could then start writing 
imperative style Haskell programs immediately, and yeah that's not good style, 
but you can't learn good style if you can't accomplish anything and are stuck at 
square one.

Frustratedly,
Sean

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


Re: Haskell naming conventions

2003-12-23 Thread Marc A. Ziegert
to all: excuse my bad english.
to javas: excuse my extreme opinions. - regard me as s.o. of an other... religion.
to newbies: read it.
to haskellers: you don't need to.

johi, Sean.

i remember that i've had the same problems with haskell, at the beginning.
you are right, that there should be a special introduction just for 
imperative-programmers.
but you are wrong, not haskell has to change sth. - the other languages have to do it, 
if anyone at all. but if the others are imperative languages, like all those you 
learned before, the change would imply to nullify their existence. ;)

 asm to forth to basic, pascal, C, C++, java, and C#...
i've learned the following:
MS-DOS-3.3/5.0 .bat files
QBASIC
QUICKBASIC
turbo-pascal + intel-asm
delphi
vc++ (while my university was/is_still teaching java like bill gates foists windows)
aversed look at java - whatabullshit!!! (all the extremest down running prejudices 
-not knowing the language- seem to fit -especially after having learned the language-. 
the power of half-oop, easy to learn like risc-asm, with the speed of basic, and the 
no-compiletime-but-runtime-typechecking of cLisp or Tcl. but as a psychology student 
i'm fascinated about those obvious marketing-tricks, making s.o. believe in java.)
cLisp
haskell
little bit prolog
vc++
haskell
vc++stl
linux :) :) :) :)
Tcl/Tk
haskell
c++stl
math (!!!best!!! - but not a computer language)
...

so i know those cut and dried opinions one has by learning new languages.
i've learned that there are at least two types of languages: the lower (-asm) and the 
higher (-math) ones.
in c++ the difference between struct and class is that its default is public or 
private. that has nearly nothing to do with classes - except oop.
if you have data somewhere in memory, you call it an instance of a (struct- or 
class- or whatever-) type.
in math you have types, sets, elements, classes, instances, ... (but not interface - 
don't think in java. a human-machine interface like monitor+keyboard+mouse is an 
interface, too. to define an interface does mean to use a pattern, not an special 
abstract-only--no-variable--no-default-functionimplementation--java-class to simulate 
cumbersomely multi-inheritance.)
the language haskell is an attempt to implement math as computer language. (Haskell 
Brooks Curry was a genius who invented the banal function we call curry.)
any function has a type; the data in your memory has a type; combinations of functions 
and data_structures_in_memory have types.
but a function is not a variable piece of memory - it depends on its definition, like 
a constant.
the types of data structures, which are instanciated in memory, are defined with 
that data keyword in haskell.

all types - functions too - are instances of classes; means: types are 
elements(instances) in special sets(classes), for which some individual attributes (in 
haskell: individual function-implementations) are defined.
try to proof this view in haskell and c++. you will see, that the sense of oop-classes 
is not the definition of types but the unification of inherited types.


some examples in c++ (didn't try to compile it):

templatetypename a
class Eq
{
protected:
Eq(){} // This constructor exists just to be protected.
public:
virtual bool operator ==( const a r ) const {return !( (*this) != r );}
virtual bool operator !=( const a r ) const {return !( (*this) == r );}
};

templatetypename a
struct Maybe : public virtual EqMaybea 
{
enum Constructor_t {Nothing, Just};
union{
struct{
Constructor constructor_;
};
struct{
Constructor constructorNothing;
};
struct{
Constructor constructorJust;
const a *data;
};
};

Maybe() { constructorNothing = Nothing; }
Maybe(const a d) { constructorJust = Just; data = new a(d); }
Maybe(const Maybe m) { constructor_ = m.constructor_; 
if(m.constructorJust==Just) data = new a(*m.data); }
~Maybe() { if( constructorJust == Just ) delete data; }

virtual bool operator ==( const Maybe r ) const
{
switch( constructor_ )
{
case Nothing:
return (r.constructorNothing==Nothing);
case Just:
return (r.constructorJust !=Just) ? (false) : 
(*data==*r.data);
}
throw undefined;
}
};


// functionname :: (Eq a) = a - returntype
templatetypename a
inline returntype functionname( const a param )
{
static_castconst Eqa*(param); // ignore result of casting, but test 
wether...  param is instance / a (TYPE of param) is instance ...of Eq class.
...
}



merry xmas,
- marc





Am Mittwoch, 24. Dezember 2003 02:29 schrieb Sean L. Palmer:
 It occurs to 

Re: Perspectives on learning and using Haskell

2003-12-23 Thread Marc A. Ziegert
 In recent conversation with a colleague, he mentioned to me that the term 
 functional programming has an image problem.  He suggested that the term 

short komment:
meta programming and meta-language makes people curious, functional programming 
seems to have the opposite effect.

merry xmas
- marc

Am Dienstag, 23. Dezember 2003 18:26 schrieb Graham Klyne:
 I've spent part of the past few months learning Haskell and developing a 
 moderately sized application.  I came to this from a long background (20 
 years or so) of conventional programming in a variety of languages (from 
 Fortran and Algol W to Java and Python).  For me, learning Haskell has been 
 one of the steepest learning curves of any new language that I have ever 
 learned.  Before this project, I was aware of some aspects of functional 
 programming, but had never previously done any in anger (i.e. for real).
 
 Throughout this period, I've been accumulating some notes about some things 
 that I found challenging along the way.  The notes are not organized in any 
 way, and they're certainly not complete.  I've published them on my web 
 site [1] in case the perspective might be useful to any old hands here.
 
 [1] http://www.ninebynine.org/Software/Learning-Haskell-Notes.html
 
 ...
 
 Also on the topic of perspectives:
 
 In recent conversation with a colleague, he mentioned to me that the term 
 functional programming has an image problem.  He suggested that the term 
 conveys an impression of an approach that is staid, non-progressive or 
 lacking novelty, and is prone to elicit a response of been there, done 
 that from programmers who don't realize the full significance of the term 
 functional.  I've also noticed that when I talk about functional 
 programming, some people tend to think I'm talking about using techniques 
 like functions in C or Pascal (which is course is very desirable, but old 
 hat and not worthy of great excitement).
 
 #g
 
 
 
 Graham Klyne
 For email:
 http://www.ninebynine.org/#Contact
 
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
 
 

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


Re: Perspectives on learning and using Haskell

2003-12-23 Thread Derek Elkins
On Tue, 23 Dec 2003 17:26:20 +
Graham Klyne [EMAIL PROTECTED] wrote:

(moved to Haskell-Cafe as this reply might generate several more)

 I've spent part of the past few months learning Haskell and developing
 a moderately sized application.  I came to this from a long background
 (20 years or so) of conventional programming in a variety of
 languages (from Fortran and Algol W to Java and Python).  For me,
 learning Haskell has been one of the steepest learning curves of any
 new language that I have ever learned.  Before this project, I was
 aware of some aspects of functional programming, but had never
 previously done any in anger (i.e. for real).

Well, the obvious question is: after climbing partway up that curve,
what do you think of the view?  Was it worth learning?  Is it worth
continuing to use?  Does the code seem 'better' than what you might
produce in other languages you've used?
 
 Throughout this period, I've been accumulating some notes about some
 things that I found challenging along the way.  The notes are not
 organized in any way, and they're certainly not complete.  I've
 published them on my web site [1] in case the perspective might be
 useful to any old hands here.
 
 [1] http://www.ninebynine.org/Software/Learning-Haskell-Notes.html

When I saw this page earlier, I was thinking about suggesting to you to
add it and any new thoughts to the wiki so that it's more readily
accessible to other Haskell newbies and can be annotated with pointers
to resources and comments; kind of like an annotated unidirectional
version of A Newbie's on-going tutorial on the Squeak wiki
(http://minnow.cc.gatech.edu/squeak/1928). 

 Also on the topic of perspectives:
 
 In recent conversation with a colleague, he mentioned to me that the
 term functional programming has an image problem.  He suggested that
 the term conveys an impression of an approach that is staid,
 non-progressive or lacking novelty, and is prone to elicit a response
 of been there, done that from programmers who don't realize the full
 significance of the term functional.  I've also noticed that when I
 talk about functional programming, some people tend to think I'm
 talking about using techniques like functions in C or Pascal (which is
 course is very desirable, but old hat and not worthy of great
 excitement).

Yes.  People often use the term 'procedural' to describe the C style
break down of a problem.  Of course, some people use procedural to refer
to functional and others functional to refer to procedural.  Then, of
course, there are also dynamic typers who equate static typing with
C/Pascal.  On the OO side, there are the people who equate OO with
C++/Java much to the chagrin of Smalltalkers and CLOS users.  At any
rate, functional programming is a pretty well established term so there
isn't much Haskell can do about it.  Perhaps throwing in 'higher-order'
will help, and certainly laziness/purity can't be said to be lacking
novelty.

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