-- | A module for running compilable data types that take a list of file paths to compile.
module System.Build.Runner(
                            -- * Runners
                            Runner,
                            RunnerExit,
                            -- * Chaining Runners
                            (>--),
                            (>==),
                            -- * Transforming file paths
                            pathTransform,
                            pathTransform',
                            -- * Running system command
                            (!!!),
                            (>->),
                            (->-),
                            -- * Chaining References.
                            (+>>),
                            (++>>),
                            (>===>),
                            (>=>=>)
                          ) where

import Control.Monad
import Data.Maybe
import System.Cmd
import System.Directory
import System.Exit
import System.Build.FilePather
import System.Build.Extensions
import System.Build.Command
import System.Build.CompilePaths
import System.Build.OutputDirectory
import System.Build.OutputReferenceGet
import System.Build.OutputReferenceSet

type Runner e r = r -> [FilePath] -> IO e

type RunnerExit r = Runner ExitCode r

-- | Applies the second value only if the first produces @ExitSuccess@.
(>--) :: (Monad m) =>
         m ExitCode ->
         m ExitCode ->
         m ExitCode
f >-- g = do e <- f
             if e == ExitSuccess
               then g
               else return e

-- | Executes the second action only if the first produces @ExitSuccess@.
(>==) :: (Monad m) =>
         m ExitCode ->
         m () ->
         m ()
p >== q = do e <- p
             when (e == ExitSuccess) q


-- | Transform the list of file paths before executing the runner.
pathTransform :: ([FilePath] -> IO [FilePath]) ->
                 Runner x t ->
                 Runner x t
pathTransform k f c p = k p >>= f c

-- | Get all file paths with the given file extension (recursively) and execute the runner on those.
pathTransform' :: (Extensions e) =>
                  e ->
                  Runner x r ->
                  Runner x r
pathTransform' = pathTransform . recurse
  where
  recurse c p = fmap concat $ find always (constant $ extension ==|| exts' c) `mapM` p

(!!!) :: (Command c, CompilePaths c) =>
         RunnerExit c
c !!! z = do s <- command c
             system (s ++ ' ' : c =>> z)

-- | Create the output target directory then execute the compile result as a system command.
(>->) :: (OutputDirectory c, Command c, CompilePaths c) =>
         RunnerExit c
c >-> z = do mkdirectory (outdir c)
             c !!! z
  where
  mkdirectory = mapM_ (createDirectoryIfMissing True) . maybeToList

-- | A runner that recursively searches the output target for files that match a given extension and compiles them as a system command.
(->-) :: (OutputDirectory c, Extensions c, CompilePaths c, Command c) =>
          RunnerExit c
c ->- p = pathTransform' c (>->) c p

-- | Adds the given file path to the reference target of the given value.
(+>>) :: (OutputReferenceGet r, OutputReferenceSet r) =>
         FilePath -- ^ The file path to add.
         -> r     -- ^ The value to add the given file path to.
         -> r     -- ^ The value with the given file path added.
v +>> k = setReference (v : getReference k) k

-- | Adds the given file paths to the reference target of the given value.
(++>>) :: (OutputReferenceGet r, OutputReferenceSet r) =>
          [FilePath] -- ^ The file paths to add.
          -> r       -- ^ The value to add the given file paths to.
          -> r       -- ^ The value with the given file paths added.
v ++>> k = setReference (v ++ getReference k) k

-- | Adds the (potential) output target of the given value to the output target of the given value.
(>===>) :: (OutputDirectory o, OutputReferenceGet r, OutputReferenceSet r) =>
           o    -- ^ The value with an output target value to add.
           -> r -- ^ The value to add the output target to.
           -> r -- ^ The value after the output target has been added.
v >===> w = case outdir v of Nothing -> w
                             Just y -> y +>> w

-- | Adds the (potential) output target and output references of the given value to the output target of the given value.
(>=>=>) :: (OutputDirectory o, OutputReferenceGet o, OutputReferenceGet r, OutputReferenceSet r) =>
           o    -- ^ The value with an output target and output references to add.
           -> r -- ^ The value to add the output target and output references to.
           -> r -- ^ The value after the output target has been added.
v >=>=> w = v >===> (getReference v ++>> w)