Re: module Data.Bits

2002-09-11 Thread Manuel M T Chakravarty

Alastair Reid <[EMAIL PROTECTED]> wrote,

> 
> > Another conflict between the FFI spec and the current library
> > implementation: the spec says
> 
> > "The function bitSize returns 0 for types that don't have a
> > fixed bitsize (e.g. Integer)."
> 
> > whereas the current ghc implementation defines bitSize of Integer as
> > a runtime error.
> 
> I think both are unfortunate - we should just admit that not every
> type has a bitsize and return a Maybe.  But that doesn't seem likely
> to happen...
> 
> It isn't clear which is the lesser of the two evils:
> 
> - returning 0 is easy to catch but equally easy to carelessly forget
> 
> - raising an exception is harder to catch but has the huge advantage
>   that the failure is close to the broken code.
> 
>   (Does NHC support non-deterministic exceptions?  Dead easy to add if
>   not.)
> 
> Hugs is silent on the issue because we never implemented Bits Integer.
> I think I prefer the GHC semantics.

Ok, I changed the spec to GHC's semantics.

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



Re: module Data.Bits

2002-09-11 Thread Manuel M T Chakravarty

"Simon Marlow" <[EMAIL PROTECTED]> wrote,

> > The FFI Addendum actually doesn't commit to which operations
> > are in the class.  It just says defines all these ops to
> > have a context `Bits a', which is definitely the case.  In
> > other words, you proposed implementation is valid by the
> > spec and your argument for it makes sense to me.
> 
> The spec really ought to say what the member functions of the class are,
> if we expect people to be able to define their own instances of Bits,
> and I don't see why we shouldn't allow that.

True.

> I think Malcolm's proposed change looks reasonable, although there was
> probably a reason why these functions weren't made class members in the
> first place.  Alastair: it was your design originally I believe, any
> thoughts?  I think it would be a small optimisation in GHC too, at least
> for shifts by non-constant amounts.

I applied Malcolm's change now.

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



Re: module Data.Bits

2002-09-10 Thread Alastair Reid


> Another conflict between the FFI spec and the current library
> implementation: the spec says

> "The function bitSize returns 0 for types that don't have a
> fixed bitsize (e.g. Integer)."

> whereas the current ghc implementation defines bitSize of Integer as
> a runtime error.

I think both are unfortunate - we should just admit that not every
type has a bitsize and return a Maybe.  But that doesn't seem likely
to happen...

It isn't clear which is the lesser of the two evils:

- returning 0 is easy to catch but equally easy to carelessly forget

- raising an exception is harder to catch but has the huge advantage
  that the failure is close to the broken code.

  (Does NHC support non-deterministic exceptions?  Dead easy to add if
  not.)

Hugs is silent on the issue because we never implemented Bits Integer.
I think I prefer the GHC semantics.

--
Alastair

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



Re: module Data.Bits

2002-09-10 Thread Alastair Reid


> Errm, but in C there is no unified shift operator.  You have << for
> left shift and and >> for right shift, and a negative shift is
> undefined.

[blush]

>> This makes the specification come out nice and clean - you're
>> multiplying the number by 2^n instead of 2^{-n}.

> Errm, but then right shift comes out as dividing by 2^{-n}, instead
> of 2^n.  For a unified shift operation, I don't think there is any
> good reason to prefer one direction over the other, since there is
> no precedent in another language (AFAIK).

I think this spec (for >0 == left shift)

  shift x n = x * 2^^n

is simpler than (for >0 == right shift)

  shift x n = x * 2^^(-n)

[Ok, I probably need a few from/to Fractionals added to those specs]


--
A
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: module Data.Bits

2002-09-10 Thread Alastair Reid


> Alastair: it was your design originally I believe, any thoughts? 

Actually, I think it was Lennart's - though he might disown our variant...

The change seems fine.  


(Actually, it feels a bit like another instance of defining the
language to allow particular optimizations in particular technology...
but I can only hold up progress for so long :-)

--
A
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: module Data.Bits

2002-09-10 Thread Malcolm Wallace

Manuel M T Chakravarty <[EMAIL PROTECTED]> writes:

> So, I would propose to
> change the FFI spec.  The main reason being that there is
> already plenty of code which relies on the current
> definition in GHC's Bits and there is no good reason to
> break that code.  Objections?

That's fine with me.

Another conflict between the FFI spec and the current
library implementation:  the spec says

"The function bitSize returns 0 for types that don't have a
 fixed bitsize (e.g. Integer)."

whereas the current ghc implementation defines bitSize of Integer
as a runtime error.

Regards,
Malcolm
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



RE: module Data.Bits

2002-09-10 Thread Simon Marlow


> The FFI Addendum actually doesn't commit to which operations
> are in the class.  It just says defines all these ops to
> have a context `Bits a', which is definitely the case.  In
> other words, you proposed implementation is valid by the
> spec and your argument for it makes sense to me.

