Can't code my component in a tagless-final way / using type classes and instances

160 Views Asked by At

(This is the concrete case behind How do I conditionally declare an instance?)

In my small project players can create/join/watch a game session or list the ongoing sessions. A very simple Yesod app exposes some endpoints to match the use-cases.

Step 1) I want to abstract away the concept of "being able to hold multiple ongoing games":

class Host m k s where
  create :: s -> m k
  read :: k -> m s
  write :: k -> s -> m ()
  update :: (s -> s) -> k -> m ()
  delete :: k -> m ()

An instance of Host m k s means m can host games (states) of s, identified (keyed) by k.

Step 2) A very practical host is a shared Map :

newtype InMemory k s a = InMemory {run :: TVar (M.Map k s) -> STM a}

A TVar holding a Map k s is captured in InMemory. InMemory keyed with Int can host :

instance Host (InMemory Int a) Int a where
  create s = InMemory $ \tvar -> do
    id <- succ . M.size <$> readTVar tvar
    modifyTVar tvar (M.insert id s)
    return id

  read id = InMemory $ \tvar -> do
    s <- M.lookup id <$> readTVar tvar
    maybe err return s
    where
      err = throwSTM $ NotFound id

  write id s = modify $ M.insert id s -- modify is just a small helper, returns InMemory
  update f id = modify $ M.update (Just . f) id
  delete id = modify $ M.delete id

Step 3) Any m that can produce the correct tvar is a host as well. For example a Yesod app can make the HandlerFor a host:

newtype App = App {rooms :: TVar (M.Map Int Game)} -- (1)
instance MonadReader (HandlerFor App) (M.Map Int Game) where ... -- (2) HandlerFor App can produce the correct tvar
-- (1) && (2) ==> the HandlerFor App is a Host

So let's have this notion:

-- smt is a just a small helper, needs MonadIO

-- this instance declaration is *wrong* and not what I want to say
instance (C.MonadIO m, R.MonadReader (TVar (M.Map k s)) m) => Host m GameId s where
  create s = GameId <$> stm (create s)
  write (GameId id) s = stm (write id s)
  update f (GameId id) = stm (update f id)
  delete (GameId id) = stm (delete id)
  read (GameId id) = stm (read id)

Idea is any m who can produce the right piece of data can host.

Now here comes the trouble. This:

instance R.MonadReader (TVar (M.Map k s)) m => Host m GameId s where

is not saying "IF m satisfies the context THEN it can host", it is saying "ALL m that are host MUST satisfy the context" which is not what I want to say. So I'm stuck in expressing the following in Haskell:

IF m satisfies the context THEN it can host, if it does not then this line has abs. no effect whatsoever. Don't force the context on m and it is not an error if m can host but does not satisfy the context.

There is a question of its own about this very topic (how to opt-in for a instance but leave undisturbed otherwise) and apparently this is not possible to express in Haskell. So question is:

  1. What are my options here ?
  2. In my thinking process (1,2 and 3) where did I go wrong that got me to a dead end ?
  3. What is the right way of thinking for this ?
2

There are 2 best solutions below

0
On

The first thing you should consider in any problem like this is whether having a class makes sense in the first place. The fact that both Haskell and OO languages use the same class keyword can easily trick one into thinking they have the same uses, but (as was written many times before) Haskell typeclasses are really fundamentally different beasts from OO classes or even interfaces.

And in many cases, the most sensible translation of an OO class is simply as a struct, which after all can contain functions corresponding to OO methods, just as well as traditional "scalar" values. Any class-y code can be translated to this style, with the main change being that you explicitly pass around “instances” and any inferences between them:

data Host m k s = Host
  { create :: s -> m k
  , read :: k -> m s
  , write :: k -> s -> m ()
  , update :: (s -> s) -> k -> m ()
  , delete :: k -> m ()
  }

newtype InMemory k s a = InMemory {run :: TVar (M.Map k s) -> STM a}

inMemoryHost :: Host (InMemory Int a) Int a
inMemoryHost = Host
  { create = \s -> InMemory $ \tvar -> do
      id <- succ . M.size <$> readTVar tvar
      modifyTVar tvar (M.insert id s)
      return id
  , read = ...
  ...
  }

Because instances are now first-class citizens, there is no problem making something like the Scala one you thought of:

monadReaderHost :: (C.MonadIO m, R.MonadReader (TVar (M.Map k s)) m)
      => Host m GameId s where
monadReaderHost = Host
  { create = \s -> GameId <$> stm (create s)
  , read = ...
  ...
  }

This does exactly what you asked for: it can produce a Host for m, provided that m fulfills the mentioned constraints – without any extrapolation that this is what should be done for every m.

Of course, this struct-approach does have its downsides though: not only can you pass around instances explicitly now, you actually must do it always. And in some cases this can incur a lot of boilerplate. One workaround is to use -XImplicitParams, which basically lets you treat a variable as if it were a typeclass constraint. This is not often done, and indeed has been criticised – the problem basically goes back to again using class-tooling for something that doesn't behave like a class, much like your original attempt.

