safe-exceptions-checked-0.1.0: Safe, checked exceptions

Safe HaskellNone
LanguageHaskell2010

Control.Exception.Safe.Checked

Contents

Description

Lightweight checked exceptions, based on https://www.well-typed.com/blog/2015/07/checked-exceptions/.

Synopsis

Throwing

class X e => Throws e Source #

A Throws e constraint indicates a computation may throw synchronous exception e. Introduce a constraint with throw, and discharge it with catch.

You may ignore the X superclass; it exists only to prevent additional Throws instances from being created.

class X e => ThrowsImpure e Source #

A ThrowsImpure e constraint indicates a computation may throw impure exception e. Introduce a constraint with impureThrow, and discharge it with catchDeep.

You may ignore the X superclass; it exists only to prevent additional ThrowsImpure instances from being created.

throw :: (MonadThrow m, Exception e, Throws e) => e -> m a Source #

Like throw, but for checked exceptions.

Since: 0.1.0

impureThrow :: (Exception e, ThrowsImpure e) => e -> a Source #

Like impureThrow, but for checked exceptions.

Since: 0.1.0

Catching

catch :: (MonadCatch m, Exception e) => (Throws e => m a) -> (e -> m a) -> m a Source #

Like catch, but for checked exceptions.

Since: 0.1.0

catchDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (ThrowsImpure e => m a) -> (e -> m a) -> m a Source #

Like catchDeep, but for checked exceptions.

Since: 0.1.0

handle :: (MonadCatch m, Exception e) => (e -> m a) -> (Throws e => m a) -> m a Source #

Like handle, but for checked exceptions.

Since: 0.1.0

handleDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (e -> m a) -> (ThrowsImpure e => m a) -> m a Source #

Like handleDeep, but for checked exceptions.

Since: 0.1.0

try :: (MonadCatch m, Exception e) => (Throws e => m a) -> m (Either e a) Source #

Like try, but for checked exceptions.

Since: 0.1.0

tryDeep :: (MonadCatch m, MonadIO m, Exception e, NFData a) => (ThrowsImpure e => m a) -> m (Either e a) Source #

Like tryDeep, but for checked exceptions.

Since: 0.1.0

Unchecking exceptions

uncheck :: forall a e proxy. proxy e -> (Throws e => a) -> a Source #

Uncheck a checked exception.

This is exported for completeness, but normally you should discharge a Throws constraint with catch.

Since: 0.1.0

uncheckImpure :: forall a e proxy. proxy e -> (ThrowsImpure e => a) -> a Source #

Unchecked a checked, impure exception.

This is exported for completeness, but normally you should discharge a ThrowsImpure constraint with catchDeep.

Since: 0.1.0

Re-exports

class (Typeable * e, Show e) => Exception e #

Any type that you wish to throw or catch as an exception must be an instance of the Exception class. The simplest case is a new exception type directly below the root:

data MyException = ThisException | ThatException
    deriving (Show, Typeable)

instance Exception MyException

The default method definitions in the Exception class do what we need in this case. You can now throw and catch ThisException and ThatException as exceptions:

*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
Caught ThisException

In more complicated examples, you may wish to define a whole hierarchy of exceptions:

---------------------------------------------------------------------
-- Make the root exception type for all the exceptions in a compiler

data SomeCompilerException = forall e . Exception e => SomeCompilerException e
    deriving Typeable

instance Show SomeCompilerException where
    show (SomeCompilerException e) = show e

instance Exception SomeCompilerException

compilerExceptionToException :: Exception e => e -> SomeException
compilerExceptionToException = toException . SomeCompilerException

compilerExceptionFromException :: Exception e => SomeException -> Maybe e
compilerExceptionFromException x = do
    SomeCompilerException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make a subhierarchy for exceptions in the frontend of the compiler

data SomeFrontendException = forall e . Exception e => SomeFrontendException e
    deriving Typeable

instance Show SomeFrontendException where
    show (SomeFrontendException e) = show e

instance Exception SomeFrontendException where
    toException = compilerExceptionToException
    fromException = compilerExceptionFromException

frontendExceptionToException :: Exception e => e -> SomeException
frontendExceptionToException = toException . SomeFrontendException

frontendExceptionFromException :: Exception e => SomeException -> Maybe e
frontendExceptionFromException x = do
    SomeFrontendException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make an exception type for a particular frontend compiler exception

