PageRenderTime 52ms CodeModel.GetById 30ms RepoModel.GetById 0ms app.codeStats 1ms

/src/Language/ObjC/Data/Error.hs

http://github.com/JohnLato/language-objc
Haskell | 170 lines | 94 code | 24 blank | 52 comment | 5 complexity | f88106e46162ac65cfa234ed877a4f45 MD5 | raw file
Possible License(s): BSD-3-Clause
  1. {-# LANGUAGE ExistentialQuantification, DeriveDataTypeable #-}
  2. -----------------------------------------------------------------------------
  3. -- |
  4. -- Module : Language.ObjC.Data.Error
  5. -- Copyright : (c) 2008 Benedikt Huber, Manuel M. T. Chakravarty
  6. -- License : BSD-style
  7. -- Maintainer : jwlato@gmail.com
  8. -- Stability : experimental
  9. -- Portability : ghc
  10. --
  11. -- Base type for errors occurring in parsing, analysing and pretty-printing.
  12. -- With ideas from Simon Marlow's
  13. -- "An extensible dynamically-typed hierarchy of execeptions [2006]"
  14. -----------------------------------------------------------------------------
  15. module Language.ObjC.Data.Error (
  16. -- * Severity Level
  17. ErrorLevel(..), isHardError,
  18. -- * Error class
  19. Error(..), errorPos, errorLevel, errorMsgs,
  20. -- * Error 'supertype'
  21. CError(..),
  22. -- * Infos attached to errors
  23. ErrorInfo(..),showError,showErrorInfo,mkErrorInfo,
  24. -- * Default error types
  25. UnsupportedFeature, unsupportedFeature, unsupportedFeature_,
  26. UserError, userErr,
  27. -- * Raising internal errors
  28. internalErr,
  29. )
  30. where
  31. import Data.Typeable
  32. import Language.ObjC.Data.Node
  33. import Language.ObjC.Data.Position
  34. -- | Error levels (severity)
  35. data ErrorLevel = LevelWarn
  36. | LevelError
  37. | LevelFatal
  38. deriving (Eq, Ord)
  39. instance Show ErrorLevel where
  40. show LevelWarn = "WARNING"
  41. show LevelError = "ERROR"
  42. show LevelFatal = "FATAL ERROR"
  43. -- | return @True@ when the given error makes it impossible to continue
  44. -- analysis or compilation.
  45. isHardError :: (Error ex) => ex -> Bool
  46. isHardError = ( > LevelWarn) . errorLevel
  47. -- | information attached to every error in Language.ObjC
  48. data ErrorInfo = ErrorInfo ErrorLevel Position [String] deriving Typeable
  49. -- to facilitate newtype deriving
  50. instance Show ErrorInfo where show = showErrorInfo "error"
  51. instance Error ErrorInfo where
  52. errorInfo = id
  53. changeErrorLevel (ErrorInfo _ pos msgs) lvl' = ErrorInfo lvl' pos msgs
  54. mkErrorInfo :: ErrorLevel -> String -> NodeInfo -> ErrorInfo
  55. mkErrorInfo lvl msg node = ErrorInfo lvl (posOfNode node) (lines msg)
  56. -- | `supertype' of all errors
  57. data CError
  58. = forall err. (Error err) => CError err
  59. deriving Typeable
  60. -- | errors in Language.ObjC are instance of 'Error'
  61. class (Typeable e, Show e) => Error e where
  62. -- | obtain source location etc. of an error
  63. errorInfo :: e -> ErrorInfo
  64. -- | wrap error in 'CError'
  65. toError :: e -> CError
  66. -- | try to cast a generic 'CError' to the specific error type
  67. fromError :: CError -> (Maybe e)
  68. -- | modify the error level
  69. changeErrorLevel :: e -> ErrorLevel -> e
  70. -- default implementation
  71. fromError (CError e) = cast e
  72. toError = CError
  73. changeErrorLevel e lvl =
  74. if errorLevel e == lvl
  75. then e
  76. else error $ "changeErrorLevel: not possible for " ++ show e
  77. instance Show CError where
  78. show (CError e) = show e
  79. instance Error CError where
  80. errorInfo (CError err) = errorInfo err
  81. toError = id
  82. fromError = Just
  83. changeErrorLevel (CError e) = CError . changeErrorLevel e
  84. -- | position of an @Error@
  85. errorPos :: (Error e) => e -> Position
  86. errorPos = ( \(ErrorInfo _ pos _) -> pos ) . errorInfo
  87. -- | severity level of an @Error@
  88. errorLevel :: (Error e) => e -> ErrorLevel
  89. errorLevel = ( \(ErrorInfo lvl _ _) -> lvl ) . errorInfo
  90. -- | message lines of an @Error@
  91. errorMsgs :: (Error e) => e -> [String]
  92. errorMsgs = ( \(ErrorInfo _ _ msgs) -> msgs ) . errorInfo
  93. -- | error raised if a operation requires an unsupported or not yet implemented feature.
  94. data UnsupportedFeature = UnsupportedFeature String Position deriving Typeable
  95. instance Error UnsupportedFeature where
  96. errorInfo (UnsupportedFeature msg pos) = ErrorInfo LevelError pos (lines msg)
  97. instance Show UnsupportedFeature where show = showError "Unsupported Feature"
  98. unsupportedFeature :: (Pos a) => String -> a -> UnsupportedFeature
  99. unsupportedFeature msg a = UnsupportedFeature msg (posOf a)
  100. unsupportedFeature_ :: String -> UnsupportedFeature
  101. unsupportedFeature_ msg = UnsupportedFeature msg internalPos
  102. -- | unspecified error raised by the user (in case the user does not want to define
  103. -- her own error types).
  104. newtype UserError = UserError ErrorInfo deriving Typeable
  105. instance Error UserError where
  106. errorInfo (UserError info) = info
  107. instance Show UserError where show = showError "User Error"
  108. userErr :: String -> UserError
  109. userErr msg = UserError (ErrorInfo LevelError internalPos (lines msg))
  110. -- other errors to be defined elsewhere
  111. showError :: (Error e) => String -> e -> String
  112. showError short_msg = showErrorInfo short_msg . errorInfo
  113. -- | converts an error into a string using a fixed format
  114. --
  115. -- * either the lines of the long error message or the short message has to be non-empty
  116. --
  117. -- * the format is
  118. --
  119. -- > <fname>:<row>: (column <col>) [<err lvl>]
  120. -- > >>> <line_1>
  121. -- > <line_2>
  122. -- > ...
  123. -- > <line_n>
  124. showErrorInfo :: String -> ErrorInfo -> String
  125. showErrorInfo short_msg (ErrorInfo level pos msgs) =
  126. header ++ showMsgLines (if null short_msg then msgs else short_msg:msgs)
  127. where
  128. header = (posFile pos) ++ ":" ++ show (posRow pos) ++ ": " ++
  129. "(column " ++ show (posColumn pos) ++ ") " ++
  130. "[" ++ show level ++ "]"
  131. showMsgLines [] = internalErr "No short message or error message provided."
  132. showMsgLines (x:xs) = indent ++ ">>> " ++ x ++ "\n" ++ unlines (map (indent++) xs)
  133. -- internal errors
  134. internalErrPrefix :: String
  135. internalErrPrefix = unlines [ "Language.ObjC : Internal Error" ,
  136. "This is propably a bug, and should be reported at "++
  137. "http://www.sivity.net/projects/language.c/newticket"]
  138. -- | raise a fatal internal error; message may have multiple lines
  139. internalErr :: String -> a
  140. internalErr msg = error (internalErrPrefix ++ "\n"
  141. ++ indentLines msg
  142. ++ "\n")
  143. indent :: String
  144. indent = " "
  145. indentLines :: String -> String
  146. indentLines = unlines . map (indent++) . lines