Also, changing from classes to data basically makes the whole code weaker typed. You could mix e.g. the create and read method from different “instances”, which could well create complete mayhem.

A different option is to keep the decisions on the type level like, using class mechanisms, but still have a means of uniquely distinguishing between different instances. This can be done with phantom types. In your example, it seems sensible to tie the unique distuishing role to the key values, which after all already serve a related purpose anyway.

newtype GameKey g k = GameKey {getGameKey :: k}

class Host g m k s where
  create :: s -> m (GameKey g k)
  read :: GameKey g k -> m s
  write :: GameKey g k -> s -> m ()
  update :: (s -> s) -> GameKey g k -> m ()
  delete :: GameKey g k -> m ()

Now before you write an instance, you declare a unique tag identifying this kind of instance:

data InMemoryGame

instance Host InMemoryGame (InMemory Int a) Int a where
  create s = InMemory $ \tvar -> do
    k <- GameKey . succ . M.size <$> readTVar tvar
    modifyTVar tvar (M.insert k s)
    return k
  ...

and similarly

data MonadReaderGame

instance (C.MonadIO m, R.MonadReader (TVar (M.Map k s)) m)
           => Host MonadReaderGame m GameId s where

This approach still requires to pass around some explicit information, but basically you only need to once be explicit which sort of instance you want, then this is automatically synchronised to every connected piece of code via the keys' types. A nice way of doing that is to use -XTypeApplications on create:

       do
         ...
         k <- create @InMemoryGame s
         ...
6
On

Basically, Haskell's vanilla typeclass system just doesn't very well support having both a catch-all instance where one or more of the parameters is a variable (like instance ... => Host m GameId s) and also having other instances with specific types for the same parameter (like Host (InMemory Int a) Int a).

So for question 2 "where did you go wrong", I think it's when you thought "Any m that can produce the correct tvar is a host as well." If having a MonadReader instance that gives access to the tvar is the only way some m can be a host then that would be fine, but if you also want to have any other instances that implement "being a host" in a different way (whether it's for specific types or additional general instances with different constraints), then a general instance for any m that happens to have the right functionality (expressed via constraints) doesn't fit.

In a way, the precise reading of the implication when you have constraints on an instance is a red herring. Yes, it is true that you can't use constraints on an instance to select between two instances that would both otherwise match. But there's no other mechanism either! The no-overlapping rule means that you can read instance C a => D a as either "if C a holds then D a holds" or "D a holds for all a, but using any methods from D a also requires C a" or "D a holds if-and-only-if C a holds"; all of those are true statements, and in combination with the no-overlap rule they all have exactly the same consequences. So there's really not a lot of point getting hung up on exactly which is the best way to think about it; use whichever one feels natural and best helps you remember how the system works. (I think several of the comment threads on your other question were simply people using these different starting points)


So for question 3 and 1, here's how I would think about this sort of problem (I implemented the structure I'm going to describe in a personal project literally yesterday).

Haskell's typeclass system wants me to declare either instances specific for each type, or a single general instance that covers everything. If I have a general way of implementing an instance that will work for many types but not all, I should not declare the general instance. If you have your heart set on the general instance so that no one needs to declare anything to say which type uses that instance, then Haskell (without overlapping) doesn't let you do that. But that's a means, not an end in itself.

So each type should have its own instance. But I don't want to repeat the code that works for many types in each-and-every instance. And especially if this is a library and I expect clients might want to make their own instances, I don't want them to have to copy that code (and keep it in sync as I update the library!). So I want a way of writing down the desired general instance in some form and exporting it so that individual instances can just use my general implementation. Haskell can do this. You can have one (or more) general implementations of a class alongside other implementations, and you can export them so they can be re-used. You just have to give up on the specific way you were trying to do that, and you have to be okay with each type having a very small declaration explicitly saying which general instance applies (I personally actually like that part).

