[Haskell-cafe] Re: Selecting Array type

Jeff φ jeff1.61803 at gmail.com
Tue Feb 19 14:48:09 EST 2008


I apologize if this has already been posted.  I sent the following message
several hours ago and I haven't seen it post.  So, I'm resending.

I'm trying to create a type called SmartArray.  It is a type synonym for an
array.  If the element type can be unboxed, then SmartArray is an unboxed
array.  Otherwise, it is a boxed array.

For instance,

(SmartArray Int Double) is the same as (UArray Int Double)
(SmartArray Int String) is the same as (Array Int String)

However, my implementation of SmartArray requires me to create an instance
of a selector class to tell the compiler whether the type is boxed or
unboxed.  I'm hoping to avoid creating instances of the selector class for
every possible type.  I'd be grateful for any suggestions.

Please see my code:

{-# OPTIONS_GHC
    -fglasgow-exts
    -fbreak-on-exception
    -XOverlappingInstances
#-}

import Data.Ix
import Data.Array.Unboxed
import Data.Complex

type SmartArray i e = (Ix i, SmartArraySelector a e) => (a i e)

-- smartArray is similar to array function from Data.Array. But, it
-- will return a UArray if e can be unboxed.  Otherwise, it returns an
Array.

smartArray :: (i, i) -> [(i, e)] -> SmartArray i e
smartArray bnd eLst = array bnd eLst


class (IArray a e) => SmartArraySelector a e | e -> a where
    arrayType :: Ix i => a i e -> a i e
    arrayType = id

-- SmartArraySelector selects UArray for all types that can be
-- unboxed.  An instance has to be created for each unboxed type.  I'd
-- like to avoid listing all unboxed types here.  However, since there
-- are only a few unboxed types, it's not too burdensome to list them
-- all.  (For brevity, I didn't create all possible instances.)

instance SmartArraySelector UArray Bool   where
instance SmartArraySelector UArray Char   where
instance SmartArraySelector UArray Double where
instance SmartArraySelector UArray Float  where
instance SmartArraySelector UArray Int    where


-- SmartArraySelector selects Array for all types that can't be
-- unboxed.  An instance has to be created for EVERY possible unboxed
-- type that might be used with SmartArray.  Since, the list of
-- possible types is unlimited, this is pretty annoying.

instance SmartArraySelector Array String where
instance SmartArraySelector Array (Complex e) where


-- I'd like to replace all the boxed instances above with one instance
-- like . . .
--
-- instance SmartArraySelector Array e where
--
-- However, this generates an error even though,
-- -XOverlappingInstances turned on.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080219/041b0a32/attachment.htm


More information about the Haskell-Cafe mailing list