What should I use for effect handling?

I was passing handles individually as parameters, but I found number of arguments rising and eventually the type became too big. This is why I resorted to MTL style.

Haskellā€™s function type (->), when partially applied: (->) r ā€¦is monadic:

# ghci
GHCi, version 9.0.2: https://www.haskell.org/ghc/  :? for help
ghci> :i ->
type (->) :: * -> * -> *
type (->) = FUN 'Many :: * -> * -> *
  	-- Defined in ā€˜GHC.Typesā€™
infixr -1 ->
instance Applicative ((->) r) -- Defined in ā€˜GHC.Baseā€™
instance Functor ((->) r) -- Defined in ā€˜GHC.Baseā€™
instance Monad ((->) r) -- Defined in ā€˜GHC.Baseā€™
instance Monoid b => Monoid (a -> b) -- Defined in ā€˜GHC.Baseā€™
instance Semigroup b => Semigroup (a -> b) -- Defined in ā€˜GHC.Baseā€™
ghci> :q
Leaving GHCi.
#

If your code only uses that extra argument for reading, that is usually enough. But if writing is also required, youā€™ll need a specific variant of ((->) r) which is sequential. Assuming WriteOut is intended for writing:

{-# LANGUAGE BangPatterns, FlexibleInstances #-}

instance {-# OVERLAPPING #-} Monad ((->) WriteOut) where
    m >>= k = \ wr -> let !x = m wr in k x wr

instance {-# OVERLAPPING #-} Applicative ((->) WriteOut) where
    pure x    = \ wr -> x
    f' <*> x' = \ wr -> let !f = f' wr in
                        let !x = x' wr in
                        f x

instance {-# OVERLAPPING #-} Functor ((->) WriteOut) where
    fmap f m = \ wr -> let !x = m wr in f x

ā€¦and if needed, a type synonym can help to avoid repetitive keystrokes:

type WrOut a = WriteOut -> a

Those long argument lists can then be used more monadicallyā€¦

I mean, my problem is just having a function with 10s of arguments. Itā€™s too long and hard to track for me.

For inspiration, you could read this old thread, and the associated article:

So package up arguments that are commonly used together into a product type?

1 Like

Sorry, but I do not understand how the thread could help. Could you elaborate?

I cannot, each handle/config/parameter is sometimes used and sometimes not used and it all differs.

Whyā€™s that a problem? If itā€™s not used, then just donā€™t use it!

Perhaps you could point to some example code, because Iā€™m finding it hard to understand in the abstract what exactly you are looking for.

I mean if I were to use each as a separate parameter, I would have something like:

foo :: A -> B -> C -> D -> E -> IO ..
bar :: A -> C -> D -> E -> IO ..
baz :: B -> C -> D -> E -> IO ..
barf :: A -> B -> C -> E -> IO ..
baze :: A -> B -> C -> IO ..

Grouping parameters do not make it more convenient here.

Why not? Why not put them all in

Params = Params A B C D E

?

@tomjaguarpaw I donā€™t understand why youā€™re so adamant on using this (suboptimal) technique.

We had similar conversation on reddit recently and I pointed out the same thing @Abab9579 says, i.e. that passing these explicitly is unwieldy for more than a few effects and if you want to group them in a record, youā€™ll have to create a bunch of records because your functions take various subsets of these.

This will work for foo. What about the rest of functions?

1 Like

I donā€™t understand why youā€™re so adamant on using this (suboptimal) technique.

I donā€™t understand why you think itā€™s suboptimal! Normally in functional programming when we want to depend on something we pass it in. Why not for depending on effects, just the same as for depending on normal values? And if you get really tired of passing it in manually, use a ReaderT.

This will work for foo. What about the rest of functions?

The rest of the functions also take a subset of those parameters, so will work equally well. This is no worse than two other situations @Abab9579 might be in:

  1. Already using a sequence of concrete monad transformers, so passing in each one individually is not really worse

    AT a (BT b (CT c (DT d (ET e m)))) a
    

    is not really better than

    A -> B -> C -> D -> E -> m a
    
  2. Already using a single concrete monad

    AppT m a
    

    is not really better than

    ReaderT Handles m a
    
2 Likes

It wonā€™t, because now your type signatures ā€œlieā€ in a sense that it looks like they use all these effects, whereas in reality they donā€™t.

This is your post from the other thread:

With what you propose you lose this propoerty, donā€™t you? :thinking: Now it looks like your functions are using more effects than they do in reality.

Looks like heā€™s using a polymorphic monad and class constraints:

2 Likes

Sure, but only in the sense that pure () :: MonadState Int m => m () is a lie. Itā€™s not a very bad lie.

With what you propose you lose this propoerty, donā€™t you? :thinking:

Yes, itā€™s a lie that acts against that nice property.

Looks like heā€™s using a polymorphic monad and class constraints

Yes maybe. Iā€™m having trouble understanding the baseline for comparison, which is why Iā€™m having trouble making a concrete suggestion. Most of my dialogue in this thread has been Socratic.

That said, Iā€™ve been doing some experiments with ā€œhandles as argumentsā€ and so far Iā€™m very pleased with the experience, versus ā€œhandles only in a type-level listā€.

Oh I forgot, there are also things like

createC :: A -> B -> IO C
createE :: A -> B  -> C -> D -> IO E

in addition to the above, used to create other handles.

For instance, Logger is positioned at the baseline and used for constructing other handles.

This is also why I found ā€œtying the knotā€ approach enticing. I am wary of the additional dependency footprint though.

Interesting! I think Iā€™m finding this code hard to imagine. I can certainly imagine a logger effect being used in handling another effect, but I canā€™t imagine it being used to create another effect. I guess at this point Iā€™m out of suggestions unless you can link to some real code.

Sorry that I cannot specify concrete code now.
I could roughly talk why I need logging for creating handles though.

For instance, I find it good practice to log when connecting to a DB. That way, I can know if error happened later, and what was the problem.

I am making a desktop application for linux, and interfacing with DBus.
Connecting to DBus could be complicated, so I also put some logging inside it.

2 Likes

Oh yes, makes perfect sense. I guess I am just too used to seeing handlers in CPS form, such as

withC :: A -> B -> (C -> r) -> r

So I rescind my previous puzzlement.

2 Likes

Look at e.g. section 4.2.1 (pages 32-33 of 59) of the associated article.

Thank you, I should stop caring about having too many parameters and embrace the length of types.
With some global variables sprinkled around, it should be manageable I think.

2 Likes