[Haskell-cafe] Instances for (->) a (b :: * -> *)?

Oleg oleg at okmij.org
Tue Jun 28 07:36:47 UTC 2016


Jim Pryor wrote:

> If one wants to declare instances for a type schema `a -> _`, one writes
> something like this:
>     instance Context => Class parameters ... ((->) a) where { ... }
> But what if you want to declare instances for a type schema `a -> b _`,
> that is, where the slot to be filled is not just the result of (->) a,
> but rather the composition of that together with another type operation
> b :: * -> *? 

Then one defines a new type:

    newtype TwoArrow a b x = TwoArrow{unTA:: a -> b -> x}
    instance MyClass (TwoArrow a b) where ...

Ditto for the composition. Alas, one is stuck with adding the dummy conversions
TwoArrow/unTA at various places.

> Concretely, here's what I'm trying to achieve. I wrote a typeclass for
> MonadReaders that are embedded inside (one level) of other MonadReaders,
> like this:
>     {-# LANGUAGE FunctionalDependencies FlexibleInstances
>     UndecidableInstances  #-}
>     class MonadReader w m => DeepMonadReader w r m | m -> r where
>       { deepask   :: m r
>       ; deepask = deepreader id

The first instance of the curly-braces notation on this list in more
than a decade!

I think you are trying to build a monad with several pieces of
environment. Assuming that just making a record with two different
pieces (and making that record the single environment) doesn't work
for you, you can find many solutions on Hackage. For example, various
extensible effects libraries offer the desired functionality right out
of the box. Or, if you really want to define a new class, why not to
do something more general, like

class Monad m => MonadMReader var r m | var m -> r where
  ask :: var -> m r


to be used like
data Var1 = Var1; data Var2 = Var2
do
  x <- ask Var1
  y <- ask Var2
  return $ x + y

(and implement it, that is, define the instance any way you wish,
e.g., with a Free or a Freer monad).

For completeness, the old `reflection' trick, see 
        https://hackage.haskell.org/package/reflection
offers multiple pieces of configuration data.



More information about the Haskell-Cafe mailing list