Hello all,
I’m trying to create an array type whose underlying representation depends on the type of its contents. In particular, if the contents of the array can be unboxed, I’d want to use Data.Vector.Unboxed.Vector
:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DatatypeContexts #-}
import qualified Data.Vector as Boxed
import qualified Data.Vector.Unboxed as Unboxed
data family MyArray a
newtype instance Unbox u => MyArray u = UnboxedArray (Unboxed.Vector u)
newtype instance MyArray b = BoxedArray (Boxed.Vector b)
From my experience with pattern-matching, I would have expected the second instance to be chosen for a type T
only if T
is not an instance of Unbox
. Unfortunately, I get a Conflicting family instance declarations
error and no suggestion of resolution.
In order to fix this, I would need something like the negative of Unbox
, i.e. a class who’s instances are all types in scope which are NOT instances of Unbox:
class Not (Unbox a) => Box a
newtype instance Unbox u => MyArray u = UnboxedArray (Unboxed.Vector u)
newtype instance Box b => MyArray b = BoxedArray (Boxed.Vector b)
The idea here is that all types are either part of Unbox
or Box
, which means that the type MyArray
can contain anything.
How can I create a class like Box
here?