{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
module Language.Ninja.Errors.Compile
(
CompileError (..)
, throwCompileError, throwGenericCompileError
, CompileMetaError (..)
, throwCompileMetaError, throwGenericCompileMetaError
, throwVersionParseFailure
, CompilePhonyError (..)
, throwCompilePhonyError, throwGenericCompilePhonyError
, CompileDefaultError (..)
, throwCompileDefaultError, throwGenericCompileDefaultError
, CompileBuildError (..)
, throwCompileBuildError, throwGenericCompileBuildError
, throwBuildRuleNotFound
, CompileRuleError (..)
, throwCompileRuleError, throwGenericCompileRuleError
, throwRuleLookupFailure
, throwUnknownDeps
, throwUnexpectedMSVCPrefix
, CompilePoolError (..)
, throwCompilePoolError, throwGenericCompilePoolError
, throwInvalidPoolDepth
, throwEmptyPoolName
) where
import Control.Exception (Exception)
import Control.Monad.Error.Class (MonadError (throwError))
import GHC.Generics (Generic)
import Data.Text (Text)
import Data.Aeson ((.=))
import qualified Data.Aeson as Aeson
import qualified Text.Megaparsec as M
import qualified Data.Versions as Ver
import Data.Foldable (toList)
import Flow ((.>), (|>))
data CompileError
=
GenericCompileError !Text
|
CompileMetaError !CompileMetaError
|
CompileBuildError !CompileBuildError
|
CompileRuleError !CompileRuleError
|
CompilePhonyError !CompilePhonyError
|
CompileDefaultError !CompileDefaultError
|
CompilePoolError !CompilePoolError
deriving (Eq, Show, Generic)
throwCompileError :: (MonadError CompileError m) => CompileError -> m a
throwCompileError = throwError
throwGenericCompileError :: (MonadError CompileError m) => Text -> m a
throwGenericCompileError msg = throwCompileError (GenericCompileError msg)
instance Exception CompileError
instance Aeson.ToJSON CompileError where
toJSON = go
where
go (GenericCompileError text) = obj "generic-compile-error" text
go (CompileMetaError cme) = obj "compile-meta-error" cme
go (CompileBuildError cbe) = obj "compile-build-error" cbe
go (CompileRuleError cre) = obj "compile-rule-error" cre
go (CompilePhonyError cpe) = obj "compile-phony-error" cpe
go (CompileDefaultError cde) = obj "compile-default-error" cde
go (CompilePoolError cpe) = obj "compile-pool-error" cpe
obj :: (Aeson.ToJSON x) => Text -> x -> Aeson.Value
obj tag value = Aeson.object ["tag" .= tag, "value" .= value]
data CompileMetaError
=
GenericCompileMetaError !Text
|
VersionParseFailure !Ver.ParsingError
deriving (Eq, Show, Generic)
throwCompileMetaError :: (MonadError CompileError m) => CompileMetaError -> m a
throwCompileMetaError = CompileMetaError .> throwCompileError
throwGenericCompileMetaError :: (MonadError CompileError m) => Text -> m a
throwGenericCompileMetaError = GenericCompileMetaError .> throwCompileMetaError
throwVersionParseFailure :: (MonadError CompileError m)
=> Ver.ParsingError -> m a
throwVersionParseFailure pe = throwCompileMetaError (VersionParseFailure pe)
instance Aeson.ToJSON CompileMetaError where
toJSON = go
where
go (GenericCompileMetaError t) = obj "generic-compile-meta-error" t
go (VersionParseFailure e) = obj "version-parse-failure" (peJ e)
peJ :: M.ParseError Char M.Dec -> Aeson.Value
peJ (decomposePE -> (pos, custom, unexpected, expected))
= [ "pos" .= (posJ <$> pos)
, "unexpected" .= (errItemJ <$> unexpected)
, "expected" .= (errItemJ <$> expected)
, "custom" .= (decJ <$> custom)
] |> Aeson.object
decomposePE :: M.ParseError Char M.Dec
-> ( [M.SourcePos], [M.Dec]
, [M.ErrorItem Char], [M.ErrorItem Char] )
decomposePE (M.ParseError {..})
= ( toList errorPos, toList errorCustom
, toList errorUnexpected, toList errorExpected )
posJ :: M.SourcePos -> Aeson.Value
posJ (M.SourcePos {..}) = [ "name" .= sourceName
, "line" .= M.unPos sourceLine
, "column" .= M.unPos sourceColumn
] |> Aeson.object
errItemJ :: M.ErrorItem Char -> Aeson.Value
errItemJ (M.Tokens xs) = Aeson.toJSON (toList xs)
errItemJ (M.Label xs) = Aeson.toJSON (toList xs)
errItemJ M.EndOfInput = "eof"
decJ :: M.Dec -> Aeson.Value
decJ (M.DecFail message) = [ "message" .= message
] |> Aeson.object |> obj "fail"
decJ (M.DecIndentation ord x y) = [ "ordering" .= ord
, "start" .= M.unPos x
, "end" .= M.unPos y
] |> Aeson.object |> obj "indentation"
obj :: (Aeson.ToJSON x) => Text -> x -> Aeson.Value
obj tag value = Aeson.object ["tag" .= tag, "value" .= value]
data CompilePhonyError
=
GenericCompilePhonyError !Text
deriving (Eq, Show, Generic)
throwCompilePhonyError :: (MonadError CompileError m)
=> CompilePhonyError -> m a
throwCompilePhonyError = CompilePhonyError .> throwCompileError
throwGenericCompilePhonyError :: (MonadError CompileError m) => Text -> m a
throwGenericCompilePhonyError = GenericCompilePhonyError
.> throwCompilePhonyError
instance Aeson.ToJSON CompilePhonyError where
toJSON = go
where
go (GenericCompilePhonyError t) = obj "generic-compile-phony-error" t
obj :: (Aeson.ToJSON x) => Text -> x -> Aeson.Value
obj tag value = Aeson.object ["tag" .= tag, "value" .= value]
data CompileDefaultError
=
GenericCompileDefaultError !Text
deriving (Eq, Show, Generic)
throwCompileDefaultError :: (MonadError CompileError m)
=> CompileDefaultError -> m a
throwCompileDefaultError = CompileDefaultError .> throwCompileError
throwGenericCompileDefaultError :: (MonadError CompileError m) => Text -> m a
throwGenericCompileDefaultError = GenericCompileDefaultError
.> throwCompileDefaultError
instance Aeson.ToJSON CompileDefaultError where
toJSON = go
where
go (GenericCompileDefaultError t) = obj "generic-compile-default-error" t
obj :: (Aeson.ToJSON x) => Text -> x -> Aeson.Value
obj tag value = Aeson.object ["tag" .= tag, "value" .= value]
data CompileBuildError
=
GenericCompileBuildError !Text
|
BuildRuleNotFound !Text
deriving (Eq, Show, Generic)
throwCompileBuildError :: (MonadError CompileError m)
=> CompileBuildError -> m a
throwCompileBuildError = CompileBuildError .> throwCompileError
throwGenericCompileBuildError :: (MonadError CompileError m) => Text -> m a
throwGenericCompileBuildError = GenericCompileBuildError
.> throwCompileBuildError
throwBuildRuleNotFound :: (MonadError CompileError m) => Text -> m a
throwBuildRuleNotFound name = throwCompileBuildError (BuildRuleNotFound name)
instance Aeson.ToJSON CompileBuildError where
toJSON = go
where
go (GenericCompileBuildError t) = obj "generic-compile-build-error" t
go (BuildRuleNotFound n) = obj "build-rule-not-found" n
obj :: (Aeson.ToJSON x) => Text -> x -> Aeson.Value
obj tag value = Aeson.object ["tag" .= tag, "value" .= value]
data CompileRuleError
=
GenericCompileRuleError !Text
|
RuleLookupFailure !Text
|
UnknownDepsValue !Text
|
UnexpectedMSVCPrefix !Text
deriving (Eq, Show, Generic)
throwCompileRuleError :: (MonadError CompileError m) => CompileRuleError -> m a
throwCompileRuleError = CompileRuleError .> throwCompileError
throwGenericCompileRuleError :: (MonadError CompileError m) => Text -> m a
throwGenericCompileRuleError = GenericCompileRuleError .> throwCompileRuleError
throwRuleLookupFailure :: (MonadError CompileError m) => Text -> m a
throwRuleLookupFailure v = throwCompileRuleError (RuleLookupFailure v)
throwUnknownDeps :: (MonadError CompileError m) => Text -> m a
throwUnknownDeps deps = throwCompileRuleError (UnknownDepsValue deps)
throwUnexpectedMSVCPrefix :: (MonadError CompileError m) => Text -> m a
throwUnexpectedMSVCPrefix deps = throwCompileRuleError
(UnexpectedMSVCPrefix deps)
instance Aeson.ToJSON CompileRuleError where
toJSON = go
where
go (GenericCompileRuleError t) = obj "generic-compile-build-error" t
go (RuleLookupFailure n) = obj "rule-lookup-failure" n
go (UnknownDepsValue d) = obj "unknown-deps-value" d
go (UnexpectedMSVCPrefix d) = obj "unexpected-msvc-prefix" d
obj :: (Aeson.ToJSON x) => Text -> x -> Aeson.Value
obj tag value = Aeson.object ["tag" .= tag, "value" .= value]
data CompilePoolError
=
GenericCompilePoolError !Text
|
InvalidPoolDepth !Int
|
EmptyPoolName
deriving (Eq, Show, Generic)
throwCompilePoolError :: (MonadError CompileError m) => CompilePoolError -> m a
throwCompilePoolError = CompilePoolError .> throwCompileError
throwGenericCompilePoolError :: (MonadError CompileError m) => Text -> m a
throwGenericCompilePoolError = GenericCompilePoolError .> throwCompilePoolError
throwInvalidPoolDepth :: (MonadError CompileError m) => Int -> m a
throwInvalidPoolDepth d = throwCompilePoolError (InvalidPoolDepth d)
throwEmptyPoolName :: (MonadError CompileError m) => m a
throwEmptyPoolName = throwCompilePoolError EmptyPoolName
instance Aeson.ToJSON CompilePoolError where
toJSON = go
where
go (GenericCompilePoolError t) = obj "generic-compile-pool-error" t
go (InvalidPoolDepth d) = obj "invalid-pool-depth" d
go EmptyPoolName = obj "empty-pool-name" nullJ
obj :: (Aeson.ToJSON x) => Text -> x -> Aeson.Value
obj tag value = Aeson.object ["tag" .= tag, "value" .= value]
nullJ = Aeson.Null :: Aeson.Value