{-# OPTIONS_GHC -fglasgow-exts #-} -- | A compilation of minor array combinators used extensively in "Data.RangeMin". module Data.RangeMin.Internal.HandyArray where import Data.Array.IArray import Data.Array.Base -- | asPureArray is a simple syntax to force an ambiguous array to a standard 'Array'. asPureArray :: Ix i => Array i e -> Array i e asPureArray = id {-# INLINE listToArray #-} -- | @listToArray@ converts a list to an arbitrary array type. listToArray :: IArray a e => [e] -- ^ A list of arbitrary elements. -> a Int e -- ^ A zero-indexed array containing precisely the elements of the list. listToArray list = listArray (0, length list - 1) list {-# INLINE listToArray' #-} -- | @listToArray' n l@ is a version of 'listToArray' used when the array size is foreknown. listToArray' :: IArray a e => Int -> [e] -> a Int e listToArray' n list = listArray (0, n - 1) list {-# INLINE arraySize #-} -- | Shorthand for the size of an array. arraySize :: (Ix i, IArray a e) => a i e -> Int arraySize = rangeSize . bounds -- used for both coercing an untyped array to a standard Array, and simultaneously returning the lookup function -- of that array {-# INLINE pureLookup #-} -- | A lookup function that also forces its array argument to an 'Array'. pureLookup :: Ix i => Array i e -> i -> e pureLookup = (!) {-# INLINE pureUnsafeLookup #-} -- | An unsafe lookup function on standard 'Array' types that does not range-check its argument. pureUnsafeLookup :: Ix i => Array i e -> Int -> e pureUnsafeLookup = unsafeAt {-# INLINE unsafeMemoize #-} -- | A memoization function. unsafeMemoize :: (Int -> e) -- ^ An arbitrary function on integer values. -> Int -- ^ n -> (Int -> e) -- ^ A function on integers from @0@ to @n-1@ that memoizes its values. unsafeMemoize f n = unsafeMemoize' f (n-1) {-# INLINE unsafeMemoize' #-} -- | A memoization function that indexes to @n@ inclusive. unsafeMemoize' :: (Int -> e) -- ^ An arbitrary function on integer values. -> Int -- ^ n -> (Int -> e) -- ^ A function on integers from @0@ to @n@ that memoizes its values. unsafeMemoize' f n = pureUnsafeLookup (listArray (0, n) (map f [0..n])) {-# INLINE listLookup' #-} -- | Given a list and its length, memoizes lookups on the list. listLookup' :: Int -> [e] -> (Int -> e) listLookup' n l = pureUnsafeLookup (listArray (0, n-1) l)