Selecting Array type

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 wheither 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. test e = smartArray (0,10) [ (i,e) | i <- [0..10]]

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.

Jeff φ wrote:
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.
Using ghc-6.8.2 I get test.hs:30:0: Functional dependencies conflict between instance declarations: instance [overlap ok] SmartArraySelector UArray Bool -- Defined at test.hs:30:0-46 instance [overlap ok] SmartArraySelector Array e -- Defined at test.hs:49:0-40 [more of the same for the other classes omitted] The offending lines are instance SmartArraySelector UArray Bool where vs. instance SmartArraySelector Array e where Note that it explicitly says 'overlap ok' but the functional dependencies cannot be fulfilled. You defined class (IArray a e) => SmartArraySelector a e | e -> a Your generic instance says that it determines the 'a' type for /all/ types 'e' as 'Array'. This conflicts with the other instance which says it determines the 'a' for the specific type 'Bool' as 'UArray'. That leaves the question how to achieve what you want, for which unfortunately I have no answer. Cheers Ben

2008/2/19 Jeff φ
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
Well, I'm not sure of the answer to your question, so I'll just make a frivolous observation instead: I think you can leave off the "where" on instances without any method definitions. -Brent

On Wed, 20 Feb 2008, Brent Yorgey wrote:
2008/2/19 Jeff ö
:
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
Well, I'm not sure of the answer to your question, so I'll just make a frivolous observation instead: I think you can leave off the "where" on instances without any method definitions.
Haddock 0.* makes a difference at this point.

Oleg's done a lot of work here; there's a bunch of magic that can be done with TypeCast. I took my inspiration from here: http://okmij.org/ftp/Haskell/typecast.html#ambiguity-resolution Here are some tests in ghci (note that I specialized the index type in "test" to Int to make this shorter; doing so isn't technically required): Prelude SmartArray> :t test (1::Int) test (1::Int) :: Data.Array.Base.UArray Int Int Prelude SmartArray> :t test (1::Int, 2::Int) test (1::Int, 2::Int) :: GHC.Arr.Array Int (Int, Int) Prelude SmartArray> :t test "Foo" test "Foo" :: GHC.Arr.Array Int [Char] Prelude SmartArray> :t test False test False :: Data.Array.Base.UArray Int Bool Prelude SmartArray> The trick is to represent whether a type is boxed or not via a type-level boolean, which you can then use to affect the instance selecton. Here is the source: {-# OPTIONS_GHC -fglasgow-exts -fbreak-on-exception -fallow-undecidable-instances -fallow-overlapping-instances #-} module SmartArray where 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 -- 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.) class IsUnboxed t b | t -> b instance TypeCast b HTrue => IsUnboxed Bool b instance TypeCast b HTrue => IsUnboxed Char b instance TypeCast b HTrue => IsUnboxed Double b instance TypeCast b HTrue => IsUnboxed Float b instance TypeCast b HTrue => IsUnboxed Int b instance TypeCast b HFalse => IsUnboxed a b -- overlap here class IArray a t => ArraySelector b t a | b t -> a -- where array' :: Ix i => b -> (i,i) -> [(i,t)] -> a i t instance IArray UArray a => ArraySelector HTrue a UArray -- where array' _ = array instance ArraySelector HFalse a Array -- where array' _ = array instance (IsUnboxed t b, ArraySelector b t a) => SmartArraySelector a t test :: SmartArraySelector a e => e -> a Int e test e = smartArray (0,10) [ (i,e) | i <- [0..10]] -- Magic toolbox that solves everything! Thanks Oleg! data HTrue data HFalse class TypeCast a b | a -> b, b->a where typeCast :: a -> b class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast'' instance TypeCast'' () a a where typeCast'' _ x = x
participants (5)
-
Ben Franksen
-
Brent Yorgey
-
Henning Thielemann
-
Jeff φ
-
Ryan Ingram