{-# LANGUAGE MagicHash #-}
module Data.RangeMin.Common.Types (LEq, RM, toRM, runRM, onRM, module Data.RangeMin.Common.Types.IPVector) where

import GHC.Exts (Int#, Int(..))
import Data.RangeMin.Common.Types.IPVector

type RM = (Int# -> Int# -> Int#)

-- | A function of type @'LEq' a@ is used as if it were @('<=')@ for comparison purposes.
type LEq a = a -> a -> Bool

{-# INLINE toRM #-}
toRM :: (Int -> Int -> Int) -> RM
toRM f = \ i# j# -> case f (I# i#) (I# j#) of
	I# k# -> k#

runRM :: RM -> Int -> Int -> Int
runRM f (I# i#) (I# j#) = I# (f i# j#)

{-# INLINE onRM #-}
onRM :: (Int -> Int) -> RM -> RM
onRM f rm = toRM (\ i j -> f (runRM rm i j))