{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.Halves (
Halves(..)
, quarters
, eighths
, upperHalf
, lowerHalf
, swappedHalves
, chunkHalves
, chunkQuarters
, chunkEighths
, collectHalves
, collectQuarters
, collectEighths
, finiteBitHalves
) where
import Control.Lens
import Data.Bits (Bits (..), finiteBitSize)
import Data.Halves.FiniteBits (AsFiniteBits (..))
import Data.Halves.Tuple (tuple4, tuple8)
import Data.Int
import Data.Monoid ((<>))
import Data.Word
class Halves a b | a -> b, b -> a where
halves :: Iso' a (b, b)
instance Halves Word16 Word8 where
halves =
finiteBitHalves
instance Halves Word32 Word16 where
halves =
finiteBitHalves
instance Halves Word64 Word32 where
halves =
finiteBitHalves
instance Halves Int16 Int8 where
halves =
finiteBitHalves
instance Halves Int32 Int16 where
halves =
finiteBitHalves
instance Halves Int64 Int32 where
halves =
finiteBitHalves
quarters ::
(Halves a b, Halves b c) =>
Iso' a (c, c, c, c)
quarters =
halves . bimapping halves halves . tuple4
eighths ::
(Halves a b, Halves b c, Halves c d) =>
Iso' a (d, d, d, d, d, d, d, d)
eighths =
halves . bimapping quarters quarters . tuple8
upperHalf ::
(Halves a b) =>
Lens' a b
upperHalf =
halves . _1
lowerHalf ::
(Halves a b) =>
Lens' a b
lowerHalf =
halves . _2
swappedHalves ::
(Halves a b) =>
Iso' a a
swappedHalves =
halves . swapped . from halves
chunkHalves ::
(Halves a b) =>
Iso' [b] ([a], [b])
chunkHalves =
iso f g
where
f (a:b:xs) =
([(a, b) ^. from halves], []) <> f xs
f xs =
([], xs)
g (xs, ys) =
((h . (^. halves)) =<< xs) <> ys
h (a, b) =
[a, b]
chunkQuarters ::
(Halves a b, Halves b c) =>
Iso' [c] ([a], [c])
chunkQuarters =
iso f g
where
f (a:b:c:d:xs) =
([(a, b, c, d) ^. from quarters], []) <> f xs
f xs =
([], xs)
g (xs, ys) =
((h . (^. quarters)) =<< xs) <> ys
h (a, b, c, d) =
[a, b, c, d]
chunkEighths ::
(Halves a b, Halves b c, Halves c d) =>
Iso' [d] ([a], [d])
chunkEighths =
iso f g
where
f (a:b:c:d:e:f':g':h':xs) =
([(a, b, c, d, e, f', g', h') ^. from eighths], []) <> f xs
f xs =
([], xs)
g (xs, ys) =
((h . (^. eighths)) =<< xs) <> ys
h (a, b, c, d, e, f', g', h') =
[a, b, c, d, e, f', g', h']
collectHalves ::
(Halves a b) =>
Lens' [b] [a]
collectHalves =
chunkHalves . _1
collectQuarters ::
(Halves a b, Halves b c) =>
Lens' [c] [a]
collectQuarters =
chunkQuarters . _1
collectEighths ::
(Halves a b, Halves b c, Halves c d) =>
Lens' [d] [a]
collectEighths =
chunkEighths . _1
finiteBitHalves ::
forall a b c.
(Integral a, Integral b, Integral c, Bits a, AsFiniteBits b c) =>
Iso' a (b, b)
finiteBitHalves =
iso f g
where
s =
finiteBitSize (zeroBits :: c)
f a =
(fromIntegral (unsafeShiftR a s), fromIntegral a)
g (a, b) =
unsafeShiftL (fromIntegral a) s .|. fromIntegral (b ^. asFiniteBits)