Skip to content
Snippets Groups Projects
Commit 9646846a authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1998-05-29 12:29:02 by simonm]

Replace more GENERATE_SPECs with explicit SPECIALISE.
parent 41c4e4a0
No related merge requests found
......@@ -40,23 +40,23 @@ infixl 9 !, //
{-# INLINE assocs #-}
#endif
{-# GENERATE_SPECS listArray a{~,Int,IPr} b{} #-}
{-# SPECIALISE listArray :: (Int,Int) -> [b] -> Array Int b #-}
listArray :: (Ix a) => (a,a) -> [b] -> Array a b
listArray b vs = array b (zipWith (\ a b -> (a,b)) (range b) vs)
{-# GENERATE_SPECS indices a{~,Int,IPr} b{} #-}
{-# SPECIALISE indices :: Array Int b -> [Int] #-}
indices :: (Ix a) => Array a b -> [a]
indices = range . bounds
{-# GENERATE_SPECS elems a{~,Int,IPr} b{} #-}
{-# SPECIALISE elems :: Array Int b -> [b] #-}
elems :: (Ix a) => Array a b -> [b]
elems a = [a!i | i <- indices a]
{-# GENERATE_SPECS assocs a{~,Int,IPr} b{} #-}
{-# SPECIALISE assocs :: Array Int b -> [(Int,b)] #-}
assocs :: (Ix a) => Array a b -> [(a,b)]
assocs a = [(i, a!i) | i <- indices a]
{-# GENERATE_SPECS amap a{~,Int,IPr} b{} c{} #-}
{-# SPECIALISE amap :: (b -> c) -> Array Int b -> Array Int c #-}
amap :: (Ix a) => (b -> c) -> Array a b -> Array a c
amap f a = array b [(i, f (a!i)) | i <- range b]
where b = bounds a
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment