
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.