The spec really ought to say what the member functions of the class are,
if we expect people to be able to define their own instances of Bits,
and I don't see why we shouldn't allow that.

I think Malcolm's proposed change looks reasonable, although there was
probably a reason why these functions weren't made class members in the
first place.  Alastair: it was your design originally I believe, any
thoughts?  I think it would be a small optimisation in GHC too, at least
for shifts by non-constant amounts.

Cheers,
Simon
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: module Data.Bits

2002-09-09 Thread Manuel M T Chakravarty

Malcolm Wallace <[EMAIL PROTECTED]> wrote,

> Alastair Reid <[EMAIL PROTECTED]> writes:
> 
> > > The FFI spec says that the operations called 'shift' and 'rotate',
> > > shift and rotate their argument to the right.  However, the GHC
> > > implementation in CVS shifts and rotates to the left, and is
> > > documented to do so.
[..]
> > This makes the specification come out nice and clean - you're
> > multiplying the number by 2^n instead of 2^{-n}.
> 
> Errm, but then right shift comes out as dividing by 2^{-n}, instead
> of 2^n.  For a unified shift operation, I don't think there is any
> good reason to prefer one direction over the other, since there is
> no precedent in another language (AFAIK).

I have no idea why I did it other than in GHC's libs.  I
think, it is a typo, because my intention was to duplicate
the Bits interface of GHC's libs.  So, I would propose to
change the FFI spec.  The main reason being that there is
already plenty of code which relies on the current
definition in GHC's Bits and there is no good reason to
break that code.  Objections?

> However, while I'm on the subject, I'd like to request that the operations
> 
> shiftL, shiftR,-- :: a -> Int -> a
> rotateL, rotateR,  -- :: a -> Int -> a
> 
> should become members of the class, with new default implementations
> 
> x `shift`   i  | i<0  = x `shiftL` i
>| i==0 = x
>| i>0  = x `shiftR` i
> x `rotate`  i  | i<0  = x `rotateL` i
>| i==0 = x
>| i>0  = x `rotateR` i
> 
> x `shiftL`  i  = x `shift`  (-i)
> x `shiftR`  i  = x `shift`  i
> x `rotateL` i  = x `rotate` (-i)
> x `rotateR` i  = x `rotate` i
> 
> (or with the directions the other way round if you insist.)
> 
> As I already noted, languages such as C provide only left and right
> shift (with no unified variant), and it would be nice to have the
> ability to override the default implementations of shiftL etc for
> specific types where we can call C directly.  At the moment, a right
> shift turns into two negations in Haskell followed by the primitive
> call, and I'd like to squeeze the extra efficiency in if I can.

