Re: [Haskell] why don't we have const Ptrs?

2005-11-05 Thread John Meacham
On Thu, Nov 03, 2005 at 06:35:55PM -0500, David Roundy wrote:
 then I wouldn't have a guarantee that strcat isn't specialized for
 writeable Ptrs, in which case it might have the result of modifying a
 pointer when I don't want it to.  Admittedly, this isn't a likely scenario,
 but when I have the typechecker check something, I'd like it to give me a
 guarantee, with the usual caveat that certain unsafe functions aren't
 called.  Does the RULES pragma fall in that unsafe category?

RULES are in the very unsafe category. you can cause the compiler itself
to bottom out using them. 
John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] why don't we have const Ptrs?

2005-11-04 Thread David Roundy
On Wed, Nov 02, 2005 at 04:27:03PM +0100, Daan Leijen wrote:
 Hi David,

Hello,

 One way of dealing with constant pointer is to introduce (yet another)
 phantom type variable 'r' to pointers:
...
 And we can derive the const attribute too:
 
  data FooPtr r = FooPtr String (Ptr r Foo)

This is indeed very cool (and much better than I was imagining), but it
seems like there may still be one problem.

It seems to me that a bad person could escape the constness feature using
the RULES pragma.  So if all I knew was that hsstrcat had signature

 strcat :: Ptr Write CChar - Ptr r CChar - IO ()

then I wouldn't have a guarantee that strcat isn't specialized for
writeable Ptrs, in which case it might have the result of modifying a
pointer when I don't want it to.  Admittedly, this isn't a likely scenario,
but when I have the typechecker check something, I'd like it to give me a
guarantee, with the usual caveat that certain unsafe functions aren't
called.  Does the RULES pragma fall in that unsafe category?
-- 
David Roundy
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] why don't we have const Ptrs?

2005-11-04 Thread Arjan van IJzendoorn

Hello all,

David darcs Roundy wrote:

I was thinking this morning as I lay on the floor (where I sleep)  
about

static typechecking, [...]


I think we should get together and collect some money for David to  
buy a bed. Maybe a Paypal button at the darcs site? Maybe use the  
time we save by not using CVS anymore to get a second job and send  
our income to David? Just some suggestions.


Cheers, Arjan

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


Re: [Haskell] why don't we have const Ptrs?

2005-11-03 Thread Sven Panne
Am Mittwoch, 2. November 2005 15:02 schrieb David Roundy:
 [...] Why is it that in C++ I can write

 void strcpy(char *dest, const char *src);

 but in Haskell I must import this function as

  foreign import ccall unsafe static string.h strcpy
   strcpy :: Ptr CChar - Ptr CChar - IO ()

 and lose that wonderful information that the function doesn't modify the
 contents of its second argument? [...]

This topic has been raised several times when the FFI was in its design phase, 
(you might find some mail threads in ffi@haskell.org), but there was no real 
enthusiasm at that time to do something about it. Actually I see 2 problems 
here:

   * Tell the FFI that the pointer is const, so we don't get that annoying 
warnings from the C compiler anymore.

   * Ensure that a pointer is actually used the const way in Haskell.

Personally I think that the first problem is more severe and should be tackled 
first. But given the widespread use of the FFI nowadays, it is very important 
that we don't break existing code and delay the nice and correct soution 
until Haskell2 (or whatever it will be called) is out.

I would even be happy if something simple  ugly like

   data Const p = Const p -- somewhere in a library

   foreign import ccall unsafe static string.h strcpy
  strcpy :: Ptr CChar - Const (Ptr CChar) - IO ()

would be officially sanctioned. Pro: Backwards compatibility. Cons: The caller 
has to wrap the pointer explicitly (a small burden, IMHO); vague semantics 
(what does Const (Ptr (Const (Const a))) or Const Int mean?); no 
const-checking on the Haskell side.

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


[Haskell] why don't we have const Ptrs?

2005-11-02 Thread David Roundy
Hello all,

I was thinking this morning as I lay on the floor (where I sleep) about
static typechecking, and how much more wonderful Haskell is than any other
language, when it occurred to me that when working with pointers, Haskell
actually has *less* static typechecking than C or C++.  It was a very
disturbing thought, so much so that I was almost compelled to arise early
to place this question before this learned audience.

Why is it that in C++ I can write

void strcpy(char *dest, const char *src);