data MismatchedParentheses = MismatchedParentheses
    deriving (Typeable, Show)

instance Exception MismatchedParentheses where
    toException   = frontendExceptionToException
    fromException = frontendExceptionFromException

We can now catch a MismatchedParentheses exception as MismatchedParentheses, SomeFrontendException or SomeCompilerException, but not other types, e.g. IOException:

*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
*** Exception: MismatchedParentheses

class Monad m => MonadIO m #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Minimal complete definition

liftIO

Instances

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

class MonadThrow m => MonadCatch m #

A class for monads which allow exceptions to be caught, in particular exceptions which were thrown by throwM.

Instances should obey the following law:

catch (throwM e) f = f e

Note that the ability to catch an exception does not guarantee that we can deal with all possible exit points from a computation. Some monads, such as continuation-based stacks, allow for more than just a success/failure strategy, and therefore catch cannot be used by those monads to properly implement a function such as finally. For more information, see MonadMask.

Minimal complete definition

catch

Instances

MonadCatch IO 

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a #

MonadCatch STM 

Methods

catch :: Exception e => STM a -> (e -> STM a) -> STM a #

(~) * e SomeException => MonadCatch (Either e)

Since: 0.8.3

Methods

catch :: Exception e => Either e a -> (e -> Either e a) -> Either e a #

MonadCatch m => MonadCatch (ListT m) 

Methods

catch :: Exception e => ListT m a -> (e -> ListT m a) -> ListT m a #

