> On Jan 9, 2017, at 1:57 PM, Gershom B <[email protected]> wrote:
>
> Richard — your idea is really interesting. How would the dreaded role
> restriction have to be modified to detect and allow this sort of granularity?
It wouldn't. The role restriction is purely on a method-by-method basis. (Right
now, the role restriction is not enforced at the class level -- you just get a
type error on the method that GND produces. See below.) So this new feature
wouldn't interact with roles directly, at all.
Also, looking back through these emails, I realize my "insight" was really just
the logical conclusion of David's original suggestion. Not much of an insight
really, just some concrete syntax.
Richard
Example of bad GND:
> class Functor m => M m where
> join :: m (m a) -> m a
>
> newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
>
> instance Functor m => Functor (ReaderT r m) where
> fmap f x = ReaderT $ \r -> fmap f (runReaderT x r)
>
> instance M m => M (ReaderT r m) where
> join x = ReaderT $ \r -> join (fmap (($ r) . runReaderT) (runReaderT x r))
>
> newtype N m a = MkN (ReaderT Int m a)
> deriving (Functor, M)
>
This produces
> • Couldn't match representation of type ‘m (N m a)’
> with that of ‘m (ReaderT Int m a)’
> arising from the coercion of the method ‘join’
> from type ‘forall a.
> ReaderT Int m (ReaderT Int m a) -> ReaderT Int m a’
> to type ‘forall a. N m (N m a) -> N m a’
> NB: We cannot know what roles the parameters to ‘m’ have;
> we must assume that the role is nominal
> • When deriving the instance for (M (N m))
in GHC 8.0.1.
>
> —g
>
>
> On January 9, 2017 at 1:34:17 PM, Richard Eisenberg ([email protected])
> wrote:
>> I agree with David that using explicit `coerce`s can be quite verbose and
>> may need ScopedTypeVariables
>> and InstanceSigs. But visible type application should always work, because
>> class methods
>> always have a fixed type argument order. Regardless, requiring users to do
>> all this for
>> GND on Monad would be frustrating.
>>
>> Actually, I just had an insight about this: there is no reason to use one
>> deriving strategy
>> for all methods in an instance. I can think of 4 ways to fill in the
>> implementation of a class
>> method in an instance:
>>
>> 1. Explicit, hand-written implementation
>> 2. Defaulting to the implementation written in the class (or `error
>> "undefined method"`
>> in the absence of a default. This is essentially the default default.)
>> 3. Stock implementation provided by GHC
>> 4. Coerce
>>
>> Ways 2, 3, and 4 all have extra restrictions: Way 2 might have extra type
>> constraints due
>> to a `default` signature. Way 3 restricts the choice of class and type. Way
>> 4 works only
>> on newtypes and then imposes role restrictions on the method's type.
>>
>> GHC provides a `deriving` mechanism so that you can request Way 2
>> (`default`), 3 (`stock`),
>> or 4 (`newtype`) to fill in every method in a class. But there's no need to
>> provide this
>> feature at such a course granularity. What about:
>>
>>> newtype N a = MkN (Foo a)
>>> instance Blah a => C (N a) where
>>> meth1 = ...
>>> deriving default meth2 -- a bit silly really, as you can just leave meth2
>>> out
>>> deriving stock meth3 -- also silly, as C isn't a stock class, but you get
>>> the idea
>>> deriving newtype meth4
>>
>> We could also imagine
>>
>>> deriving newtype instance Blah a => Monad (N a) where
>>> deriving default join -- not so silly anymore!
>>
>> This syntax allows a `where` clause on standalone deriving allowing you to
>> override
>> the overall `deriving` behavior on a per-method basis.
>>
>> I actually quite like this extension...
>>
>> Richard
>>
>>
>>> On Jan 8, 2017, at 11:54 PM, David Feuer wrote:
>>>
>>> You *can* do this, but it's often not so concise. When the type constructor
>>> has parameters,
>> you need to pin them down using ScopedTypeVariables. So you end up needing
>> to give a signature
>> for the method type in order to bring into scope variables you then use in
>> the argument
>> to coerce. If you have
>>>
>>> newtype Foo f a = Foo (Foo f a)
>>>
>>> then you may need
>>>
>>> instance Bar f => Bar (Foo f) where
>>> bah = coerce (bah @ f @ a)
>>> :: forall a . C a => ...
>>>
>>> to pin down the C instance.
>>>
>>> If you don't want to use explicit type application (e.g., you're using a
>>> library that
>> does not claim to have stable type argument order), things get even more
>> verbose.
>>>
>>> On Jan 8, 2017 11:32 PM, "Joachim Breitner" >
>> wrote:
>>> Hi,
>>>
>>> just responding to this one aspect:
>>>
>>> Am Sonntag, den 08.01.2017, 21:16 -0500 schrieb David Feuer:
>>>> but using defaults for
>>>> the others would give poor implementations. To cover this case, I
>>>> think it would be nice to add per-method GND-deriving syntax. This
>>>> could look something like
>>>>
>>>> instance C T where
>>>> deriving f
>>>> g = ....
>>>
>>> Assuming
>>> newtype T = MkT S
>>>
>>> You can achieve this using
>>>
>>> instance C T where
>>> f = coerce (f @F)
>>> g = ....
>>>
>>> (which is precisely what GND does), so I don’t think any new syntax is
>>> needed here.
>>>
>>> Greetings,
>>> Joachim
>>>
>>> --
>>> Joachim “nomeata” Breitner
>>> [email protected] • https://www.joachim-breitner.de/
>>
>>> XMPP: [email protected] • OpenPGP-Key:
>> 0xF0FBF51F
>>> Debian Developer: [email protected]
>>> _______________________________________________
>>> Glasgow-haskell-users mailing list
>>> [email protected]
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>>
>>>
>>> _______________________________________________
>>> Glasgow-haskell-users mailing list
>>> [email protected]
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>>
>> _______________________________________________
>> Glasgow-haskell-users mailing list
>> [email protected]
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users