module Telescope.Asdf.Error where import Control.Monad.Catch (Exception, MonadThrow, throwM) import Effectful import Effectful.Error.Static data AsdfError = YamlError String | BlockError String | ParseError String | EncodeError String deriving (Show AsdfError Typeable AsdfError (Typeable AsdfError, Show AsdfError) => (AsdfError -> SomeException) -> (SomeException -> Maybe AsdfError) -> (AsdfError -> String) -> Exception AsdfError SomeException -> Maybe AsdfError AsdfError -> String AsdfError -> SomeException forall e. (Typeable e, Show e) => (e -> SomeException) -> (SomeException -> Maybe e) -> (e -> String) -> Exception e $ctoException :: AsdfError -> SomeException toException :: AsdfError -> SomeException $cfromException :: SomeException -> Maybe AsdfError fromException :: SomeException -> Maybe AsdfError $cdisplayException :: AsdfError -> String displayException :: AsdfError -> String Exception, AsdfError -> AsdfError -> Bool (AsdfError -> AsdfError -> Bool) -> (AsdfError -> AsdfError -> Bool) -> Eq AsdfError forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: AsdfError -> AsdfError -> Bool == :: AsdfError -> AsdfError -> Bool $c/= :: AsdfError -> AsdfError -> Bool /= :: AsdfError -> AsdfError -> Bool Eq) instance Show AsdfError where show :: AsdfError -> String show (YamlError String s) = String "YamlError " String -> ShowS forall a. [a] -> [a] -> [a] ++ String s show (BlockError String s) = String "BlockError " String -> ShowS forall a. [a] -> [a] -> [a] ++ String s show (ParseError String s) = String "ParseError " String -> ShowS forall a. [a] -> [a] -> [a] ++ String s show (EncodeError String s) = String "EncodeError " String -> ShowS forall a. [a] -> [a] -> [a] ++ String s runAsdfM :: (MonadIO m, MonadThrow m) => Eff [Error AsdfError, IOE] a -> m a runAsdfM :: forall (m :: * -> *) a. (MonadIO m, MonadThrow m) => Eff '[Error AsdfError, IOE] a -> m a runAsdfM = IO a -> m a forall a. IO a -> m a forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO a -> m a) -> (Eff '[Error AsdfError, IOE] a -> IO a) -> Eff '[Error AsdfError, IOE] a -> m a forall b c a. (b -> c) -> (a -> b) -> a -> c . Eff '[IOE] a -> IO a forall a. HasCallStack => Eff '[IOE] a -> IO a runEff (Eff '[IOE] a -> IO a) -> (Eff '[Error AsdfError, IOE] a -> Eff '[IOE] a) -> Eff '[Error AsdfError, IOE] a -> IO a forall b c a. (b -> c) -> (a -> b) -> a -> c . forall e (es :: [(* -> *) -> * -> *]) a. HasCallStack => (e -> Eff es a) -> Eff (Error e : es) a -> Eff es a runErrorNoCallStackWith @AsdfError AsdfError -> Eff '[IOE] a forall e a. (HasCallStack, Exception e) => e -> Eff '[IOE] a forall (m :: * -> *) e a. (MonadThrow m, HasCallStack, Exception e) => e -> m a throwM