There have always been a few ways of doing this. In the bad old days you would have to make a newtype wrapper and then actually use that wrapper instead of the "real" type, or export functions with the generic implementation of each method and then the downstream user would write an explicit instance where each method explicitly called the general one. But with the DerivingVia extension (which isn't even that new anymore), we can do better.

I'm going to use a simpler example than yours so that I can give a complete working example (and I'm assuming GHC2021, so if you're using Haskell2010 or not specifying in a compiler older than ghc 9.2, you may need some additional extensions). Lets say what you wanted to write was this:

module Example where

import Control.Monad.Reader (MonadReader, ask, ReaderT, lift)
import Control.Monad.Identity (Identity (Identity))

-- dumb class, but it's multi param and has a Type -> Type parameter
class Example k m where
  example :: m k

-- We can implement Example for any MonadReader
instance MonadReader k m => Example k m where
  example = ask

-- We can also implement Example for Identity
instance Example String Identity where
  example = Identity "default"


-- Monad stack using ReaderT
type MyMonadStack r = ReaderT r IO

-- Use example with a monad stack that has MonadReader
printExampleReader :: MyMonadStack String ()
printExampleReader = do
  s <- example
  lift $ putStrLn s

-- Use example with Identity
printExampleIdentity :: IO ()
printExampleIdentity =
  let Identity s = example
   in putStrLn s

You'll get an error at the second call to example, complaining about overlapping instances. So instead we should introduce a newtype wrapper (around any m), and then instead of providing a general instance for all m (requiring MonadReader r m), we provide a general instance for ReaderExample m (still requiring MonadReader r m).

-- Newtype wrapper that will inherit the same MonadReader instance
-- that the wrapped m has
newtype ReaderExample m a = ReaderExample (m a)
  deriving (Functor, Applicative, Monad, MonadReader r)

-- Now we implement Example for `ReaderExample m`, instead of `m` directly
instance MonadReader k m => Example k (ReaderExample m) where
  example = ask

You then could go ahead and actually use ReaderExample m a everywhere you need to call these class methods instead of using m directly but that means the client code has a lot of wrapping and unwrapping, which is unpleasant. So what I recommend you do instead is see ReaderExample not as a type to ever be actually used, but purely as a mechanism for providing a named instance.

The DerivingVia extension allows client code to use this name to opt-in to this implementation in their own instances. There is then no need for client code to wrap/unwrap the newtype (or even be aware that it exists at all). deriving via syntax allows us to "copy" an instance from a different type with a compatible representation, in much the same way as GeneralisedNewtypeDeriving does but GND can only copy an instance from one type to a newtype wrapper around it. Here we've defined an instance on a polymorphic newtype wrapper, and we need to copy it to instances for concrete types that could be wrapped by the newtype.

In our example that could look like this:

type MyMonadStack r = ReaderT r IO

deriving via ReaderExample (MyMonadStack r)
  instance Example r (MyMonadStack r)

We just have to say "I want instance Example r (MyMonadStrack r), and I want you to copy the implementation from an instance for ReaderExample (MyMonadStack r)". That's it. You do need a declaration for each type saying which named instance to use, but you can mix-and-match where different types use different named instances (e.g. you might also have a general recipe relying on MonadState rather than MonadReader), so I find it's actually helpful to have those explicit links.

We needed a standalone deriving clause here because the concrete monad stack was defined as a type alias; if we wanted to opt-in to a named instance with a new data type we were declaring ourselves, it could look more like:

data MyMonad a = ...
  deriving (Example r) via (ReaderExample MyMonad))

(You would have to provide the required MonadReader instance for MyMonad as well, of course)

NOTE: One very important thing is that the DerivingVia magic only works on the last parameter of the class. So to use it with your class Host m k s you would need to move the m parameter to the end, unfortunately.

Here's the full example:

{-# LANGUAGE DerivingVia #-}

module Example where

import Control.Monad.Reader (MonadReader, ask, ReaderT, lift)
import Control.Monad.Identity (Identity (Identity))

-- dumb class, but it's multi param and has a Type -> Type parameter
class Example k m where
  example :: m k

-- Newtype wrapper that will inherit the same MonadReader instance
-- that the wrapped m has
newtype ReaderExample m a = ReaderExample (m a)
  deriving (Functor, Applicative, Monad, MonadReader r)

-- Now we implement Example for `ReaderExample m`, instead of `m` directly
instance MonadReader k m => Example k (ReaderExample m) where
  example = ask

-- We can also implement Example for Identity
instance Example String Identity where
  example = Identity "default"


-- Monad stack using ReaderT
type MyMonadStack r = ReaderT r IO

-- And we simply add these two lines to apply the "named instance" for
-- ReaderExample to this particular type
deriving via ReaderExample (MyMonadStack r)
  instance Example r (MyMonadStack r)

-- Note that here we're working with MyMonadStack directly; we *don't*
-- need to wrap it into ReaderExample to invoke the instance
printExampleReader :: MyMonadStack String ()
printExampleReader = do
  s <- example
  lift $ putStrLn s

-- But now we can use this as well, since it no longer overlaps
printExampleIdentity :: IO ()
printExampleIdentity =
  let Identity s = example
   in putStrLn s

To sum up, you can't do exactly what you were trying to do in Haskell in the same way you would in Scala. But you can use the tools Haskell does give you to meet the goal of "I want to be able to provide a general implementation that can be used by any type meeting these conditions". It requires only a very small compromise that each type needs a small explicit declaration, and then your design fits into the architecture of Haskell's type class system instead of fighting against it.


As a footnote, I've basically written this post pretending that the functionality for allowing overlapping instances doesn't exist. If you want to continue to fight against Haskell's typeclass system, that would be what you need to look at. I do know pretty much how these pragmas work, but I haven't used them since the days when they were language extensions that had to be turned on for the whole module, and barely even back then (not because I would never use them, but simply because I haven't needed to).

I can't answer off the top of my head how close to what you want is achievable, or whether the pitfalls would be a problem in your intended usage. But in general I would not recommend relying on overlapping instances for Haskellers who aren't yet very familiar and comfortable with the "normal" type class system; not simply to avoid the minimal boilerplate of a handful of deriving via instances.