{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-ignore-asserts #-} module Data.RangeMin.Cartesian.Spec (invertValue, 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 #include "MachDeps.h" {-# INLINE [0] equivVectorMin #-} {-# INLINE [0] equivVectorMax #-} equivVectorMin, equivVectorMax :: (Ord a, Vector v a) => v a -> PVector Value equivVectorMin = equivVectorBy (<=) 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 (fmap f (G.stream xs)) {-# INLINE equivInjectorMin #-} {-# INLINE equivInjectorMax #-} equivInjectorMin, equivInjectorMax :: (Ord a, Vector v a, Injective a) => a -> v a -> PVector Value equivInjectorMin _ = equivMap inject 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 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 #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; \ #-} #define wordInject(int,word) \ instance Injective word where { \ inject w = if w < minInt then fromIntegral w + minBound \ else fromIntegral (w - minInt) \ where minInt = assert (shiftL (-1 :: int ) intBits \ == minBound) (bit intBits); \ intBits = bitSize (0 :: int ) - 1 } wordInject(Int,Word) {-# 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) wordInject(Int32,Word32) equivVector(Word32) #if SIZEOF_INT >= SIZEOF_INT64 instance Injective Int64 equivVector(Int64) wordInject(Int64,Word64) equivVector(Word64) #endif #endif