module Rattletrap.Exception.CrcMismatch where import qualified Control.Exception as Exception import qualified Data.Word as Word data CrcMismatch = CrcMismatch Word.Word32 Word.Word32 deriving (CrcMismatch -> CrcMismatch -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: CrcMismatch -> CrcMismatch -> Bool $c/= :: CrcMismatch -> CrcMismatch -> Bool == :: CrcMismatch -> CrcMismatch -> Bool $c== :: CrcMismatch -> CrcMismatch -> Bool Eq, Int -> CrcMismatch -> ShowS [CrcMismatch] -> ShowS CrcMismatch -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [CrcMismatch] -> ShowS $cshowList :: [CrcMismatch] -> ShowS show :: CrcMismatch -> String $cshow :: CrcMismatch -> String showsPrec :: Int -> CrcMismatch -> ShowS $cshowsPrec :: Int -> CrcMismatch -> ShowS Show) instance Exception.Exception CrcMismatch where displayException :: CrcMismatch -> String displayException (CrcMismatch Word32 x Word32 y) = [String] -> String unwords [String "invalid CRC: expected", forall a. Show a => a -> String show Word32 x, String "but got", forall a. Show a => a -> String show Word32 y]