DefaultSignatures for associated types

In Lifts for free: making mtl typeclasses derivable, @lexi.lambda introduces a way to simplify deriving of instances of some type classes. Indeed, when one has a custom MonadFoo m, adding default implementations using DefaultSignatures for (essentially) (MonadTrans t, MonadFoo n) => MonadFoo (t n) allows for cheap instance definitions for all kinds of transformers.

However, associated types seem to complicate this: indeed, if MonadFoo has some associated type F m (defined as a member of the class), then I can’t find a way to provide a default implementation.

In code:

{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE TypeFamilies #-}

module F where

import Control.Monad.Trans.Class (MonadTrans, lift)
import Control.Monad.Trans.Reader (ReaderT)

class (Monad m) => MonadFoo m where
  type F m

  foo :: F m -> m ()
  default foo :: (F n ~ F (t n), MonadFoo n, MonadTrans t, m ~ t n) => F m -> m ()
  foo = lift . foo

Now, the following fails:

instance (MonadFoo m) => MonadFoo (ReaderT r m)

gives

    • Couldn't match type: F (ReaderT r m)
                     with: F m
        arising from a use of ‘F.$dmfoo’
      NB: ‘F’ is a non-injective type family
    • In the expression: F.$dmfoo @(ReaderT r m)
      In an equation for ‘foo’: foo = F.$dmfoo @(ReaderT r m)
      In the instance declaration for ‘MonadFoo (ReaderT r m)’
    • Relevant bindings include
        foo :: F (ReaderT r m) -> ReaderT r m () (bound at F.hs:16:10)          

Providing the associated type does work:

instance (MonadFoo m) => MonadFoo (ReaderT r m)
  type F (ReaderT r m) = F m

Is there a way to provide a default “implementation” of type F m a-la MonadTrans t, MonadFoo n => type F (t n) = F n so single-line instance MonadFoo m => MonadFoo (SomeTrans m) remains possible?

You should try TypeFamilyDependencies 6.4.9. Type families — Glasgow Haskell Compiler 9.7.20230201 User's Guide

This can make your F m injective

I tried myself, couldn’t make it work for your code snippets.

class (Monad m) => MonadFoo m where
  foo :: F m -> m ()
  -- default foo :: (F n ~ F (t n), MonadFoo n, MonadTrans t, m ~ t n) => F m -> m ()
  default foo :: (F n ~ F (T m n), MonadFoo n, MonadTrans (T m), m ~ T m n) => F m -> m ()
  foo = lift . foo

  type family T m :: (* -> *) -> * -> *
  -- type family T m = (t :: (* -> *) -> * -> *) | t -> m
  type family F m

instance (MonadFoo m) => MonadFoo (ReaderT r m) where
  type T (ReaderT r m) = ReaderT r
  type F (ReaderT r m) = F m

This compiles, but not sure how to use it :slight_smile:

This would still require to provide family instances for F and T for every class instance, right? Hence, my current approach (where only the “direct” family instance must be provided in every class instance) seems simpler.