{-# LANGUAGE DeriveDataTypeable #-}
module FinalException (
FinalException(..)
, catchEnd
) where
import Data.Typeable
import Control.Exception (Exception, catch, throw)
import System.Environment (getProgName)
import System.IO
data FinalException = NeededInfoIsShown | ExecutableNotProperlyInstalled | MaybePartiallyTrimmed | NotCreatedWithEffect String
| InitialFileNotChanged String | NotCreated String | NotRecorded String | NoiseProfileNotCreatedB String | NoiseProfileNotCreatedE String
| NotEnoughData String | NotCreatedWithEffects String
deriving ( Typeable )
instance Exception FinalException
instance Show FinalException where
show NeededInfoIsShown = "NeededInfoIsShown: the program has given you the asked information.\n"
show (ExecutableNotProperlyInstalled) = "ExecutableNotProperlyInstalled: SoX is not properly installed in your system. Please, install it properly and then call the function again.\n"
show MaybePartiallyTrimmed = "MaybePartiallyTrimmed: The function did not create the needed file, but may be it trimmed the initial one (not enough)!\n"
show (NotCreatedWithEffect xs) = "NotCreatedWithEffect: File was not created with " ++ show xs ++ " effect!\n"
show (InitialFileNotChanged xs) = "InitialFileNotChanged: The initial file " ++ show xs ++ " was not changed!\n"
show (NotCreated xs) = "NotCreated: The function did not create the needed file " ++ show xs ++ "!\n"
show (NotRecorded xs) = "NotRecorded: The file " ++ show xs ++ " was not recorded!\n"
show (NoiseProfileNotCreatedB xs) = "NoiseProfileNotCreatedB: The noise profile " ++ xs ++ ".b.prof was not created!\n"
show (NoiseProfileNotCreatedE xs) = "NoiseProfileNotCreatedE: The noise profile " ++ xs ++ ".e.prof was not created!\n"
show (NotEnoughData xs) = "NotEnoughData: SoX cannot determine the number of the samples in the file " ++ show xs ++
"! May be it is a RAW file and it needs additional parameters to be processed.\n"
show (NotCreatedWithEffects xs) = "NotCreatedWithEffects: File was not created with " ++ (init . unwords . map ((++ ",") . show) . words $ xs) ++ " effects!\n"
catchEnd :: FinalException -> IO ()
catchEnd e = do
progName <- getProgName
case e of
NeededInfoIsShown -> catch (throw e) (\e0 -> hPutStr stdout (progName ++ ": " ++ show (e0 :: FinalException)))
_ -> catch (throw e) (\e0 -> hPutStr stderr (progName ++ ": " ++ show (e0 :: FinalException)))