{-# LANGUAGE DeriveDataTypeable #-}
module Data.GraphViz.Exception
( GraphvizException(..)
, mapException
, throw
, handle
, bracket
) where
import Control.Exception
import Data.Typeable
data GraphvizException = NotDotCode String
| NotUTF8Dot String
| GVProgramExc String
| NotCustomAttr String
deriving (Eq, Ord, Typeable)
instance Show GraphvizException where
showsPrec _ (NotDotCode str) = showString $ "Error when parsing Dot code:\n" ++ str
showsPrec _ (NotUTF8Dot str) = showString $ "Invalid UTF-8 Dot code: " ++ str
showsPrec _ (GVProgramExc str) = showString $ "Error running utility program: " ++ str
showsPrec _ (NotCustomAttr str) = showString $ "Not a custom Attribute: " ++ str
instance Exception GraphvizException