Type classes vs interfaces

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

In C++, it’s “concepts”. I was able to implement the mtl style with concepts easily although with some C++ specific. However, I would avoid using concepts as an interface mechanism because it’s a type-level mess. Implementing the whole Haskell’s ecosystem of generic concepts (Foldable, Traversable etc) in C++ concepts makes a lot of sense, and people do it already

Unironically, I’m doing exactly this in the next chapter of the Pragmatic Type-Level Design book that I’m currently writing. Type classes as interfaces. I have an excuse though. If it was a book about functional design, I would go with real interface-like abstractions. But it’s about the type-level design in which type classes play a significant role. And I’m going to use the results of this discussion to complement the material, so thank you for your insights!

2 Likes

Talking about multi-paradigm languages, C++ is the “pathological” one. C++ was my first language from decades ago, but I haven’t touched it for a while. Now that I look at it, its latest syntax is so different from what I knew of. For example, “constexpr” seems taking over the limelight from concepts lately too. I think Bartorz Milewski was from C++ community and he did lots of porting of Haskell stuff to C++ that nobody asked for it (/jk).

I suspect many Haskell98/2010 old timers coming back to Haskell would feel quite the same way.

For entertaining, I am just gonna throwing another wrench to the mix. Here is a tongue-in-cheek “strongly duck typing” using GHC (not Haskell admittedly to some folks) HasField and overloaded dot extensions etc.:

{- cabal:
build-depends: base, constraints, text
default-language: GHC2021
-}
{-# LANGUAGE ConstraintKinds       #-}
{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedRecordDot   #-}


-- Taking an OO example from https://developer.mozilla.org/en-US/docs/Learn/JavaScript/Objects/Object-oriented_programming

import           Data.Constraint (Dict)
import           Data.Kind       (Constraint, Type)
import           Data.Text       (Text)
import           GHC.Records     (HasField (..))

--------------------------------------------------------------------------------
-- Toy Object-Oriented Domain
--------------------------------------------------------------------------------

data PersonHood = MkPersonHood
    { personalPublicRecord   :: Text
    , personalPrivateHistory :: Text
    }

data Subject = Math
             | OtherStuff

newtype Paper = MkPaper Text

newtype Grade = MkGrade Int
-- use mkYear to create valid grade values.

newtype Year = MkYear Int
-- use mkYear to create valid year values.

--------------------------------------------------------------------------------
-- Interfaces
--------------------------------------------------------------------------------

-- What is a person?
type IPerson r = ( HasField "name" r String
                 , HasField "introduceSelf" r (r -> IO ())
                 )
-- A data type for a person.
data Person r = MkPerson { name          :: String     -- static function
                         , introduceSelf :: r -> IO () -- member function
                         }

data Student = MkStudent { _person :: Person Student
                         , year    :: Year
                         }

-- NOTE: I wish this could work
-- @@
-- instance HasField x (Person Student) a => HasField x Student a where
--   getField (MkStudent { _person = p }) = getField @x (getField @"_person" p)
-- @@
-- NOTE: ugly boilerplate that can be done via TH or something similar to above?
instance HasField "name" Student String where
  getField (MkStudent { _person = p}) = p.name
instance HasField "introduceSelf" Student (Student -> IO ()) where
  getField (MkStudent { _person = p}) = p.introduceSelf

data Professor = MkProfessor { _person :: Person Professor
                             , year    :: Year
                             , teaches :: [Subject]
                             }

dramaticEntrance :: IPerson p => p -> IO ()
dramaticEntrance p = print $ "GM Y'all, I am " ++ p.name ++ "!!"

-- This is duck-typing!
introduce :: IPerson r => r -> IO ()
introduce p = do
  print $ "Here is our next person, " <> p.name
  p.introduceSelf p

main = do
  let bob = MkStudent (MkPerson "Bob" dramaticEntrance) (MkYear 2023)
  introduce bob
  print "Bye!"

Notice that dramaticEntrance and introduce have the “duck typing” feelings, but a bit stronger. Some may call it “row types” as far as I recall.

Some boilerplate still required, but I think with some more dark GHC magic, it may make a quite decent OO-style subclassing framework.

But why?

Well, this is very much OOPish now to me. I would also ask the same - but why.

Let me clarify why I don’t think that my approaches are OOP although the borders are very blured today, and there is no a single view on what OOP is.

I’ve implemented a working Free-monad based monadic STM in C++ with the same interface as Haskell’s STM has. It doesn’t feel OOPish at all. It’s definitely FP although we might want to discuss whether it’s the imperative programming already.

So monadic, pure and declarative to me is much more FPish than it’s OOPish. Yes, it uses similar ideas to encapsulate some behaviour behind a (Free monad) interface, and even looks like OOP’s aggregation, and even can mimic OOP quite close, but it’s still monadic and functional. Your Free monad scripts/“objects” are chains of immutable computations while OOP’s class implementations aren’t.

Well, they actually can mimic it, and OOP can suddenly be turned into a kind of FP (I guess “Elegant objects” fit into this category), and this is where the borders become totally vague.

So monadic programming to me is FP and is much bigger than imperative/OOP programming. This all is, of course, debatable from the theoretical POV, but I’m interested in practice and how to write a good code.

2 Likes

I mean, you wrote some type-class-based code that makes no sense to you (given your “how to make this compile?”) and doesn’t make sense to me either and then you concluded that it demonstrates something. I think it only demonstrates that you haven’t created enough proofs-by-lack-of-imagination to recognize them (I’ve made way too many of those).

I can keep the bottom block of your code (after csampleCookingMachine) intact and mechanically transform the free monad stuff to classes without turning my brain on using the trick I told you about earlier.

You may argue that QuantifiedConstraints and friends are a bit much and it would be fair, but they are just quality of life improvements, the same can be done without them if you actually translate the types right.

Admittedly, both approaches are more complex than yours, but the first one is a mechanic translation that is more ergonomic than your approach (see the referenced above blog post for details) and is more expressive when it comes to higher-order effects (I might be wrong about that one, it’s been a long time).

As a bonus, I can tell you why people don’t seem to understand what you’re talking about while you seem to bump into such problems a lot: it’s because you reify effects as data in user space and this just isn’t something that others to a lot. Even algebraic effect folks who are comfortable with effects being data in their library of choice do not commonly return polymorphic effectful computations from other effectful computations (partially because there’s rarely need for that, partially because it’s a pain as is visible from this thread). To be very concrete, in the real world PizzaRecipe wouldn’t be an effect like in your code (you basically encode effects with Free) and it doesn’t even make sense in your own contrived example to begin with, since given the definition

data PizzaConstructor next
 = MakeCirclePizza Crust [PizzaComponent] (Pizza -> next)
 | MakeSquarePizza Crust [PizzaComponent] (Pizza -> next)

type PizzaRecipe a = Free PizzaConstructor a

what are you even going to do with a Pizza once you get it from either of constructors? Stack it on top of another pizza to get a higher-order pizza or something?

So yeah PizzaRecipe would be a normal data type and not anything effectful like a Free monad or a constraint or whatever and then all your problems are completely gone as you can now suddenly return a PizzaRecipe from cmakeRandomPizzaRceipe without attempting to sneak a polymorphic effectful computation into the result of another effectful computation.

I do admit there may be value in reifying effects as data. I just don’t think it’s a good basis to build your entire software development methodology on.

Having written all of that, I’m still not confident about anything, it feels like there’s some kind of a general rule about data vs effects hidden in here that I’m failing to see. I’m not sure why you seem to be so confident.

1 Like

Yes of course. I’m not following why you think Haskell (or FP in general) lacks interfaces. The input interface is the argument type(s); the output interface is the result type.

With type classes, you can make the result type depend on the input type(s), via Type Functions/FunDeps – or even make the input types depend on the result type (demand-driven interface).

a) Why ‘runtime’? Don’t we want static type safety?
b) I’da thought Type Classes are exactly the mechanism.

