3
votes

I recently had the idea to build a monad that counted the number of binds a computation goes through. I came up with the following:

newtype K a = K { runK :: Int -> (a, Int) }

instance Functor K where
  fmap f k = K $ \s ->
    let (iv, s') = runK k s
     in (f iv, s')

instance Applicative K where
  pure x = K $ \s -> (x, s)
  f <*> b = K $ \s ->
    let (f', s')  = runK f s
        (ih, s'') = runK b s'
     in (f' ih, s'')

instance Monad K where
  return x = K $ \s -> (x, s)
  a >>= f = K $ \s ->
    let (iv, s') = runK a s
     in runK (f iv) (s' + 1)

which I later realized was just the State monad and not very interesting. Then, I had the idea to try to build an arrow that counted "connections". Here I am a bit stumped.

newtype L a b = L { runL :: Int -> (a -> b, Int) }

instance Category L where
  id = arr Prelude.id
  b . a = L $ \s ->
    let (f1, s') = runL a s
        (f2, s'') = runL b s'
     in (f2 Prelude.. f1, s'' + 1)

instance Arrow L where
  arr f = L $ \s -> (f, s + 1)
  first a = L $ \s ->
    let (f1, s') = runL a s
     in (\(x, y) -> (f1 x, y), s')

I came up with the above which would count the number of connections, but doesn't count the number of connections a computation goes through. Suggestions?

2
In your definition of Category L, why are you returning s''+1 instead of s''+s'? The asymmetry just stands out as odd.ErikR
Your Monad instance for K is not law-abiding. Counting binds can't be, because some laws have a different number of binds on the two sides of the equation, e.g. return x >>= f = f x. Counting uses of . in a Category has a similar problem, since id . f = f is an equation.Daniel Wagner
@DanielWagner Does this mean that the concept of a monad that counts binds or an arrow that counts connections cannot be done?rityzmon
@ritzymon No. It just means the interface you propose is not compatible with being a well-behaved monad/arrow. Consider designing a different interface -- e.g. adding an explicit "bump the counter" operation would be a straightforward and perfectly-law-abiding fix. If you say more about what you hope to achieve, we may also be able to advise you on other routes to take.Daniel Wagner

2 Answers

5
votes

(This is really the same as Daniel Wagner's observation, but I thought I'd make it friendlier.)

You should meditate on what the meaning is of having laws like the monad laws. This is a topic that can get subtle and complicated, but a very simple rule of thumb that you can apply is this:

  • If a type or function promises that it obeys a law that says x = y, clients of that class should not be able to tell x and y apart.
  • I.e., you should not be able to write a function f such that:
    • The law says that x = y;
    • But f x /= f y

Now this cannot be an absolute rule. Take for example sorting; merge sort and bubble sort are both stable sorting algorithms, and thus they "the same function" in the sense that you cannot tell them apart from looking at the inputs and outputs. But if you use a "side channel" like timing you could still tell them apart, but we normally exclude that from consideration when we ask whether some code obeys a given law.

Now when we apply this to your K type, then the problem is that you can write a program that distinguishes two expressions that the monad laws say should be indistinguishable. For example, in the documentation for the Monad class it says that:

Furthermore, the Monad and Applicative operations should relate as follows:

pure = return
(<*>) = ap

And we can easily refute the second one of these with a QuickCheck test like this:

import Control.Monad (ap)
import Test.QuickCheck
import Test.QuickCheck.Function

-- Snipped your code for `K`

prop_ap :: Fun Int Int -> Int -> Bool
prop_ap f x = runK applicative 0 == runK monadic 0
    where applicative = pure (apply f) <*> pure x
          monadic = return (apply f) `ap` return x

Testing this fails right away:

>>>  quickCheck prop_ap
*** Failed! Falsifiable (after 1 test and 2 shrinks): 
{_->0}
0

The reason here being that your Monad instance is doing the +1 but your Applicative one isn't doing anything of the sort. So we can distinguish between equivalent computations, but one of them was built with <*> and the other with ap.

2
votes

As described by others, you can't count "connections" such as binds or arrow binding operations, because then they won't satisfy monad/arrow laws.

However, what you can do is to create an arrow where you can explicitly give sizes to your building blocks and then compute the size of such an circuit. To give an example: {-# LANGUAGE Arrows #-}

import Control.Arrow
import qualified Control.Category as C

data A a b c = A { runA :: a b c, sizeA :: !Int }

Here we defined an arrow transformer that wraps an existing arrow and adds its size.

instance (C.Category a) => C.Category (A a) where
    id = A C.id 0
    (A a1 s1) . (A a2 s2) = A (a1 C.. a2) (s1 + s2)

instance (Arrow a) => Arrow (A a) where
    arr f = A (arr f) 0
    first (A f s) = A (first f) s

instance (ArrowChoice a) => ArrowChoice (A a) where
    left (A f s) = A (left f) s

-- instance (Arrow a) => ArrowTransformer A a where
--     lift a = A a 0

The default size must be always 0 to satisfy the laws. For example id must have size of 0, as x . id === x, thanks to law arr id === id we have that arr f must also have size of 0 etc.

But we can define a custom function that assigns a given size to an underlying arrow:

sized :: Int -> a b c -> A a b c
sized = flip A

To give an example, let's construct some arrows of type A (->). That is, the underlying arrows are just functions.

-- * Example (adapted from https://wiki.haskell.org/Arrow_tutorial)

-- | Both 'f' and 'g' are constructed to have a size of 1.
f, g :: A (->) Int Int
f = sized 1 $ arr (`div` 2)
g = sized 1 $ arr (\x -> x*3 + 1)

h :: A (->) Int Int
h = proc x -> do
      fx <- f -< x
      gx <- g -< x
      returnA -< (fx + gx)

You can run h for example as runA h 5. But you can also measure its size by sizeA h, which returns 2, as expected. Note that you don't need to run the arrow to get its size. You can picture it as a circuit, and you don't need to actually power up a circuit to just view its size.

Note that we can't do this for a monad, so we can't have instance ArrowChoice A. In a monad we can compute the next "effect" from a previous result, which means we can never compute the size without actually running the monadic computation.