Haskell: What monad did I just reinvent?
Asked Answered
S

6

27

I just reinvented some monad, but I'm not sure which. It lets you model steps of a computation, so you can interleave the steps of numerous computations to find which one finishes first.

{-# LANGUAGE ExistentialQuantification #-}
module Computation where

-- model the steps of a computation
data Computation a = forall b. Step b (b -> Computation a) | Done a

instance Monad Computation where
   (Step b g) >>= f = Step b $ (>>=f) . g
   (Done b) >>= f = Step b f
   return = Done

runComputation :: Computation a -> a
runComputation (Step b g) = runComputation (g b)
runComputation (Done a) = a

isDone :: Computation a -> Bool
isDone (Done _) = True
isDone _ = False

-- an order for a set of computations
data Schedule a = a :> Computation (Schedule a) | Last

toList :: Schedule a -> [a]
toList Last = []
toList (a :> c) = a : (toList . runComputation) c

-- given a set of computations, find a schedule to generate all their results
type Strategy a = [Computation a] -> Computation (Schedule a)

-- schedule all the completed computations, and step the rest, 
-- passing the remaining to the given function
scheduleOrStep :: (Queue (Computation a) -> Computation (Schedule a)) -> Strategy a
scheduleOrStep s cs = scheduleOrStep' id cs
  where scheduleOrStep' q ((Done a):cs) = Done $ a :> scheduleOrStep' q cs
        scheduleOrStep' q ((Step b g):cs) = scheduleOrStep' (q . (g b:)) cs
        scheduleOrStep' q [] = s q

-- schedule all completed compuations, step all the rest once, and repeat
-- (may never complete for infinite lists)
-- checking each row of 
-- [ [ c0s0, c1s0, c2s0, ... ]
-- , [ c0s1, c1s1, c2s1, ... ]
-- , [ c0s2, c1s2, c2s2, ... ]
-- ...
-- ]
-- (where cNsM is computation N stepped M times)
fair :: Strategy a
fair [] = Done Last
fair cs = scheduleOrStep (fair . ($[])) cs

-- schedule more steps for earlier computations rather than later computations
-- (works on infinite lists)
-- checking the sw-ne diagonals of 
-- [ [ c0s0, c1s0, c2s0, ... ]
-- , [ c0s1, c1s1, c2s1, ... ]
-- , [ c0s2, c1s2, c2s2, ... ]
-- ...
-- ]
-- (where cNsM is computation N stepped M times)
diag :: Enqueue (Computation a)-> Strategy a
diag _ [] = Done Last
diag enq cs = diag' cs id
  where diag' (c:cs) q = scheduleOrStep (diag' cs) (enq c q $ [])
        diag' [] q = fair (q [])

-- diagonal downwards : 
-- [ c0s0, 
--   c1s0, c0s1, 
--   c2s0, c1s1, c0s2, 
--   ... 
--   cNs0, c{N-1}s1, ..., c1s{N-1}, c0sN,
--   ...
--  ]
diagd :: Strategy a
diagd = diag prepend

-- diagonal upwards : 
-- [ c0s0, 
--   c0s1, c1s0, 
--   c0s2, c1s1, c2s0, 
--   ... 
--   c0sN, c1s{N-1}, ..., c{s1N-1}, cNs0,
--   ...
--  ]
diagu :: Strategy a
diagu = diag append 

-- a queue type
type Queue a = [a] -> [a]
type Enqueue a = a -> Queue a -> Queue a

append :: Enqueue a
append x q = q . (x:)

prepend :: Enqueue a
prepend x q = (x:) . q

I feel like this is probably some kind of threading monad?