MonadCatch m => MonadCatch (MaybeT m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a #

(Error e, MonadCatch m) => MonadCatch (ErrorT e m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a #

MonadCatch m => MonadCatch (ExceptT e m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a #

MonadCatch m => MonadCatch (StateT s m) 

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadCatch m => MonadCatch (StateT s m) 

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

MonadCatch m => MonadCatch (IdentityT * m) 

Methods

catch :: Exception e => IdentityT * m a -> (e -> IdentityT * m a) -> IdentityT * m a #

MonadCatch m => MonadCatch (ReaderT * r m) 

Methods

catch :: Exception e => ReaderT * r m a -> (e -> ReaderT * r m a) -> ReaderT * r m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

class MonadCatch m => MonadMask m #

A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads, and stacks such as ErrorT e IO which provide for multiple failure modes, are invalid instances of this class.

Note that this package does provide a MonadMask instance for CatchT. This instance is only valid if the base monad provides no ability to provide multiple exit. For example, IO or Either would be invalid base monads, but Reader or State would be acceptable.

Instances should ensure that, in the following code:

f `finally` g

The action g is called regardless of what occurs within f, including async exceptions.

Minimal complete definition

mask, uninterruptibleMask

Instances

MonadMask IO 

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

(~) * e SomeException => MonadMask (Either e)

Since: 0.8.3

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

MonadMask m => MonadMask (IdentityT * m) 

Methods

mask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

uninterruptibleMask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

MonadMask m => MonadMask (ReaderT * r m) 

Methods

mask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

uninterruptibleMask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

class Monad m => MonadThrow m #

A class for monads in which exceptions may be thrown.

Instances should obey the following law:

throwM e >> x = throwM e

In other words, throwing an exception short-circuits the rest of the monadic computation.

Minimal complete definition

throwM

Instances

MonadThrow [] 

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 

Methods

throwM :: Exception e => e -> Maybe a #

MonadThrow IO 

Methods

throwM :: Exception e => e -> IO a #

MonadThrow Q 

Methods

throwM :: Exception e => e -> Q a #

MonadThrow STM 

Methods

throwM :: Exception e => e -> STM a #

(~) * e SomeException => MonadThrow (Either e) 

Methods

throwM :: Exception e => e -> Either e a #

MonadThrow m => MonadThrow (ListT m) 

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> MaybeT m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> ErrorT e m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> ExceptT e m a #

MonadThrow m => MonadThrow (StateT s m) 

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 

Methods

throwM :: Exception e => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 

Methods

throwM :: Exception e => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (IdentityT * m) 

Methods

throwM :: Exception e => e -> IdentityT * m a #

MonadThrow m => MonadThrow (ContT * r m) 

Methods

throwM :: Exception e => e -> ContT * r m a #

MonadThrow m => MonadThrow (ReaderT * r m) 

Methods

throwM :: Exception e => e -> ReaderT * r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

Methods

throwM :: Exception e => e -> RWST r w s m a #

class NFData a #

A class of types that can be fully evaluated.

Since: 1.1.0.0

Instances

NFData Bool 

Methods

rnf :: Bool -> () #

NFData Char 

Methods

rnf :: Char -> () #

NFData Double 

Methods

rnf :: Double -> () #

NFData Float 

Methods

rnf :: Float -> () #

NFData Int 

Methods

rnf :: Int -> () #

NFData Int8 

Methods

rnf :: Int8 -> () #

NFData Int16 

Methods

rnf :: Int16 -> () #

NFData Int32 

Methods

rnf :: Int32 -> () #

NFData Int64 

Methods

rnf :: Int64 -> () #

NFData Integer 

Methods

rnf :: Integer -> () #

NFData Word 

Methods

rnf :: Word -> () #

NFData Word8 

Methods

rnf :: Word8 -> () #

NFData Word16 

Methods

rnf :: Word16 -> () #

NFData Word32 

Methods

rnf :: Word32 -> () #

NFData Word64 

Methods

rnf :: Word64 -> () #

NFData CallStack

Since: 1.4.2.0

Methods

rnf :: CallStack -> () #

NFData TypeRep

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TypeRep -> () #

NFData () 

Methods

rnf :: () -> () #

NFData TyCon

NOTE: Only defined for base-4.8.0.0 and later

Since: 1.4.0.0

Methods

rnf :: TyCon -> () #

NFData Natural

Since: 1.4.0.0

Methods

rnf :: Natural -> () #

NFData Void

Defined as rnf = absurd.

Since: 1.4.0.0

Methods

rnf :: Void -> () #

NFData Version

Since: 1.3.0.0

Methods

rnf :: Version -> () #

NFData Unique

Since: 1.4.0.0

Methods

rnf :: Unique -> () #

NFData ThreadId

Since: 1.4.0.0

Methods

rnf :: ThreadId -> () #

NFData ExitCode

Since: 1.4.2.0

Methods

rnf :: ExitCode -> () #

NFData CChar

Since: 1.4.0.0

Methods

rnf :: CChar -> () #

NFData CSChar

Since: 1.4.0.0

Methods

rnf :: CSChar -> () #

NFData CUChar

Since: 1.4.0.0

Methods

rnf :: CUChar -> () #

NFData CShort

Since: 1.4.0.0

Methods

rnf :: CShort -> () #

NFData CUShort

Since: 1.4.0.0

Methods

rnf :: CUShort -> () #

NFData CInt

Since: 1.4.0.0

Methods

rnf :: CInt -> () #

NFData CUInt

Since: 1.4.0.0

Methods

rnf :: CUInt -> () #

NFData CLong

Since: 1.4.0.0

Methods

rnf :: CLong -> () #

NFData CULong

Since: 1.4.0.0

Methods

rnf :: CULong -> () #

NFData CLLong

Since: 1.4.0.0

Methods

rnf :: CLLong -> () #

NFData CULLong

Since: 1.4.0.0

Methods

rnf :: CULLong -> () #

NFData CFloat

Since: 1.4.0.0

Methods

rnf :: CFloat -> () #

NFData CDouble

Since: 1.4.0.0

Methods

rnf :: CDouble -> () #

NFData CPtrdiff

Since: 1.4.0.0

Methods

rnf :: CPtrdiff -> () #

NFData CSize

Since: 1.4.0.0

Methods

rnf :: CSize -> () #

NFData CWchar

Since: 1.4.0.0

Methods

rnf :: CWchar -> () #

NFData CSigAtomic

Since: 1.4.0.0

Methods

rnf :: CSigAtomic -> () #

NFData CClock

Since: 1.4.0.0

Methods

rnf :: CClock -> () #

NFData CTime

Since: 1.4.0.0

Methods

rnf :: CTime -> () #

NFData CUSeconds

Since: 1.4.0.0

Methods

rnf :: CUSeconds -> () #

NFData CSUSeconds

Since: 1.4.0.0

Methods

rnf :: CSUSeconds -> () #

NFData CFile

Since: 1.4.0.0

Methods

rnf :: CFile -> () #

NFData CFpos

Since: 1.4.0.0

Methods

rnf :: CFpos -> () #

NFData CJmpBuf

Since: 1.4.0.0

Methods

rnf :: CJmpBuf -> () #

NFData CIntPtr

Since: 1.4.0.0

Methods

rnf :: CIntPtr -> () #

NFData CUIntPtr

Since: 1.4.0.0

Methods

rnf :: CUIntPtr -> () #

NFData CIntMax

Since: 1.4.0.0

Methods

rnf :: CIntMax -> () #

NFData CUIntMax

Since: 1.4.0.0

Methods

rnf :: CUIntMax -> () #

NFData All

Since: 1.4.0.0

Methods

rnf :: All -> () #

NFData Any

Since: 1.4.0.0

Methods

rnf :: Any -> () #

NFData Fingerprint

Since: 1.4.0.0

Methods

rnf :: Fingerprint -> () #

NFData SrcLoc

Since: 1.4.2.0

Methods

rnf :: SrcLoc -> () #

NFData a => NFData [a] 

Methods

rnf :: [a] -> () #

NFData a => NFData (Maybe a) 

Methods

rnf :: Maybe a -> () #

NFData a => NFData (Ratio a) 

Methods

rnf :: Ratio a -> () #

NFData (Ptr a)

Since: 1.4.2.0

Methods

rnf :: Ptr a -> () #

NFData (FunPtr a)

Since: 1.4.2.0

Methods

rnf :: FunPtr a -> () #

NFData a => NFData (Identity a)

Since: 1.4.0.0

Methods

rnf :: Identity a -> () #

NFData a => NFData (Min a)

Since: 1.4.2.0

Methods

rnf :: Min a -> () #

NFData a => NFData (Max a)

Since: 1.4.2.0

Methods

rnf :: Max a -> () #

NFData a => NFData (First a)

Since: 1.4.2.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.2.0

Methods

rnf :: Last a -> () #

NFData m => NFData (WrappedMonoid m)

Since: 1.4.2.0

Methods

rnf :: WrappedMonoid m -> () #

NFData a => NFData (Option a)

Since: 1.4.2.0

Methods

rnf :: Option a -> () #

NFData a => NFData (NonEmpty a)

Since: 1.4.2.0

Methods

rnf :: NonEmpty a -> () #

NFData (Fixed a)

Since: 1.3.0.0

Methods

rnf :: Fixed a -> () #

NFData a => NFData (Complex a) 

Methods

rnf :: Complex a -> () #

NFData (StableName a)

Since: 1.4.0.0

Methods

rnf :: StableName a -> () #

NFData a => NFData (ZipList a)

Since: 1.4.0.0

Methods

rnf :: ZipList a -> () #

NFData a => NFData (Dual a)

Since: 1.4.0.0

Methods

rnf :: Dual a -> () #

NFData a => NFData (Sum a)

Since: 1.4.0.0

Methods

rnf :: Sum a -> () #

NFData a => NFData (Product a)

Since: 1.4.0.0

Methods

rnf :: Product a -> () #

NFData a => NFData (First a)

Since: 1.4.0.0

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: 1.4.0.0

Methods

rnf :: Last a -> () #

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: IORef a -> () #

NFData a => NFData (Down a)

Since: 1.4.0.0

Methods

rnf :: Down a -> () #

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: MVar a -> () #

NFData (a -> b)

This instance is for convenience and consistency with seq. This assumes that WHNF is equivalent to NF for functions.

Since: 1.3.0.0

Methods

rnf :: (a -> b) -> () #

(NFData a, NFData b) => NFData (Either a b) 

Methods

rnf :: Either a b -> () #

(NFData a, NFData b) => NFData (a, b) 

Methods

rnf :: (a, b) -> () #

(NFData a, NFData b) => NFData (Array a b) 

Methods

rnf :: Array a b -> () #

(NFData a, NFData b) => NFData (Arg a b)

Since: 1.4.2.0

Methods

rnf :: Arg a b -> () #

NFData (Proxy k a)

Since: 1.4.0.0

Methods

rnf :: Proxy k a -> () #

NFData (STRef s a)

NOTE: Only strict in the reference and not the referenced value.

Since: 1.4.2.0

Methods

rnf :: STRef s a -> () #

(NFData a, NFData b, NFData c) => NFData (a, b, c) 

Methods

rnf :: (a, b, c) -> () #

NFData a => NFData (Const k a b)

Since: 1.4.0.0

Methods

rnf :: Const k a b -> () #

(NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) 

Methods

rnf :: (a, b, c, d) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 

Methods

rnf :: (a1, a2, a3, a4, a5) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> () #