Confusion with GeneralizedNewtypeDeriving + MultiParamTypeClasses

Hello all, I have run into a bit of a strange case where I can't get `GeneralizedNewtypeDeriving` to work as I'd like. In the `vector` package, under `Data.Vector.Generic`, there is a generic vector typeclass of the form `Vector v a`, where `v` is the vector type and `a` is the type of items in the vector. I have a newtype wrapper of the form `newtype Neuron a = Neuron (Vector a)`. (Note that "Vector" here is a type "Vector", not the two-parameter constraint also called "Vector".) I would like to be able to use everything in `Data.Vector.Generic` on `Neuron`s. Using `GeneralizedNewtypeDeriving`, I immediately run up against the issue that the `Vector` typeclass doesn't have the correct form of `* -> Constraint`. According to section 7.5.5.1 of https://downloads.haskell.org/~ghc/7.8.4/docs/html/users_guide/deriving.html , we should be able to derive instances of multi-parameter type classes, provided the newtype is the last parameter of the typeclass. The problem here is that it's the first parameter. Using `ConstraintKinds` to make a constraint synonym (of the form `FlippedVectorClass a v`) so that I can do something like `newtype Neuron a = Neuron (Vector a) deriving (FlippedVectorClass a)` also doesn't seem to work. Does anyone have any advice for how to make this work? It's quite tempting just to make `type Neuron a = Vector a`, but I'd rather do a proper wrapper type. Cheers, Will

Does anyone have any advice for how to make this work? It's quite tempting just to make `type Neuron a = Vector a`, but I'd rather do a proper wrapper type.
Here's my attempt (no, I didn't succeed): {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE ExistentialQuantification #-} import qualified Data.Vector.Generic as Generic import Data.Vector newtype Neuron a = Neuron (Vector a) --deriving instance (Generic.Vector Neuron a) -- Can't make a derived instance of ‘Generic.Vector Neuron a’: -- The last argument of the instance must be a data or newtype application -- In the stand-alone deriving instance for ‘Generic.Vector Neuron a’ newtype Any a = Any a --deriving instance (Generic.Vector Neuron (Any a)) {- Var/Type length mismatch: [a_aGM] [] Var/Type length mismatch: [a_aGM] [] Var/Type length mismatch: [a_aGM] [] Var/Type length mismatch: [a_aGM] [] Var/Type length mismatch: [a_aGM] [] Var/Type length mismatch: [a_aGM] [] Var/Type length mismatch: [a_aGM] [] Var/Type length mismatch: [a_aGM] [] Var/Type length mismatch: [a_aGM] [] ghc: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): tcTyVarDetails a_aGM Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug -} -- data Foo = Foo -- deriving instance (Generic.Vector Neuron Foo) -- Ditto. -- data Bar = forall a. Bar a -- deriving instance (Generic.Vector Neuron Bar) -- Same error.
participants (2)
-
Nikita Karetnikov
-
William Yager