Type classes vs interfaces

What’s wrong with this:

class Monad m => CookingMachine m where
    makePizza :: PizzaRecipe Pizza -> m Pizza
    makeSandwitch :: SandwichRecipe Sandwich -> m Sandwich
    makeRandomMeal :: m Meal

mySandwich :: SandwichRecipe Sandwich
mySandwich = undefined

makeSandwichMeal :: CookingMachine m => SandwichRecipe Sandwich -> m Meal
makeSandwichMeal = undefined

sampleCookingMachine :: CookingMachine m => m [Meal]
sampleCookingMachine = do
    sandwich   <- makeSandwichMeal mySandwich
    randomMeal <- makeRandomMeal
    pure [sandwich, randomMeal]

? Full code.

I’ll see what I can do; it’s just not easy to explain. I have an article in Russian about why type classes and existentials can’t represent the notion of interface, but it’s outdated (year 2012?).

Could you please share the article anyway?

Sure!

It was this article: Дизайн и архитектура в ФП. Часть 2 / Design and architecture in FP. Part 2.

It was a series of 3 posts I published in 2014. Not well-written, but it was definitely the start of my research on Software Engineering in Haskell.

1 Like

@tomjaguarpaw @effectfully I need to think about what you’re proposing. Not sure for now

2 Likes

I’m having trouble seeing what this would look like in an OOP language. Are you imagining something like

interface Recipe {
  Ingredient[] getIngredients();
}

class PizzaRecipe implements Recipe { ... }

class CookingMachine {
  Meal cook(Recipe r) { ... }
}

abstract class Meal {
  // what goes in here?
}

class Pizza extends Meal { ... }

If CookingMachine returns some Meal, how is the caller expected to use the result? Does Meal have some functions that all Meals implement, or will the caller use reflection (e.g. instanceof) to dynamically dispatch?

If I were to implement this in Haskell, I’d do something like

data Recipe = Recipe
  { recipeName :: Text
  , ingredients :: [Ingredient]
  }

pizzaRecipe :: Recipe
pizzaRecipe = -- some dsl for building the recipe

cook :: Recipe -> IO Meal

-- if Meal will be inspected after, caller can
-- inspect recipe name
data Meal = Meal Text

-- if every Meal has functions
data Meal = Meal
  { getSpiciness :: Int
  , consume :: Person -> IO ()
  , ...
  }
1 Like

Type classes aren’t interfaces, but you can “do interfaces” in Haskell without any pain. If you don’t need any sort of reflection shenanigans (i.e the interface is genuinely opaque), just reify the interface to a concrete type.

import Control.Monad ((>=>))
import Data.IORef (IORef, modifyIORef, newIORef, readIORef)

-- A very unprincipled typeclass to make this all a bit more ergonomic
class a `Implements` i where
  impl :: a -> i

data RunningSum = RunningSum { sum_ :: IO Integer, add_ :: Integer -> IO () }

newRunningSum :: IO RunningSum
newRunningSum = do
  ref <- newIORef 0
  pure (RunningSum (readIORef ref) (modifyIORef ref . (+)))

data Doubler = Doubler { total_ :: IO Integer, double_ :: IO () }

newDoubler :: IO Doubler
newDoubler = do
  ref <- newIORef 1
  pure (Doubler (readIORef ref) (modifyIORef ref (* 2)))

newtype Incable = Incable { inc_ :: IO () }

instance RunningSum `Implements` Incable where
  impl x = Incable ((add_ x) 1)

instance Doubler `Implements` Incable where
  impl = Incable . double_

stuttered :: Incable -> Incable
stuttered (Incable f) = Incable (f >> f)
-- or, if we wanted to abuse type classes more we could add
-- instance Implements i i where impl = id
-- and then go
-- stuttered :: (a `Implements` Incable) => a -> Incable
-- stuttered x = let f = inc_ (impl x) in Incable (f >> f)
-- but personally, I think this is a mistake.

incBoth :: Incable -> Incable -> Incable
incBoth x y = Incable (inc_ x >> inc_ y)
-- in retrospect, I should have defined this first and gone with
-- stuttered x = incBoth x x

-- Count the number of times we divide by 2 before reaching 1
collatz :: Incable -> Integer -> IO ()
collatz counter = go
  where
    go n
     | n <= 1 = pure ()
     | otherwise = inc_ counter >> go (if even n then n `div` 2 else n * 3 + 1)

