9

这个问题类似于这个问题。然而,这个是关于异常的,而不是关于惰性 I/O。

这是一个测试:

{-# LANGUAGE ScopedTypeVariables #-}

import Prelude hiding ( catch )
import Control.Exception

fooLazy :: Int -> IO Int
fooLazy m = return $ 1 `div` m

fooStrict :: Int -> IO Int
fooStrict m = return $! 1 `div` m

test :: (Int -> IO Int) -> IO ()
test f = print =<< f 0 `catch` \(_ :: SomeException) -> return 42

testLazy :: Int -> IO Int
testLazy m = (return $ 1 `div` m) `catch` \(_ :: SomeException) -> return 42

testStrict :: Int -> IO Int
testStrict m = (return $! 1 `div` m) `catch` \(_ :: SomeException) -> return 42

所以我写了两个fooLazy惰性和fooStrict严格的函数,还有两个测试testLazytestStrict,然后我尝试捕捉除以零:

> test fooLazy
*** Exception: divide by zero
> test fooStrict
42
> testLazy 0
*** Exception: divide by zero
> testStrict 0
42

在懒惰的情况下它会失败。

首先想到的是编写一个catch强制对其第一个参数求值的函数版本:

{-# LANGUAGE ScopedTypeVariables #-}

import Prelude hiding ( catch )
import Control.DeepSeq
import Control.Exception
import System.IO.Unsafe

fooLazy :: Int -> IO Int
fooLazy m = return $ 1 `div` m

fooStrict :: Int -> IO Int
fooStrict m = return $! 1 `div` m

instance NFData a => NFData (IO a) where
  rnf = rnf . unsafePerformIO

catchStrict :: (Exception e, NFData a) => IO a -> (e -> IO a) -> IO a
catchStrict = catch . force

test :: (Int -> IO Int) -> IO ()
test f = print =<< f 0 `catchStrict` \(_ :: SomeException) -> return 42

testLazy :: Int -> IO Int
testLazy m = (return $ 1 `div` m) `catchStrict` \(_ :: SomeException) -> return 42

testStrict :: Int -> IO Int
testStrict m = (return $! 1 `div` m) `catchStrict` \(_ :: SomeException) -> return 42

它似乎工作:

> test fooLazy
42
> test fooStrict
42
> testLazy 0
42
> testStrict 0
42

但我在unsafePerformIO这里使用了这个功能,这很可怕。

我有两个问题:

  1. 是否可以确定该catch函数始终捕获所有异常,而不管其第一个参数的性质如何?
  2. 如果没有,是否有一种众所周知的方法来处理这类问题?类似catchStrict功能的东西合适吗?

更新 1

这是nanothiefcatchStrict函数的更好版本:

forceM :: (Monad m, NFData a) => m a -> m a
forceM m = m >>= (return $!) . force

catchStrict :: (Exception e, NFData a) => IO a -> (e -> IO a) -> IO a
catchStrict expr = (forceM expr `catch`)

更新 2

这是另一个“坏”的例子:

main :: IO ()
main = do
  args <- getArgs
  res <- return ((+ 1) $ read $ head args) `catch` \(_ :: SomeException) -> return 0
  print res

应该这样重写:

main :: IO ()
main = do
  args <- getArgs
  print ((+ 1) $ read $ head args) `catch` \(_ :: SomeException) -> print 0
-- or
-- 
-- res <- return ((+ 1) $ read $ head args) `catchStrict` \(_ :: SomeException) -> return 0
-- print res
-- 
-- or
-- 
-- res <- returnStrcit ((+ 1) $ read $ head args) `catch` \(_ :: SomeException) -> return 0
-- print res
-- 
-- where
returnStrict :: Monad m => a -> m a
returnStrict = (return $!)

更新 3

正如nanothief所注意到的,不能保证该catch函数总是捕获任何异常。所以需要谨慎使用。

关于如何解决相关问题的一些提示:

  1. 使用($!)with return,使用forceM的第一个参数catch,使用catchStrict函数。
  2. 我还注意到,有时人们会对他们的转换器实例添加一些严格性。

这是一个例子:

{-# LANGUAGE GeneralizedNewtypeDeriving, TypeSynonymInstances, FlexibleInstances
  , MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables #-}

import System.Environment

import Prelude hiding ( IO )
import qualified Prelude as P ( IO )
import qualified Control.Exception as E
import Data.Foldable
import Data.Traversable
import Control.Applicative
import Control.Monad.Trans
import Control.Monad.Error

newtype StrictT m a = StrictT { runStrictT :: m a } deriving
  ( Foldable, Traversable, Functor, Applicative, Alternative, MonadPlus, MonadFix
  , MonadIO
  )

instance Monad m => Monad (StrictT m) where
  return = StrictT . (return $!)
  m >>= k = StrictT $ runStrictT m >>= runStrictT . k
  fail = StrictT . fail

instance MonadTrans StrictT where
  lift = StrictT

type IO = StrictT P.IO

instance E.Exception e => MonadError e IO where
  throwError = StrictT . E.throwIO
  catchError m h = StrictT $ runStrictT m `E.catch` (runStrictT . h)

io :: StrictT P.IO a -> P.IO a
io = runStrictT

它本质上是身份单子变换器,但具有严格的return

foo :: Int -> IO Int
foo m = return $ 1 `div` m

fooReadLn :: Int -> IO Int
fooReadLn x = liftM (`div` x) $ liftIO readLn

test :: (Int -> IO Int) -> P.IO ()
test f = io $ liftIO . print =<< f 0 `catchError` \(_ :: E.SomeException) -> return 42

main :: P.IO ()
main = io $ do
  args <- liftIO getArgs
  res <- return ((+ 1) $ read $ head args) `catchError` \(_ :: E.SomeException) -> return 0
  liftIO $ print res

-- > test foo
-- 42
-- > test fooReadLn
-- 1
-- 42
-- ./main
-- 0
4

1 回答 1

9

首先(我不确定您是否已经知道这一点),catch 不适用于惰性案例的原因是

1 `div` 0

表达式只有在需要时才会被评估,它在print函数内部。但是,该catch方法仅应用于f 0表达式,而不是整个print =<< f 0表达式,因此不会捕获异常。如果你这样做了:

test f = (print =<< f 0) `catch` \(_ :: SomeException) -> print 42

相反,它在这两种情况下都能正常工作。

如果你想创建一个强制对 IO 结果进行完整评估的 catch 语句,而不是创建一个新的 NFData 实例,你可以编写一个forceM方法,并在catchStrict方法中使用它:

forceM :: (Monad m, NFData a) => m a -> m a
forceM m = m >>= (return $!) . force

catchStrict :: (Exception e, NFData a) => IO a -> (e -> IO a) -> IO a
catchStrict expr = (forceM expr `catch`)

(我有点惊讶 forceM 不在Control.DeepSeq图书馆内)


关于您的评论:

不,规则是仅在计算值时抛出异常,并且仅在 haskell 需要时才进行。如果 haskell 可以延迟对某事的评估,它会。

一个不使用$!但仍会立即导致异常的示例测试函数(因此正常的 catch 将捕获除以零异常)是:

fooEvaluated :: Int -> IO Int
fooEvaluated m = case 3 `div` m of
  3 -> return 3
  0 -> return 0
  _ -> return 1

Haskell 被迫评估“3 `div` m”表达式,因为它需要将结果与 3 和 0 进行匹配。

作为最后一个示例,以下内容不会引发任何异常,并且在与测试函数一起使用时返回 1:

fooNoException :: Int -> IO Int
fooNoException m = case 3 `div` m of
  _ -> return 1

这是因为 haskell 永远不需要计算 "3 `div` m" 表达式(因为_匹配所有内容),所以它永远不会被计算,因此不会抛出异常。

于 2012-06-22T04:24:09.867 回答