{-# LANGUAGE CPP #-} #if __GLASGOW_HASKELL__ {-# LANGUAGE MagicHash #-} #endif module Data.RangeMin.Common.Types (IP (..), LEq, RM, toRM, runRM, Index, Value, Length, RangeMin, PVector, VVector) where import qualified Data.Vector.Primitive as P import qualified Data.Vector as V #if __GLASGOW_HASKELL__ import GHC.Exts (Int#, Int(..)) #endif type PVector = P.Vector type VVector = V.Vector -- | The type of a vector index. type Index = Int -- | The type for which this package provides a specialized range-min implementation. type Value = Int -- | The type of the length of a vector. type Length = Int -- | A range min function. Given an index @i@ and a length @m@, returns the -- minimum element in the range @i..i+m-1@. type RangeMin = Index -> Length -> Index -- | A function of type @'LEq' a@ is used as if it were @('<=')@ for comparison purposes. -- This function /must/ be a total ordering. type LEq a = a -> a -> Bool data IP = IP {-# UNPACK #-} !Int {-# UNPACK #-} !Int toRM :: (Index -> Length -> Index) -> RM runRM :: RM -> Index -> Length -> Index #if __GLASGOW_HASKELL__ type RM = (Int# -> Int# -> Int#) {-# INLINE toRM #-} toRM f = \ i# j# -> case f (I# i#) (I# j#) of I# k# -> k# runRM f (I# i#) (I# j#) = I# (f i# j#) #else type RM = Index -> Index -> Index toRM = id runRM = id #endif