-- | -- Module: Data.Enumerator.NetLines.Error -- Copyright: (c) 2011 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- -- Error and exception types. {-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables #-} module Data.Enumerator.NetLines.Error ( -- * Exceptions TimeoutError(..) ) where import Control.Exception as Ex import Data.Typeable -- | Exception for timed out IO operations. newtype TimeoutError = TimeoutError { timeoutErrorMessage :: String } deriving (Typeable) instance Ex.Exception TimeoutError instance Show TimeoutError where show (TimeoutError msg) = "Operation timed out: " ++ msg