如何在莫纳德州的球场上打乒乓球



是否可以使用pattens matching/guards编写函数a

{-# LANGUAGE PatternGuards #-}
import Control.Monad.State.Strict(State, gets, runStateT)
data MyState = MyState
    { counter :: Int
    } deriving (Show)

a :: State MyState String
a = do
    i <- gets counter
    case i of
        0 -> return "hello"
        1 -> return "bye"
run = runStateT a ( MyState{counter=0} )

我试着把a写成

a' :: State MyState String
a' | i <- gets counter, i == 0 = return "hello"

但是得到了错误:

No instance for (Control.Monad.State.Class.MonadState MyState m0)
  arising from a use of ‘gets’
The type variable ‘m0’ is ambiguous
Note: there are several potential instances:
  instance Control.Monad.State.Class.MonadState s m =>
           Control.Monad.State.Class.MonadState
             s (Control.Monad.Trans.Cont.ContT r m)
    -- Defined in ‘Control.Monad.State.Class’
  instance (Control.Monad.Trans.Error.Error e,
            Control.Monad.State.Class.MonadState s m) =>
           Control.Monad.State.Class.MonadState
             s (Control.Monad.Trans.Error.ErrorT e m)
    -- Defined in ‘Control.Monad.State.Class’
  instance Control.Monad.State.Class.MonadState s m =>
           Control.Monad.State.Class.MonadState
             s (Control.Monad.Trans.Except.ExceptT e m)
    -- Defined in ‘Control.Monad.State.Class’
  ...plus 12 others
In a stmt of a pattern guard for
               an equation for ‘a'’:
  i <- gets counter
In an equation for ‘a'’:
    a' | i <- gets counter, i == 0 = return "hello"
No instance for (Eq (m0 Int)) arising from a use of ‘==’
The type variable ‘m0’ is ambiguous
Relevant bindings include
  i :: m0 Int (bound at src/TestGen/Arbitrary/Helpers/Z.hs:18:6)
Note: there are several potential instances:
  instance Eq a => Eq (GHC.Real.Ratio a) -- Defined in ‘GHC.Real’
  instance (Eq e, Data.Functor.Classes.Eq1 m, Eq a) =>
           Eq (Control.Monad.Trans.Error.ErrorT e m a)
    -- Defined in ‘Control.Monad.Trans.Error’
  ...plus 118 others
In the expression: i == 0
In a stmt of a pattern guard for
               an equation for ‘a'’:
  i == 0
In an equation for ‘a'’:
    a' | i <- gets counter, i == 0 = return "hello"

这是不可能的。模式保护语法中的左箭头主要与do表示法中的左箭号无关。

如果您愿意,可以使用新的lambda case扩展:

{-# LANGUAGE LambdaCase #-}
a :: State MyState String
a = gets counter >>= case
        0 -> return "hello"
        1 -> return "bye"

或者多途径如果,也许?

{-# LANGUAGE MultiWayIf #-}
a :: State MyState String
a = do
    i <- gets counter
    if
      | i == 0 -> return "hello"
      | i == 1 -> return "bye"

否。这里有一些真正根本的概念不匹配。

模式匹配只有当表达式的最顶部是构造函数函数时才有效,但do样式块的头将是normal函数(在这种情况下是在类型类Monad中定义的函数>>=)。

Guards需要Bool类型的值,但您要交给它们的值必须是State MyState Bool类型(因为monad的一个独特之处是您无法逃离它们)。所以警卫也永远不会工作。

但是,可以访问函子实例。前奏曲中定义了函数;在CCD_ 10中存在CCD_ 8的中缀形式CCD_。你可以这样说:

a' = process <$> gets counter
    where 
        process 0 = "hello"
        process _ = "bye"

或者使用process函数做任何您想做的事情。要得到更像>>=的东西,您还可以将自己的运算符定义为flip fmap,然后您可以编写gets counter >= x -> case x of ...

为什么不写一个助手?

pureA :: MyState -> String
pureA (MyState 0) = "hello"
pureA (MyState 1) = "bye"
pureA _           = ""
a :: State MyState String
a = fmap doA get

这也遵循了将纯粹逻辑的关注点与你的不纯逻辑分离的哲学。

是的,这是可能的,但我建议你不要这样做——很难跟踪哪一块去了哪里。

import Control.Monad.State.Strict(StateT(..))
import Data.Functor.Identity(Identity(..))
data MyState = MyState
    { counter :: Int
    } deriving (Show)
a :: StateT MyState Identity String
a = StateT $  s@(MyState i) -> Identity $
  case i of
    0 -> ("hello", s)
    1 -> ("bye", s)

相关内容

  • 没有找到相关文章

最新更新