module Language.C.Data.Error (
    
    ErrorLevel(..), isHardError,
    
    Error(..), errorPos, errorLevel, errorMsgs,
    
    CError(..),
    
    ErrorInfo(..),showError,showErrorInfo,mkErrorInfo,
    
    UnsupportedFeature, unsupportedFeature, unsupportedFeature_,
    UserError, userErr,
    
    internalErr,
)
where
import Data.Typeable
import Language.C.Data.Node
import Language.C.Data.Position
data ErrorLevel = LevelWarn
                | LevelError
                | LevelFatal
              deriving (Eq, Ord)
instance Show ErrorLevel where
    show LevelWarn  = "WARNING"
    show LevelError = "ERROR"
    show LevelFatal = "FATAL ERROR"
isHardError :: (Error ex) => ex -> Bool
isHardError = ( > LevelWarn) . errorLevel
data ErrorInfo = ErrorInfo ErrorLevel Position [String] deriving Typeable
instance Show ErrorInfo where show = showErrorInfo "error"
instance Error ErrorInfo where
    errorInfo = id
    changeErrorLevel (ErrorInfo _ pos msgs) lvl' = ErrorInfo lvl' pos msgs
mkErrorInfo :: ErrorLevel -> String -> NodeInfo -> ErrorInfo
mkErrorInfo lvl msg node = ErrorInfo lvl (posOfNode node) (lines msg)
data CError
    = forall err. (Error err) => CError err
    deriving Typeable
class (Typeable e, Show e) => Error e where
    
    errorInfo        :: e -> ErrorInfo
    
    toError          :: e -> CError
    
    fromError     :: CError -> (Maybe e)
    
    changeErrorLevel :: e -> ErrorLevel -> e
    
    fromError (CError e) = cast e
    toError = CError
    changeErrorLevel e lvl =
        if errorLevel e == lvl
            then e
            else error $ "changeErrorLevel: not possible for " ++ show e
instance Show CError where
    show (CError e) = show e
instance Error CError where
    errorInfo (CError err) = errorInfo err
    toError = id
    fromError = Just
    changeErrorLevel (CError e) = CError . changeErrorLevel e
errorPos   :: (Error e) => e -> Position
errorPos = ( \(ErrorInfo _ pos _) -> pos ) . errorInfo
errorLevel :: (Error e) => e -> ErrorLevel
errorLevel = ( \(ErrorInfo lvl _ _) -> lvl ) . errorInfo
errorMsgs   :: (Error e) => e -> [String]
errorMsgs = ( \(ErrorInfo _ _ msgs) -> msgs ) . errorInfo
data UnsupportedFeature = UnsupportedFeature String Position deriving Typeable
instance Error UnsupportedFeature where
    errorInfo (UnsupportedFeature msg pos) = ErrorInfo LevelError pos (lines msg)
instance Show UnsupportedFeature where show = showError "Unsupported Feature"
unsupportedFeature :: (Pos a) => String -> a -> UnsupportedFeature
unsupportedFeature msg a = UnsupportedFeature msg (posOf a)
unsupportedFeature_ :: String -> UnsupportedFeature
unsupportedFeature_ msg = UnsupportedFeature msg internalPos
newtype UserError     = UserError ErrorInfo deriving Typeable
instance Error UserError where
    errorInfo (UserError info) = info
instance Show UserError where show = showError "User Error"
userErr :: String -> UserError
userErr msg = UserError (ErrorInfo LevelError internalPos (lines msg))
showError :: (Error e) => String -> e -> String
showError short_msg = showErrorInfo short_msg . errorInfo
showErrorInfo :: String -> ErrorInfo -> String
showErrorInfo short_msg (ErrorInfo level pos msgs) =
    header ++ showMsgLines (if null short_msg then msgs else short_msg:msgs)
    where
    header = showPos pos ++ "[" ++ show level ++ "]"
    showPos p | isSourcePos p = (posFile p) ++ ":" ++ show (posRow pos) ++ ": " ++
                                "(column " ++ show (posColumn pos) ++ ") "
              | otherwise = show p ++ ":: "
    showMsgLines []     = internalErr "No short message or error message provided."
    showMsgLines (x:xs) = indent ++ ">>> " ++ x ++ "\n" ++ unlines (map (indent++) xs)
internalErrPrefix :: String
internalErrPrefix = unlines [ "Language.C : Internal Error" ,
                              "This is propably a bug, and should be reported at "++
                              "http://www.sivity.net/projects/language.c/newticket"]
internalErr     :: String -> a
internalErr msg  = error (internalErrPrefix ++ "\n"
                       ++ indentLines msg
                       ++ "\n")
indent :: String
indent = "  "
indentLines :: String -> String
indentLines = unlines . map (indent++) . lines