-- |
-- Module      :  FinalException
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- 
-- Maintainer  :  olexandr543@yahoo.com
--
-- A program and a library that can be used as a simple 
-- basic interface to some SoX functionality or for producing 
-- the approximately Ukrainian speech with your own recorded 
-- voice (actually it produces the needed sound representations).
--

{-# LANGUAGE DeriveDataTypeable #-}

module FinalException (
  FinalException(..)
  -- * Exception
  , catchEnd
) where

import Data.Typeable
import Control.Exception (Exception, catch, throw)
import System.Environment (getProgName)
import System.IO

-- | Data type 'FinalException' is used to terminate the not needed further execution.
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"

-- | Function to work with exception 'FinalException' similarly to the example in the documentation for the 'catch' function. It throws an exception
-- to the thread where it is called. Basically, the function is intended to terminate the program with the informational message (if used in the main thread
-- without exception handler). Because 'NeededInfoIsShown' is exception that actually only is a signal that the needed information is given and is not
-- any exceptional but rather standard situation the output of the function in such a case is printed to the 'stdout' handle (with the default to 'stderr'
-- in all other cases). 
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)))