I agree you might get a pile-up of Class constraints. That’s a different criticism vs “won’t allow”.

Yeah. There is that. We need a snappy term for overloadable-bunch-of-methods-that-contain-no-data.

1 Like

@effectfully Your arguments sound too weak to me. Sorry, I’m not convinced yet.

Type-class based code makes sense to me because it follows the Free monadic counterpart to demonstrate the difference. And what’s so wrong with it? This code looks pretty valid from the domain point of view (might be the question of why we want such a strange domain but that’s a separate question):

The Free monadic counterpart works and looks great. I’ve expanded it for better demonstrability and updated the gist:

sampleCookingMachine :: CookingMachine [Meal]
sampleCookingMachine = do
 pizza <- makePizza (makeCirclePizza ThickCrust [])

The difference between the mechanisms is clear, and it’s a fact.

This is not an argument to me. You can mechanically transform it into Assembly/Machine code (which we all do constantly), but this doesn’t mean the two solutions are equal from the developer’s point of view. I can mechanically transform my Free monadic approach into the Service Handle pattern, but it will be quite a different solution, with its own design issues and subtle differences that are important.

class (CPizzaRecipe m, CSandwichRecipe m) => CCookingMachine m where
  withRandomPizzaRecipe :: ((forall p. CPizzaRecipe p => p Pizza) -> m b) -> m b

makePizza :: CCookingMachine m => (forall p. CPizzaRecipe p => p Pizza) -> m Meal
makePizza receipe = undefined

makeSandwich :: CCookingMachine m => (forall p. CSandwichRecipe p => p Sandwich) -> m Meal
makeSandwich receipe = undefined

This all looks like that I really want to avoid such a code in my projects. There is nothing to be proud of here, it’s a lot of accidental complexity that is unneeded and unnecessary unless it’s really, really justified.

Your referenced blog post wasn’t convincing to me long ago, and it isn’t today.

Apparently, the fact that people don’t do this, isn’t an argument against my approaches. It only tells that people didn’t know about other ways to do stuff. And I’m happy I could show a highly different solution that was unique to Haskell and turned out to be both very powerful and very simple.

You keep calling it “effects”, but it’s not effects to me in this particular example, and neither they are subsystems.

In my FDaA book, I’m dedicating half of it to Domain-Driven Design, and half of it to building an application framework. You’d call the latter “an effect system” and “effects”, but I prefer “framework” and “subsystems” because it’s what it is in 95% of all other programming languages. Here, however, we’re doing Domain-Driven Design, and there are no “effects” here, it’s how the business domain is organized. The task itself might be questionable a little but nevertheless it works for demonstrating the difference.

So I would really argue agains doing DDD with type classes. I might understand using the type classes for “effects”/application frameworks though.

Not an argument to me. There is a methodology, and it doesn’t care how you evaluate the “goodness” of its fundamentals. It may exist, - it has a right to exist, - it must exist to provide people a choice. The opposite would be not having the methodology at all.

Given that I’m still not convinced by your arguments, I’m sure that my methodology works and works quite well. I’m confident because it’s proven in practice and is the most formulated and most described methodology in Haskell.