Simplifying the invocation of functions stored inside an ReaderT environment

149 views Asked by At

Let's assume I have an environment record like this:

import Control.Monad.IO.Class
import Control.Monad.Trans.Reader

type RIO env a = ReaderT env IO a

data Env = Env
  { foo :: Int -> String -> RIO Env (),
    bar :: Int -> RIO Env Int
  }

env :: Env
env =
  Env
    { foo = \_ _ -> do
        liftIO $ putStrLn "foo",
      bar = \_ -> do
        liftIO $ putStrLn "bar"
        return 5
    }

The functions stored in the environment might have different number of arguments, but they will always produce values in the RIO Env monad, that is, in a ReaderT over IO parameterized by the environment itself.

I would like to have a succinct way of invoking these functions while inside the RIO Env monad.

I could write something like this call function:

import Control.Monad.Reader 

call :: MonadReader env m => (env -> f) -> (f -> m r) -> m r
call getter execute = do
  f <- asks getter
  execute f

And use it like this (possibly in combination with -XBlockArguments):

 example1 :: RIO Env ()
 example1 = call foo $ \f -> f 0 "fooarg"

But, ideally, I would like to have a version of call which allowed the following more direct syntax, and still worked for functions with a different number of parameters:

 example2 :: RIO Env ()
 example2 = call foo 0 "fooarg"

 example3 :: RIO Env Int
 example3 = call bar 3

Is that possible?

2

There are 2 answers

4
Li-yao Xia On BEST ANSWER

From the two examples, we can guess that call would have type (Env -> r) -> r.

example2 :: RIO Env ()
example2 = call foo 0 "fooarg"

example3 :: RIO Env Int
example3 = call bar 3

Put that in a type class, and consider two cases, r is an arrow a -> r', or r is an RIO Env r'. Implementing variadics with type classes is generally frowned upon because of how fragile they are, but it works well here because the RIO type provides a natural base case, and everything is directed by the types of the accessors (so type inference isn't in the way).

class Call r where
  call :: (Env -> r) -> r

instance Call r => Call (a -> r) where
  call f x = call (\env -> f env x)

instance Call (RIO Env r') where
  call f = ask >>= f
0
dfeuer On

Here are a few minor improvements on Li-yao's answer. This version isn't specific to IO as the base monad, or to Env as the environment type. Using an equality constraint in the base case instance should improve type inference a tad, though as call is intended to be used that will probably only affect typed holes.

{-# language MultiParamTypeClasses, TypeFamilies, FlexibleInstances #-}

class e ~ TheEnv r => Call e r where
  type TheEnv r
  call :: (e -> r) -> r

instance Call e r => Call e (a -> r) where
  type TheEnv (a -> r) = TheEnv r
  call f x = call (\env -> f env x)

instance (Monad m, e ~ e') => Call e (ReaderT e' m r) where
  type TheEnv (ReaderT e' m r) = e'
  call f = ask >>= f

The associated type is arguably overkill. It would also be possible to use a functional dependency:

{-# language FunctionalDependencies, TypeFamilies, FlexibleInstances, UndecidableInstances #-}

class Call e r | r -> e where
  call :: (e -> r) -> r

instance Call e r => Call e (a -> r) where
  call f x = call (\env -> f env x)

instance (Monad m, e ~ e') => Call e (ReaderT e' m r) where
  call f = ask >>= f