RE: Type-checker bug related to implicit parameters.

2001-09-20 Thread Simon Peyton-Jones

GHC 5.02 works fine for this program.  We're going to release it this
week.

Thanks for the test -- I've added it to our test suite!

Simon

| -Original Message-
| From: John Hughes [mailto:[EMAIL PROTECTED]] 
| Sent: 19 September 2001 18:00
| To: [EMAIL PROTECTED]
| Subject: Type-checker bug related to implicit parameters.
| 
| 
| 
| Hugs -98 (Feb 2001) rejects the following program (which 
| should be well-typed)
| 
|  foo :: ((?x :: Int) = b) - Int - b
|  foo s z = s with ?x = z
| 
| with the message
| 
| ERROR Bug.hs:2 - Inferred type is not general enough
| *** Expression: foo
| *** Expected type : ((?x :: Int) = a) - Int - a
| *** Inferred type : ((?x :: Int) = a) - Int - Int
| 
| It seems to unify the type of the implicit parameter with the 
| type of the result.
| 
| GHC accepts this program (but generates wrong code).
| 
| John Hughes
| 
| ___
| Hugs-Bugs mailing list
| [EMAIL PROTECTED] 
| http://www.haskell.org/mailman/listinfo/hugs-bugs
| 

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



Re: Ptr and ForeignPtr Questions

2001-09-20 Thread Manuel M. T. Chakravarty

