Choosing data representation based on type

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?

1 Like

Generally, do not expect “not” to be easy. At least it won’t be automatable.

Here is why everyone thinks “not” is intuitive: The constraint system looks very much like Prolog, and everyone has had great success with “not” in Prolog, thanks to “negation by failure” under the Closed World Assumption (IOW all global information is available).

Here is why everyone is doomed to be disappointed: Thanks to separate compilation, you have zero global information, therefore “negation by failure” cannot work. At least not automatically.

3 Likes

Hi Laurent, I’m surprised you can use DatatypeContexts with data familys/ newtype instance. I’d expect a warning:

    -XDatatypeContexts is deprecated: It was widely considered a misfeature, and
 has been removed from the Haskell language.

(Try just commenting out the second newtype instance: do you now get a complaint about the DatatypeContext?)

One of the reasons it’s considered a misfeature is it doesn’t restrict or ‘filter’ the datatype (instance) in any way. Rather, it requires at every use of the datatype that your code carries the same constraint.

Yeah, as @treblacy points out, this is a FAQ – see thousands of explanations on StackOverflow. It’s got nothing to do with separate compilation. The constraint on a class decl is requiring that constraint to be satisfied, only after satisfying an instance. Similarly the constraint on the instance decl is required after matching the types in the instance head.

You can sometimes kinda get a “negative of” a constraint, but it needs a great deal of going round the houses and tricky extensions.

Addit: re " thousands of explanations on StackOverflow". A lot of them give the right answer (you just can’t do that – or not easily), but I’m amazed how many of the explanations are giving irrelevant grounds. It’s not because of separate compilation; it’s not to make instance search efficient. It derives from logic ex falso quodlibet: a type is an instance of class C providing it isn’t an instance of D; a type is an instance of D providing it isn’t an instance of C. Ok so which class does it belong to? And you might have a long chain of dozens of instances depending on not some other dozens of instances. The compiler isn’t going to even try to see if there’s some consistent overall logic.

2 Likes

To answer my own surprise: yes you can use DatatypeContexts with data familys/newtype instance. You do indeed get the warning I quoted, but it’s just a warning.

The reason for the Conflicting family instance declarations error is that the LHS heads of the decl are identical (modulo alpha renaming) – that is: MyArray u === MyArray b.

The DatatypeContext is not taken into account until after comparing the heads, just as an instance context is not taken into account. See my explanation above.

1 Like

Thank you for your explanation, it makes more sense now.

Looking at the usage of type families in Data.Vector.Unboxed, looks like the instance for every element type is explicitly listed:

newtype instance Vector    () = V_Unit Int
(...)
newtype instance Vector    Float = V_Float  (P.Vector    Float)
(...)
newtype instance Vector    Char = V_Char  (P.Vector    Char)
(...)

and there’s no ‘fallback’ instance like:

newtype instance Vector a = V_Boxed (Vector a)
1 Like

Yes. You can make a ‘fallback’ with closed type families. But then your instances would be – er – closed/users couldn’t add instances for their own types.

Or with OVERLAPPABLE instances for a class (not for a newtype/data family). But now beware the ‘orphan instances’ gotchas.

2 Likes