{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards, ScopedTypeVariables #-}
{-# LANGUAGE GeneralizedNewtypeDeriving, ConstraintKinds #-}
{-# LANGUAGE ExistentialQuantification, RankNTypes #-}
{-# LANGUAGE TypeFamilies, DeriveDataTypeable #-}
module Development.Shake.Internal.Core.Rules(
Rules, runRules,
RuleResult, addBuiltinRule, addBuiltinRuleEx,
noLint, noIdentity,
getShakeOptionsRules,
getUserRuleInternal, getUserRuleOne, getUserRuleList, getUserRuleMaybe,
addUserRule, alternatives, priority, versioned,
getTargets, addTarget, withTargetDocs, withoutTargets,
action, withoutActions
) where
import Control.Applicative
import Data.Tuple.Extra
import Control.Exception
import Control.Monad.Extra
import Control.Monad.Fix
import Control.Monad.IO.Class
import Control.Monad.Trans.Reader
import Development.Shake.Classes
import General.Binary
import General.Extra
import Data.Typeable
import Data.Data
import Data.List.Extra
import qualified Data.HashMap.Strict as Map
import qualified General.TypeMap as TMap
import Data.Maybe
import Data.IORef
import Data.Semigroup (Semigroup (..))
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Binary.Builder as Bin
import Data.Binary.Put
import Data.Binary.Get
import General.ListBuilder
#if __GLASGOW_HASKELL__ >= 800
import Control.Monad.Fail
#endif
import Development.Shake.Internal.Core.Types
import Development.Shake.Internal.Core.Monad
import Development.Shake.Internal.Value
import Development.Shake.Internal.Options
import Development.Shake.Internal.Errors
getShakeOptionsRules :: Rules ShakeOptions
getShakeOptionsRules = Rules $ asks fst
getUserRuleInternal :: forall key a b . (ShakeValue key, Typeable a) => key -> (a -> Maybe String) -> (a -> Maybe b) -> Action (Maybe Ver, [(Int, b)], SomeException)
getUserRuleInternal key disp test = do
Global{..} <- Action getRO
let UserRuleVersioned versioned rules = fromMaybe mempty $ TMap.lookup globalUserRules
let ver = if versioned then Nothing else Just $ Ver 0
let items = head $ (map snd $ reverse $ groupSort $ f (Ver 0) Nothing rules) ++ [[]]
let err = errorMultipleRulesMatch (typeOf key) (show key) (map snd3 items)
return (ver, map (\(Ver v,_,x) -> (v,x)) items, err)
where
f :: Ver -> Maybe Double -> UserRule a -> [(Double,(Ver,Maybe String,b))]
f v p (UserRule x) = [(fromMaybe 1 p, (v,disp x,x2)) | Just x2 <- [test x]]
f v p (Unordered xs) = concatMap (f v p) xs
f v p (Priority p2 x) = f v (Just $ fromMaybe p2 p) x
f _ p (Versioned v x) = f v p x
f v p (Alternative x) = take 1 $ f v p x
getUserRuleList :: Typeable a => (a -> Maybe b) -> Action [(Int, b)]
getUserRuleList test = snd3 <$> getUserRuleInternal () (const Nothing) test
getUserRuleMaybe :: (ShakeValue key, Typeable a) => key -> (a -> Maybe String) -> (a -> Maybe b) -> Action (Maybe (Int, b))
getUserRuleMaybe key disp test = do
(_, xs, err) <- getUserRuleInternal key disp test
case xs of
[] -> return Nothing
[x] -> return $ Just x
_ -> throwM err
getUserRuleOne :: (ShakeValue key, Typeable a) => key -> (a -> Maybe String) -> (a -> Maybe b) -> Action (Int, b)
getUserRuleOne key disp test = do
(_, xs, err) <- getUserRuleInternal key disp test
case xs of
[x] -> return x
_ -> throwM err
newtype Rules a = Rules (ReaderT (ShakeOptions, IORef SRules) IO a)
deriving (Functor, Applicative, Monad, MonadIO, MonadFix
#if __GLASGOW_HASKELL__ >= 800
,MonadFail
#endif
)
newRules :: SRules -> Rules ()
newRules x = Rules $ liftIO . flip modifyIORef' (<> x) =<< asks snd
modifyRulesScoped :: (SRules -> SRules) -> Rules a -> Rules a
modifyRulesScoped f (Rules r) = Rules $ do
(opts, refOld) <- ask
liftIO $ do
refNew <- newIORef mempty
res <- runReaderT r (opts, refNew)
rules <- readIORef refNew
modifyIORef' refOld (<> f rules)
return res
runRules :: ShakeOptions -> Rules () -> IO ([(Stack, Action ())], Map.HashMap TypeRep BuiltinRule, TMap.Map UserRuleVersioned, [Target])
runRules opts (Rules r) = do
ref <- newIORef mempty
runReaderT r (opts, ref)
SRules{..} <- readIORef ref
return (runListBuilder actions, builtinRules, userRules, runListBuilder targets)
getTargets :: ShakeOptions -> Rules () -> IO [(String, Maybe String)]
getTargets opts rs = do
(_actions, _ruleinfo, _userRules, targets) <- runRules opts rs
return [(target, documentation) | Target{..} <- targets]
data Target = Target
{target :: !String
,documentation :: !(Maybe String)
} deriving (Eq,Ord,Show,Read,Data,Typeable)
data SRules = SRules
{actions :: !(ListBuilder (Stack, Action ()))
,builtinRules :: !(Map.HashMap TypeRep BuiltinRule)
,userRules :: !(TMap.Map UserRuleVersioned)
,targets :: !(ListBuilder Target)
}
instance Semigroup SRules where
(SRules x1 x2 x3 x4) <> (SRules y1 y2 y3 y4) = SRules (mappend x1 y1) (Map.unionWithKey f x2 y2) (TMap.unionWith (<>) x3 y3) (mappend x4 y4)
where f k a b = throwImpure $ errorRuleDefinedMultipleTimes k [builtinLocation a, builtinLocation b]
instance Monoid SRules where
mempty = SRules mempty Map.empty TMap.empty mempty
mappend = (<>)
instance Semigroup a => Semigroup (Rules a) where
(<>) = liftA2 (<>)
instance (Semigroup a, Monoid a) => Monoid (Rules a) where
mempty = return mempty
mappend = (<>)
addUserRule :: Typeable a => a -> Rules ()
addUserRule r = newRules mempty{userRules = TMap.singleton $ UserRuleVersioned False $ UserRule r}
addTarget :: String -> Rules ()
addTarget t = newRules mempty{targets = newListBuilder $ Target t Nothing}
withTargetDocs :: String -> Rules () -> Rules ()
withTargetDocs d = modifyRulesScoped $ \x -> x{targets = f <$> targets x}
where f (Target a b) = Target a $ Just $ fromMaybe d b
withoutTargets :: Rules a -> Rules a
withoutTargets = modifyRulesScoped $ \x -> x{targets=mempty}
noLint :: BuiltinLint key value
noLint _ _ = return Nothing
noIdentity :: Typeable key => BuiltinIdentity key value
noIdentity _ _ = Nothing
type family RuleResult key
addBuiltinRule
:: (RuleResult key ~ value, ShakeValue key, Typeable value, NFData value, Show value, Partial)
=> BuiltinLint key value -> BuiltinIdentity key value -> BuiltinRun key value -> Rules ()
addBuiltinRule = withFrozenCallStack $ addBuiltinRuleInternal $ BinaryOp
(putEx . Bin.toLazyByteString . execPut . put)
(runGet get . LBS.fromChunks . return)
addBuiltinRuleEx
:: (RuleResult key ~ value, ShakeValue key, BinaryEx key, Typeable value, NFData value, Show value, Partial)
=> BuiltinLint key value -> BuiltinIdentity key value -> BuiltinRun key value -> Rules ()
addBuiltinRuleEx = addBuiltinRuleInternal $ BinaryOp putEx getEx
addBuiltinRuleInternal
:: (RuleResult key ~ value, ShakeValue key, Typeable value, NFData value, Show value, Partial)
=> BinaryOp key -> BuiltinLint key value -> BuiltinIdentity key value -> BuiltinRun key value -> Rules ()
addBuiltinRuleInternal binary lint check (run :: BuiltinRun key value) = do
let k = Proxy :: Proxy key
let lint_ k v = lint (fromKey k) (fromValue v)
let check_ k v = check (fromKey k) (fromValue v)
let run_ k v b = fmap newValue <$> run (fromKey k) v b
let binary_ = BinaryOp (putOp binary . fromKey) (newKey . getOp binary)
newRules mempty{builtinRules = Map.singleton (typeRep k) $ BuiltinRule lint_ check_ run_ binary_ (Ver 0) callStackTop}
priority :: Double -> Rules a -> Rules a
priority d = modifyRulesScoped $ \s -> s{userRules = TMap.map (\(UserRuleVersioned b x) -> UserRuleVersioned b $ Priority d x) $ userRules s}
versioned :: Int -> Rules a -> Rules a
versioned v = modifyRulesScoped $ \s -> s
{userRules = TMap.map (\(UserRuleVersioned b x) -> UserRuleVersioned (b || v /= 0) $ Versioned (Ver v) x) $ userRules s
,builtinRules = Map.map (\b -> b{builtinVersion = Ver v}) $ builtinRules s
}
alternatives :: Rules a -> Rules a
alternatives = modifyRulesScoped $ \r -> r{userRules = TMap.map (\(UserRuleVersioned b x) -> UserRuleVersioned b $ Alternative x) $ userRules r}
action :: Partial => Action a -> Rules ()
action act = newRules mempty{actions=newListBuilder (addCallStack callStackFull emptyStack, void act)}
withoutActions :: Rules a -> Rules a
withoutActions = modifyRulesScoped $ \x -> x{actions=mempty}