Ashley Yakeley [EMAIL PROTECTED] wrote,

 The documentation for FFI in the GHC user's guide seems to be out of date 
 with regard to passing Ptrs across.
 
 1. My reference is 
 http://www.haskell.org/ghc/docs/latest/set/ffi.html
 (from http://www.haskell.org/ghc/docs/latest/set/book-users-guide.html)
 Is this the latest documentation available?
 
 2. My understanding is that you can use any instance of 'Storable a = 
 Ptr a' as an FFI argument and return type for both imported and exported 
 functions? Is this correct? 

If I understand you question correctly and you want to pass
a pointer to C land and back, yes, this is possible.

 What if the type is polymorphic (e.g. 
 declared as 'Storable a = Ptr a' rather than something like 'Ptr Word8')?

Also possible, as the argument to `Ptr' is just dummy.

 3. What about ForeignPtr? Can instances of 'Storable a = ForeignPtr a' 
 be used in FFI?

They can be passed to C, but you can't get them back.  (The
storange manager wouldn't know what finaliser to attach.)

 4. Does newForeignPtr work safely with null pointers, and will the 
 finalizer get called? For instance:
 
  fp - newForeignPtr nullPtr finalFunc;
  let {isNull = (foreignPtrToPtr fp) == nullPtr};
  r - withForeign fp (\p - foo p);
 
 Will foo be passed nullPtr? Will finalFunc ever get called? Is my use, 
 above, of foreignPtrToPtr safe, and will isNull be True?

Should work.  From the storage managers point of view, a
`Ptr' is just an uninterpreted bit-pattern.  A glorified
`Int'.  Of course, you should better make sure that
`finalFunc' can handle getting a `nullPtr'.

Cheers,
Manuel


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



RE: Ptr and ForeignPtr Questions

2001-09-20 Thread Simon Marlow

 Ashley Yakeley [EMAIL PROTECTED] wrote,
 
  The documentation for FFI in the GHC user's guide seems to 
 be out of date 
  with regard to passing Ptrs across.
  
  1. My reference is 
  http://www.haskell.org/ghc/docs/latest/set/ffi.html
  (from 
 http://www.haskell.org/ghc/docs/latest/set/book-users-guide.html)
  Is this the latest documentation available?
  
  2. My understanding is that you can use any instance of 
 'Storable a = 
  Ptr a' as an FFI argument and return type for both imported 
 and exported 
  functions? Is this correct? 
 
 If I understand you question correctly and you want to pass
 a pointer to C land and back, yes, this is possible.

I'll just add that the docs have been updated for 5.02, and the FFI
section now refers to Ptr and ForeignPtr instead of Addr and ForeignObj.

  4. Does newForeignPtr work safely with null pointers, and will the 
  finalizer get called? For instance:
  
   fp - newForeignPtr nullPtr finalFunc;
   let {isNull = (foreignPtrToPtr fp) == nullPtr};
   r - withForeign fp (\p - foo p);
  
  Will foo be passed nullPtr? Will finalFunc ever get called? 
 Is my use, 
  above, of foreignPtrToPtr safe, and will isNull be True?
 
 Should work.  From the storage managers point of view, a
 `Ptr' is just an uninterpreted bit-pattern.  A glorified
 `Int'.  Of course, you should better make sure that
 `finalFunc' can handle getting a `nullPtr'.

And don't forget that using foreignPtrToPtr is quite dangerous; much
better to use withForeignPtr instead, otherwise you might find the
ForeignPtr being finalised earlier than you expect.

Cheers,
Simon

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



Re: Ptr and ForeignPtr Questions

2001-09-20 Thread Ashley Yakeley

At 2001-09-19 23:45, Manuel M. T. Chakravarty wrote:

 What if the type is polymorphic (e.g. 
 declared as 'Storable a = Ptr a' rather than something like 'Ptr Word8')?

Also possible, as the argument to `Ptr' is just dummy.

What? What about 'withObject'? A Haskell 'Ptr a' is a C array-pointer of 
whatever corresponds to 'a'. I don't think the argument is dummy.

Consider this:

 int foo (char selector,char* arg)
  {
  if (selector == 100)
   return reinterpret_castunsigned char*(arg)[1];
  if (selector == 200)
   return reinterpret_castunsigned short*(arg)[1];
  return 0;
  }

 foreign import foo foo :: Storable a = Word8 - Ptr a - IO Int32;
 
 a - withObject ([1,2] :: [Word8]) (foo 100);
 b - withObject ([3,4] :: [Word16]) (foo 200);

Will this work as expected? I expect 'a' to be 2 and 'b' to be 4...

 3. What about ForeignPtr? Can instances of 'Storable a = ForeignPtr a' 
 be used in FFI?

They can be passed to C, but you can't get them back.  (The
storange manager wouldn't know what finaliser to attach.)

OK. Are ForeignPtrs intelligible in the C function as pointers to the 
named type?

 4. Does newForeignPtr work safely with null pointers, and will the 
 finalizer get called? For instance:
 
  fp - newForeignPtr nullPtr finalFunc;
  let {isNull = (foreignPtrToPtr fp) == nullPtr};
  r - withForeign fp (\p - foo p);
 
 Will foo be passed nullPtr? Will finalFunc ever get called? Is my use, 
 above, of foreignPtrToPtr safe, and will isNull be True?

Should work.  From the storage managers point of view, a
`Ptr' is just an uninterpreted bit-pattern.  A glorified
`Int'. 

So you are saying that the ForeignPtr code is not interested in the 
pointer-ness of the Ptr contents of a ForeignPtr, except when a 
ForeignPtr is used as an FFI argument?

Presumably this also means that one can create two separate ForeignPtrs 
around the same Ptr, each with their own finaliser set. Presumably they 
would not be equal (note that Eq (ForeignPtr a)). Is this correct?

Also, I assume that a ForeignPtr is eligible for garbage collection 
whenever it is no longer 'reachable', even if the Ptr it contains is 
reachable. Is that correct?

Is there anything resembling Java's 'soft' and 'weak references'?

 Of course, you should better make sure that
`finalFunc' can handle getting a `nullPtr'.

Of course...

-- 
Ashley Yakeley, Seattle WA


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



RE: Ptr and ForeignPtr Questions

2001-09-20 Thread Ashley Yakeley

At 2001-09-20 02:14, Simon Marlow wrote:

I'll just add that the docs have been updated for 5.02,

Do you have a URL for that?

And don't forget that using foreignPtrToPtr is quite dangerous; much
better to use withForeignPtr instead, otherwise you might find the
ForeignPtr being finalised earlier than you expect.

This is because foreignPtrToPtr is not in the IO monad, correct?

 foreignPtrToPtr :: ForeignPtr a - Ptr a;

A function like this:

 ioForeignPtrToPtr :: ForeignPtr a - IO (Ptr a);
 ioForeignPtrToPtr fp = withForeignPtr fp return;

...would surely be safe? The 5.00 documentation claims that it isn't, 
however, but I don't see why.

-- 
Ashley Yakeley, Seattle WA


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



Re: Ptr and ForeignPtr Questions

2001-09-20 Thread Ashley Yakeley

At 2001-09-20 02:31, I wrote:

int foo (char selector,char* arg)
...
  if (selector == 200)

I guess that should be

int foo (unsigned char selector,char* arg)


-- 
Ashley Yakeley, Seattle WA


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



RE: Ptr and ForeignPtr Questions

2001-09-20 Thread Simon Marlow

 At 2001-09-20 02:14, Simon Marlow wrote:
 
 I'll just add that the docs have been updated for 5.02,
 
 Do you have a URL for that?

Not yet, but the release is imminent (really!) so it'll be up on the web
site shortly.

 And don't forget that using foreignPtrToPtr is quite dangerous; much
 better to use withForeignPtr instead, otherwise you might find the
 ForeignPtr being finalised earlier than you expect.
 
 This is because foreignPtrToPtr is not in the IO monad, correct?
 
  foreignPtrToPtr :: ForeignPtr a - Ptr a;
 
 A function like this:
 
  ioForeignPtrToPtr :: ForeignPtr a - IO (Ptr a);
  ioForeignPtrToPtr fp = withForeignPtr fp return;
 
 ...would surely be safe? The 5.00 documentation claims that it isn't, 
 however, but I don't see why.

No, it's not safe.  The reason is that the compiler can track a
ForeignPtr to discover when it dies, in order to run the finalizer, but
it can't track a Ptr.  As soon as you drop all references to the
ForeignPtr then the finalizer will run, even if you converted it to a
Ptr and you're still using it.

withForeignPtr is safe to use because it ensures that the ForeignPtr is
kept live until it returns.  The documentation is a little terse on this
issue; I'll see if I can improve it.

Cheers,
Simon


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



RE: Ptr and ForeignPtr Questions

2001-09-20 Thread Ashley Yakeley

At 2001-09-20 02:46, Simon Marlow wrote:

No, it's not safe.  The reason is that the compiler can track a
ForeignPtr to discover when it dies, in order to run the finalizer, but
it can't track a Ptr.  As soon as you drop all references to the
ForeignPtr then the finalizer will run, even if you converted it to a
Ptr and you're still using it.

OK, there are different types of safety. The risk here is that the 
finalisers may have been called by the time you use the Ptr. But if you 
don't mind that, for instance, if for some reason the finalisers don't 
render the Ptr invalid, I assume you can still use the Ptr.

-- 
Ashley Yakeley, Seattle WA


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



Alternative Design for Finalisation

2001-09-20 Thread Ashley Yakeley

If ForeignPtrs work the way I think they do, then I'm surprised they're 
designed as pointers. I believe the 'pointer' functionality is orthogonal 
to the 'finalisable' functionality and should be separated like this:

--
data Finalisable a  -- abstract handle to finalisable object
instance Eq (Finalisable a);
newFinalisable  :: a - IO () - IO (Finalisable a);
addFinaliser:: Finalisable a - IO () - IO (); 
withFinalisable :: Finalisable a - (a - IO b) - IO b;
touchFinalisable:: Finalisable a - IO ();
finalisableContents :: Finalisable a - a;

type ForeignPtr a = Finalisable (Ptr a);
newForeignPtr  :: Ptr a- IO () - IO (ForeignPtr a);
newForeignPtr = newFinalisable;
addForeignPtrFinalizer :: ForeignPtr a - IO () - IO () ;
addForeignPtrFinalizer = addFinaliser;
withForeignPtr :: ForeignPtr a - (Ptr a - IO b) - IO b;
withForeignPtr = withFinalisable;
touchForeignPtr:: ForeignPtr a - IO ();
touchForeignPtr = touchFinalisable;
foreignPtrToPtr:: ForeignPtr a - Ptr a;
foreignPtrToPtr = finalisableContents;
--

I am slightly bothered by the type of 
finalisableContents/foreignPtrToPtr. Shouldn't it be in the IO monad? 
Apart from 'finalisers already run' risk, is it safe?

But 'castForeignPtr' would not be definable, unless you wanted to do 
something like this:

--
instance Functor Finalisable;
castForeignPtr  :: ForeignPtr a - ForeignPtr b;
castForeignPtr = fmap castPtr;
--

...which I don't believe is appropriate.

The only time when ForeignPtrs act like Ptrs is when they are used as FFI 
arguments. But I believe that's purely syntactic sugar for 
withForeignPtr, and would be no loss.

--
foreign import foo fooFP :: ForeignPtr a - IO ();
foreign import foo fooP  :: Ptr a - IO ();

fooFP' :: ForeignPtr a - IO ();
fooFP' fp = withForeignPtr fp fooP;
--


-- 
Ashley Yakeley, Seattle WA


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



Re: Ptr and ForeignPtr Questions

2001-09-20 Thread Ashley Yakeley

At 2001-09-20 06:55, Manuel M. T. Chakravarty wrote:

The FFI does not ensure any type consistency between the
arguments to `Ptr'/`ForeignPtr' and the corresponding C
types.

I've been using 'Ptr Word8' with newArray to pass lists of bytes to C 
functions. They appear as unsigned char arrays in the C function. Is this 
wrong, or not guaranteed?

-- 
Ashley Yakeley, Seattle WA


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



Re: Ptr and ForeignPtr Questions

2001-09-20 Thread Manuel M. T. Chakravarty

Ashley Yakeley [EMAIL PROTECTED] wrote,

 At 2001-09-20 06:55, Manuel M. T. Chakravarty wrote:
 
 The FFI does not ensure any type consistency between the
 arguments to `Ptr'/`ForeignPtr' and the corresponding C
 types.
 
 I've been using 'Ptr Word8' with newArray to pass lists of bytes to C 
 functions. They appear as unsigned char arrays in the C function. Is this 
 wrong, or not guaranteed?

It is guaranteed that when you marshal a `[Word8]' into a
`Ptr Word8' with newArray that you get a contiguous memory
area filled with the bytes from the list.  So, what you are
doing is perfectly fine.  

What I meant with the remark that you quote is that if you
would use

  foreign import foo :: Ptr Int - IO Float

with

  float foo (float *x)
  {
return *x;
  }

the system will not complain, but your program may dump
core.

Manuel

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



Re: Ptr and ForeignPtr Questions

2001-09-20 Thread Ashley Yakeley

At 2001-09-20 19:32, Manuel M. T. Chakravarty wrote:

What I meant with the remark that you quote is that if you
would use

  foreign import foo :: Ptr Int - IO Float

with

  float foo (float *x)
  {
return *x;
  }

the system will not complain, but your program may dump
core.

What if the C looked like this:

  float foo (int *x)
  {
return *x;
  }

...?

-- 
Ashley Yakeley, Seattle WA


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



Re: Student Programming Projects

2001-09-20 Thread Albert Lai

Consider goal-directed theorem prover (or proof checker).  Two existing
samples are in Lawrence Paulson's ML for the Working Programmer, and
yours truly's http://www.cs.utoronto.ca/~trebla/fp/prover/index.html

The advantage of mine is it illustrates monads.  The advantage of Paulson's
is it doesn't scare people with monads :) and it includes a substitution
library (yet another monad, but shhh) for use in first-order logic.

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



RE: Prelude and (:) and []((:), []) bugs?

2001-09-20 Thread Simon Marlow


 As far as I can tell, the report doesn't allow (:) or []((:), 
 []) in the
 export list, yet the hugs prelude has the first and the GHC 
 prelude has
 the second. Have I missed something that allows them or is 
 this a bug in
 the preludes or the report?

(:) is allowed in an export list; it is just a normal operator.  

GHC has a couple of extensions to export lists: we allow gcon instead of
just qcon, and gtycon instead of qtycon.  These are quite natural
extensions, and just reduce the amount of built-in compiler magic needed
to express the Prelude.

Cheers,
Simon

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



Re: Prelude and (:) and []((:), []) bugs?

2001-09-20 Thread Ian Lynagh

On Thu, Sep 20, 2001 at 01:32:54PM +0100, Simon Marlow wrote:
 
  As far as I can tell, the report doesn't allow (:) or []((:), 
  []) in the
  export list, yet the hugs prelude has the first and the GHC 
  prelude has
  the second. Have I missed something that allows them or is 
  this a bug in
  the preludes or the report?
 
 (:) is allowed in an export list; it is just a normal operator.  