but in Haskell I must import this function as

 foreign import ccall unsafe static string.h strcpy
  strcpy :: Ptr CChar - Ptr CChar - IO ()

and lose that wonderful information that the function doesn't modify the
contents of its second argument?

One could pretty easily create a ConstPtr type which one could peek into,
but not poke to, but then you'd have to explicitely convert a Ptr into a
ConstPtr when passing it as an argument.  That feels a bit silly.

One could get around this by introducing a class to get around this

 class ReadablePtr p where
peek :: p a - IO a
peekOff ...

and then make both Ptr and ConstPtr instances of this class, but this still
seems like a very hackish solution.

Moreover, I'd like to be able to have const objects quite apart from Ptrs,
such as a const Handle, which I can read from, but cannot write to, or a
const IORef--and we wouldn't want to leave out const ForeignPtrs.  Of
course, even reading affects a Handle's internal state, so one would need
to be explicit about what const indicates.  But it seems to me that in
the IO world there are a whole slew of things that refer to other things
which could all be grouped together.

And a const attribute ought to be derived, so that if I create a data
type

 data FooPtr = FooPtr String (Ptr Foo)

one should ideally be able to automatically understand that a const FooPtr
holds a const (Ptr Foo).

One could go further, at least when dealing with Ptrs, and create a way of
handling restricted pointers--which we could interpret as a const pointer
to an object that cannot be changed by anyone else either.  One could
safely create restricted pointers with a function of the type

 mallocRestrictedPtr :: (Ptr a - IO ()) - RestrictedPtr a

which would allow one to ensure at the typechecking level that
RestrictedPtrs point to memory that cannot be modified.  There's still some
unstafety involved, in that you could read out of bounds, but you would
know that apart from that possibility the contents of a RestrictedPtr truly
will never change.

So my question is, how would one implement such an annotation extension?
I'd like to be able to pass a (Ptr a) as a (Const (Ptr a)) without an
explicit typecast, since the Const really isn't changing the type of the
pointer, it's just marking it as one that can't be modified.  A function
that accepts a (Const (Ptr a)) should also accept a (Restricted (Ptr
a))--but Restricted pointers are really just pudding, as they only differ
from Const pointers in what optimizations are allowed.  On the other hand,
it's not just compiler optimizations that they would allow, but also
user-code optimizations, which could be much more useful.  They also have
the advantage of making certain unsafe functions safe.

The hard part seems to be the lack of a conversion.  One could quite easily
implement a

 data Const a = Const a  -- this constructor is *not exported*
 toConst :: x - Const x
 unsafeAccessConst :: Const x - x

 peek :: Const (Ptr a) - IO a
 peekOff ...

etc, and everything would work fine, except that you'd always need to
explicitely convert from Ptr to Const Ptr.  Perhaps one could make Const be
a class as well as a data type:

 class (Const a) x where
 toConst :: x - Const a
 instance (Const x) x where
 toConst = Const
 instance (Const x) (Const x) where
 toConst = id

and then one could write code like

 peek :: Const (cp a) = cp a - IO a

which would move the typecasting burden out of the calling function and
into the function that accepts a const argument.  Perhaps this would be
sufficient, as many data types have only a limited number of primitive
const functions, and all the other const functions wouldn't actually
need to call toConst.

What this doesn't allow is deriving of constness, so that a Const
ForeignPtr would automatically hold a Const Ptr.

This whole class+data type scheme seems like it might be useful, but is
pretty ugly.  Is there a better way this could be done?

Might one be able to extend the language so that one could add attribute
such as Const to data type without changing the the type itself (which
would be analogous to what one does in C/C++)?
-- 
David Roundy
http://www.darcs.net
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] why don't we have const Ptrs?

2005-11-02 Thread Daan Leijen

Hi David,

 One could pretty easily create a ConstPtr type which one could peek into,
 but not poke to, but then you'd have to explicitely convert a Ptr into a
 ConstPtr when passing it as an argument.  That feels a bit silly.

One way of dealing with constant pointer is to introduce (yet another)
phantom type variable 'r' to pointers:

 data Ptr r a = ...

and introduce a read access hierarchy:

 data Read a
 data Write

