Ok I think I found a solution to my problem however it requires a new
data type thus the is not completely transparent to the end user.
However using implicit conversion (which to my knowledge haskell does
not have) it can be made completely transparent.
import qualified Array
data Array_ c ix el ixel = MkArray c
type Array ix el = Array_ (Array.Array ix el) ix el (ix,el)
type Array' ix el = Array_ (Array.Array ix el) ix el
class Listable c a where
toList :: c a -> [a]
class Find c a b where
find :: a -> c (a,b) -> Maybe b
instance Listable [] a where
toList c = c
instance (Eq a, Listable c (a,b)) => Find c a b where
find a c = lookup a (toList c)
instance Ix ix => Listable (Array' ix el) (ix,el) where
toList (MkArray c) = Array.assocs c
instance Ix ix => Find (Array' ix el) ix el where
find a (MkArray c) = Just ((Array.!) c a)
-- now I rename the array functions
array :: Ix ix => (ix, ix) -> [(ix,el)] -> Array ix el
array a b = MkArray (Array.array a b)
listArray :: Ix ix => (ix, ix) -> [el] -> Array ix el
listArray a b = MkArray (Array.listArray a b)
-- etc...
-- However this will not work for exiting functions that I don't know
about.
-- For these the user will have to explitly convert to and from our new
-- Array structure to the orignal one:
toNewArray :: Array.Array ix el -> Array ix el
toNewArray a = MkArray a
fromNewArray :: Array ix el -> Array.Array ix el
fromNewArray (MkArray a) = a
-- A better solution (in my view) would be to have an implicit
conversion
-- which could have a syntax like:
--
--implicit :: Array.Array ix el -> Array ix el
--implicit a = MkArray a
--
--implicit :: Array ix el -> Array.Array ix el
--implicit (MkArray a) = a
--
-- Now whenever a function is given an Array_ but is expecting
-- an Array.Array (or vise versa) it will automatically perform the
-- conversion function. For example if a is an Array_
-- assocs a
-- will be interpreted as
-- assocs ((\(MkArray a) -> a) a)
-- and if a is an Array.Array
-- toList a
-- will be interpreted as
-- toList (MkArray a)
--
-- Thus the fact that toList really takes an Array_ will be completely
-- transparent to the end user
-- The renaming functions will also not be needed
So I was wondering if they any plans for bringing implicit conversions
into Haskell?
--
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/