{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.ZigZag (ZigZag(..)) where
import Data.Bits (Bits (shiftL, shiftR, xor, (.&.)),
FiniteBits (finiteBitSize))
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Word (Word16, Word32, Word64, Word8)
import Numeric.Natural (Natural)
class (Integral signed, Integral unsigned)
=> ZigZag signed unsigned | unsigned -> signed, signed -> unsigned where
zigZag :: signed -> unsigned
default zigZag :: FiniteBits signed => signed -> unsigned
zigZag signed
s = forall a b. (Integral a, Num b) => a -> b
fromIntegral
((signed
s forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Bits a => a -> a -> a
`xor` (signed
s forall a. Bits a => a -> Int -> a
`shiftR` (forall b. FiniteBits b => b -> Int
finiteBitSize signed
s forall a. Num a => a -> a -> a
- Int
1)))
{-# INLINE zigZag #-}
zagZig :: unsigned -> signed
default zagZig :: (Bits unsigned) => unsigned -> signed
zagZig unsigned
u = forall a b. (Integral a, Num b) => a -> b
fromIntegral ((unsigned
u forall a. Bits a => a -> Int -> a
`shiftR` Int
1) forall a. Bits a => a -> a -> a
`xor` forall a. Num a => a -> a
negate (unsigned
u forall a. Bits a => a -> a -> a
.&. unsigned
1))
{-# INLINE zagZig #-}
instance ZigZag Int8 Word8
instance ZigZag Int16 Word16
instance ZigZag Int32 Word32
instance ZigZag Int64 Word64
instance ZigZag Integer Natural where
zigZag :: Integer -> Natural
zigZag Integer
x
| Integer
x forall a. Ord a => a -> a -> Bool
>= Integer
0 = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Integer
x forall a. Bits a => a -> Int -> a
`shiftL` Int
1
| Bool
otherwise = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall a. Num a => a -> a
negate (Integer
x forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Num a => a -> a -> a
- Integer
1
zagZig :: Natural -> Integer
zagZig Natural
u = let s :: Integer
s = forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
u
in ((Integer
s forall a. Bits a => a -> Int -> a
`shiftR` Int
1) forall a. Bits a => a -> a -> a
`xor` forall a. Num a => a -> a
negate (Integer
s forall a. Bits a => a -> a -> a
.&. Integer
1))