Versionbump: Added further missing instances for Word24.
This commit is contained in:
parent
a42cf28f7d
commit
e28e0c5afb
@ -6,17 +6,25 @@
|
||||
-- case, therefore we have deprecated only as warning so that it
|
||||
-- compiles at least.
|
||||
{-# OPTIONS_GHC -Wwarn=deprecations #-}
|
||||
{-# LANGUAGE DerivingStrategies #-}
|
||||
|
||||
module Data.Word.Word24
|
||||
( Word24
|
||||
) where
|
||||
|
||||
import ClassyPrelude
|
||||
import ClassyPrelude hiding (index)
|
||||
|
||||
import Data.Data (Data)
|
||||
import Data.Bits
|
||||
import Data.Ix
|
||||
|
||||
import GHC.Read
|
||||
|
||||
import Control.DeepSeq()
|
||||
|
||||
newtype Word24 = Word24 Word32
|
||||
deriving (Data, Generic)
|
||||
deriving anyclass NFData
|
||||
|
||||
maxWord24 :: Num a => a
|
||||
maxWord24 = 16777215
|
||||
@ -36,6 +44,15 @@ instance Num Word24 where
|
||||
fromInteger i = word24 (fromInteger i)
|
||||
negate (Word24 a) = word24 (negate a)
|
||||
|
||||
instance Ix Word24 where
|
||||
{- MINIMAL range, (index | unsafeIndex), inRange -}
|
||||
-- range :: (a, a) -> [a]
|
||||
range (Word24 a, Word24 b) = map word24 $ range (a,b)
|
||||
-- index :: (a, a) -> a -> Int
|
||||
index (Word24 a, Word24 b) (Word24 c) = index (a,b) c
|
||||
-- inRange :: (a, a) -> a -> Bool
|
||||
inRange (Word24 a, Word24 b) (Word24 c) = inRange (a,b) c
|
||||
|
||||
instance Eq Word24 where
|
||||
(==) (Word24 a) (Word24 b) = a == b
|
||||
|
||||
@ -69,6 +86,26 @@ instance Bits Word24 where
|
||||
bit = word24 . bit
|
||||
popCount (Word24 a) = popCount a
|
||||
|
||||
instance Read Word24 where
|
||||
-- readsPrec :: Int -> ReadS Word24
|
||||
-- readsPrec :: Int -> String -> [(Word24, String)]
|
||||
readsPrec i = map (\(j,t) -> (word24 j, t)) . readsPrec i
|
||||
|
||||
instance Show Word24 where
|
||||
show (Word24 i) = show i
|
||||
|
||||
--instance Typeable Word24
|
||||
--where
|
||||
-- typeRep#
|
||||
|
||||
{-
|
||||
{- MINIMAL gunfold, toConstr, dataTypeOf -}
|
||||
instance Data Word24 where
|
||||
-- Data.Data.gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Data.Data.Constr -> c a
|
||||
gunfold
|
||||
-- Data.Data.toConstr :: a -> Data.Data.Constr
|
||||
toConstr
|
||||
-- Data.Data.dataTypeOf :: a -> Data.Data.DataType
|
||||
dataTypeOf
|
||||
-}
|
||||
|
||||
|
||||
Reference in New Issue
Block a user