5

Stateそこで私は最近、厳密なトランスフォーマーモジュールと怠惰なトランスフォーマーモジュールの間でコードを共有することを期待して、この素晴らしいアイデアを思いつきました。

{-# LANGUAGE FlexibleInstances, DataKinds, KindSignatures #-}
module State where

data Strictness = Strict | Lazy
newtype State (t :: Strictness) s a = State (s -> (s, a))

returnState :: a -> State t s a
returnState x = State $ \s -> (s, x)

instance Monad (State Lazy s) where
  return = returnState
  State ma >>= amb = State $ \s -> case ma s of
    ~(s', x) -> runState (amb x) s'

instance Monad (State Strict s) where
  return = returnState
  State ma >>= amb = State $ \s -> case ma s of
    (s', x) -> runState (amb x) s'

get :: State t s s
get = State $ \s -> (s, s)

put :: s -> State t s ()
put s = State $ \_ -> (s, ())

厳密な型と怠惰な型の両方で、重複することなく、つまり型クラスインスタンスも何もなしで機能getすることがわかります。putただし、の両方の可能なケースをカバーしていますが、一般的StrictnessにはMonadインスタンスがありません。State t s a

-- from http://blog.melding-monads.com/2009/12/30/fun-with-the-lazy-state-monad/
pro :: State t [Bool] ()
pro = do
  pro
  s <- get
  put (True : s)

-- No instance for (Monad (State t [Bool])) arising from a do statement

以下は、必要FlexibleContextsですが、正常に機能します。

pro :: (Monad (State t [Bool])) => State t [Bool] ()
-- otherwise as before

t次に、Lazyまたはでインスタンス化しStrictて結果を実行し、期待どおりの結果を得ることができます。しかし、なぜ私はその文脈を与えなければならないのですか?これは概念的な制限ですか、それとも実際的な制限ですか?なぜMonad (State t s a)実際に成り立たないのか、私が見逃している理由があるのでしょうか、それともGHCにそれを納得させる方法がまだないのでしょうか。

(余談ですが、コンテキストの使用はMonad (State t s) 機能しません

Could not deduce (Monad (State t [Bool])) arising from a do statement from the context (Monad (State t s))

それは私をさらに混乱させます。確かに前者は後者から推論可能ですか?)

4

1 に答える 1

5

これは制限ですが、正当な理由があります。それがそのように機能しなかった場合、期待されるセマンティクスはどうなるでしょうか。

runState :: State t s a -> s -> (s,a)
runState (State f) s = f s

example :: s -> a
example = snd $ runState ((State undefined) >> return 1) ()

まあ、それは可能性があります

example = snd $ runState ((State undefined) >>= \_ -> return 1) ()
        = snd $ runState (State $ \s -> case undefined s of (s',_) -> (s',1)) ()
        = snd $ case undefined () of (s',_) -> (s',1)
        = snd $ case undefined of (s',_) -> (s',1)
        = snd undefined
        = undefined

またはそれは可能性があります

example = snd $ runState ((State undefined) >>= \_ -> return 1) ()
        = snd $ runState (State $ \s -> case undefined s of ~(s',_) -> (s',1)) ()
        = snd $ case undefined () of ~(s',_) -> (s',1)
        = snd $ (undefined,1)
        = 1

これらは同じではありません。1つのオプションは、関数を次のような追加のクラスで定義することです。

class IsStrictness t where
   bindState :: State t s a -> (a -> State t s b) -> State t s b

次に定義します

instance IsStrictness t => Monad (State t s) where
   return = returnState
   (>>=) = bindState

bindStateの一部として定義する代わりにIsStrictness、シングルトンを使用できます

data SingStrictness (t :: Strictness) where
   SingStrict :: SingStrictness Strict
   SingLazy   :: SingStrictness Lazy

class IsStrictness t where
   singStrictness :: SingStrictness t

bindState :: IsStrictness t => State t s a -> (a -> State t s b) -> State t s b
bindState ma' amb' = go singStrictness ma' amb' where
  go :: SingStrictness t -> State t s a -> (a -> State t s b) -> State t s b
  go SingStrict ma amb = ...
  go SingLazy ma amb = ...

これは、カスタムクラスとシングルトンタイプの代わりに、GHC7.6のシングルトンインフラストラクチャを使用してさらに拡張できます。あなたは

instance SingI t => Monad (State t s)

それほど怖くないです。SingI _制約セットにたくさんあることに慣れてください。これは、少なくともしばらくの間は機能する方法であり、それほど醜いものではありません。

State t [Bool]から推論できない理由についてはState t s、問題はState t sトップレベルのコンテキストにあることです。つまりs、最も外側のレベルで定量化されます。あなたは、「モナド(状態ts)があなたに与えるような任意のtとsに対して...」という関数を定義しています。しかし、これは「モナド(State t [Bool])私があなたにあげるようなtのために...」とは言いません。悲しいことに、これらの全称記号の制約はHaskellではそれほど簡単ではありません。

于 2013-01-11T04:34:29.013 に答える