Destroying GND for Bits _is_ a pretty huge downside. =/_______________________________________________On Thu, May 27, 2021 at 10:45 AM Oleg Grenrus <oleg.grenrus@iki.fi> wrote:_______________________________________________I don't think this as good idea, as that definition doesn't work with GND.
{-# LANGUAGE RankNTypes, GeneralizedNewtypeDeriving, ConstrainedClassMethods #-}
import Data.Bits
import Data.Word
class Bits a => Bits' a where
withFiniteBits :: Bits a => a -> (FiniteBits a => r) -> r -> r
instance Bits' Word8 where
withFiniteBits _ x _ = x
newtype W = W Word8 deriving (Eq, Show, Bits, Bits', FiniteBits)
fails with
Bi.hs:12:47: error:
• Couldn't match type ‘Word8’ with ‘W’
arising from the coercion of the method ‘withFiniteBits’
from type ‘forall r.
Bits Word8 =>
Word8 -> (FiniteBits Word8 => r) -> r -> r’
to type ‘forall r. Bits W => W -> (FiniteBits W => r) -> r -> r’
• When deriving the instance for (Bits' W)
|
12 | newtype W = W Word8 deriving (Eq, Show, Bits, Bits', FiniteBits)
Note, FiniteBits has nominal role, so cannot be coerced to FiniteBits W.
If CLC decides this is still fine, then I'd suggest to not have
any migration period as adding method is breaking change for GND users,
so rather break everyone at once, maybe even by moving bitSizeMaybe out of the class.
- Oleg
On 27.5.2021 20.22, Edward Kmett wrote:
This does seem like a strict improvement over the status quo.
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.
-Edward
On Tue, May 18, 2021 at 9:30 AM Zemyla <zemyla@gmail.com> wrote:
Every Bits instance has to know that whether it's a FiniteBits
instance as well, due to bitSizeMaybe. Therefore, it should also be
able to tell a program that it is in fact a FiniteBits instance. There
should be a function added to Data.Bits.Bits:
withFiniteBits :: Bits a => a -> (FiniteBits a => r) -> r -> r
The default should be withFiniteBits _ _ x = x, at least for the next
several versions. bitSizeMaybe can be defined as
bitSizeMaybe x = withFiniteBits x (Just (finiteBitSize x)) Nothing
once everyone is on board with properly defining the value.
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries