-- | A module for running compilable data types that take a list of file paths to compile. module Lastik.Runner( Runner, runner, runnerPath, codeRunner, pathRunner, valueRunner, andThen, ifRun, (+++), (-+-), pathTransform, (!!!), (>->), (+>->), (->-), (+->-) ) where import Data.Maybe import System.Cmd import System.Directory import System.Exit import Lastik.Find import Lastik.Compile import Lastik.Extension import Lastik.Output -- | A runner takes a list of file paths and runs a system command on them. type Runner r = r -> [FilePath] -> IO ExitCode -- | A runner that can access its arguments. runner :: (r -> [FilePath] -> Runner r) -> Runner r runner f = (\c p -> (f c p) c p) -- | A runner that can access its list of file paths. runnerPath :: ([FilePath] -> Runner r) -> Runner r runnerPath = runner . const -- | A runner that can access its data type value. runnerValue :: (r -> Runner r) -> Runner r runnerValue = runner . (const .) -- | A runner that always produces the given exit code. codeRunner :: ExitCode -> Runner r codeRunner c = \_ _ -> return c -- | A runner that ignores its data type value. pathRunner :: ([FilePath] -> IO ExitCode) -> Runner r pathRunner f = \_ -> f -- | A runner that ignores its list of file paths. valueRunner :: (r -> IO ExitCode) -> Runner r valueRunner f = const . f -- | Executes an action using runner arguments then produces a runner with the value of the previous action. andThen :: (r -> [FilePath] -> IO a) -> (a -> Runner r) -> Runner r andThen f g = \c p -> f c p >>= \k -> (g k) c p -- | Executes an action using runner arguments then produces a runner. andThen' :: (r -> [FilePath] -> IO a) -> Runner r -> Runner r andThen' = (. const) . andThen -- | Execute the second runner only if the exit code of the first runner satisfies the given predicate. ifRun :: (ExitCode -> Bool) -> Runner r -> Runner r -> Runner r ifRun z j k = \c p -> do j' <- j c p if z j' then k c p else return j' -- | Execute the second runner only if the exit code of the first runner is @ExitSuccess@. (+++) :: Runner r -> Runner r -> Runner r (+++) = ifRun (== ExitSuccess) -- | Execute the second runner only if the exit code of the first runner is not @ExitSuccess@. (-+-) :: Runner r -> Runner r -> Runner r (-+-) = ifRun (/= ExitSuccess) -- | Transform the list of file paths before executing the runner. pathTransform :: ([FilePath] -> IO [FilePath]) -> Runner t -> Runner t pathTransform k f = \c p -> do v <- k p f c v -- | Get all file paths with the given file extension (recursively) and execute the runner on those. pathTransform' :: (Extension e) => e -> Runner r -> Runner r pathTransform' = pathTransform . recurse where recurse c p = fmap concat $ find always (constant $ extension ==? ext' c) `mapM` p -- | Execute the compile result as a system command. (!!!) :: (Compile c) => Runner c (!!!) = (system .) . compile -- | Create the output target directory then execute the compile result as a system command. (>->) :: (Output c, Compile c) => Runner c (>->) = (const . mkdirectory . output) `andThen'` (!!!) where mkdirectory s = createDirectoryIfMissing True `mapM_` maybeToList s -- | Create the output target directory then incrementally execute the compile result as a system command. The output target is searched for the latest last-modification time and only those files in the output reference that are modified later than this time are submitted for compilation. (+>->) :: (Output c, Compile c, OutputReference c) => Runner c (+>->) = \c p -> do d <- c <===> p if null d then return ExitSuccess else (>->) (outref c) d -- | A runner that recursively searches the output target for files that match a given extension and compiles them as a system command. (->-) :: (Output c, Extension c, Compile c) => Runner c (->-) = runnerValue (flip pathTransform' (>->)) -- | A runner that recursively searches the output target for files that match a given extension and compiles them incrementally as a system command. The output target is searched for the latest last-modification time and only those files in the output reference that are modified later than this time are submitted for compilation. (+->-) :: (Output r, Extension r, Compile r, OutputReference r) => Runner r (+->-) = runnerValue (flip pathTransform' (+>->))