Safe Haskell | None |
---|---|
Language | Haskell2010 |
Signed numbers
Synopsis
- newtype Signed (b :: Nat) = Signed (BitNat (b + 1))
- type SignedIsZero b = BitNatShiftRight (b + 1) 1
- signedIsZero :: forall b. SignedIsZero b => Signed b -> Bool
- type SignedFromBitNat b = (ShiftableBits (BitNatWord (b + 1)), Widen b (b + 1))
- signedFromBitNat :: forall b. SignedFromBitNat b => BitNat b -> Signed b
- type SignedNegate b = IsBitNat (b + 1)
- signedNegate :: SignedNegate b => Signed b -> Signed b
- type SignedPos b v = (b ~ NatBitCount v, MakeBitNat b, KnownNat v, BitNatShiftLeft b 1)
- signedPos :: forall (v :: Nat) b. SignedPos b v => Signed b
- type SignedNeg b v = (SignedPos b v, SignedNegate b)
- signedNeg :: forall (v :: Nat) b. SignedNeg b v => Signed b
Documentation
newtype Signed (b :: Nat) Source #
A signed number (not in two-complement form)
- Bits: ddd..ddds where "s" is the sign bit
- Allows symetric positive and negative numbers
- Positive and negative zeros are zero
Instances
(KnownNat b, Integral (BitNatWord b), IndexableBits (BitNatWord (b + 1)), Num (BitNatWord (b + 1)), Eq (BitNatWord (b + 1)), Integral (BitNatWord (b + 1)), ShiftableBits (BitNatWord (b + 1)), Narrow (b + 1) ((b + 1) - 1)) => Show (Signed b) Source # | Show instance for Signed |
type SignedIsZero b = BitNatShiftRight (b + 1) 1 Source #
signedIsZero :: forall b. SignedIsZero b => Signed b -> Bool Source #
Test for zero
>>>
signedIsZero (signedNeg @5)
False>>>
signedIsZero (signedNeg @0)
True
type SignedFromBitNat b = (ShiftableBits (BitNatWord (b + 1)), Widen b (b + 1)) Source #
signedFromBitNat :: forall b. SignedFromBitNat b => BitNat b -> Signed b Source #
Create from a BitNat
>>>
signedFromBitNat (bitNat @18)
18
type SignedNegate b = IsBitNat (b + 1) Source #
signedNegate :: SignedNegate b => Signed b -> Signed b Source #
Negate a signed number
>>>
signedNegate (signedPos @5)
-5>>>
signedNegate (signedNeg @5)
5
type SignedPos b v = (b ~ NatBitCount v, MakeBitNat b, KnownNat v, BitNatShiftLeft b 1) Source #
signedPos :: forall (v :: Nat) b. SignedPos b v => Signed b Source #
Positive signed literal
>>>
signedPos @5
5>>>
signedPos @0
0
type SignedNeg b v = (SignedPos b v, SignedNegate b) Source #