main :: IO ()
main = do
  s <- newRunningSum
  d <- newDoubler
  readLn >>= collatz (incBoth (stuttered (impl s)) (impl d))
  (sum_ >=> print) s
  (total_ >=> print) d

That is indeed @graninas’s point, as far as I can tell.

Are there any existing specification/s of “interface-centric” semantics available? (They don’t have to be yours.)

Type classes basically can’t do this. They simply don’t have [what’s required.]

As I vaguely recall, type classes were introduced to allow overloading of identifiers. While there have been attempts to extend them into supporting (variants or features of) object orientation, overloading is still their primary use. And since they’re a language feature, this observation applies:

Furthermore:

…along with the use of extensions like free or existential types.


…hmm:

If I’m understanding that correctly…right now, that could only be achieved by making Haskell’s regular function type (->) more “permissive”, much like that of Standard ML or OCaml: languages where all those type-level bits don’t have to be carried throughout your programs. Those observations by @maxigit apply here too:

  • The purity of Haskell’s function type is at the cost of effects;

  • Allowing direct effects for the corresponding type in SML or OCaml is at the cost of purity.

This is another reason why I’m interested in that specification: it’s then much easier to see objectively what Haskell lacks, instead of trying to rely on subjective personal experience with other languages.


…existentials seem to work quite well here:

And that confinement of mutable state (and the associated side-effects!) to otherwise-regular (pure) Haskell definitions alleviates the need to need to carry those particular type-level bits around! Then there’s the classic:

Perhaps it can help explain why existential types have been mentioned so often in this context.

1 Like

I think @graninas has made it clear that he hasn’t got a fully worked out description of the semantics (which is totally fine; experience and intuition are also important):

1 Like

Duly noted - I was thinking of pre-existing specifications, articles, et al by others: I’ve updated that post.

Hi all, I finally found a convincing argument and a differentiating property.

Firstly, there are two sorts of abstractions: genericity-like abstractions and interface-like ones. The differences between the two are the following (cite from my materials):

  • Interface-like abstractions. Describe the common behavior of similar domain notions and allow the client code to treat each of them uniformly. Implementations can be substituted in runtime transparently for the client code. Does information hiding and encapsulation. Examples: Java and C# interfaces, Haskell’s Free monads, Service Handle pattern, and usual first-class functions.

  • Genericity-like abstractions. Handle the essence of a domain notion with generic type-level declarations. Providing an implementation means specifying the generic type with a specific one at design time and compile time. Examples: generics, type classes, templates in C++, Haskell’s Foldable, Traversable, Monoid, Semigroup, and so on.

So type classes are mostly genericity-like abstractions, but can somewhat mimic interfaces.

The borderline here lies in the information hiding property. Type classes don’t have this property, at least without additional magic (such as existentials).

Here is the modified code of the cooking machine. I added a possibility for the machine to create random recipes for pizza. Notice that it returns another Free monadic language as a result (PizzaRecipe):

data CookingMethod next
 = MakePizza (PizzaRecipe Pizza) (Pizza -> next)
 | MakeSandwich (SandwichRecipe Sandwich) (Sandwich -> next)

 | MakeRandomPizzaRecipe (PizzaRecipe Pizza -> next)

Now, we can ask for a random recipe and run it without leaving the client function:

sampleCookingMachine :: CookingMachine [Meal]
sampleCookingMachine = do
 pizza <- makePizza myPizza

 rndPizzaRecipe <- makeRandomPizzaRecipe    -- asking for rnd recipe 
 rndPizza <- makePizza rndPizzaRecipe       -- evaluating
 pure [pizza, rndPizza]

The type class based solution needs type classes for recipes that are lacking in the previous examples:

class Monad m => CPizzaRecipe m where
  -- TODO

class Monad m => CCookingMachine m where
  cmakePizza :: CPizzaRecipe r => r Pizza -> m Pizza
  cmakeSandwitch :: CSandwichRecipe r => r Sandwich -> m Sandwich

  cmakeRandomPizzaRceipe :: CPizzaRecipe mm => m (mm Pizza)

csampleCookingMachine
  :: forall m mm
  . CPizzaRecipe mm     -- information leaking
  => CCookingMachine m
  => m [Meal]
