{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Ninja.IR.Target
(
Target, makeTarget, targetIText, targetText
, Output, makeOutput, outputTarget
, Dependency, makeDependency, dependencyTarget, dependencyType
, DependencyType (..), _NormalDependency, _OrderOnlyDependency
) 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 Data.String (IsString)
import GHC.Generics (Generic)
import Test.SmallCheck.Series ((>>-))
import qualified Test.SmallCheck.Series as SC
import qualified Language.Ninja.Misc.IText as Misc
import Flow ((.>), (|>))
newtype Target
= MkTarget
{ _targetIText :: Misc.IText
}
deriving ( Eq, Ord, Show, Read, IsString, Generic, Hashable, NFData
, Aeson.ToJSON, Aeson.FromJSON, Aeson.ToJSONKey, Aeson.FromJSONKey )
{-# INLINE makeTarget #-}
makeTarget :: Text -> Target
makeTarget = Lens.view Misc.itext .> MkTarget
{-# INLINE targetIText #-}
targetIText :: Lens.Iso' Target Misc.IText
targetIText = Lens.iso _targetIText MkTarget
{-# INLINE targetText #-}
targetText :: Lens.Iso' Target Text
targetText = targetIText . Lens.from Misc.itext
instance (Monad m, SC.Serial m Text) => SC.Serial m Target where
series = SC.newtypeCons MkTarget
instance (Monad m, SC.CoSerial m Text) => SC.CoSerial m Target where
coseries rs = SC.newtypeAlts rs
>>- \f -> pure (_targetIText .> f)
newtype Output
= MkOutput
{ _outputTarget :: Target
}
deriving (Eq, Ord, Show, Read, Generic)
{-# INLINE makeOutput #-}
makeOutput :: Target
-> Output
makeOutput = MkOutput
{-# INLINE outputTarget #-}
outputTarget :: Lens.Lens' Output Target
outputTarget = Lens.lens _outputTarget
$ \(MkOutput {..}) new -> MkOutput { _outputTarget = new, .. }
instance Aeson.ToJSON Output where
toJSON (MkOutput {..})
= [ "target" .= _outputTarget
] |> Aeson.object
instance Aeson.FromJSON Output where
parseJSON = (Aeson.withObject "Output" $ \o -> do
_outputTarget <- (o .: "target") >>= pure
pure (MkOutput {..}))
instance Hashable Output
instance NFData Output
instance (Monad m, SC.Serial m Text) => SC.Serial m Output
instance (Monad m, SC.CoSerial m Text) => SC.CoSerial m Output
data Dependency
= MkDependency
{ _dependencyTarget :: !Target
, _dependencyType :: !DependencyType
}
deriving (Eq, Ord, Show, Read, Generic)
{-# INLINE makeDependency #-}
makeDependency :: Target
-> DependencyType
-> Dependency
makeDependency = MkDependency
{-# INLINE dependencyTarget #-}
dependencyTarget :: Lens.Lens' Dependency Target
dependencyTarget
= Lens.lens _dependencyTarget
$ \(MkDependency {..}) new -> MkDependency { _dependencyTarget = new, .. }
{-# INLINE dependencyType #-}
dependencyType :: Lens.Lens' Dependency DependencyType
dependencyType
= Lens.lens _dependencyType
$ \(MkDependency {..}) new -> MkDependency { _dependencyType = new, .. }
instance Aeson.ToJSON Dependency where
toJSON (MkDependency {..})
= [ "target" .= _dependencyTarget
, "type" .= _dependencyType
] |> Aeson.object
instance Aeson.FromJSON Dependency where
parseJSON = (Aeson.withObject "Dependency" $ \o -> do
_dependencyTarget <- (o .: "target") >>= pure
_dependencyType <- (o .: "type") >>= pure
pure (MkDependency {..}))
instance Hashable Dependency
instance NFData Dependency
instance (Monad m, SC.Serial m Text) => SC.Serial m Dependency
instance (Monad m, SC.CoSerial m Text) => SC.CoSerial m Dependency
data DependencyType
=
NormalDependency
|
OrderOnlyDependency
deriving (Eq, Ord, Show, Read, Generic)
{-# INLINE _NormalDependency #-}
_NormalDependency :: Lens.Prism' DependencyType ()
_NormalDependency = Lens.prism' (const NormalDependency)
$ \case NormalDependency -> Just ()
_ -> Nothing
{-# INLINE _OrderOnlyDependency #-}
_OrderOnlyDependency :: Lens.Prism' DependencyType ()
_OrderOnlyDependency = Lens.prism' (const OrderOnlyDependency)
$ \case OrderOnlyDependency -> Just ()
_ -> Nothing
instance Aeson.ToJSON DependencyType where
toJSON NormalDependency = "normal"
toJSON OrderOnlyDependency = "order-only"
instance Aeson.FromJSON DependencyType where
parseJSON = (Aeson.withText "DependencyType" $ \case
"normal" -> pure NormalDependency
"order-only" -> pure OrderOnlyDependency
owise -> [ "Invalid dependency type "
, "\"", owise, "\"; should be one of "
, "[\"normal\", \"order-only\"]"
] |> mconcat |> Text.unpack |> fail)
instance Hashable DependencyType
instance NFData DependencyType
instance (Monad m) => SC.Serial m DependencyType
instance (Monad m) => SC.CoSerial m DependencyType