{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTSyntax #-}
module Bcc.Api.Error
( Error(..)
, throwErrorAsException
, ErrorAsException(..)
, FileError(..)
) where
import Prelude
import Control.Exception (Exception(..), IOException, throwIO)
import System.IO (Handle)
class Show e => Error e where
displayError :: e -> String
instance Error () where
displayError :: () -> String
displayError () = String
""
throwErrorAsException :: Error e => e -> IO a
throwErrorAsException :: e -> IO a
throwErrorAsException e
e = ErrorAsException -> IO a
forall e a. Exception e => e -> IO a
throwIO (e -> ErrorAsException
forall e. Error e => e -> ErrorAsException
ErrorAsException e
e)
data ErrorAsException where
ErrorAsException :: Error e => e -> ErrorAsException
instance Show ErrorAsException where
show :: ErrorAsException -> String
show (ErrorAsException e
e) = e -> String
forall a. Show a => a -> String
show e
e
instance Exception ErrorAsException where
displayException :: ErrorAsException -> String
displayException (ErrorAsException e
e) = e -> String
forall e. Error e => e -> String
displayError e
e
data FileError e = FileError FilePath e
| FileErrorTempFile
FilePath
FilePath
Handle
| FileIOError FilePath IOException
deriving Int -> FileError e -> ShowS
[FileError e] -> ShowS
FileError e -> String
(Int -> FileError e -> ShowS)
-> (FileError e -> String)
-> ([FileError e] -> ShowS)
-> Show (FileError e)
forall e. Show e => Int -> FileError e -> ShowS
forall e. Show e => [FileError e] -> ShowS
forall e. Show e => FileError e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileError e] -> ShowS
$cshowList :: forall e. Show e => [FileError e] -> ShowS
show :: FileError e -> String
$cshow :: forall e. Show e => FileError e -> String
showsPrec :: Int -> FileError e -> ShowS
$cshowsPrec :: forall e. Show e => Int -> FileError e -> ShowS
Show
instance Error e => Error (FileError e) where
displayError :: FileError e -> String
displayError (FileErrorTempFile String
targetPath String
tempPath Handle
h)=
String
"Error creating temporary file at: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
tempPath String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"/n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Target path: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
targetPath String -> ShowS
forall a. [a] -> [a] -> [a]
++
String
"/n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"Handle: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Handle -> String
forall a. Show a => a -> String
show Handle
h
displayError (FileIOError String
path IOException
ioe) =
String
path String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++ IOException -> String
forall e. Exception e => e -> String
displayException IOException
ioe
displayError (FileError String
path e
e) =
String
path String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++ e -> String
forall e. Error e => e -> String
displayError e
e