[GHC] #13328: Foldable, Functor, and Traversable deriving handle phantom types badly
GHC
ghc-devs at haskell.org
Tue Mar 7 02:11:00 UTC 2017
#13328: Foldable, Functor, and Traversable deriving handle phantom types badly
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.4.1
Component: Compiler | Version: 8.1
Resolution: | Keywords: deriving-perf
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Sadly, a role annotation would affect the datatype even in the module in
which it is originally defined:
{{{#!hs
{-# LANGUAGE RoleAnnotations, TemplateHaskell #-}
import Language.Haskell.TH
type role Foo nominal
data Foo a = Foo a
$(return [])
main :: IO ()
main = putStrLn $(reifyRoles ''Foo >>= stringE . show)
}}}
{{{
$ runghc Bug.hs
[NominalR]
}}}
The issue is really that role annotations are only a crude approximation
of the property we actually want here. For `Functor` and `Traversable`, we
really are using `coerce`, so a phantom role annotation is precisely what
you need. But we aren't using `coerce` in the proposed `Foldable`
instance, and moreover, the property we really want to ensure is that the
type parameter doesn't appear anywhere in any constructor's fields. Sadly,
a phantom role does not always imply this.
I'm tempted to suggest a workaround in which we re-infer the roles for
every data type, but this time, we ignore all user-supplied role
annotations. That way, we would get precisely the right information about
whether the last type parameter appears somewhere in the datatype's
definition. But sadly, this would necessarily break abstraction in the
case where a constructor's field mentions an abstract type that has been
given a role annotation of representational or nominal.
Another option we could choose is to simply skip over this optimization
for `Foldable`. That's likely not what you'd prefer, but there are a
number of properties which make dealing with `Foldable` awkward that
aren't present with `Functor` and `Traversable`.
In any event, presenting this idea via a proposal would certainly be a
good thing. I'm curious to know what others think about this.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13328#comment:9>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list