我试图创建单子变压器的堆栈和我遇到麻烦正确的类型签名我的功能。 (我还是很新的哈斯克尔)

在堆栈将多个StateT变压器,因为我有多个状态,我需要跟踪(可以tupled两个,但我会得到在第二)和日志记录WriterT。

这是我到目前为止有:

module Pass1 where
import Control.Monad.Identity
import Control.Monad.State
import Control.Monad.Writer
import Data.Maybe
import qualified Data.Map as Map
import Types

data Msg = Error String
         | Warning String

type Pass1 a = WriterT [Msg] (StateT Int (StateT [Line] (StateT [Address] Identity))) a


runPass1 addrs instrs msgs = runIdentity (runStateT (runStateT (runStateT (runWriterT msgs) 1) instrs) addrs)


--popLine :: (MonadState s m) => m (Maybe s)
--popLine :: (Monad m) => StateT [Line] m (Maybe Line)
popLine :: (MonadState s m) => m (Maybe Line)
popLine = do
        ls <- get
        case ls of
          x:xs -> do
                    put xs
                    return $ Just x
          []   -> return Nothing


incLineNum :: (Num s, MonadState s m) => m ()
incLineNum = do
               ln <- get
               put $ ln + 1

curLineNum :: (MonadState s m) => m s
curLineNum = do
               ln <- get
               return ln

evalr = do l <- popLine
           --incLineNum
           return l

我想popLine乱用的[Line]状态和xLineNum功能以影响Int状态。 evalr是将被传递到runPass1计算。

每当加载代码我碰上其通常是以下各种错误:

Pass1.hs:23:14:
    No instance for (MonadState [t] m)
      arising from a use of `get' at Pass1.hs:23:14-16
    Possible fix: add an instance declaration for (MonadState [t] m)
    In a stmt of a 'do' expression: ls <- get
    In the expression:
        do ls <- get
           case ls of {
             x : xs -> do ...
             [] -> return Nothing }
    In the definition of `popLine':
        popLine = do ls <- get
                     case ls of {
                       x : xs -> ...
                       [] -> return Nothing }


Pass1.hs:22:0:
    Couldn't match expected type `s' against inferred type `[Line]'
      `s' is a rigid type variable bound by                        
          the type signature for `popLine' at Pass1.hs:21:23        
    When using functional dependencies to combine                  
      MonadState [Line] m,                                         
        arising from a use of `get' at Pass1.hs:23:14-16            
      MonadState s m,                                              
        arising from the type signature for `popLine'              
                     at Pass1.hs:(22,0)-(28,31)                     
    When generalising the type(s) for `popLine'         




Pass1.hs:23:14:
    Could not deduce (MonadState [Line] m)
      from the context (MonadState s m)   
      arising from a use of `get' at Pass1.hs:23:14-16
    Possible fix:                                    
      add (MonadState [Line] m) to the context of    
        the type signature for `popLine'             
      or add an instance declaration for (MonadState [Line] m)
    In a stmt of a 'do' expression: ls <- get
    In the expression:
        do ls <- get
           case ls of {
             x : xs -> do ...
             [] -> return Nothing }
    In the definition of `popLine':
        popLine = do ls <- get
                     case ls of {
                       x : xs -> ...
                       [] -> return Nothing }

签名的无似乎是正确的,但是POPLINE是第一功能,所以它是唯一一个立即导致一个错误。

我尝试添加它表明在签名类型(如:popLine :: (MonadState [Line] m) => ...但随后像这样它的错误:

Pass1.hs:21:0:
    Non type-variable argument in the constraint: MonadState [Line] m
    (Use -XFlexibleContexts to permit this)                          
    In the type signature for `popLine':                             
      popLine :: (MonadState [Line] m) => m (Maybe Line)

我似乎总是得到这个消息时,我尝试做一些事情,不是一个类型的变量。这似乎喜欢上别的(MonadState s m) OK和错误,但是当我尝试将其与[a],而不是类似上述s它的错误。 (最初[行]和Int在一个单一的状态被tupled,但所以我想我会尝试把它们放在独立的国家,我收到此错误)。

