2012-05-24 2 views
5

나는 ErrorT을 포함하는 모나드 변압기 스택을 가지고 있으며, 전체적으로 ContT r 변압기를 감싸고 싶습니다. 이 작업을 시도 할 때 throwError에 대한 호출은 유형 오류를 생성합니다. 분명히 ContT rMonadError의 인스턴스가 아닙니다. 좋아, 내가 생각 - 난 그냥 하나에 그것을 만들 수 있습니다 :왜 ContT를 MonadError의 인스턴스로 만들 수 없습니까?

instance MonadError e m => MonadError e (ContT r m) where 
    throwError = lift . throwError 
    catchError = liftCatch . catchError 

liftCatch의 일부에 적합한 정의를 사용.

src\Language\Types.hs:68:10: 
    Illegal instance declaration for `MonadError e (ContT r m)' 
     (the Coverage Condition fails for one of the functional dependencies; 
     Use -XUndecidableInstances to permit this) 
    In the instance declaration for `MonadError e (ContT r m)' 

을 나는 UndecidableInstances 프라그 (나는 예 this question를 참조 너무 걱정하지의 인상을 해요) 사용하는 것이 행복 해요하지만 제작에 어려움이 있다면 궁금 :하지만 지금 컴파일 할 때 나는 오류를 얻을 MonadError의 인스턴스로 연속 트랜스포머 - 괜찮 으면, Control.Monad.Trans 패키지의 저자는 이미 그것을했을 것입니다 ... 맞습니까?

+1

은 괜찮지 만 수행 변압기 라이브러리의 제작자에게 잠재적으로 위험하고 휴대하기 어려운 UndecidableInstances를 가져옵니다. –

답변

8

ContT 및 ErrorT 모두 비표준 제어 흐름을 허용합니다. ErrorT 유형을 ContT에서 mtl로 둘러 쌀 수있는 방법이 있습니다.

instance (Error e, MonadCont m) => MonadCont (ErrorT e m) 

그러나이 두 모나드 변환기는 통근하지 않습니다. 기억하는 :

newtype Identity a = Identity {runIdentity :: a} 
newtype ErrorT e m a = ErrorT {runErrorT :: m (Either e a)} 
newtype ContT r m a = ContT {runContT :: (a -> m r) -> m r} 

ErrorT String (ContT Bool Identity)() 패키지 MTL에 괜찮 수 :

ErrorT (ContT (\ (k :: Either String() -> Identity Bool) -> k (Right()))) 

ContT r (ErrorT e Identity) a는 패키지 MTL에서 좋아하지 않습니다. 그러나 당신은 그것을 쓸 수 있습니다.

결합 모나드에서 원하는 (>> =) 의미는 무엇입니까? 중첩 된 오류 처리기 스택이 로컬이 아닌 callCC와 어떻게 상호 작용할 것으로 예상합니까? 여기

내가 그것을 쓸 수있는 방법은 다음과 같습니다 단지 MTL과

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-} 
import Control.Monad 
import Control.Monad.Cont 
import Control.Monad.Error 
import Data.Function 
import Data.IORef 

handleError :: MonadError e m => (e -> m a) -> m a -> m a 
handleError = flip catchError 

test2 :: ErrorT String (ContT() IO)() 
test2 = handleError (\e -> throwError (e ++ ":top")) $ do 
    x <- liftIO $ newIORef 1 
    label <- callCC (return . fix) 
    v <- liftIO (readIORef x) 
    liftIO (print v) 
    handleError (\e -> throwError (e ++ ":middle")) $ do 
    when (v==4) $ do 
     throwError "ouch" 
    when (v < 10) $ do 
     liftIO (writeIORef x (succ v)) 
     handleError (\e -> throwError (e ++ ":" ++ show v)) label 
    liftIO $ print "done" 

go2 = runContT (runErrorT test2) (either error return) 

{- 

*Main> go2 
1 
2 
3 
4 
*** Exception: ouch:middle:top 

-} 

따라서 위 작품, 여기에 새로운 인스턴스이며 어떻게 작동하는지 :

instance MonadError e m => MonadError e (ContT r m) where 
    throwError = lift . throwError 
    catchError op h = ContT $ \k -> catchError (runContT op k) (\e -> runContT (h e) k) 

test3 :: ContT() (ErrorT String IO)() 
test3 = handleError (\e -> throwError (e ++ ":top")) $ do 
    x <- liftIO $ newIORef 1 
    label <- callCC (return . fix) 
    v <- liftIO (readIORef x) 
    liftIO (print v) 
    handleError (\e -> throwError (e ++ ":middle")) $ do 
    when (v==4) $ do 
     throwError "ouch" 
    when (v < 10) $ do 
     liftIO (writeIORef x (succ v)) 
     handleError (\e -> throwError (e ++ ":" ++ show v)) label 
    liftIO $ print "done" 

go3 = runErrorT (runContT test3 return) 

{- 

*Main> go3 
1 
2 
3 
4 
Left "ouch:middle:3:middle:2:middle:1:middle:top" 

-}