The FFI Addendum actually doesn't commit to which operations
are in the class.  It just says defines all these ops to
have a context `Bits a', which is definitely the case.  In
other words, you proposed implementation is valid by the
spec and your argument for it makes sense to me.

Cheers,
Manuel
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: module Data.Bits

2002-09-09 Thread Malcolm Wallace

Malcolm Wallace <[EMAIL PROTECTED]> writes:

> x `shift`   i  | i<0  = x `shiftL` i
>| i==0 = x
>| i>0  = x `shiftR` i

Oops, of course that should be

> x `shift`   i  | i<0  = x `shiftL` (-i)
>| i==0 = x
>| i>0  = x `shiftR` i

etc.

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



Re: module Data.Bits

2002-09-09 Thread Malcolm Wallace

Alastair Reid <[EMAIL PROTECTED]> writes:

> > The FFI spec says that the operations called 'shift' and 'rotate',
> > shift and rotate their argument to the right.  However, the GHC
> > implementation in CVS shifts and rotates to the left, and is
> > documented to do so.
> 
> They shift to the left as in C, etc.

Errm, but in C there is no unified shift operator.  You have <<
for left shift and and >> for right shift, and a negative shift
is undefined.

> This makes the specification come out nice and clean - you're
> multiplying the number by 2^n instead of 2^{-n}.

Errm, but then right shift comes out as dividing by 2^{-n}, instead
of 2^n.  For a unified shift operation, I don't think there is any
good reason to prefer one direction over the other, since there is
no precedent in another language (AFAIK).

However, while I'm on the subject, I'd like to request that the operations

shiftL, shiftR,-- :: a -> Int -> a
rotateL, rotateR,  -- :: a -> Int -> a

should become members of the class, with new default implementations

x `shift`   i  | i<0  = x `shiftL` i
   | i==0 = x
   | i>0  = x `shiftR` i
x `rotate`  i  | i<0  = x `rotateL` i
   | i==0 = x
   | i>0  = x `rotateR` i

x `shiftL`  i  = x `shift`  (-i)
x `shiftR`  i  = x `shift`  i
x `rotateL` i  = x `rotate` (-i)
x `rotateR` i  = x `rotate` i

(or with the directions the other way round if you insist.)

As I already noted, languages such as C provide only left and right
shift (with no unified variant), and it would be nice to have the
ability to override the default implementations of shiftL etc for
specific types where we can call C directly.  At the moment, a right
shift turns into two negations in Haskell followed by the primitive
call, and I'd like to squeeze the extra efficiency in if I can.

Regards,
Malcolm
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



Re: module Data.Bits

2002-09-09 Thread Alastair Reid


> The FFI spec says that the operations called 'shift' and 'rotate',
> shift and rotate their argument to the right.  However, the GHC
> implementation in CVS shifts and rotates to the left, and is
> documented to do so.

> Who is right?  FWIW, before I read any documentation I expected the
> undecorated forms to be rightward.

They shift to the left as in C, etc.

This makes the specification come out nice and clean - you're
multiplying the number by 2^n instead of 2^{-n}.

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



RE: module Data.Bits

2002-09-09 Thread Simon Marlow

> I have just been implementing the library module `Data.Bits' 
> for nhc98,
> as part of an effort to bring that compiler up-to-date with 
> the latest FFI spec.
> 
> The FFI spec says that the operations called 'shift' and 'rotate',
> shift and rotate their argument to the right.  However, the GHC
> implementation in CVS shifts and rotates to the left, and is 
> documented to do so.
> 
> Who is right?  FWIW, before I read any documentation I expected the
> undecorated forms to be rightward.

I think it's probably a mistake in the FFI addendum.  As far as I can
tell, the GHC/Hugs implementation of Bits has always worked the other
way around.

Cheers,
Simon
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi



module Data.Bits

2002-09-06 Thread Malcolm Wallace

I have just been implementing the library module `Data.Bits' for nhc98,
as part of an effort to bring that compiler up-to-date with the latest FFI
spec.

The FFI spec says that the operations called 'shift' and 'rotate',
shift and rotate their argument to the right.  However, the GHC
implementation in CVS shifts and rotates to the left, and is documented
to do so.

Who is right?  FWIW, before I read any documentation I expected the
undecorated forms to be rightward.

Regards,
Malcolm
___
FFI mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/ffi