4

Given the following class:

class ListIsomorphic l where
    toList   :: l a -> [a]
    fromList :: [a] -> l a

How can I write a instance for vector types using Data.Vector.Generic? This doesn't work:

instance (V.Vector v a) => ListIsomorphic v where
    toList   = V.toList
    fromList = V.fromList

Giving me:

test.hs:31:10:
    Variable ‘a’ occurs more often than in the instance head
      in the constraint: V.Vector v a
    (Use UndecidableInstances to permit this)
    In the instance declaration for ‘ListIsomorphic v’
MaiaVictor
  • 51,090
  • 44
  • 144
  • 286

2 Answers2

6

Don't. Adding an instance for all v to your Listable class will become cumbersome to use due to overlapping instances.

A Vector v a => v isn't isomorphic to a list because it is constrained by which items can be elements of the list. You'd need a class that captures this constraint, something like

{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}

import Data.Constraint

class ConstrainedList l where
    type Elem l a :: Constraint
    toList   :: Elem l a => l a -> [a]
    fromList :: Elem l a => [a] -> l a

Instead of adding ConstrainedList instances for all types Vector v a => v which would get us into overlapping instances territory, instead we'll define it only for the types we're interested in. The following will cover all the types with a Vector instance in the vector package.

import qualified Data.Vector.Primitive as VP
import qualified Data.Vector.Generic as VG

instance ConstrainedList VP.Vector where
    type Elem VP.Vector a = VG.Vector VP.Vector a
    toList   = VG.toList
    fromList = VG.fromList

Instances for other types

You can write a ConstrainedList instance for regular lists [] that requires only the empty constraint for its elements.

instance ConstrainedList [] where
    type Elem [] a = ()
    toList   = id
    fromList = id

Anywhere that uses toList or fromList will also require an Elem l a instance.

cmap :: (ConstrainedList l, Elem l a, Elem l b) => (a -> b) -> l a -> l b
cmap f = fromList . map f . toList

When we know concrete types for the lists and elements these functions will be easy to use without messing around with constraints.

cmap (+1) [1,2,3,4]

Here Be Dragons

Don't try what follows. If you are interested in the class of things that are isomorphic to lists without additional constraints, just make another class for it. This just demonstrates what you can do when you've designed yourself into a corner: summon a dragon.

You can also write functions that require a proof that there is no constraint on the elements of a ConstrainedList. This is way off into the realms of the constraints package and programming styles that aren't really supported by GHC, but there aren't enough constraints examples so I'll leave this one here.

{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}

map' :: forall l a b. (ConstrainedList l, () :=> Elem l a, () :=> Elem l b) =>
                      (a -> b) -> l a -> l b
map' f = case (ins :: () :- Elem l a) of { Sub Dict ->
         case (ins :: () :- Elem l b) of { Sub Dict ->
         fromList . map f . toList
         }}

We could check that a ConstrainedList has no constraint by just checking that Elem l a ~ (), but that wouldn't work if its constraint was written in a different way.

{-# LANGUAGE FlexibleInstances #-}

class Any a
instance Any a

data AList a = AList {getList :: [a]}
    deriving (Show)

instance ConstrainedList AList where
    type Elem AList a = Any a
    toList   = getList
    fromList = AList

() isn't the same type as Any a even though () implies Any a. The constraints package captures relationships like this by reifying them to the type classes Class and :=>

{-# LANGUAGE MultiParamTypeClasses #-}

--       class () => Any a
instance Class ()   (Any a) where
    cls = Sub Dict

-- instance ()  => Any a
instance    () :=> Any a where
    ins = Sub Dict

All of that work lets us easily reuse functions without providing all those dictionaries when a concrete list type is known.

map'' :: (a -> b) -> AList a -> AList b
map'' = map'
Cirdec
  • 24,019
  • 2
  • 50
  • 100
  • Thanks. I don't understand any of those advanced type system features, do you suggest any resource? – MaiaVictor Aug 20 '15 at 23:14
  • [`TypeFamilies`](https://wiki.haskell.org/GHC/Type_families) makes functions that match on types. It's used to define the `Elem` function that takes the type of the `ConstrainedList` instance and produces the constraint on its member elements. – Cirdec Aug 20 '15 at 23:19
  • [`ConstraintKinds`](https://downloads.haskell.org/~ghc/7.4.1/docs/html/users_guide/constraint-kind.html) lets you talk about the kind of constraints (the things to the left of `=>`). For example `Show :: * -> Constraint`, `Show a :: Constraint`, and `a ~ b :: Constraint`. There's some `GHC` module that defines [`Constraint :: BOX`](https://hackage.haskell.org/package/constraints/docs/Data-Constraint.html#t:Constraint); it's easier to import from constraints. – Cirdec Aug 20 '15 at 23:25
  • Wait, does this mean that functions written for "ListIsomorphic" (the original one) can't work for vectors? – MaiaVictor Aug 21 '15 at 02:07
  • Or, just... are you suggesting that I just use that class instead? In that case, how would I write the `type Elem ... = ...` line for common types such as `[]`? – MaiaVictor Aug 21 '15 at 02:47
  • 1
    @Viclib, Cirdec is suggesting you use the one they suggested instead. Designing classes is a bit of an art, and one I wouldn't claim to have mastered myself. But any time you see `instance ... => C a` or `instance ... => C (a ...)`, you've probably taken a wrong turn. Such instances will overlap with others one might wish to define. – dfeuer Aug 21 '15 at 03:20
  • How/where I'm supposed to learn that art? I still don't understand, though, if I use it, how do I write a normal instance - and does that mean I have to write functions like `(ListIso l, Elem l a) => (a → b) → l a → l b`, instead of just `ListIso l => (a → b) → l a → l b`? – MaiaVictor Aug 21 '15 at 03:25
  • 1
    The art is mostly learned by reading recent code by good library designers and making mistakes. Normal instances start with type constructors, not type variables. I have no idea what you are asking in the rest, and I have to go to sleep. – dfeuer Aug 21 '15 at 04:29
  • I understand now why dfeuer said this is an art. It is all the same... I can look at it and appreciate its beauty, yet wonder if I'd ever be able to come up with something similar. – MaiaVictor Aug 21 '15 at 06:36
5

I frequently run into this problem. Here are two solutions I've come up with:

  1. Change the class parameters:

    class ListIsomorphic l a where
      toList :: l a -> [a]
      fromList :: [a] -> l a
    
    instance (V.Vector v a) => Listable v a where
      ...
    
  2. Use constraint kinds

    class ListIsomorphic l where
      type C l a :: Constraint
      toList :: l a -> [a]
      fromList :: [a] -> l a
    
    instance Listable v where
      type C v a = (V.Vector v a)
      ...
    
crockeea
  • 21,651
  • 10
  • 48
  • 101
  • Are you sure? (2) gives me `‘Listable’ is applied to too many type arguments`. – MaiaVictor Aug 21 '15 at 02:05
  • I actually tried that before, but it gave me `‘V.Vector’ is applied to too many type arguments`... I tried a few combinations of that too. – MaiaVictor Aug 21 '15 at 02:45
  • My guess is that you have imported `Data.Vector` instead of `Data.Vector.Generic`, since the `Vector` types in those libraries take different number of arguments. – crockeea Aug 21 '15 at 02:59
  • Ah, or you might need some explicit kind signatures (`-XKindSignatures`). Something like `type C (l :: * -> *) a :: Constraint` , sorry I don't have a compiler with me right now. – crockeea Aug 21 '15 at 03:02