I find this topic fascinating, because I feel like this is an instance of the Blub paradox for me. I don’t know if this is related to your viewpoint @graninas, but a while ago I also encountered a difference between type classes and backpack modules. I came up with Semigroup
as the example:
class Semigroup a where
(<>) :: a -> a -> a
Now the thing type classes can do and backpack modules can’t is to instantiate this with another parametrised (what Java calls generic) type:
instance Semigroup [a] where
(<>) = (++)
So now you have:
(<>) :: [a] -> [a] -> [a]
If we instead had a backpack signature:
signature Semigroup where
type S
(<>) :: S -> S -> S
Then we cannot instantiate it like this:
module Semigroup where
type S = [a]
Because the a
would come from nowhere. At best we could use a forall:
type S = forall a. [a]
But now the type of (<>)
doesn’t work: (<>) :: (forall a. [a]) -> (forall a. [a]) -> (forall a. [a])
.
I think Java interfaces have the same problem as backpack modules in this respect.
By the way, I think it is a bit easier to read backpack-style interface declaration that free monad ones. Here’s how I would translate your example:
signature Meal where
type Meal
-- we don't have subtyping, so we need manual conversions
-- but I think that is a separate concern
class IsMeal a where
toMeal :: a -> Meal
signature PizzaRecipe where
type PizzaRecipe
...
signature CookingMethod where
import PizzaRecipe
type CookingMachine a
instance Functor CookingMachine
instance Applicative CookingMachine
instance Monad CookingMachine
makePizza :: PizzaRecipe -> CookingMachine Pizza
makeSandwich :: SandwichRecipe -> CookingMachine Sandwich
makeRandomPizzaRecipe :: CookingMachine PizzaRecipe
And used as:
import Meal
import CookingMethod
sampleCookingMachine :: CookingMachine [Meal]
sampleCookingMachine = do
pizza <- makePizza myPizza
rndPizzaRecipe <- makeRandomPizzaRecipe -- asking for rnd recipe
rndPizza <- makePizza rndPizzaRecipe -- evaluating
pure [toMeal pizza, toMeal rndPizza]