[Haskell-cafe] shake and cmd argument dependency
Peter Simons
simons at nospf.cryp.to
Wed Apr 17 10:28:59 UTC 2019
Hi,
> How can I teach shake to rebuild a rules when
> the argument of the cmd change?
wrap the arguments that are subject to change into
an oracle to detect changes and to re-run all
actions that depend on the value:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
import Development.Shake
import Development.Shake.Classes
newtype GetCmdlineArgs = GetCmdlineArgs () deriving (Show,Typeable,Eq,Hashable,Binary,NFData)
type instance RuleResult GetCmdlineArgs = String
main :: IO ()
main =
shake shakeOptions $ do
want ["foo.txt"]
getCmdlineArgs <- addOracle $ \(GetCmdlineArgs ()) ->
return "This is a test!"
"*.txt" %> \out -> do
args <- getCmdlineArgs (GetCmdlineArgs ())
command [FileStdout out] "echo" [args]
Best regards,
Peter
More information about the Haskell-Cafe
mailing list