Cli*_*ton 11 monads haskell state-monad
考虑以下:
do
x1 <- new 2
set x1 3
x2 <- get x1
y1 <- new 10
set y1 20
y2 <- get y1
return (x2 + y2)
Run Code Online (Sandbox Code Playgroud)
我想要这个结果23
.有没有办法在纯Haskell中实现这样的东西,如果是这样的话怎么样?我理解STRef
这样的事情,但我只是想在普通的Haskell中做到这一点(现在不担心效率).我认为我必须创建一个数据类型并使其成为实例Monad
,但我不确定细节,所以一个有用的例子会有所帮助.
这允许多个值,但它更加毛茸茸:)这很好地简化了丹尼尔的建议Dynamic
.
import Data.Dynamic
import Data.Maybe
import Control.Monad.State
import Data.Map as M
newtype Ref a = Ref {ref :: Int}
type MutState = State (Int, Map Int Dynamic)
val :: Typeable a => Ref a -> MutState a
val r = snd `fmap` get >>=
return . fromJust . (>>= fromDynamic) . M.lookup (ref r)
new :: Typeable a => a -> MutState (Ref a)
new a = do
(curr, binds) <- get
put (curr + 1, M.insert (curr + 1) (toDyn a) binds)
return . Ref $ curr + 1
set :: Typeable a => Ref a -> a -> MutState ()
set (Ref i) a = do
(c, m) <- get
put (c, M.insert i (toDyn a) m)
runMut :: MutState a -> a
runMut = flip evalState (0, M.fromList [])
Run Code Online (Sandbox Code Playgroud)
然后使用它
default (Int) -- too lazy for signatures :)
test :: Int
test = runMut $ do
x1 <- new 2
set x1 3
x2 <- val x1
y1 <- new 10
set y1 20
y2 <- val y1
return (x2 + y2)
Run Code Online (Sandbox Code Playgroud)
Ref
s基本上Int
是s附加了一些类型信息,val
并将查找相应的Dynamic
并尝试强制它进入正确的类型.
如果这是真正的代码,你应该隐藏的实现Ref
和MutState
.为方便起见,如果你想要一个安全的实现我已经fromJust
编辑了val
bur 的返回我想你可以分层State
和Maybe
monad来处理未绑定的变量.
如果您担心类型限制,如上所示,它们可以简单地推导出来.
已经有了一个实现Control.Monad.State
,但是为了一般性起见它很麻烦:一个复杂性来自MonadState类,另一个复杂性来自于State
更普遍的实现StateT
.
以下是使用该实现的任务示例.没有使用可变性.请注意,您的示例按原样粘贴,只需添加x
前缀:
import Control.Monad.State
import qualified Data.Map as M
type MyMap a = M.Map Int a
type MyState a b = State (MyMap a) b
type MyRef = Int
xrun :: MyState a b -> b
xrun x = evalState x (M.empty)
mget :: MyState a (MyMap a)
mget = get
mput :: MyMap a -> MyState a ()
mput = put
mmodify :: (MyMap a -> MyMap a) -> MyState a ()
mmodify x = modify x
xnew :: s -> MyState s MyRef
xnew val = do
s <- mget
let newRef = if M.null s then 0 else fst (M.findMax s) + 1
mput $ M.insert newRef val s
return newRef
xset :: MyRef -> a -> MyState a ()
xset ref val = modify $ M.insert ref val
xget :: MyRef -> MyState a a
xget ref = fmap (\s -> case M.lookup ref s of Just v -> v) get
test :: MyState Int Int
test = do
x1 <- xnew 2
xset x1 3
x2 <- xget x1
y1 <- xnew 10
xset y1 20
y2 <- xget y1
return (x2 + y2)
main = print $ xrun test
Run Code Online (Sandbox Code Playgroud)
可以实现模块中的所有功能和>>=
/或return
不使用库存实现来Control.Monad
保留签名.
这里是:
module MyState (State, get, put, modify, evalState) where
newtype State s a = State (s -> (a, s))
evalState :: State s a -> s -> a
evalState (State f) = fst . f
instance Monad (State s) where
return a = State $ \s -> (a, s)
State f >>= g = State $ \s ->
case f s of
(a', s') -> case g a' of
State h -> h s'
instance Functor (State s) where
fmap f (State g) = State $
\s -> case g s of (a, s) -> (f a, s)
get :: State s s
get = State (\s -> (s, s))
put :: s -> State s ()
put s = State $ \_ -> ((), s)
modify :: (s -> s) -> State s ()
modify f = get >>= put . f
Run Code Online (Sandbox Code Playgroud)
保存MyState.hs
并替换import Control.Monad.State
为import MyState
.
归档时间: |
|
查看次数: |
1295 次 |
最近记录: |