#ifdef __GLASGOW_HASKELL__
#define LANGUAGE_DeriveDataTypeable
#endif
#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 702
#ifdef MIN_VERSION_hashable
#else
#endif
#endif
module Numeric.Natural ( Natural ) where
import Control.Exception ( throw, ArithException(Underflow) )
import Data.Bits
import Data.Ix
#ifdef LANGUAGE_DeriveDataTypeable
import Data.Data
#endif
#ifdef MIN_VERSION_hashable
import Data.Hashable
#endif
newtype Natural = Natural { runNatural :: Integer } deriving
( Eq
, Ord
, Ix
#ifdef LANGUAGE_DeriveDataTypeable
, Typeable
#endif
)
#ifdef MIN_VERSION_hashable
instance Hashable Natural where
#if MIN_VERSION_hashable(1,2,0)
hashWithSalt p (Natural a) = hashWithSalt p a
#else
hash (Natural a) = hash a
#endif
#endif
#ifdef LANGUAGE_DeriveDataTypeable
naturalType :: DataType
naturalType = mkIntType "Numeric.Natural.Natural"
instance Data Natural where
toConstr x = mkIntegralConstr naturalType x
gunfold _ z c = case constrRep c of
(IntConstr x) -> z (fromIntegral x)
_ -> error $ "Data.Data.gunfold: Constructor " ++ show c
++ " is not of type Natural"
dataTypeOf _ = naturalType
#endif
instance Show Natural where
showsPrec d (Natural n) = showsPrec d n
instance Read Natural where
readsPrec d = map (\(n, s) -> (Natural n, s)) . filter ((>= 0) . fst) . readsPrec d
instance Num Natural where
Natural n + Natural m = Natural (n + m)
Natural n * Natural m = Natural (n * m)
Natural n Natural m | result < 0 = throw Underflow
| otherwise = Natural result
where result = n m
abs (Natural n) = Natural n
signum (Natural n) = Natural (signum n)
fromInteger n
| n >= 0 = Natural n
| otherwise = throw Underflow
instance Bits Natural where
Natural n .&. Natural m = Natural (n .&. m)
Natural n .|. Natural m = Natural (n .|. m)
xor (Natural n) (Natural m) = Natural (xor n m)
complement _ = error "Bits.complement: Natural complement undefined"
shift (Natural n) = Natural . shift n
rotate (Natural n) = Natural . rotate n
bit = Natural . bit
setBit (Natural n) = Natural . setBit n
clearBit (Natural n) = Natural . clearBit n
complementBit (Natural n) = Natural . complementBit n
testBit = testBit . runNatural
#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 707
bitSizeMaybe _ = Nothing
#endif
bitSize = error "Natural: bitSize"
isSigned _ = False
shiftL (Natural n) = Natural . shiftL n
shiftR (Natural n) = Natural . shiftR n
rotateL (Natural n) = Natural . rotateL n
rotateR (Natural n) = Natural . rotateR n
#if MIN_VERSION_base(4,6,0)
popCount = popCountDefault
#endif
instance Real Natural where
toRational (Natural a) = toRational a
instance Enum Natural where
pred (Natural 0) = throw Underflow
pred (Natural n) = Natural (pred n)
succ (Natural n) = Natural (succ n)
fromEnum (Natural n) = fromEnum n
toEnum n | n < 0 = error "Natural.toEnum: negative"
| otherwise = Natural (toEnum n)
enumFrom = map Natural . enumFrom . runNatural
enumFromThen x y
| x <= y = map Natural (enumFromThen (runNatural x) (runNatural y))
| otherwise = map Natural (enumFromThenTo (runNatural x) (runNatural y) 0)
enumFromTo x y = map Natural (enumFromTo (runNatural x) (runNatural y))
enumFromThenTo x x1 y
= map Natural (enumFromThenTo (runNatural x) (runNatural x1) (runNatural y))
instance Integral Natural where
quot (Natural a) (Natural b) = Natural (quot a b)
rem (Natural a) (Natural b) = Natural (rem a b)
div (Natural a) (Natural b) = Natural (div a b)
mod (Natural a) (Natural b) = Natural (mod a b)
divMod (Natural a) (Natural b) = (Natural q, Natural r) where (q,r) = divMod a b
quotRem (Natural a) (Natural b) = (Natural q, Natural r) where (q,r) = quotRem a b
toInteger = runNatural