12

次の点を考慮してください。

do
  x1 <- new 2
  set x1 3
  x2 <- get x1
  y1 <- new 10
  set y1 20
  y2 <- get y1
  return (x2 + y2)

私はこれを結果にしたい23。純粋な Haskell でこのようなものを実装する方法はありますか? このようなことは理解STRefしていますが、通常のHaskellでやりたいだけです(現時点では効率について心配していません)。データ型を作成して のインスタンスにする必要があると思いますがMonad、詳細がわからないため、実際の例が役立ちます。

4

4 に答える 4

6

これは複数の値を許可しますが、より複雑です:) これは、ダニエルの提案でうまく単純化されてい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 [])

それからそれを使用する

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)

Refs は基本的にInt、いくつかの型情報が添付された s でありval、適切なものを検索しDynamicて正しい型に強制しようとします。

これが実際のコードである場合は、 と の実装を非表示にする必要がRefありMutStateます。便宜上、安全な実装が必要な場合fromJustは、bur の戻り値を編集しました。バインドされていない変数を処理するためにレイヤーとモナドを使用できると思います。valStateMaybe

上記のように、型付け可能な制約が心配な場合は、簡単に派生します。

于 2013-10-07T15:02:36.957 に答える
5

にはすでに実装がありますが、Control.Monad.State一般性のために面倒です。1 つの複雑さは MonadState クラスに由来し、もう 1 つの複雑Stateさはより一般的な観点から Plain が実装されているという事実に由来し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

モジュール内のすべての関数を実装することが可能であり、>>=/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

に保存してにMyState.hs置き換えます。import Control.Monad.Stateimport MyState

于 2013-10-07T14:51:08.497 に答える
2

Stateまたは、それStateTをエミュレートすることができます(State1つの値のみを許可します)。最も簡単な方法は次の使用Mapです。

 do
  put empty
  set "x1" 3  
  x2 <-  getKey "x1"
  set "y1" 20
  y2 <-  getKey "y1"
  return (x2 + y2)
    where
      getKey k = fromJust . (lookup k) `fmap` get
      set = modify replace
      replace d k m = if k `member` m then update (\_ -> Just d) k m
                      else insert k d m
于 2013-10-07T14:56:19.640 に答える