A constant pointer has type  Ptr (Read ()) a
A normal pointer has typePtr (Read Write) a
At least read pointerPtr (Read r) a
And a 'don't care' pointer   Ptr r a

 peek :: Ptr (Read r) a - IO a
 poke :: Ptr (Read Write) a - a - IO ()
 alloc:: IO (Ptr (Read Write) a)

So, the type signature for strcat is:

 foreign import strcat :: Ptr (Read Write) CChar - Ptr (Read a) CChar - IO ()

And we can derive the const attribute too:

 data FooPtr r = FooPtr String (Ptr r Foo)

Since the read-write restrictions of Ptr carry over to FooPtr.

The design can be refined since four kinds of pointers is a bit too much.
We could use for example:

 type Const   = ()
 data Write

and say:

 Ptr Const a  == constant pointer
 Ptr Write a  == read-write pointer
 Ptr r a  == at least readable

And strcat would be:

  foreign import strcat :: Ptr Write CChar - Ptr r CChar - IO ()

and we would have:

  constantMalloc :: (Ptr Write a - IO ()) - Ptr Const a
  malloc :: Ptr Write a

  peek :: Ptr r a - IO a
  poke :: Ptr Write a - a - IO ()

So, this is another solution, although I am not sure if it is worth the
trouble making the distinction between normal and constant pointers.

All the best,
-- Daan.

David Roundy wrote:

Hello all,

I was thinking this morning as I lay on the floor (where I sleep) about
static typechecking, and how much more wonderful Haskell is than any other
language, when it occurred to me that when working with pointers, Haskell
actually has *less* static typechecking than C or C++.  It was a very
disturbing thought, so much so that I was almost compelled to arise early
to place this question before this learned audience.

Why is it that in C++ I can write

void strcpy(char *dest, const char *src);

but in Haskell I must import this function as


foreign import ccall unsafe static string.h strcpy
 strcpy :: Ptr CChar - Ptr CChar - IO ()


and lose that wonderful information that the function doesn't modify the
contents of its second argument?

One could pretty easily create a ConstPtr type which one could peek into,
but not poke to, but then you'd have to explicitely convert a Ptr into a
ConstPtr when passing it as an argument.  That feels a bit silly.

One could get around this by introducing a class to get around this


class ReadablePtr p where
   peek :: p a - IO a
   peekOff ...


and then make both Ptr and ConstPtr instances of this class, but this still
seems like a very hackish solution.

Moreover, I'd like to be able to have const objects quite apart from Ptrs,
such as a const Handle, which I can read from, but cannot write to, or a
const IORef--and we wouldn't want to leave out const ForeignPtrs.  Of
course, even reading affects a Handle's internal state, so one would need
to be explicit about what const indicates.  But it seems to me that in
the IO world there are a whole slew of things that refer to other things
which could all be grouped together.

And a const attribute ought to be derived, so that if I create a data
type


data FooPtr = FooPtr String (Ptr Foo)


one should ideally be able to automatically understand that a const FooPtr
holds a const (Ptr Foo).

One could go further, at least when dealing with Ptrs, and create a way of
handling restricted pointers--which we could interpret as a const pointer
to an object that cannot be changed by anyone else either.  One could
safely create restricted pointers with a function of the type


mallocRestrictedPtr :: (Ptr a - IO ()) - RestrictedPtr a


which would allow one to ensure at the typechecking level that
RestrictedPtrs point to memory that cannot be modified.  There's still some
unstafety involved, in that you could read out of bounds, but you would
know that apart from that possibility the contents of a RestrictedPtr truly
will never change.

So my question is, how would one implement such an annotation extension?
I'd like to be able to pass a (Ptr a) as a (Const (Ptr a)) without an
explicit typecast, since the Const really isn't changing the type of the
pointer, it's just marking it as one that can't be modified.  A function
that accepts a (Const (Ptr a)) should also accept a (Restricted (Ptr
a))--but Restricted pointers are really just pudding, as they only differ
from Const pointers in what optimizations are allowed.  On the other hand,
it's not just compiler optimizations that they would allow, but also
user-code optimizations, which could be much more useful.  They also have
the advantage of making certain unsafe functions safe.

The hard part seems to be the lack of a conversion.  

Re: [Haskell] why don't we have const Ptrs?

2005-11-02 Thread Bjorn Lisper
Hi,

Annotated type systems have been around for some time in static program
analysis. I think this is what you want. For instance, you can design such a
system to record possible side effects from a function call, as annotations
on the type of the function.

