{-# LANGUAGE BangPatterns, CPP #-} {-# OPTIONS_GHC -fno-ignore-asserts #-} -- | The purpose of "Data.RangeMin.Cartesian" is to convert a vector -- into a @'PVector' 'Value'@ with equivalent range-min queries. -- This module provides rewrite rules to recognize when the original -- vector is in this form, or can be converted into this form with -- stream fusion. module Data.RangeMin.Cartesian.Spec (equivMap, equivVectorMin, equivVectorMax, equivVectorBy, Injective) where import Control.Exception (assert) import Data.Bits (Bits (..)) import Data.Int import Data.Word import Data.RangeMin.Cartesian import Data.RangeMin.Common.Vector import Data.RangeMin.Common.Types import qualified Data.Vector.Generic as G import qualified Data.Vector.Fusion.Stream as S #include "MachDeps.h" {-# INLINE [0] equivVectorMin #-} equivVectorMin :: (Ord a, Vector v a) => v a -> PVector Value equivVectorMin = equivVectorBy (<=) {-# INLINE [0] equivVectorMax #-} equivVectorMax :: (Ord a, Vector v a) => v a -> PVector Value equivVectorMax = equivVectorBy (>=) {-# INLINE invertVector #-} invertVector :: PVector Value -> PVector Value invertVector = G.map invertValue -- An order-reversing bijection on 'Value'. invertValue :: Value -> Value invertValue x = assert ((minBound :: Int) == -maxBound - 1) (-1 - x) {-# INLINE equivMap #-} equivMap :: (Ord a, Vector v a) => (a -> Value) -> v a -> PVector Value equivMap f xs = G.unstream (S.map f (G.stream xs)) {-# INLINE equivInjectorMin #-} equivInjectorMin :: (Ord a, Vector v a, Injective a) => a -> v a -> PVector Value equivInjectorMin _ xs = equivMap inject xs {-# INLINE equivInjectorMax #-} equivInjectorMax :: (Ord a, Vector v a, Injective a) => a -> v a -> PVector Value equivInjectorMax _ xs = invertVector (equivMap inject xs) -- | A type is an instance of 'Injective' if it has a natural order-preserving injection -- into 'Int', typically but not always 'fromEnum'. Functions like @rangeMin@ and -- @unsafeVecRangeMax@ which use the element type's natural ordering may be auto-specialized -- when the element type is an 'Injective' instance. class Enum a => Injective a where inject :: a -> Value inject = fromEnum -- Warning to hackers: making an 'Injective' instance isn't sufficient to get rewriting -- for a particular type; it also requires appropriate rewrite rules. If you have another type -- that you want efficient range-mins on, just do the conversion yourself. instance Injective Bool instance Injective Int instance Injective Char instance Injective Ordering instance Injective () instance Injective Int8 instance Injective Int16 instance Injective Word8 instance Injective Word16 instance Injective Word where inject w | w < minInt = fromIntegral w + minBound | otherwise = fromIntegral (w - minInt) where minInt = assert (shiftL (-1 :: Int) intBits == minBound) (bit intBits) intBits = bitSize (0 :: Int) - 1 #define equivVector(ty) \ {-# RULES \ "equivVectorMin/ty" forall xs . \ equivVectorMin xs = equivInjectorMin \ (toEnum 0 :: ty) xs; \ "equivVectorMax/ty" forall xs . \ equivVectorMax xs = equivInjectorMax \ (toEnum 0 :: ty) xs; \ #-} {-# RULES "equivVectorMin/Data.Vector.Primitive Int" forall xs . equivVectorMin xs = xs; "equivVectorMax/Data.Vector.Primitive Int" forall xs . equivVectorMax xs = invertVector xs; "equivVectorMin/Int" [1] forall xs . equivVectorMin xs = equivInjectorMin (0 :: Int) xs; "equivVectorMax/Int" [1] forall xs . equivVectorMax xs = equivInjectorMax (0 :: Int) xs; #-} equivVector(Bool) equivVector(Char) equivVector(Ordering) equivVector(()) equivVector(Int8) equivVector(Int16) equivVector(Word8) equivVector(Word16) equivVector(Word) #if SIZEOF_INT >= SIZEOF_INT32 instance Injective Int32 equivVector(Int32) instance Injective Word32 where inject w | w < minInt32 = fromIntegral w + fromIntegral (minBound :: Int32) | otherwise = fromIntegral (w - minInt32) where minInt32 = assert (shiftL (-1 :: Int32) intBits32 == minBound) (bit intBits32) intBits32 = bitSize (0 :: Int32) - 1 equivVector(Word32) #if SIZEOF_INT >= SIZEOF_INT64 instance Injective Int64 equivVector(Int64) instance Injective Word64 where inject w | w < minInt64 = fromIntegral w + fromIntegral (minBound :: Int64) | otherwise = fromIntegral (w - minInt64) where minInt64 = assert (shiftL (-1 :: Int64) intBits64 == minBound) (bit intBits64) intBits64 = bitSize (0 :: Int64) - 1 equivVector(Word64) #endif #endif