GHC 6.10.4,Kubuntu的

那么,谁能告诉我是怎么回事,并给予解释/告诉我正确的类型签名,或有没有人知道这个东西很有参考价值(到目前为止已帮助是“单子变形金刚步骤的唯一的事情通过步骤”,但只是使用一个辅助状态函数和一个StateT)?

预先非常感谢。

修改结果 下面是结合JFT的和Edward的建议的编译代码:

{-# LANGUAGE GeneralizedNewtypeDeriving #-} -- needed for: deriving (Functor,Monad)
{-# LANGUAGE MultiParamTypeClasses #-}      -- needed for: MonadState instance
{-# LANGUAGE FlexibleContexts #-}           -- needed for: (MonadState PassState m) => ...

module Pass1 where
import Control.Monad.State
import Control.Monad.Writer
import Data.Maybe
import Types

type Lines     = [Line]
type Addresses = [Address]
type LineNum   = Int
type Messages  = [Msg]
data Msg = Error String
         | Warning String

data PassState = PassState { passLineNum :: LineNum
                           , passLines :: Lines
                           , passAddresses :: Addresses
                           }

newtype Pass1 a = Pass1 { unPass1 :: WriterT Messages (State PassState) a
                        }
                        deriving (Functor,Monad)

instance MonadState PassState Pass1 where
        get   = Pass1 . lift $ get
        put s = Pass1 . lift $ put s



runPass1 :: PassState -> Pass1 a -> ((a, Messages), PassState)
runPass1 state = flip runState state .
                 runWriterT          .
                 unPass1


curLineNum :: (MonadState PassState m) => m LineNum
curLineNum = do
               state <- get
               return $ passLineNum state


nextLine :: (MonadState PassState m) => m (Maybe Line)
nextLine = do
             state <- get
             let c = passLineNum state
             let l = passLines state
             case l of
               x:xs -> do
                         put state { passLines = xs, passLineNum = (c+1) }
                         return $ Just x
               _ -> return Nothing



evalr :: Pass1 (Maybe Line,LineNum)
evalr = do
          l <- nextLine
          c <- curLineNum
          --tell $ Warning "hello"
          return (l,c)

我结合incLineNumpopLinenextLine我仍然需要得到作家单子部分工作,但我想知道在哪里可以从这里走。感谢,各位。

有帮助吗?

解决方案

有与您的代码段的许多问题。我定你的代码片段添加解释什么被打破,并加入了一些风格的建议,如果你的关心。

module Pass1_JFT where
import Control.Monad.Identity
import Control.Monad.State
import Control.Monad.Writer
import Data.Maybe
import qualified Data.Map as Map

{ - 用简单的定义替换汇入类型 - }

--import Types
type Line       = String
type Address    = String
type LineNumber = Int

{ -     不是你的问题,但在这里我的2美分的一部分...     说,你要如果你不改变集合你的状态     使用类型别名,你必须寻找everwhere你使用它。而不是仅仅     如果需要更改这些定义 - }

type Lines     = [Line]
type Addresses = [Address]
type Messages  = [Msg]


data Msg = Error String
         | Warning String

{ -     什么是诠释在StateT诠释?将它命名为便于阅读,推理     和改变。声明FTW让我们使用LineNumber上,而不是 - }

--type Pass1 a = WriterT [Msg] (StateT Int (StateT [Line] (StateT [Address] Identity))) a

{ -     让我们用一个“真实”的类型,这样的实例可以得出。     由于1步是不是一个单子转印即没有被定义为1步米,     使用StateT最深StateT即StateT [地址]身份没有点     所以我们只用一个国家[联系地址] - }

newtype Pass1 a = Pass1 {
    unPass1 :: WriterT Messages (StateT LineNumber (StateT Lines (State Addresses))) a
                        }
                        deriving (Functor,Monad)

--runIdentity (runStateT (runStateT (runStateT (runWriterT msgs) 1) instrs) addrs)

{ -     让我们剥开从最外层是堆栈(lefmost在声明)     到最里面的是身份在你原来的声明。     需要注意的是runWriterT并不需要一个初始状态...     对于runStateT(和runState)第一个参数不是初始状态     但单子......让我们翻转! - }

runPass1' :: Addresses -> Lines -> Messages -> Pass1 a ->  ((((a, Messages), LineNumber), Lines), Addresses)
runPass1' addrs instrs msgs = flip runState addrs   .
                              flip runStateT instrs .
                              flip runStateT 1      .
                              runWriterT            . -- then get process the WriterT (the second outermost)
                              unPass1                 -- let's peel the outside Pass1

{ -     现在最后一个函数不去做你想做的,因为你要提供     初始日志追加到与WriterT。     既然是单子转换我们将在这里做一些技巧 - }

-- I keep the runStateT convention for the order of the arguments: Monad then state
runWriterT' :: (Monad m,Monoid w) => WriterT w m a -> w -> m (a,w)
runWriterT' writer log = do
    (result,log') <- runWriterT writer
    -- let's use the monoid generic append in case you change container...
    return (result,log `mappend` log')

runPass1 :: Addresses -> Lines -> Messages -> Pass1 a ->  ((((a, Messages), LineNumber), Lines), Addresses)
runPass1 addrs instrs msgs = flip runState addrs   .
                             flip runStateT instrs .
                             flip runStateT 1      .
                             flip runWriterT' msgs . -- then get process the WriterT (the second outermost)
                             unPass1                 -- let's peel the outside Pass1

{ -     你打算直接从1步调用堆栈POPLINE?     如果是这样,你需要“教” 1步是“MonadState线”     要做到这一点,让我们得到1步(这就是为什么我们与NEWTYPE宣布它!) - }

instance MonadState Lines Pass1 where
    -- we need to dig inside the stack and "lift" the proper get
    get   = Pass1 . lift . lift $ get
    put s = Pass1 . lift . lift $ put s

{ -    较好地保持通用的东西,但我们现在可以这样写:    POPLINE :: 1步(也许行) - }

popLine :: (MonadState Lines m) => m (Maybe Line)
popLine = do
        ls <- get
        case ls of
          x:xs -> do
                    put xs
                    return $ Just x
          []   -> return Nothing

{ -     好了,现在我得到了诠释=> LineNumber上....     我们可以使1步和MonadState LineNumber上,但LineNumber上的实例     不应该这样,而不是被弄乱我的斜坡直接编码     和将如果需要的会诊提供MonadReader实例

check ":t incLineNum and :t curLineNum"

- }

incLineNum = Pass1 . lift $ modify (+1)

curLineNum = Pass1 $ lift get

evalr = do l <- popLine
           incLineNum
           return l

有它是一个长缠绕响应但单子和单子堆栈正如所看到的在第一挑战。我固定的代码,但我鼓励你发挥和检查类型的各种功能,了解正在发生的事情,并以比较原始的。 Haskell的类型推理装置通常类型的注释多余的(除非以去除模糊)。一般来说,我们会给予函数的类型不太通用,这是是推断所以最好不要键入注释。型注释是明确了良好的调试技术虽然;)

干杯

P.S。在单子转换真实世界哈斯克尔章是极好的: http://book.realworldhaskell.org/read/monad-transformers.html

其他提示

在一般你会发现代码卷起使用一个StateT与所有你需要状态的位中的一个较大的复合结构更加清晰。一个很好的理由是,当你拿出一块,你忘了你总是可以通过一个字段增长结构,并可以使用记录糖写出单个字段更新或转向有点像fclabels或数据存取状态软件包操纵状态。

data PassState = PassState { passLine :: Int, passLines :: [Line] }

popLine :: MonadState PassState m => m (Maybe Line).   
popLine = do
   state <- get
   case passLines state of
      x:xs -> do 
         put state { passLines = xs }
         return (Just x)
      _ -> return Nothing
许可以下: CC-BY-SA归因
不隶属于 StackOverflow
scroll top