module System.JBI.Commands.BuildTool where
import System.JBI.Commands.Tool
import System.JBI.Environment
import System.JBI.Tagged
import Control.Applicative (liftA2)
import Control.Exception (SomeException(SomeException), handle)
import Control.Monad (filterM, forM)
import Data.Aeson (ToJSON(toJSON))
import Data.List (span)
import Data.Maybe (isJust)
import Data.String (IsString(..))
import GHC.Generics (Generic)
import System.Directory (doesFileExist, getCurrentDirectory, listDirectory)
import System.Exit (ExitCode)
import System.FilePath (dropTrailingPathSeparator, isDrive, takeDirectory,
(</>))
class (Tool bt) => BuildTool bt where
canUseCommand :: GlobalEnv -> Installed bt -> IO Bool
canUseCommand _ _ = return True
commandProjectRoot :: Tagged bt CommandPath -> IO (Maybe (Tagged bt ProjectRoot))
hasBuildArtifacts :: Tagged bt ProjectRoot -> IO Bool
commandPrepare :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode
commandTargets :: Tagged bt CommandPath -> IO [Tagged bt ProjectTarget]
commandBuild :: GlobalEnv -> Tagged bt CommandPath -> Maybe (Tagged bt ProjectTarget)
-> IO ExitCode
commandRepl :: GlobalEnv -> Tagged bt CommandPath -> Maybe (Tagged bt ProjectTarget)
-> IO ExitCode
commandClean :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode
commandTest :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode
commandBench :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode
commandExec :: GlobalEnv -> Tagged bt CommandPath -> String -> Args -> IO ExitCode
commandRun :: GlobalEnv -> Tagged bt CommandPath -> Tagged bt ProjectTarget
-> Args -> IO ExitCode
commandUpdate :: GlobalEnv -> Tagged bt CommandPath -> IO ExitCode
class (BuildTool bt) => NamedTool bt where
prettyName :: proxy bt -> String
prettyName = nameOfCommand . proxy commandName
data ToolInformation bt = ToolInformation
{ tool :: !String
, information :: !(Maybe (BuildUsage bt))
} deriving (Eq, Show, Read, Generic, ToJSON)
commandToolInformation :: (NamedTool bt)
=> GlobalEnv -> proxy bt
-> IO (ToolInformation bt)
commandToolInformation env pr =
ToolInformation (prettyName pr) <$> commandBuildUsage env
data BuildUsage bt = BuildUsage
{ installation :: !(Installed bt)
, usable :: !Bool
, project :: !(Maybe (BuildProject bt))
} deriving (Eq, Show, Read, Generic, ToJSON)
data BuildProject bt = BuildProject
{ projectRoot :: !(Tagged bt ProjectRoot)
, artifactsPresent :: !Bool
} deriving (Eq, Show, Read, Generic, ToJSON)
commandBuildUsage :: (BuildTool bt)
=> GlobalEnv
-> IO (Maybe (BuildUsage bt))
commandBuildUsage env = do
mInst <- commandInformation
forM mInst $ \inst ->
BuildUsage inst <$> canUseCommand env inst
<*> commandBuildProject (path inst)
commandBuildProject :: (BuildTool bt) => Tagged bt CommandPath
-> IO (Maybe (BuildProject bt))
commandBuildProject cmd = do
mroot <- commandProjectRoot cmd
forM mroot $ \root ->
BuildProject root <$> hasBuildArtifacts root
canUseBuildTool :: Maybe (BuildUsage bt) -> Bool
canUseBuildTool = maybe False (liftA2 (&&) usable (isJust . project))
newtype ProjectRoot = ProjectRoot { rootPath :: FilePath }
deriving (Eq, Ord, Show, Read)
instance IsString ProjectRoot where
fromString = ProjectRoot
instance ToJSON ProjectRoot where
toJSON = toJSON . rootPath
newtype ProjectTarget = ProjectTarget { projectTarget :: String }
deriving (Eq, Ord, Show, Read)
instance IsString ProjectTarget where
fromString = ProjectTarget
componentName :: Tagged bt ProjectTarget -> String
componentName = safeLast . splitOn ':' . stripTag
safeLast :: [[a]] -> [a]
safeLast [] = []
safeLast ass = last ass
splitOn :: (Eq a) => a -> [a] -> [[a]]
splitOn sep = go
where
go [] = []
go as = case span (/= sep) as of
(seg, []) -> seg : []
(seg, _:as') -> seg : go as'
tryIO :: IO (Maybe a) -> IO (Maybe a)
tryIO = handle (\SomeException{} -> return Nothing)
recurseUpFindFile :: (FilePath -> Bool) -> IO (Maybe FilePath)
recurseUpFindFile p = tryIO $ go . dropTrailingPathSeparator =<< getCurrentDirectory
where
go dir = do cntns <- listDirectory dir
files <- filterM (doesFileExist . (dir </>)) cntns
if any p files
then return (Just dir)
else if isDrive dir
then return Nothing
else go (takeDirectory dir)