初識狀態(tài)
先看一個小游戲项贺,這個小游戲用字符串來控制君躺,最后得到總分峭判。
c
用來啟動和停止計分,在啟動計分狀態(tài)下a
加一分棕叫,在停止計分狀態(tài)下b
減一分林螃。
本例中用abcaaacbbcabbab
控制,最終得分為2
俺泣。
module Main where
import Control.Monad.State
-- Example use of State monad
-- Passes a string of dictionary {a,b,c}
-- Game is to produce a number from the string.
-- By default the game is off, a C toggles the
-- game on and off. A 'a' gives +1 and a b gives -1.
-- E.g
-- 'ab' = 0
-- 'ca' = 1
-- 'cabca' = 0
-- State = game is on or off & current score
-- = (Bool, Int)
type GameValue = Int
type GameState = (Bool, Int)
playGame :: String -> State GameState GameValue
playGame [] = do
(_, score) <- get
return score
playGame (x:xs) = do
(on, score) <- get
case x of
'a' | on -> put (on, score + 1)
'b' | on -> put (on, score - 1)
'c' -> put (not on, score)
_ -> put (on, score)
playGame xs
startState = (False, 0)
main = print $ evalState (playGame "abcaaacbbcabbab") startState
定義State Monad
-- 's' is the state, 'a' is the value
newtype State s a = State {
runState :: s -> (a, s)
}
returnState :: a -> State s a
returnState a = State $ \s -> (a, s)
bindState :: State s a -> (a -> State s b) -> State s b
bindState m k = State $ \s -> runState (k a) s'
where (a, s') = runState m s
instance Monad (State s) where
m >>= k = bindState m k
return a = returnState a
注意其中某些值的類型:
runState :: State s a -> s -> (a, s)
m :: State s a
k :: a -> State s b
還需注意治宣,State s a
中的s
是類型,而\s -> ...
中的s
是值砌滞。
單步狀態(tài)轉(zhuǎn)移
-- runState (return 'a') 1 = ('a', 1)
return :: a -> State s a
return x = State $ \s -> (x, s)
-- runState get 1 = (1, 1)
get :: State s a
get = State $ \s -> (s, s)
-- runState (put 5) 1 = ((), 5)
put :: a -> State s ()
put x = State $ \s -> ((), x)
-- evalState (return 'a') 1 = 'a'
evalState :: State s a -> s -> a
evalState s = fst . runState s
-- execState (return 'a') 1 = 1
execState :: State s a -> s -> s
execState s = snd . runState s
用do-notation組合多步轉(zhuǎn)移
因為(State s)
是Monad的實例,
所以坏怪,類型State s a
的值是一個monad value(也稱為action
action中包裝了類型為a
的值贝润。
do-notation可以把各個action串聯(lián)起來。
還可以提取各action中包裝的值铝宵,進行傳遞打掘。
-- runState (do {put 5; return 'a'}) 1 = ('a', 5)
-- runState (do {x <- get; put (x+1); return x) 1 = (1, 2)
-- runState (do {x <- get; put (x-1); get) 1 = (0, 0)
這里詳細(xì)解釋一下runState (do {put 5; return 'a'}) 1
的執(zhí)行過程,
-- put 5 = State $ \s -> ((), 5)
-- return 'a' = State $ \s -> ('a', s)
-- do {put 5; return 'a'}
-- = (put 5) >>= (\_ -> (return 'a'))
-- = (State $ \s -> ((), 5)) >>= (\_ -> (State $ \s -> ('a', s)))
-- = bindState (State $ \s -> ((), 5)) (\_ -> (State $ \s -> ('a', s)))
-- = State $ \s -> runState ((\_ -> (State $ \s -> ('a', s))) a) s' where (a, s') = runState (State $ \s -> ((), 5)) s
-- = State $ \s -> ('a', 5)
-- runState (do {put 5; return 'a'}) 1
-- = runState (State $ \s -> ('a', 5)) 1
-- = ('a', 5)
總結(jié)
evalState 狀態(tài)轉(zhuǎn)移過程 初始狀態(tài)
鹏秋,從初始狀態(tài)出發(fā)尊蚁,最終得到一個結(jié)果值
,
execState 狀態(tài)轉(zhuǎn)移過程 初始狀態(tài)
侣夷,從初始狀態(tài)出發(fā)横朋,最終得到一個結(jié)果狀態(tài)
,
runState 狀態(tài)轉(zhuǎn)移過程 初始狀態(tài)
百拓,從初始狀態(tài)出發(fā)琴锭,最終得到一個元組(結(jié)果值, 結(jié)果狀態(tài))
。
而狀態(tài)轉(zhuǎn)移過程
可以是狀態(tài)的單步轉(zhuǎn)移衙传,也可以是用do-notation串聯(lián)起來的多步轉(zhuǎn)移决帖。
因此,State Monad的做法蓖捶,可以看做將狀態(tài)轉(zhuǎn)移過程
固化下來地回,最后再一次性從初始狀態(tài)轉(zhuǎn)移到最終狀態(tài)。