[Haskell-cafe] 2 line finite (monadic) state machine

Izaak Meckler izaakmeckler at me.com
Sat Oct 13 19:09:14 CEST 2012


Hi all,

I just wrote some nice code: A finite state machine with monadic state, allowing both DFAs and NFAs to be expressed with the same functions. I've only used it in [], Set, and Maybe, but I think it would be interesting in several others (a probability monad comes to mind). Also, if anyone has any sensible interpretation of this in the continuation monad, let me know.
import Control.Monad
import Data.Maybe

type State = String
type Map a b = [(a, b)]

-- In Map State (Map Char (m State)), the monad m determines the kind of FSM that is being run.
-- If m = [] (or Set), these functions work as a NFA. If m = Maybe, we essentially have a DFA.

transition :: (MonadPlus m) => Map State (Map Char (m State)) -> State -> Char -> m State
transition transMap q c = fromMaybe mzero $ lookup q transMap >>= lookup c

toFSM :: (MonadPlus m) => Map State (Map Char (m State)) -> State -> (String -> m State)
toFSM transMap q0 = foldM (transition transMap) q0

egMachine = toFSM [("p", [ ('0', ["p"])
                         , ('1', ["p", "q"])])]
                  "p"

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121013/212c8bae/attachment.htm>


More information about the Haskell-Cafe mailing list