module Data.ZigZag (
zzEncode,
zzDecode64,
) where
import RON.Prelude
import Data.Bits (Bits, FiniteBits, finiteBitSize, shiftL, shiftR,
xor, (.&.))
{-# SPECIALIZE INLINE zzEncode :: Int8 -> Word8 #-}
{-# SPECIALIZE INLINE zzEncode :: Int16 -> Word16 #-}
{-# SPECIALIZE INLINE zzEncode :: Int32 -> Word32 #-}
{-# SPECIALIZE INLINE zzEncode :: Int64 -> Word64 #-}
zzEncode :: (Num b, Integral a, FiniteBits a) => a -> b
zzEncode :: a -> b
zzEncode a
w =
a -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((a
w a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
1) a -> a -> a
forall a. Bits a => a -> a -> a
`xor` (a
w a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` (a -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize a
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)))
{-# INLINE zzDecode #-}
zzDecode :: (Num a, Integral a1, Bits a1) => a1 -> a
zzDecode :: a1 -> a
zzDecode a1
w = a1 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((a1
w a1 -> Int -> a1
forall a. Bits a => a -> Int -> a
`shiftR` Int
1) a1 -> a1 -> a1
forall a. Bits a => a -> a -> a
`xor` a1 -> a1
forall a. Num a => a -> a
negate (a1
w a1 -> a1 -> a1
forall a. Bits a => a -> a -> a
.&. a1
1))
{-# INLINE zzDecode64 #-}
zzDecode64 :: Word64 -> Int64
zzDecode64 :: Word64 -> Int64
zzDecode64 = Word64 -> Int64
forall a a1. (Num a, Integral a1, Bits a1) => a1 -> a
zzDecode