An export is

export - qvar
   |  qtycon [(..) | ( qcname1 , ... , qcnamen )] (n=0)
   |  qtycls [(..) | ( qvar1 , ... , qvarn )] (n=0)
   |  module modid

and we need to match (:). We can clearly reduce this to

export - qvar | qtycon | qtycls

Now apply qvar - qvarid | ( qvarsym )
  qtycon - [ modid . ] tycon
  qtycls - [ modid . ] tycls

export - qvarid | ( qvarsym ) | [modid .] tycon | [modid .] tycls

Apply qvarid - [ modid . ] varid
  qvarsym - [ modid . ] varsym

export - [ modid . ] varid | ( [ modid . ] varsym )
   |  [ modid . ] tycon | [ modid . ] tycls

As there is no . we can reduce this to

export - varid | ( varsym ) | tycon | tycls

Now
varid - (small {small | large | digit | ' })reservedid
and ( is not in small, so we can eliminate that.

tycon - conid, tycls - conid and
conid - large {small | large | digit | ' }
( is also not in large, so we can eliminate that.

Therefore we need to match : with varsym. But
varsym - ( symbol {symbol | :})reservedop
and
reservedop - .. | : | :: | = | \ | | | - | - | @ | ~ | =

Did I screw up somewhere?

 GHC has a couple of extensions to export lists: we allow gcon instead of
 just qcon, and gtycon instead of qtycon.  These are quite natural
 extensions, and just reduce the amount of built-in compiler magic needed
 to express the Prelude.

I think it would be nice if the prelude was valid Haskell 98 - if these
extensions are useful and natural, and as I can't see how they could
break existing code, could they be put into the revised report?


Thanks
Ian


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



Re: Haskell Communities Survey - Call for Contacts

2001-09-20 Thread Ketil Malde


...or how about a web zine along the lines of (the Linux) Kernel Notes
and cousins (http://kt.zork.net/)?  This is just a (couple of?) guy(s)
closely following the kernel mailing list, and summarizing, quoting
interesting mail, providing links where appropriate and so on.

Immensely useful for those of us who can't follow the tons of messages
on the Linux kernel mailing list, but who still likes to know what's
going on.  I believe the systems allows for multiple contributors, and
I think it would work as well for multiple low-volume lists as for a
single high-volume one.

Worth having a look at?

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

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



Problem: invalid argument emitted by sendTo

2001-09-20 Thread mgross


I am using SocketPrim to send a udp packet to each of 254 addresses on a
network. The message packets have been preconstructed and placed in a
list, whose content has already been checked for correctness and appear
to meet the specifications in the appropriate RFC. When I go
through the list (using mapM_), sending a packet to each address with
sendTo, I get a valid return code from sendTo (used trace to check that) 
for the addresses from 10.129.129.1 through 10.129.129.239. Address
10.129.129.240, however, fails with the messages

Fail: invalid argument
Action: sendTo
Reason: invalid argument


The message invalid argument does not appear within the source of
SocketPrim, but it does appear in several of the binary files in the
library. I've begun to dig around in the source code, but I've taken to
hoping that someone out there in Haskell land may be able to point me
directly to where (and for what) I should be looking to determine just
what triggered those messages. 

Oh, yes, verson info: ghc-5.00.2, linux (debian testing). 

Thanks in advance for attention. 

Murray Gross
[EMAIL PROTECTED]




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



Problem: invalid argument emitted by sendTo

2001-09-20 Thread mgross


Found the error. No need to follow up. 

Apologies to anyone who objects to mail that turns out not to need
answering. 

Murray Gross
[EMAIL PROTECTED]




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



RE: Prelude and (:) and []((:), []) bugs?

2001-09-20 Thread Simon Marlow

Ian Lynagh writes:
 On Thu, Sep 20, 2001 at 01:32:54PM +0100, Simon Marlow wrote:
  (:) is allowed in an export list; it is just a normal operator.  
 
 An export is
 
 export - qvar
|  qtycon [(..) | ( qcname1 , ... , qcnamen )] (n=0)
|  qtycls [(..) | ( qvar1 , ... , qvarn )] (n=0)
|  module modid
 
 and we need to match (:). We can clearly reduce this to
[ proof that this isn't possible deleted ]

Ah, I forgot that you can't export a constructor on its own.  In which
case, I would like to submit a bug report for Hugs:  Hugs allows
constructors to be named in an export list, and it shouldn't (see
Section 5.2 in The Report, point 2 in the enumerated list).

Cheers,
Simon

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



Re: Prelude and (:) and []((:), []) bugs?

2001-09-20 Thread Alastair David Reid


 Ah, I forgot that you can't export a constructor on its own.  

You can't?

I probably knew this once but looking at it now, it seems kinda
surprising.  Haskell's module system is supposed to be just namespace
control --nothing more-- so why is it preventing me from doing something
which is perfectly safe and well-defined?

I'll readily agree that there's no strong motivation for exporting a
constructor on its own (I think the only reason Hugs allows it is just
so we can export (:) from the Prelude) but what is the motivation for
disallowing it?

-- 
Alastair Reid[EMAIL PROTECTED]http://www.cs.utah.edu/~reid/

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