module Ribosome.Data.RiboError where

import Ribosome.Data.Mapping (MappingError)
import Ribosome.Data.PersistError (PersistError)
import Ribosome.Data.SettingError (SettingError)
import Ribosome.Error.Report.Class (ReportError(..))
import Ribosome.Msgpack.Error (DecodeError)
import Ribosome.Nvim.Api.RpcCall (RpcError)

data RiboError =
  Mapping MappingError
  |
  Decode DecodeError
  |
  Rpc RpcError
  |
  Persist PersistError
  |
  Setting SettingError
  deriving (Int -> RiboError -> ShowS
[RiboError] -> ShowS
RiboError -> String
(Int -> RiboError -> ShowS)
-> (RiboError -> String)
-> ([RiboError] -> ShowS)
-> Show RiboError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RiboError] -> ShowS
$cshowList :: [RiboError] -> ShowS
show :: RiboError -> String
$cshow :: RiboError -> String
showsPrec :: Int -> RiboError -> ShowS
$cshowsPrec :: Int -> RiboError -> ShowS
Show, (forall x. RiboError -> Rep RiboError x)
-> (forall x. Rep RiboError x -> RiboError) -> Generic RiboError
forall x. Rep RiboError x -> RiboError
forall x. RiboError -> Rep RiboError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RiboError x -> RiboError
$cfrom :: forall x. RiboError -> Rep RiboError x
Generic, RiboError -> ErrorReport
(RiboError -> ErrorReport) -> ReportError RiboError
forall a. (a -> ErrorReport) -> ReportError a
errorReport :: RiboError -> ErrorReport
$cerrorReport :: RiboError -> ErrorReport
ReportError)

deepPrisms ''RiboError