Is it possible to use type synonyms to hide type variables when declaring instances?
Asked Answered
V

1

6

I have this typeclass:

class Monad m => Convertible m a b where
  convert :: a -> m b

For many pairs of types, the conversion can be done purely, without requiring a monadic effect.

Now, I know I can write a related typeclass like

class PureConvertible a b where
  convertPurely :: a -> b

and then make one a superclass of the other, and/or define instances of one in terms of the other using DerivingVia.

But the question is about something different. What if I define a type synonym like

import Data.Kind
type PureConvertible :: Type -> Type -> Constraint
type PureConvertible a b = forall m . Monad m => Convertible m a b 

The idea is that I could perhaps avoid mentioning m when defining Convertible instances, if my conversion doesn't require the features of any concrete monad. An attempt:

instance PureConvertible Int String where
  convert _ = pure undefined

Alas, this doesn't compile. The error is:

‘convert’ is not a (visible) method of class ‘PureConvertible’

Curiously enough, if I remove the convert method from the typeclass, the following compiles!

class Monad m => Convertible m a b where

type PureConvertible :: Type -> Type -> Constraint
type PureConvertible a b = forall m . Monad m => Convertible m a b 

instance PureConvertible Int String where

Is there a way to make this type synonym that hides m work, when there are methods in the typeclass?

I'm using GHC 9.2.4. Some language pragmas which might be useful:

{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE StandaloneKindSignatures #-}
Villager answered 25/11, 2022 at 20:1 Comment(2)
Yikes. Adding a default method in the class like default convert :: b ~ String => a -> m b ; convert _ = pure "uhm.." compiles. Not a real solution to your problem, but it's super weird, IMO. Something looks off: the fact that without the method compiles at all, despite the class name being hidden behind a type synonym, is surprising. I wonder if that was intended -- it's so inconsistent that it looks like a bug to me, especially since you can't add methods.Chaliapin
I though that TypeSynonymInstances would only allow 0) instance C T where... for type T = Int. I never knew that would allow to 1) alias type C2 = C ; instance C2 Int where..., 2) alias type C3 = C Int ; instance C3 where..., and even 3) provide the instance context (!!?!) as in you case. At least in my experience I have seen 0) many times in use, but 1,2,3) are novel to me.Chaliapin
H
0

Not a direct answer to your question, but I would suggest:

import Data.Functor.Identity

type PureConvertible = Convertible Identity

convertPurely :: PureConvertible a b => a -> b
convertPurely = runIdentity . convert

The amount of boilerplate is minimal, and the compiler should do a good job of optimizing the Identity-related fluff away.

Helterskelter answered 26/11, 2022 at 19:55 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.