See the book Principles of Program Analysis,
http://www2.imm.dtu.dk/~riis/PPA/ppa.html.

Björn Lisper


David Roundy:
Hello all,

I was thinking this morning as I lay on the floor (where I sleep) about
static typechecking, and how much more wonderful Haskell is than any other
language, when it occurred to me that when working with pointers, Haskell
actually has *less* static typechecking than C or C++.  It was a very
disturbing thought, so much so that I was almost compelled to arise early
to place this question before this learned audience.

Why is it that in C++ I can write

void strcpy(char *dest, const char *src);

but in Haskell I must import this function as

 foreign import ccall unsafe static string.h strcpy
  strcpy :: Ptr CChar - Ptr CChar - IO ()

and lose that wonderful information that the function doesn't modify the
contents of its second argument?

One could pretty easily create a ConstPtr type which one could peek into,
but not poke to, but then you'd have to explicitely convert a Ptr into a
ConstPtr when passing it as an argument.  That feels a bit silly.

One could get around this by introducing a class to get around this

 class ReadablePtr p where
peek :: p a - IO a
peekOff ...

and then make both Ptr and ConstPtr instances of this class, but this still
seems like a very hackish solution.

Moreover, I'd like to be able to have const objects quite apart from Ptrs,
such as a const Handle, which I can read from, but cannot write to, or a
const IORef--and we wouldn't want to leave out const ForeignPtrs.  Of
course, even reading affects a Handle's internal state, so one would need
to be explicit about what const indicates.  But it seems to me that in
the IO world there are a whole slew of things that refer to other things
which could all be grouped together.

And a const attribute ought to be derived, so that if I create a data
type

 data FooPtr = FooPtr String (Ptr Foo)

one should ideally be able to automatically understand that a const FooPtr
holds a const (Ptr Foo).

One could go further, at least when dealing with Ptrs, and create a way of
handling restricted pointers--which we could interpret as a const pointer
to an object that cannot be changed by anyone else either.  One could
safely create restricted pointers with a function of the type

 mallocRestrictedPtr :: (Ptr a - IO ()) - RestrictedPtr a

which would allow one to ensure at the typechecking level that
RestrictedPtrs point to memory that cannot be modified.  There's still some
unstafety involved, in that you could read out of bounds, but you would
know that apart from that possibility the contents of a RestrictedPtr truly
will never change.

So my question is, how would one implement such an annotation extension?
I'd like to be able to pass a (Ptr a) as a (Const (Ptr a)) without an
explicit typecast, since the Const really isn't changing the type of the
pointer, it's just marking it as one that can't be modified.  A function
that accepts a (Const (Ptr a)) should also accept a (Restricted (Ptr
a))--but Restricted pointers are really just pudding, as they only differ
from Const pointers in what optimizations are allowed.  On the other hand,
it's not just compiler optimizations that they would allow, but also
user-code optimizations, which could be much more useful.  They also have
the advantage of making certain unsafe functions safe.

The hard part seems to be the lack of a conversion.  One could quite easily
implement a

 data Const a = Const a  -- this constructor is *not exported*
 toConst :: x - Const x
 unsafeAccessConst :: Const x - x

 peek :: Const (Ptr a) - IO a
 peekOff ...

etc, and everything would work fine, except that you'd always need to
explicitely convert from Ptr to Const Ptr.  Perhaps one could make Const be
a class as well as a data type:

 class (Const a) x where
 toConst :: x - Const a
 instance (Const x) x where
 toConst = Const
 instance (Const x) (Const x) where
 toConst = id

and then one could write code like

 peek :: Const (cp a) = cp a - IO a

which would move the typecasting burden out of the calling function and
into the function that accepts a const argument.  Perhaps this would be
sufficient, as many data types have only a limited number of primitive
const functions, and all the other const functions wouldn't actually
need to call toConst.

What this doesn't allow is deriving of constness, so that a Const
ForeignPtr would automatically hold a Const Ptr.

This whole class+data type scheme seems like it might be useful, but is
pretty ugly.  Is there a better way this could be done?

Might one be able to extend the language so that one could add attribute
such as Const to data type without changing the the 

Re: [Haskell] why don't we have const Ptrs?

2005-11-02 Thread Josef Svenningsson
Hi,

