LoginSignup
2
3

More than 5 years have passed since last update.

Haskell でミーリマシン (Mealy Machine)

Last updated at Posted at 2015-01-09

Auto アローについて調べていたらとてもわかりやすい Auto についての記事を見つけたのでその紹介と, Auto 型に慣れるために Mealy machine を実装してみたのでメモ.

Intro to Machines & Arrows (Part 1: Stream and Auto) · in Code
Auto as Category, Applicative & Arrow (Intro to Machines/Arrows Part 2) · in Code

コード中の myMealyhttp://en.wikipedia.org/wiki/Mealy_machine の Example にあったもので,現在の入力と一つ前の入力の XOR を出力する Mealy machine.

コード

mealy_machine.hs
{-# LANGUAGE NamedFieldPuns #-}

newtype Auto a b = ACons { runAuto :: a -> (b, Auto a b) }

data S = Si | S0 | S1
  deriving Show

data Σ = Σ0 | Σ1
  deriving Show

data Λ = Λ0 | Λ1
  deriving Show


data Mealy s σ λ = Mealy { s0 :: s
                         , t :: (s, σ) -> s
                         , g :: (s, σ) -> λ
                         }

mealyToAuto :: Mealy s σ λ -> Auto σ λ
mealyToAuto Mealy { s0, t, g } = mealy s0
  where mealy s = ACons $ \σ -> (g (s, σ), mealy $ t (s, σ))

myMealy :: Mealy S Σ Λ
myMealy = Mealy { s0 = Si, t, g }
  where t (_,  Σ0) = S0
        t (_,  Σ1) = S1
        g (S0, Σ1) = Λ1
        g (S1, Σ0) = Λ1
        g _        = Λ0


testAuto :: Auto a b -> [a] -> ([b], Auto a b)
testAuto auto []      = ([]  , auto )
testAuto auto (x:xs)  = (y:ys, final)
  where
    (y,  next ) = runAuto  auto x
    (ys, final) = testAuto next xs

testAuto_ :: Auto a b -> [a] -> [b]
testAuto_ = (fst .) . testAuto


test = testAuto_ (mealyToAuto myMealy) [Σ0, Σ1, Σ0, Σ1, Σ1, Σ1, Σ0, Σ0]

解説

ミーリマシン : 有限オートマトンのうち,トランスデューサ (変換機 : 入力を出力に変換するオートマトン) と呼ばれるもののひとつ.出力が入力と現在の状態から決まる.

NamedFieldPuns : Mealy { s0 = s0, t = t, g = g } みたいに書くところを Mealy { s0, t, g } でよくなる

Auto : オートマトンを表す型.入力 a と現在の内部状態から出力 b と 新しい内部状態をもったオートマトン Auto a b を生み出す計算.

S : 状態の集合.初期状態 Si
Σ : 入力の集合.0 か 1 の一ビット.
Λ : 出力の集合.0 か 1 の一ビット.

testAuto : オートマトンと入力のリストをとって出力のリストと新しいオートマトンを返す

testAuto_ : testAuto の出力リストだけを返す版

課題

AutoArray にする.

2
3
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
2
3