{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ConstraintKinds #-}
module Haskus.Number.Signed
( Signed (..)
, SignedIsZero
, signedIsZero
, SignedFromBitNat
, signedFromBitNat
, SignedNegate
, signedNegate
, SignedPos
, signedPos
, SignedNeg
, signedNeg
)
where
import Haskus.Number.BitNat
import Haskus.Binary.Bits
import Haskus.Utils.Types
newtype Signed (b :: Nat)
= Signed (BitNat (b+1))
instance
( 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)
where
showsPrec d x@(Signed b)
| signedIsZero x = showString "0"
| otherwise =
showParen (d /= 0)
$ showString (if signedIsPositive x
then ""
else "-")
. showsPrec 0 (bitNatToNatural (b .>>. NatVal @1))
type SignedPos b v =
( b ~ NatBitCount v
, MakeBitNat b
, KnownNat v
, BitNatShiftLeft b 1
)
signedPos :: forall (v :: Nat) b.
( SignedPos b v
) => Signed b
signedPos = Signed @b (bitNat @v .<<. NatVal @1)
type SignedNeg b v =
( SignedPos b v
, SignedNegate b
)
signedNeg :: forall (v :: Nat) b.
( SignedNeg b v
) => Signed b
signedNeg = signedNegate (signedPos @v @b)
type SignedIsZero b =
( BitNatShiftRight (b+1) 1
)
signedIsZero :: forall b.
( SignedIsZero b
) => Signed b -> Bool
signedIsZero (Signed b) = (b .>>. NatVal @1 == bitNatZero)
type SignedIsPositive b =
( IndexableBits (BitNatWord (b+1))
)
signedIsPositive :: forall b.
( SignedIsPositive b
) => Signed b -> Bool
signedIsPositive (Signed b) = not (bitNatTestBit b 0)
type SignedFromBitNat b =
( ShiftableBits (BitNatWord (b+1))
, Widen b (b+1)
)
signedFromBitNat :: forall b.
( SignedFromBitNat b
) => BitNat b -> Signed b
signedFromBitNat b = Signed (b .<<. NatVal @1)
type SignedNegate b =
( IsBitNat (b+1)
)
signedNegate ::
( SignedNegate b
) => Signed b -> Signed b
signedNegate (Signed b)= Signed (b `bitNatXor` bitNatOne)