[Haskell-cafe] how would I do this properly in Haskell?

John Wiegley johnw at newartisans.com
Fri Aug 25 05:30:56 UTC 2017


>>>>> "DR" == Dennis Raddle <dennis.raddle at gmail.com> writes:

DR> I'm an advanced beginner, and I'm finding it hard to comprehend
DR> Data.Machine.Moore. Is there a way to explain more to me how this would
DR> look in practice? Or is there another way to organize it that is less
DR> "computer-sciency" and I could work with more easily?

Thinks of a Moore machine as a packaged up State function, where you have an
initial state, and the type of that state is hidden within the machine.  For
example:

    {-# LANGUAGE ExistentialQuantification #-}
    
    data Moore i m o = forall s. Moore
        { mooreInit :: s
        , mooreFunc :: i -> StateT s m o
        }

This machine is really just a packaged function, yielding outputs from inputs,
while dependent on an internal state that may vary at each call.

Since the state is "existential" (or private to Moore), it can be changed
freely when you combine machines:

    instance (Monad m, Monoid o) => Monoid (Moore i m o) where
        mempty = Moore () (const (return mempty))
        Moore s1 f1 `mappend` Moore s2 f2 = Moore (s1, s2) go
          where
            go ev = StateT $ \(st1, st2) -> do
                (mres, st1')  <- runStateT (f1 ev) st1
                (mres', st2') <- runStateT (f2 ev) st2
                return (mres <> mres', (st1', st2'))

Something like this could serve your needs, without needing an external
package like 'machines'. I've used it to do almost just what you described
initially.

-- 
John Wiegley                  GPG fingerprint = 4710 CF98 AF9B 327B B80F
http://newartisans.com                          60E1 46C4 BD1A 7AC1 4BA2


More information about the Haskell-Cafe mailing list