X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=clash%2FData%2FParam%2FUnsigned.hs;h=92dc24dfa5ddcaed9e13041c442cbf287e4ec611;hb=30969fa41ee30295f00cf089f4ee4385bb709871;hp=aae032d21b0b48eda6b18127018ebe60b132d3db;hpb=04f836932ad17dd557af0ba388a12d2b74c1e7d7;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/clash/Data/Param/Unsigned.hs b/clash/Data/Param/Unsigned.hs index aae032d..92dc24d 100644 --- a/clash/Data/Param/Unsigned.hs +++ b/clash/Data/Param/Unsigned.hs @@ -1,13 +1,13 @@ {-# LANGUAGE TypeFamilies, TypeOperators, ScopedTypeVariables, FlexibleInstances, TemplateHaskell, Rank2Types, FlexibleContexts #-} module Data.Param.Unsigned ( Unsigned - , resize + , resizeUnsigned , fromIndex ) where import Language.Haskell.TH import Language.Haskell.TH.Syntax (Lift(..)) -import Data.Bits +import qualified Data.Bits as B import Types import Types.Data.Num.Decimal.Literals.TH @@ -27,8 +27,8 @@ fromIndex :: ) => Index nT -> Unsigned nT' fromIndex index = Unsigned (toInteger index) -resize :: (NaturalT nT, NaturalT nT') => Unsigned nT -> Unsigned nT' -resize a = fromInteger (toInteger a) +resizeUnsigned :: (NaturalT nT, NaturalT nT') => Unsigned nT -> Unsigned nT' +resizeUnsigned a = fromInteger (toInteger a) sizeT :: Unsigned nT -> nT @@ -37,7 +37,7 @@ sizeT _ = undefined mask :: forall nT . NaturalT nT => nT -> Integer -mask _ = bit (fromIntegerT (undefined :: nT)) - 1 +mask _ = B.bit (fromIntegerT (undefined :: nT)) - 1 instance NaturalT nT => Eq (Unsigned nT) where (Unsigned x) == (Unsigned y) = x == y @@ -57,7 +57,7 @@ instance NaturalT nT => Ord (Unsigned nT) where instance NaturalT nT => Bounded (Unsigned nT) where minBound = 0 - maxBound = Unsigned $ (1 `shiftL` (fromIntegerT (undefined :: nT))) - 1 + maxBound = Unsigned $ (1 `B.shiftL` (fromIntegerT (undefined :: nT))) - 1 instance NaturalT nT => Enum (Unsigned nT) where succ x @@ -88,13 +88,13 @@ instance NaturalT nT => Num (Unsigned nT) where (Unsigned a) * (Unsigned b) = fromInteger $ a * b negate s@(Unsigned n) = - fromInteger $ (n `xor` mask (sizeT s)) + 1 + fromInteger $ (n `B.xor` mask (sizeT s)) + 1 a - b = a + (negate b) fromInteger n | n > 0 = - Unsigned $ n .&. mask (undefined :: nT) + Unsigned $ n B..&. mask (undefined :: nT) fromInteger n | n < 0 = negate $ fromInteger $ negate n @@ -128,30 +128,34 @@ instance NaturalT nT => Integral (Unsigned nT) where in (fromInteger div, fromInteger mod) toInteger s@(Unsigned x) = x -instance NaturalT nT => Bits (Unsigned nT) where - (Unsigned a) .&. (Unsigned b) = Unsigned $ a .&. b - (Unsigned a) .|. (Unsigned b) = Unsigned $ a .|. b - (Unsigned a) `xor` Unsigned b = Unsigned $ a `xor` b - complement (Unsigned x) = Unsigned $ x `xor` mask (undefined :: nT) +instance NaturalT nT => B.Bits (Unsigned nT) where + (Unsigned a) .&. (Unsigned b) = Unsigned $ a B..&. b + (Unsigned a) .|. (Unsigned b) = Unsigned $ a B..|. b + (Unsigned a) `xor` Unsigned b = Unsigned $ a `B.xor` b + complement (Unsigned x) = Unsigned $ x `B.xor` mask (undefined :: nT) s@(Unsigned x) `shiftL` b - | b < 0 = error $ "Bits.shiftL{Unsigned " ++ show (bitSize s) ++ "}: tried to shift by negative amount" + | b < 0 = error $ "Bits.shiftL{Unsigned " ++ show (B.bitSize s) ++ "}: tried to shift by negative amount" | otherwise = - Unsigned $ mask (undefined :: nT) .&. (x `shiftL` b) + Unsigned $ mask (undefined :: nT) B..&. (x `B.shiftL` b) s@(Unsigned x) `shiftR` b - | b < 0 = error $ "Bits.shiftR{Unsigned " ++ show (bitSize s) ++ "}: tried to shift by negative amount" + | b < 0 = error $ "Bits.shiftR{Unsigned " ++ show (B.bitSize s) ++ "}: tried to shift by negative amount" | otherwise = - Unsigned $ (x `shiftR` b) + Unsigned $ (x `B.shiftR` b) s@(Unsigned x) `rotateL` b | b < 0 = - error $ "Bits.rotateL{Unsigned " ++ show (bitSize s) ++ "}: tried to rotate by negative amount" + error $ "Bits.rotateL{Unsigned " ++ show (B.bitSize s) ++ "}: tried to rotate by negative amount" | otherwise = - Unsigned $ mask (undefined :: nT) .&. - ((x `shiftL` b) .|. (x `shiftR` (bitSize s - b))) + Unsigned $ mask (undefined :: nT) B..&. + ((x `B.shiftL` b) B..|. (x `B.shiftR` (B.bitSize s - b))) s@(Unsigned x) `rotateR` b | b < 0 = - error $ "Bits.rotateR{Unsigned " ++ show (bitSize s) ++ "}: tried to rotate by negative amount" + error $ "Bits.rotateR{Unsigned " ++ show (B.bitSize s) ++ "}: tried to rotate by negative amount" | otherwise = - Unsigned $ mask (undefined :: nT) .&. - ((x `shiftR` b) .|. (x `shiftL` (bitSize s - b))) + Unsigned $ mask (undefined :: nT) B..&. + ((x `B.shiftR` b) B..|. (x `B.shiftL` (B.bitSize s - b))) bitSize _ = fromIntegerT (undefined :: nT) isSigned _ = False + +instance NaturalT nT => HWBits (Unsigned nT) where + a `shiftL` b = a `B.shiftL` (fromInteger (toInteger b)) + a `shiftR` b = a `B.shiftR` (fromInteger (toInteger b))