{-# OPTIONS_HADDOCK not-home #-} module Hedgehog.Internal.Exception ( tryAll , tryEvaluate ) where import Control.Exception (Exception(..), AsyncException, SomeException(..), evaluate) import Control.Monad.Catch (MonadCatch(..), throwM) import System.IO.Unsafe (unsafePerformIO) tryAll :: MonadCatch m => m a -> m (Either SomeException a) tryAll :: forall (m :: * -> *) a. MonadCatch m => m a -> m (Either SomeException a) tryAll m a m = forall (m :: * -> *) e a. (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a catch (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. b -> Either a b Right m a m) forall a b. (a -> b) -> a -> b $ \SomeException exception -> case forall e. Exception e => SomeException -> Maybe e fromException SomeException exception :: Maybe AsyncException of Maybe AsyncException Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ forall a b. a -> Either a b Left SomeException exception Just AsyncException async -> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a throwM AsyncException async tryEvaluate :: a -> Either SomeException a tryEvaluate :: forall a. a -> Either SomeException a tryEvaluate a x = forall a. IO a -> a unsafePerformIO (forall (m :: * -> *) a. MonadCatch m => m a -> m (Either SomeException a) tryAll (forall a. a -> IO a evaluate a x))