[GHC] #9112: data families with representational matching
GHC
ghc-devs at haskell.org
Thu May 15 07:49:44 UTC 2014
#9112: data families with representational matching
-------------------------------------+------------------------------------
Reporter: jwlato | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by simonpj):
The trouble is that you can say
{{{
data instance MVector s Int = ...rep1...
data instance MVector s Age = ...rep2...
}}}
so that `MVector` over `Int` has an entirely different representation to
`MVector` over `Age`. Indeed that is often the very reason that people
define a newtype in the first place! For example, if you want `sort` to
sort into reverse order, can write
{{{
import Data.Ord( Down(..) )
downSort :: Ord a => [a] -> [a]
downSort xs = coerce (sort (coerce xs :: [Down a]))
}}}
We coerce the `[a]` to `[Down a]`, then sort (using `Down`'s ordering),
then coerce back.
It's going to be quite confusing `data instance` can sometimes match on a
newtype, and sometimes not. And then there are nested cases to worry
about:
{{{
newtype MVector s [Age] = ...
newtype MVector s [Int] = ...
}}}
Moreover, you still (presumably) want `MVector s Age` and `MVector s Int`
to be distinct types!
None of this smells good to me.
But here's an idea. You want `MVector s Age` and `MVector s Int` But you
want them to be represented the same way. That's what we use newtypes for.
So how about this:
{{{
newtype instance MVector s Age = MVA (MVector s Int)
}}}
Would that help? For example, this compiles without complaint:
{{{
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies,
GeneralizedNewtypeDeriving #-}
module T9112 where
class MVectorClass (v :: * -> * -> *) a where
basicLength :: v s a -> Int
data family MVector s a
data instance MVector s Int = MV -- implementation not important
newtype Age = Age Int deriving (MVectorClass MVector)
newtype instance MVector s Age = MV1 (MVector s Int)
instance MVectorClass MVector Int where
basicLength x = 0
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9112#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list