csampleCookingMachine = do
  -- pizza <- cmakePizza (cMakeCirclePizza ThickCrust [])    -- how to make this compile?
  rndPizzaRecipe :: mm Pizza <- cmakeRandomPizzaRceipe
  rndPizza <- cmakePizza rndPizzaRecipe
  pure [{-PreparedPizza pizza,-} PreparedPizza rndPizza]

Now we have two problems:

  • private information leaking
  • that commented-out routine that doesn’t compile

I believe this demonstrates why type classes are not interfaces although they exhibit some of the needed properties.

There are actually additional differences when it comes to substituting the implementations at runtime, and this is where the differences start being significant. One cannot easily substitute instances of type classes at runtime because it’s a type-level mechanism only.

Full example of code

2 Likes

More on this topic:

Java’s Interface and Haskell’s type class: differences and similarities?

How do type classes differ from interfaces?

What is the difference between Haskell’s type classes and Go’s interfaces?

OOP vs type classes

1 Like

Oh, I have to say the same. I know I sound rude often, and not only because English is not my first language, but because I’m sometimes rude. Sorry for that, and my ad-hominem words were not helping.

3 Likes

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]
2 Likes

@jaror Looks very interesting!

Yes, module systems are an interface-like abstractions especially if they have some additional properties, for example, first-classness

I wonder, would you consider this a ‘mimic’ of interfaces, or does it get closer to the real thing for you? Or is this ‘additional magic’ (the chooseMildlyRegressiveEthnicStereotype function does basically encode an existential type)?

class Monad m => SandwichRecipe impl m where
  startNewSandwich :: impl -> BreadType -> Component -> m SandwichBody
  addComponent :: impl -> Component -> SandwichBody -> m SandwichBody
  finishSandwich :: impl -> Maybe BreadType -> SandwichBody -> m Sandwich

class Monad m => PizzaRecipe impl m where
  makeCirclePizza :: impl -> Crust -> [PizzaComponent] -> m Pizza
  makeSquarePizza :: impl -> Crust -> [PizzaComponent] -> m Pizza

class Monad m => CookingMachine impl m where
  makePizza :: impl -> Pizza -> m Meal
  makeSandwich :: impl -> Sandwich -> m Meal
  makeRandomPizzaRecipe :: impl -> m Pizza

mySandwich :: SandwichRecipe impl m => impl -> m Sandwich
mySandwich impl = do
  body1 <- startNewSandwich impl Toast Tomato
  body2 <- addComponent impl Cheese body1
  body3 <- addComponent impl Salt body2
  finishSandwich impl Nothing body3

sampleCookingMachine :: CookingMachine cook m => PizzaRecipe pizza m => cook -> pizza -> m [Meal]
sampleCookingMachine cook pizza = do
  -- note the separation of `cook` and `pizza` allows different implementations to be provided, as long as they run in the same monad
  pizza <- makePizza cook =<< myPizza pizza

  rndPizzaRecipe <- makeRandomPizzaRecipe cook
  rndPizza <- makePizza cook rndPizzaRecipe
  pure [pizza, rndPizza]

data ItalianChef = ItalianChef
data SwedishChef = SwedishChef

instance PizzaRecipe ItalianChef IO where
  -- TODO: That's a nice-a pizza!
instance PizzaRecipe SwedishChef IO where
  -- TODO: Bork bork bork!
instance SandwichRecipe ItalianChef IO where
  -- TODO
instance SandwichRecipe SwedishChef IO where
  -- TODO
instance CookingMachine ItalianChef IO where
  -- TODO
instance CookingMachine SwedishChef IO where
  -- TODO

chooseMildlyRegressiveEthnicStereotype ::
  ( forall impl.
    PizzaRecipe impl IO =>
    SandwichRecipe impl IO =>
    CookingMachine impl IO =>
      impl -> IO a
  ) ->
    IO a
chooseMildlyRegressiveEthnicStereotype f = do
  -- lookup implementation at runtime
  condition <- lookupConfig
  if condition then f ItalianChef else f SwedishChef

main :: IO ()
main =
  chooseMildlyRegressiveEthnicStereotype $ \chef -> do
    meals <- sampleCookingMachine chef chef
    print meals
1 Like

Looks like mimicing to me!

But yes, this idea comes first in mind.

It doesn’t feel okay to me though, because having something related to implementations in the interface is quite contrary to why we need interfaces. In this case, it’s indirectly about implementations but still.

Not sure if it’s existential of any kind, I’m not an expert here.

