{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Ninja.IR.Rule
(
Rule, makeRule
, ruleName, ruleCommand, ruleDescription, rulePool, ruleDepfile
, ruleSpecialDeps, ruleGenerator, ruleRestat, ruleResponseFile
, SpecialDeps, makeSpecialDepsGCC, makeSpecialDepsMSVC
, _SpecialDepsGCC, _SpecialDepsMSVC
, ResponseFile, makeResponseFile, responseFilePath, responseFileContent
) where
import qualified Control.Lens as Lens
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Aeson ((.:), (.=))
import qualified Data.Aeson as Aeson
import Control.DeepSeq (NFData)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import qualified Test.SmallCheck.Series as SC
import Language.Ninja.IR.Pool (PoolName, makePoolNameDefault)
import Language.Ninja.Misc.Command (Command)
import Language.Ninja.Misc.Path (Path)
import Flow ((|>))
data Rule
= MkRule
{ _ruleName :: !Text
, _ruleCommand :: !Command
, _ruleDescription :: !(Maybe Text)
, _rulePool :: !PoolName
, _ruleDepfile :: !(Maybe Path)
, _ruleSpecialDeps :: !(Maybe SpecialDeps)
, _ruleGenerator :: !Bool
, _ruleRestat :: !Bool
, _ruleResponseFile :: !(Maybe ResponseFile)
}
deriving (Eq, Ord, Show, Generic)
{-# INLINE makeRule #-}
makeRule :: Text
-> Command
-> Rule
makeRule name cmd
= MkRule
{ _ruleName = name
, _ruleCommand = cmd
, _ruleDescription = Nothing
, _rulePool = makePoolNameDefault
, _ruleDepfile = Nothing
, _ruleSpecialDeps = Nothing
, _ruleGenerator = False
, _ruleRestat = False
, _ruleResponseFile = Nothing
}
{-# INLINE ruleName #-}
ruleName :: Lens.Lens' Rule Text
ruleName = Lens.lens _ruleName
$ \(MkRule {..}) x -> MkRule { _ruleName = x, .. }
{-# INLINE ruleCommand #-}
ruleCommand :: Lens.Lens' Rule Command
ruleCommand = Lens.lens _ruleCommand
$ \(MkRule {..}) x -> MkRule { _ruleCommand = x, .. }
{-# INLINE ruleDescription #-}
ruleDescription :: Lens.Lens' Rule (Maybe Text)
ruleDescription = Lens.lens _ruleDescription
$ \(MkRule {..}) x -> MkRule { _ruleDescription = x, .. }
{-# INLINE rulePool #-}
rulePool :: Lens.Lens' Rule PoolName
rulePool = Lens.lens _rulePool
$ \(MkRule {..}) x -> MkRule { _rulePool = x, .. }
{-# INLINE ruleDepfile #-}
ruleDepfile :: Lens.Lens' Rule (Maybe Path)
ruleDepfile = Lens.lens _ruleDepfile
$ \(MkRule {..}) x -> MkRule { _ruleDepfile = x, .. }
{-# INLINE ruleSpecialDeps #-}
ruleSpecialDeps :: Lens.Lens' Rule (Maybe SpecialDeps)
ruleSpecialDeps = Lens.lens _ruleSpecialDeps
$ \(MkRule {..}) x -> MkRule { _ruleSpecialDeps = x, .. }
{-# INLINE ruleGenerator #-}
ruleGenerator :: Lens.Lens' Rule Bool
ruleGenerator = Lens.lens _ruleGenerator
$ \(MkRule {..}) x -> MkRule { _ruleGenerator = x, .. }
{-# INLINE ruleRestat #-}
ruleRestat :: Lens.Lens' Rule Bool
ruleRestat = Lens.lens _ruleRestat
$ \(MkRule {..}) x -> MkRule { _ruleRestat = x, .. }
{-# INLINE ruleResponseFile #-}
ruleResponseFile :: Lens.Lens' Rule (Maybe ResponseFile)
ruleResponseFile = Lens.lens _ruleResponseFile
$ \(MkRule {..}) x -> MkRule { _ruleResponseFile = x, .. }
instance Aeson.ToJSON Rule where
toJSON (MkRule {..})
= [ "name" .= _ruleName
, "command" .= _ruleCommand
, "desc" .= _ruleDescription
, "pool" .= _rulePool
, "depfile" .= _ruleDepfile
, "deps" .= _ruleSpecialDeps
, "generator" .= _ruleGenerator
, "restat" .= _ruleRestat
, "rsp" .= _ruleResponseFile
] |> Aeson.object
instance Aeson.FromJSON Rule where
parseJSON = (Aeson.withObject "Rule" $ \o -> do
_ruleName <- (o .: "name") >>= pure
_ruleCommand <- (o .: "command") >>= pure
_ruleDescription <- (o .: "desc") >>= pure
_rulePool <- (o .: "pool") >>= pure
_ruleDepfile <- (o .: "depfile") >>= pure
_ruleSpecialDeps <- (o .: "deps") >>= pure
_ruleGenerator <- (o .: "generator") >>= pure
_ruleRestat <- (o .: "restat") >>= pure
_ruleResponseFile <- (o .: "rsp") >>= pure
pure (MkRule {..}))
instance Hashable Rule
instance NFData Rule
instance ( Monad m
, SC.Serial m Text
) => SC.Serial m Rule
instance ( Monad m
, SC.CoSerial m Text
) => SC.CoSerial m Rule
data SpecialDeps
= SpecialDepsGCC
| SpecialDepsMSVC !Text
deriving (Eq, Ord, Show, Read, Generic)
{-# INLINE makeSpecialDepsGCC #-}
makeSpecialDepsGCC :: SpecialDeps
makeSpecialDepsGCC = SpecialDepsGCC
{-# INLINE makeSpecialDepsMSVC #-}
makeSpecialDepsMSVC :: Text
-> SpecialDeps
makeSpecialDepsMSVC = SpecialDepsMSVC
{-# INLINE _SpecialDepsGCC #-}
_SpecialDepsGCC :: Lens.Prism' SpecialDeps ()
_SpecialDepsGCC = Lens.prism (const makeSpecialDepsGCC)
$ \case SpecialDepsGCC -> Right ()
owise -> Left owise
{-# INLINE _SpecialDepsMSVC #-}
_SpecialDepsMSVC :: Lens.Prism' SpecialDeps Text
_SpecialDepsMSVC = Lens.prism makeSpecialDepsMSVC
$ \case (SpecialDepsMSVC prefix) -> Right prefix
owise -> Left owise
instance Aeson.ToJSON SpecialDeps where
toJSON = go
where
go SpecialDepsGCC = Aeson.object ["deps" .= gcc]
go (SpecialDepsMSVC p) = Aeson.object ["deps" .= msvc, "prefix" .= p]
(gcc, msvc) = ("gcc", "msvc") :: (Aeson.Value, Aeson.Value)
instance Aeson.FromJSON SpecialDeps where
parseJSON = Aeson.withObject "SpecialDeps" $ \o -> do
deps <- o .: "deps"
case Text.pack deps of
"gcc" -> pure SpecialDepsGCC
"msvc" -> SpecialDepsMSVC <$> (o .: "prefix")
owise -> [ "Invalid deps type ", "\"", owise, "\"; "
, "should be one of [\"gcc\", \"msvc\"]."
] |> mconcat |> Text.unpack |> fail
instance Hashable SpecialDeps
instance NFData SpecialDeps
instance ( Monad m
, SC.Serial m Text
) => SC.Serial m SpecialDeps
instance ( Monad m
, SC.CoSerial m Text
) => SC.CoSerial m SpecialDeps
data ResponseFile
= MkResponseFile
{ _responseFilePath :: !Path
, _responseFileContent :: !Text
}
deriving (Eq, Ord, Show, Generic)
{-# INLINE makeResponseFile #-}
makeResponseFile :: Path
-> Text
-> ResponseFile
makeResponseFile = MkResponseFile
{-# INLINE responseFilePath #-}
responseFilePath :: Lens.Lens' ResponseFile Path
responseFilePath = Lens.lens _responseFilePath
$ \(MkResponseFile {..}) x ->
MkResponseFile { _responseFilePath = x, .. }
{-# INLINE responseFileContent #-}
responseFileContent :: Lens.Lens' ResponseFile Text
responseFileContent = Lens.lens _responseFileContent
$ \(MkResponseFile {..}) x ->
MkResponseFile { _responseFileContent = x, .. }
instance Aeson.ToJSON ResponseFile where
toJSON (MkResponseFile {..})
= [ "path" .= _responseFilePath
, "content" .= _responseFileContent
] |> Aeson.object
instance Aeson.FromJSON ResponseFile where
parseJSON = Aeson.withObject "ResponseFile"
$ \o -> MkResponseFile <$> (o .: "path") <*> (o .: "content")
instance Hashable ResponseFile
instance NFData ResponseFile
instance ( Monad m
, SC.Serial m Text
) => SC.Serial m ResponseFile
instance ( Monad m
, SC.CoSerial m Text
) => SC.CoSerial m ResponseFile