module Client.EventLoop.Errors
( exceptionToLines
) where
import Control.Exception
import Data.List.NonEmpty (NonEmpty(..))
import OpenSSL.Session
import Hookup (ConnectionFailure(..))
exceptionToLines ::
SomeException ->
NonEmpty String
exceptionToLines :: SomeException -> NonEmpty String
exceptionToLines
= NonEmpty String -> NonEmpty String
indentMessages
(NonEmpty String -> NonEmpty String)
-> (SomeException -> NonEmpty String)
-> SomeException
-> NonEmpty String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> NonEmpty String
exceptionToLines'
indentMessages :: NonEmpty String -> NonEmpty String
indentMessages :: NonEmpty String -> NonEmpty String
indentMessages (String
x :| [String]
xs) = String
x String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"⋯ "String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
xs
exceptionToLines' ::
SomeException ->
NonEmpty String
exceptionToLines' :: SomeException -> NonEmpty String
exceptionToLines' SomeException
ex
| Just ConnectionFailure
err <- SomeException -> Maybe ConnectionFailure
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
ex = ConnectionFailure -> NonEmpty String
explainHookupError ConnectionFailure
err
| Just ConnectionAbruptlyTerminated
_ <- SomeException -> Maybe ConnectionAbruptlyTerminated
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
ex :: Maybe ConnectionAbruptlyTerminated =
String
"Connection abruptly terminated" String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| []
| Just (ProtocolError String
e) <- SomeException -> Maybe ProtocolError
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
ex =
(String
"TLS protocol error: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
e) String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| []
| Just IOError
ioe <- SomeException -> Maybe IOError
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
ex =
IOError -> String
explainIOError IOError
ioe String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| []
| Bool
otherwise = SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
ex String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| []
explainIOError :: IOError -> String
explainIOError :: IOError -> String
explainIOError IOError
ioe = String
"IO error: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ IOError -> String
forall e. Exception e => e -> String
displayException IOError
ioe
explainHookupError :: ConnectionFailure -> NonEmpty String
explainHookupError :: ConnectionFailure -> NonEmpty String
explainHookupError ConnectionFailure
e =
case ConnectionFailure
e of
ConnectionFailure [ConnectError]
exs ->
String
"Connect failed" String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| (ConnectError -> String) -> [ConnectError] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ConnectError -> String
forall e. Exception e => e -> String
displayException [ConnectError]
exs
ConnectionFailure
LineTooLong ->
String
"IRC message too long" String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| []
ConnectionFailure
LineTruncated ->
String
"IRC message incomplete" String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| []
ConnectionFailure
_ -> ConnectionFailure -> String
forall e. Exception e => e -> String
displayException ConnectionFailure
e String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
:| []