{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Ninja.AST.Deps
(
Deps, makeDeps
, depsNormal, depsImplicit, depsOrderOnly
, DepsConstraint
) where
import qualified Control.Lens as Lens
import Flow ((|>))
import Data.HashSet (HashSet)
import Data.Text (Text)
import Control.DeepSeq (NFData)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import qualified Test.QuickCheck as QC
import Test.QuickCheck.Instances ()
import qualified Test.SmallCheck.Series as SC
import GHC.Exts (Constraint)
import Data.Aeson ((.:), (.=))
import qualified Data.Aeson as Aeson
import qualified Language.Ninja.Misc as Misc
data Deps ann
= MkDeps
{ _depsAnn :: !ann
, _depsNormal :: !(HashSet Text)
, _depsImplicit :: !(HashSet Text)
, _depsOrderOnly :: !(HashSet Text)
}
deriving (Eq, Show, Generic, Functor, Foldable, Traversable)
{-# INLINE makeDeps #-}
makeDeps :: (Monoid ann) => Deps ann
makeDeps = MkDeps
{ _depsAnn = mempty
, _depsNormal = mempty
, _depsImplicit = mempty
, _depsOrderOnly = mempty
}
{-# INLINE depsNormal #-}
depsNormal :: Lens.Lens' (Deps ann) (HashSet Text)
depsNormal = Lens.lens _depsNormal
$ \(MkDeps {..}) x -> MkDeps { _depsNormal = x, .. }
{-# INLINE depsImplicit #-}
depsImplicit :: Lens.Lens' (Deps ann) (HashSet Text)
depsImplicit = Lens.lens _depsImplicit
$ \(MkDeps {..}) x -> MkDeps { _depsImplicit = x, .. }
{-# INLINE depsOrderOnly #-}
depsOrderOnly :: Lens.Lens' (Deps ann) (HashSet Text)
depsOrderOnly = Lens.lens _depsOrderOnly
$ \(MkDeps {..}) x -> MkDeps { _depsOrderOnly = x, .. }
instance Misc.Annotated Deps where
annotation' _ = Lens.lens _depsAnn
$ \(MkDeps {..}) x -> MkDeps { _depsAnn = x, .. }
instance (Aeson.ToJSON ann) => Aeson.ToJSON (Deps ann) where
toJSON (MkDeps {..})
= [ "ann" .= _depsAnn
, "normal" .= _depsNormal
, "implicit" .= _depsImplicit
, "order-only" .= _depsOrderOnly
] |> Aeson.object
instance (Aeson.FromJSON ann) => Aeson.FromJSON (Deps ann) where
parseJSON = (Aeson.withObject "Deps" $ \o -> do
_depsAnn <- (o .: "ann") >>= pure
_depsNormal <- (o .: "normal") >>= pure
_depsImplicit <- (o .: "implicit") >>= pure
_depsOrderOnly <- (o .: "order-only") >>= pure
pure (MkDeps {..}))
instance (QC.Arbitrary ann) => QC.Arbitrary (Deps ann) where
arbitrary = MkDeps
<$> QC.arbitrary
<*> QC.arbitrary
<*> QC.arbitrary
<*> QC.arbitrary
instance (Hashable ann) => Hashable (Deps ann)
instance (NFData ann) => NFData (Deps ann)
instance ( Monad m, DepsConstraint (SC.Serial m) ann
) => SC.Serial m (Deps ann)
instance ( Monad m, DepsConstraint (SC.CoSerial m) ann
) => SC.CoSerial m (Deps ann)
type DepsConstraint (c :: * -> Constraint) (ann :: *)
= ( c (HashSet Text)
, c ann
)