I am trying to follow the helpful explanation from Ryan Scot on how to use Quantified Constraints to coerce types with higher kinded type variables to derive instances.
:set -XStandaloneDeriving -XDerivingVia -XQuantifiedConstraints
import Data.Coerce
import Data.Functor.Compose
class Alternative m where (<|>) :: m a -> m a -> m a
newtype WriterT w m a = WriterT (m (a, w))
newtype Flip a c b = Flip (a b c)
instance Alternative f => Alternative (Compose f g) where (<|>) = coerce ((<|>) :: f (g a) -> f (g a) -> f (g a)) :: forall a . Compose f g a -> Compose f g a -> Compose f g a
instance Alternative Maybe where x@(Just _) <|> _ = x; _ <|> x = x
deriving via Compose m (Flip (,) w) instance (Alternative m, forall a b. Coercible (m a) (m b)) => Alternative (WriterT w m)
WriterT (Just ('a', ())) <|> WriterT Nothing :: WriterT () Maybe Char
but get the following
<interactive>:11:26: error:
Couldn't match representation of type ‘a’ with that of ‘b’
arising from a use of ‘<|>’
‘a’ is a rigid type variable bound by
a quantified context
at <interactive>:11:1-69
‘b’ is a rigid type variable bound by
a quantified context
at <interactive>:11:1-69
In the expression:
WriterT (Just ('a', ())) <|> WriterT Nothing ::
WriterT () Maybe Char
In an equation for ‘it’:
it
= WriterT (Just ('a', ())) <|> WriterT Nothing ::
WriterT () Maybe Char
Is there a way to use this derive this special version of Alternative
for WriterT
?