gdritter repos bb8 / master src / BB8 / Queue.hs
master

Tree @master (Download .tar.gz)

Queue.hs @masterraw · history · blame

module BB8.Queue where

import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified System.Directory as Sys
import           System.FilePath (FilePath, (</>))

import qualified BB8.Common as BB8
import           BB8.Jobs
import           BB8.Types


-- * Running Jobs

-- | The working directory for a job
workingDirectory :: Config -> JobID -> FilePath
workingDirectory conf ident =
  configWorkDirectory conf </> show ident ++ ".work"

-- | The build trace file for a job
buildLogFile :: Config -> JobID -> FilePath
buildLogFile conf ident =
  configWorkDirectory conf </> show ident ++ ".work" </> "build-log"

-- | The execution trace file for a job
executionLogFile :: Config -> JobID -> FilePath
executionLogFile conf ident =
  configWorkDirectory conf </> show ident ++ ".work" </> "run-log"

-- | The docker image name for a job
dockerImageName :: JobID -> String
dockerImageName ident =
  "img-" ++ show ident

getTraceData :: Config -> Integer -> IO JobTrace
getTraceData conf ident = do
  buildExists <- Sys.doesFileExist (buildLogFile conf ident)
  buildTrc <- if buildExists
                then Just `fmap` BS.readFile (buildLogFile conf ident)
                else return Nothing
  runExists <- Sys.doesFileExist (buildLogFile conf ident)
  runTrc <- if runExists
              then Just `fmap` BS.readFile (buildLogFile conf ident)
              else return Nothing
  return (JobTrace buildTrc runTrc)

-- | Run a single step of a job, returning a representation of the
-- next step of the job
runState :: Config -> Trace -> Job -> IO Job
runState conf trace job = case jobState job of

  FetchingState -> do
    -- this might not make sense any more, but we should still use it
    -- to validate that the provided job information is correct
    BB8.debug "fetching"
    return job { jobState = BuildingState }

  BuildingState -> do
    BB8.debug "building"
    let ident = jobID job
    -- let's go to the job's working directory, making sure it exists
    let dir = workingDirectory conf ident
    let image = dockerImageName ident
    let buildLog = buildLogFile conf ident
    Sys.createDirectoryIfMissing True dir

    -- and then run a docker build process
    result <- traceCommand
                "docker" ["build", "-t", image, "."] (Just dir) trace

    BB8.debug ("got result: " ++ show result)
    -- and write the build log in the appropriate place
    BSL.writeFile buildLog (buildTraceOutput (resultTrace result))

    case resultCode result of
      0 -> return job { jobState = RunningState }
      _ -> return job { jobState = FailedState }

  RunningState -> do
    BB8.debug "running"
    -- let's go to the job's working directory, making sure it exists
    let ident  = jobID job
    let dir    = workingDirectory conf ident
    let image  = dockerImageName ident
    let runLog = executionLogFile conf ident
    Sys.createDirectoryIfMissing True dir

    -- and then run a docker build process
    result <- traceCommand
                "docker" ["run", image] (Just dir) trace

    BB8.debug ("got result: " ++ show result)
    -- and write the build log in the appropriate place
    BSL.writeFile runLog (buildTraceOutput (resultTrace result))

    case resultCode result of
      0 -> return job { jobState = FinishingState }
      _ -> return job { jobState = FailedState }

  FinishingState -> do
    BB8.debug "finishing"
    return job { jobState = DoneState }

  _             -> return job