monad-control icon indicating copy to clipboard operation
monad-control copied to clipboard

Allow a transformer's context (and state) to depend on the transformed monad

Open shlevy opened this issue 3 years ago • 4 comments

(using "state" and "context" in the sense used in the MonadUnliftIO documentation)

Currently, because Run is polymorphic over its monad, the transformer's context cannot depend on the monad we've transformed. For example, I have a transformer that is isomorphic to a ReaderT r m except r is an expression referencing m as a parameter, so it can't be MonadTransControl. If instead Run took an m parameter (or took a functor, not a transformer) and liftWith was (Run t m -> m a) -> t m a (or (Run (t m) m -> m a) -> t m a), the instance could be written; would this limit the class meaningfully?

A similar consideration applies to StT if the state depends on m, but I don't currently have a use case requiring it.

shlevy avatar Dec 16 '22 13:12 shlevy

Currently putting this into my project

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneKindSignatures #-}
module Control.Monad.Trans.Control.Extra where

import Control.Monad.Trans.Class
import Control.Monad.Trans.Control
import Data.Kind

class (MonadTrans t) => MonadTransControlExtra t where
  type StTExtra t (m :: Type -> Type) a :: Type
  liftWithExtra :: (Monad m) => (RunExtra t m -> m a) -> t m a
  restoreTExtra :: (Monad m) => m (StTExtra t m a) -> t m a

type RunExtra t m = forall b. t m b -> m (StTExtra t m b)

-- | DerivingVia helper from the stronger 'MonadTransControl'
type ExtraViaOriginal :: ((Type -> Type) -> (Type -> Type)) -> ((Type -> Type) -> (Type -> Type))
newtype ExtraViaOriginal t m a = ExtraViaOriginal (t m a) deriving newtype (MonadTrans, Monad, Functor, Applicative, MonadTransControl)

instance (MonadTransControl t) => MonadTransControlExtra (ExtraViaOriginal t) where
  type StTExtra (ExtraViaOriginal t) m a = StT t a
  liftWithExtra = liftWith
  restoreTExtra = restoreT

{- snip generating instances for transformers types -}

shlevy avatar Dec 16 '22 14:12 shlevy

I have a transformer that is isomorphic to a ReaderT r m except r is an expression referencing m as a parameter

Why?

My first reaction is that you are trying to do something too fancy, and monad-control is already fancy enough. So most likely the answer is no, if there isn't a very compelling use case.

phadej avatar Dec 16 '22 15:12 phadej

For what it's worth, this makes MonadTransControl less general and arguably less "fancy".

But fair enough on my use case, it's somewhat esoteric, I want to use ReaderT to implicitly thread through a record of monadic effects which may change within a given scope (like local)... So the effects need to be in the same monad as the underlying computation.

shlevy avatar Dec 16 '22 16:12 shlevy

FWIW, e.g. https://hackage.haskell.org/package/effectful-core-2.2.1.0/docs/Effectful-Internal-Monad.html#t:Eff has MonadBaseControl instances as then there isn't such problems. (Eff es a is Env es -> IO a - read like).

So Eff es is ReaderT (Env es) IO. Env es doesn't need to mention "m" as the IO is implicitly there. In other words, when working over a concrete base monad things are simpler.

I'd suggest you to look at effectful. At least for a design perspective.

phadej avatar Dec 16 '22 17:12 phadej