I foresee some other (negative) consequences of this design to other parts, but this feel needs a careful formulation.

P.S. I still need to read all other messages here. Sorry, I’m kinda lazy

I must say I don’t fully understand the purpose of the example given, but I do recall I used type families to “hide” “private information” in some other cases:

{-# LANGUAGE TypeFamilies #-}                                                
                                                                             
import Data.Kind (Type)                                                      
                                                                             
data Crust = ThickCrust | ThinCrust                                          
  deriving (Show, Eq, Ord)                                                   
data PizzaComponent = Salami | AmericanCheese                                
  deriving (Show, Eq, Ord)                                                   
data Pizza = Pizza Crust [PizzaComponent]                                    
  deriving (Show, Eq, Ord)                                                   
                                                                             
data Meal                                                                    
 = PreparedPizza Pizza                                                       
 -- | PreparedSandwich Sandwich                                              
 deriving (Show, Eq, Ord)                                                    
                                                                             
class Monad m => CPizzaRecipe m where                                        
                                                                             
class Monad m => CCookingMachine m where                                     
    type family PIZZA_RECIPE m :: Type -> Type                               
    cmakePizza :: PIZZA_RECIPE m Pizza -> m Pizza                            
    -- cmakeSandwitch :: CSandwichRecipe r => r Sandwich -> m Sandwich       
    cmakeRandomPizzaRceipe :: m (PIZZA_RECIPE m Pizza)                       
                                                                             
csampleCookingMachine                                                        
  :: forall m                                                                
   . CCookingMachine m                                                       
  => m [Meal]                                                                
csampleCookingMachine = do                                                   
  rndPizzaRecipe <- cmakeRandomPizzaRceipe                                   
  rndPizza <- cmakePizza rndPizzaRecipe                                      
  pure [{-PreparedPizza pizza,-} PreparedPizza rndPizza]                     
1 Like

Your solution looks like another additional magic, but probably would be acceptable enough.

The task about the cooking machine is questionable of course, but the need for such solutions occurs in complex domains in OOP quite often. The need looks like this: there is some general system that produces some generalized results, and both of these should be abstracted out because they both are complex, and can be eventually extended. If not doing this, the code becomes fragile, less layered and much coupled. So it is valid to suppose that in FP, we might need something like this, too.

I’m thinking about having a declarative GUI, for example. I’m very sure that you can build a nicely organized uniformely looking type-safe extensible library for that using the Hierarchical Free Monads approach. No extra mechanisms would be needed. With type classes, existentials and type families it will have a much higher accidental complexity and probably a worser dev ux

Re declarative GUI, take console UI library brick as an example, though I am not super familiar with it, here is how many type classes you can find from it https://github.com/search?q=repo%3Ajtdaugherty%2Fbrick%20class&type=code. Very little indeed.

As a person alao having years’ of OO baggage, here’s an intuition:

  • Typeclasses are best suited for functional compositional concepts such as functors, applicative, monad etc. Its hierarchy is for conceptual generalization. See Typeclassopedia - HaskellWiki for inspiration.
  • Though because of its runtime dictionary carrying property, OO-like interfaces can be emulated with it. However, it’s very different in that there is by default no real run time dispatching; that you will have to use Typeable which is often a code smell in Haskell.
    • Something must be emphasized too is that you don’t need typeclasses perhaps for this “property”, after all it’s just a data type with bunch functions. I recall elm language doesn’t even have typeclasses.
  • Further more damningly, for OO people coming to Haskell trying to do things the old ways, typeclass may be further “abused” to model “hierarchical” relationships in data that is often subclasses in OO. Now that’s where we should probably really stop us further abusing typeclasses, and just use ADT?
1 Like

A fun note perhaps, maybe the choice of word “class” was the culprit. In Agda e.g. it seems just a record type with an special “instance” keyword in addition:

record Functor {a} (F : Set a → Set a) : Set (suc a) where
  field
    fmap : ∀ {A B} → (A → B) → F A → F B

-- Instances may be declared either by constructing a record explicitly or by using copatterns:

instance
  ListFunctor₁ : Functor List
  ListFunctor₁ = record { fmap = map }

instance
  ListFunctor₂ : Functor List
  fmap {{ListFunctor₂}} = map

I am not familiar of the programming language history related to the keyword “class”. So I don’t know who is the one misused it first, or it simply started without a proper definition.

2 Likes