<div dir="ltr">Destroying GND for Bits _is_ a pretty huge downside. =/</div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Thu, May 27, 2021 at 10:45 AM Oleg Grenrus <<a href="mailto:oleg.grenrus@iki.fi">oleg.grenrus@iki.fi</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">
<div>
<p>I don't think this as good idea, as that definition doesn't work
with GND.<br>
<br>
{-# LANGUAGE RankNTypes, GeneralizedNewtypeDeriving,
ConstrainedClassMethods #-}<br>
<br>
import Data.Bits<br>
import Data.Word<br>
<br>
class Bits a => Bits' a where<br>
withFiniteBits :: Bits a => a -> (FiniteBits a =>
r) -> r -> r<br>
<br>
instance Bits' Word8 where<br>
withFiniteBits _ x _ = x<br>
<br>
newtype W = W Word8 deriving (Eq, Show, Bits, Bits',
FiniteBits)<br>
<br>
fails with<br>
<br>
Bi.hs:12:47: error:<br>
• Couldn't match type ‘Word8’ with ‘W’<br>
arising from the coercion of the method ‘withFiniteBits’<br>
from type ‘forall r.<br>
Bits Word8 =><br>
Word8 -> (FiniteBits Word8 => r) ->
r -> r’<br>
to type ‘forall r. Bits W => W -> (FiniteBits W
=> r) -> r -> r’<br>
• When deriving the instance for (Bits' W)<br>
|<br>
12 | newtype W = W Word8 deriving (Eq, Show, Bits, Bits',
FiniteBits)<br>
<br>
<br>
Note, FiniteBits has nominal role, so cannot be coerced to
FiniteBits W.<br>
<br>
<br>
If CLC decides this is still fine, then I'd suggest to not have<br>
any migration period as adding method is breaking change for GND
users,<br>
so rather break everyone at once, maybe even by moving
bitSizeMaybe out of the class.<br>
<br>
- Oleg<br>
</p>
<div>On 27.5.2021 20.22, Edward Kmett wrote:<br>
</div>
<blockquote type="cite">
<div dir="ltr">This does seem like a strict improvement over the
status quo.
<div><br>
</div>
<div>Users can then conditionally get access to
count(Trailing|Leading)Zeros by refining the type information
available to them using this combinator, which offers a bunch
of bit twiddling usecases.</div>
<div><br>
</div>
<div>-Edward</div>
</div>
<br>
<div class="gmail_quote">
<div dir="ltr" class="gmail_attr">On Tue, May 18, 2021 at 9:30
AM Zemyla <<a href="mailto:zemyla@gmail.com" target="_blank">zemyla@gmail.com</a>> wrote:<br>
</div>
<blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">Every
Bits instance has to know that whether it's a FiniteBits<br>
instance as well, due to bitSizeMaybe. Therefore, it should
also be<br>
able to tell a program that it is in fact a FiniteBits
instance. There<br>
should be a function added to Data.Bits.Bits:<br>
<br>
withFiniteBits :: Bits a => a -> (FiniteBits a => r)
-> r -> r<br>
<br>
The default should be withFiniteBits _ _ x = x, at least for
the next<br>
several versions. bitSizeMaybe can be defined as<br>
<br>
bitSizeMaybe x = withFiniteBits x (Just (finiteBitSize x))
Nothing<br>
<br>
once everyone is on board with properly defining the value.<br>
_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
</blockquote>
</div>
<br>
<fieldset></fieldset>
<pre>_______________________________________________
Libraries mailing list
<a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a>
</pre>
</blockquote>
</div>
_______________________________________________<br>
Libraries mailing list<br>
<a href="mailto:Libraries@haskell.org" target="_blank">Libraries@haskell.org</a><br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br>
</blockquote></div>