Changes to Typeable

Edward Kmett ekmett at gmail.com
Wed Oct 3 15:03:14 CEST 2012


I'm definitely in favor of Plan A.

-Edward

On Wed, Oct 3, 2012 at 8:01 AM, Simon Peyton-Jones <simonpj at microsoft.com>wrote:

> Aha.  Gabor, you're right.  Here's my summary.
>
> * As soon as we allow constraint kinds, we can abstract over them.
>  Example:
>    data T (c :: * -> Constraint) = MkT (forall a. c a => a -> a)
>
> * Hence, (T Eq) and (T Num) are valid types.
>
> * Hence they need to be Typable
>
> * And hence we must have something very like
>      instance Typeable Eq where ...
>
> * All this is fine.  But we don't (ever) want the programmer to write
>    any instance of Typeable; that ways lies seg-faults, since we may
>    rely on their veracity.
>
> * For normal type we can say "use deriving", but not for classes,
>    which don't have a deriving clause
>
> * We could use "standalone deriving"
>      deriving instance Typeable Eq
>
> * Or alternatively we could make every data type and class
>    an instance of Typeable automatically; that would save tons
>    of lookup in the massive Typeable-instance table.
>
>    On reflection I'm quite in favour of this.
>
> * If we do make Typeable instances by default, there are two paths
>    Plan A (easy): make GHC derive Typeable for everything, deprecate
>             all uses of 'deriving Typeable'.  Small downside: some programs
>             that are currently rejected will be accepted.
>
>    Plan B (tiresome): have AutoDeriveTypable as an extension.  That
>            means maintaining the massive instance table.
>
>    Personally I vote for Plan A.   It's easier and more efficient to
> implement,
>    and the upside of Plan B is modest in the extreme.
>
> Opinions from anyone else?
>
> Simon
>
> |  -----Original Message-----
> |  From: Gábor Lehel [mailto:illissius at gmail.com]
> |  Sent: 25 September 2012 10:30
> |  To: Simon Peyton-Jones
> |  Cc: libraries at haskell.org
> |  Subject: Re: Changes to Typeable
> |
> |  On Mon, Sep 24, 2012 at 6:28 PM, Simon Peyton-Jones
> |  <simonpj at microsoft.com> wrote:
> |  > |  - Will it be possible to write e.g. deriving instance Typeable Eq?
> |  >
> |  > Not at the moment; we've only been thinking about Typable for things
> whose
> |  kinds bottom out in *, not Constraint.  There doesn't seem to be any
> fundamental
> |  obstacle -- but I can't yet see how it would be useful.
> |
> |  One aspect is that if you have SomeType :: Constraint -> * and want
> |  Typeable for SomeType c, which is *, you need Typeable c.
> |
> |  But the particular application I had in mind is that you could
> |  implement OO-style casting-to-interfaces in a relatively clean way.
> |
> |  class InterfaceCastable a where
> |      icast :: Typeable c => Proxy c -> a -> Maybe (Interface c)
> |
> |  data Interface c = forall a. (c a, InterfaceCastable a) => Interface a
> |
> |  instance InterfaceCastable (Interface c) where icast (Interface a) =
> icast a
> |
> |  deriveInterfaceCastable :: Name -> Q [Dec]
> |
> |  deriveInterfaceCastable could, for example, generate a Map TypeRep (a
> |  -> Any) based on the instances in scope for the named type, where the
> |  (a -> Any) is in reality a -> Interface c and the TypeRep is typeOf c,
> |  and then icast looks up the TypeRep for the constraint that it got,
> |  applies the function to its 'a' argument, and then unsafeCoerces the
> |  result back to Interface c. Which might be going into too much detail,
> |  but the point is that Typeable on constraints would be useful.
> |  (Workarounds are possible, the reason I ask whether this will be
> |  possible is whether it's worth working on them.)
> |
> |  >
> |  > |  - How about deriving instance Typeable Typeable? (It seems Proxy
> Proxy
> |  > |  works, so maybe this would too.)
> |  >
> |  > Ditto.
> |  >
> |  > |  - Does it make sense to have an instance for (~)?
> |  >
> |  > Ditto.
> |  >
> |  > |  - Will instances be provided for the types in base and built-in to
> GHC?
> |  >
> |  > Yes, that would make sense.
> |
> |  I should have said "for types which don't already have them and now
> |  could". But it seems you got my meaning.
> |
> |  >
> |  > |  Automatically generate Typeable instances for every type
> constructor
> |  > |  that is declared. 'deriving Typeable' becomes a no-op.
> |  >
> |  > Well, at the moment a type ONLY becomes an instance of a class if you
> ask for it
> |  to be so, so your proposal would be a change of principle.  Sometimes
> *omitting*
> |  an instance declaration may be important (eg to prevent a type being
> |  serialisable).   That said, I can't see when I'd want a type not to be
> Typeable.  I
> |  suppose it could be a compiler option.  I think the questions here are
> ones of
> |  software engineering rather than being technical.
> |
> |  Yes, it would be unorthodox. And it's definitely not applicable
> |  willy-nilly to other classes (where not having an instance can be
> |  important, as you say). But at the moment the only consequence I see
> |  of having to derive Typeable manually is hassle, with no upside.
> |  Typeable is increasingly a language feature rather than a library,
> |  with manual instances getting more-and-more discouraged, this would
> |  just take that train of thought further.
> |
> |  Although, even if this were implemented, you would still need
> |  'deriving Typeable' if you wanted to stay backwards compatible; and
> |  because it's a significant change to the language you would presumably
> |  have to hide it behind a language pragma, at which point instead of
> |  {-# LANGUAGE AutoDeriveTypeable #-} you might as well write 'deriving
> |  Typeable'; so maybe it wouldn't be so useful in practice.
> |
> |  >
> |  > Simon
> |  >
> |
> |
> |
> |  --
> |  Your ship was destroyed in a monadic eruption.
>
>
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20121003/5f7a6c1c/attachment-0001.htm>


More information about the Libraries mailing list