Here's a way to do pretty much what you're after. The idea is to add an
extra parameter to the Ptr type to indicate if it is a const pointer or
not.

 data Ptr const a

To indicate the constness we create a dummy data type which will show when the pointer type is *not* const.

 data NotConst

Now we can give more refined types to peek and poke like so:

 peek :: Ptr const a - IO a
 poke :: Ptr NotConst a - a - IO ()

With this setup peek will work with both kinds of pointers without any
casting. Constness will also be inferred. If a function is polymorphic
in a const argument that means that it doesn't change to pointer. The
use of higher rank polymorphism can be used to enforce that a pointer
is const.

This way of doing it is perhaps not the most beautiful. It would be a
little nicer if we had data kinds as Omega has. And its a shame that we
need to go outside Haskell98 if we want to enforce constness, since we
need to use higher rank polymorphism. Nevertheless this solution
adresses most of issues that you considered.

Cheers,

/JosefOn 11/2/05, David Roundy [EMAIL PROTECTED] wrote:
Hello all,I was thinking this morning as I lay on the floor (where I sleep) aboutstatic typechecking, and how much more wonderful Haskell is than any otherlanguage, when it occurred to me that when working with pointers, Haskell
actually has *less* static typechecking than C or C++.It was a verydisturbing thought, so much so that I was almost compelled to arise earlyto place this question before this learned audience.Why is it that in C++ I can write
void strcpy(char *dest, const char *src);but in Haskell I must import this function as foreign import ccall unsafe static string.h strcpystrcpy :: Ptr CChar - Ptr CChar - IO ()
and lose that wonderful information that the function doesn't modify thecontents of its second argument?One could pretty easily create a ConstPtr type which one could peek into,but not poke to, but then you'd have to explicitely convert a Ptr into a
ConstPtr when passing it as an argument.That feels a bit silly.One could get around this by introducing a class to get around this class ReadablePtr p wherepeek :: p a - IO apeekOff ...
and then make both Ptr and ConstPtr instances of this class, but this stillseems like a very hackish solution.Moreover, I'd like to be able to have const objects quite apart from Ptrs,such as a const Handle, which I can read from, but cannot write to, or a
const IORef--and we wouldn't want to leave out const ForeignPtrs.Ofcourse, even reading affects a Handle's internal state, so one would needto be explicit about what const indicates.But it seems to me that in
the IO world there are a whole slew of things that refer to other thingswhich could all be grouped together.And a const attribute ought to be derived, so that if I create a data
type data FooPtr = FooPtr String (Ptr Foo)one should ideally be able to automatically understand that a const FooPtrholds a const (Ptr Foo).One could go further, at least when dealing with Ptrs, and create a way of
handling restricted pointers--which we could interpret as a const pointerto an object that cannot be changed by anyone else either.One couldsafely create restricted pointers with a function of the type
 mallocRestrictedPtr :: (Ptr a - IO ()) - RestrictedPtr awhich would allow one to ensure at the typechecking level thatRestrictedPtrs point to memory that cannot be modified.There's still some
unstafety involved, in that you could read out of bounds, but you wouldknow that apart from that possibility the contents of a RestrictedPtr trulywill never change.So my question is, how would one implement such an annotation extension?
I'd like to be able to pass a (Ptr a) as a (Const (Ptr a)) without anexplicit typecast, since the Const really isn't changing the type of thepointer, it's just marking it as one that can't be modified.A function
that accepts a (Const (Ptr a)) should also accept a (Restricted (Ptra))--but Restricted pointers are really just pudding, as they only differfrom Const pointers in what optimizations are allowed.On the other hand,
it's not just compiler optimizations that they would allow, but alsouser-code optimizations, which could be much more useful.They also havethe advantage of making certain unsafe functions safe.The hard part seems to be the lack of a conversion.One could quite easily
implement a data Const a = Const a-- this constructor is *not exported* toConst :: x - Const x unsafeAccessConst :: Const x - x peek :: Const (Ptr a) - IO a peekOff ...
etc, and everything would work fine, except that you'd always need toexplicitely convert from Ptr to Const Ptr.Perhaps one could make Const bea class as well as a data type: class (Const a) x where
 toConst :: x - Const a instance (Const x) x where toConst = Const instance (Const x) (Const x) where toConst = idand then one could write code like peek :: Const (cp a) = cp a - IO a
which would move the typecasting burden out of the calling function andinto the