Sexology answered 28/8, 2011 at 20:57 Comment(3)
Haskell is the only language I know of where you can't tell what wheel you just reinvented...Plugugly
I was about to close as too localized, but do people really spend their time knowing they're reinventing stuff in Haskell but not what they're reinventing, making this question kind of legitimate (assuming a lot of people would end up reinventing this exact thing, whatever it is)?Diluvial
@Mat: Yes, actually. At least in certain ways. People occasionally make not-quite-jokes that in Haskell, given sufficiently generic code, if it type checks it's almost certain to be doing something useful even if you're not sure what. This is sort of along the same lines, in that if you invent something to solve a specific problem and it clearly generalizes easily, chances are it's already been done. When I was first learning Haskell, at least once I generalized a specific solution only to realize I'd reinvented an obscure corner of the standard libraries.Overhead
T
5

It looks like a resumption-with-state monad. I think there used to be a resumption monad in MTL around GHC 6.6 but if there was it disappeared. William L. Harrison has a number of papers about resumption monads, including Cheap (But Functional) Threads and The Essence of Multitasking.

Tsarina answered 28/8, 2011 at 21:7 Comment(0)
B
5

I don't understand why not

data Computation a = Step (Computation a) | Done a

instance Monad Computation where
   (Step g) >>= f = Step $ g >>= f
   (Done b) >>= f = Step (f b)
   return = Done

I'm not sure what this monad is, but it's definitely simpler and seems to be equivalent in most respects.

Byword answered 29/8, 2011 at 6:51 Comment(4)
That is the plain Resumption monad. Rampion's original monad has a threaded state like the unfoldr function, though I can't really see if the state is necessary for the example given. In one of his papers, William Harrison comments that the Resumption monad is basically "inert" without adding state to it (inert is not his original word but I can't find the quote at the moment).Tsarina
@stephen tetley: With the existential quantification I've given the state, however, there's nothing that can be done with it, so in effect, it's just delaying computation. Which is what lazy evaluation does anyway, so it's equivalent to the Resumption monad. So that's the answer.Sexology
@Sexology by expliciting the state, you can have it fed from somewhere else though. of course if you don't add any other thing in the monad instance, aka you get the state from some identity function, that should be the same as lazy evaluation indeed, but you can imagine the first "b" to be a name (type string), (or better some gadt indexed by b), and the 2nd one a real b. that's what i intuit, but have you given it some thoughts since ?Chabazite
also, it would he useful to open up your type to ComputationF a next then Fix (Computation a) it. that allows for some free monad, if you want to substitute the binds by some other monad later on, or free applicative, if you know your inputs are independent from one anotherChabazite
F
2

I haven't spent too much time understanding your code, but it really sounds like the coroutine monad from the monad-coroutine package, which may be a bit more general.

Fingertip answered 28/8, 2011 at 21:53 Comment(1)
I glanced briefly at that - it looked like coroutines were communication based, while these are non-communicative.Sexology
M
2

This looks similar to the definition of stream fusion used by Don Stewart did a while ago, and also somewhat related to iteratees (though wihtout the notion of pushing data into the iteratee using an enumerator), but less so than stream fusion I guess.

Mickey answered 29/8, 2011 at 4:36 Comment(0)
O
2

Note the Free monad construction

data Free f a = Pure a | Free (f (Free f a))

Therefore, we can write

data ComputationF a = forall b. ComputationF b (b -> a)
type Computation = Free ComputationF
Outtalk answered 20/6, 2023 at 17:26 Comment(1)
Your answer could be improved with additional supporting information. Please edit to add further details, such as citations or documentation, so that others can confirm that your answer is correct. You can find more information on how to write good answers in the help center.Barnardo
V
1

This is (isomorphic to) the delay monad, by co-yoneda:

data Computation a = forall b. Step b (b -> Computation a) | Done a
data Computation a = Step (Coyoneda Identity (Computation a)) | Done a
data Computation a = Step (Identity (Computation a)) | Done a
data Computation a = Step (Computation a) | Done a

EDIT: well, they're isomorphic as endofunctors. Your Monad instance isn't lawful because return x >>= f ≠ f x, so there's not much point commenting on that.

Veto answered 20/3, 2024 at 19:38 Comment(0)

© 2022 - 2025 — McMap. All rights reserved.