{-# LANGUAGE RecordWildCards #-}
module Devops.Cli (
Method (..), Concurrency (..)
, applyMethod
, simpleMain
, SelfPath
, ForestOptimization
, App (..)
, appMain
, appMethod
, methodArg
, getDependenciesOnly
, graphize
, opClosureFromB64
, opClosureToB64
) where
import Control.Distributed.Closure (Closure, unclosure)
import Control.Monad.Identity (runIdentity)
import qualified Data.Binary as Binary
import qualified Data.ByteString.Base64.Lazy as B64
import Data.ByteString.Lazy (ByteString)
import Data.Tree (Forest)
import Data.Typeable (Typeable)
import DepTrack (GraphData, buildGraph, evalDepForest1)
import Prelude hiding (readFile)
import System.Environment (getArgs, getExecutablePath)
import Devops.Actions (checkStatuses, concurrentTurndown, concurrentTurnup, concurrentUpkeep, defaultDotify,
display, dotifyWithStatuses, listUniqNodes, sequentialTurnDown, sequentialTurnup)
import Devops.Base (DevOp, OpUniqueId, PreOp, preOpUniqueId, getDependenciesOnly)
data Method =
TurnUp Concurrency
| TurnDown Concurrency
| Upkeep
| Print
| Dot
| CheckDot
| List
data Concurrency = Concurrently | Sequentially
applyMethod :: [(Forest PreOp -> Forest PreOp)]
-> Forest PreOp
-> Method
-> IO ()
applyMethod transformations originalForest meth = do
let forest = foldl (.) id transformations originalForest
let graph = graphize forest
case meth of
TurnUp Concurrently -> concurrentTurnup graph
TurnUp Sequentially -> sequentialTurnup graph
TurnDown Concurrently -> concurrentTurndown graph
TurnDown Sequentially -> sequentialTurnDown graph
Upkeep -> concurrentUpkeep graph
Print -> display forest
Dot -> putStrLn . defaultDotify $ graph
CheckDot -> putStrLn . dotifyWithStatuses graph =<< checkStatuses graph
List -> listUniqNodes forest
simpleMain :: DevOp env a
-> [(Forest PreOp -> Forest PreOp)]
-> [String]
-> env
-> IO ()
simpleMain devop optimizations args env = go args
where
forest = getDependenciesOnly env devop
call m = applyMethod optimizations forest m
go ("up":_) = call $ TurnUp Concurrently
go ("up-seq":_) = call $ TurnUp Sequentially
go ("down":_) = call $ TurnDown Concurrently
go ("down-seq":_) = call $ TurnDown Sequentially
go ("upkeep":_) = call Upkeep
go ("print":_) = call Print
go ("dot":_) = call Dot
go ("check-dot":_) = call CheckDot
go ("list":_) = call List
go _ = putStrLn usage
usage = unlines [ "deptrack-devops default main:"
, " Available arguments:"
, " up, down, upkeep, print, dot, check-dot, list"
]
type SelfPath = FilePath
type ForestOptimization = Forest PreOp -> Forest PreOp
data App env node = App {
_parseArgs :: [String] -> (node, Method)
, _revParse :: node -> Method -> [String]
, _target :: node -> SelfPath -> (node -> Method -> [String]) -> DevOp env ()
, _opts :: [ForestOptimization]
, _retrieveEnv :: node -> IO env
}
appMain :: App env a -> IO ()
appMain App{..} = do
self <- getExecutablePath
args <- getArgs
let (node, meth) = _parseArgs args
env <- _retrieveEnv node
let forest = getDependenciesOnly env $ _target node self _revParse
applyMethod _opts forest meth
appMethod :: String -> Method
appMethod "up" = TurnUp Concurrently
appMethod "up-seq" = TurnUp Sequentially
appMethod "down" = TurnDown Concurrently
appMethod "down-seq" = TurnDown Sequentially
appMethod "upkeep" = Upkeep
appMethod "print" = Print
appMethod "dot" = Dot
appMethod "check-dot" = CheckDot
appMethod "list" = List
appMethod str = error $ "unparsed appMethod: " ++ str
methodArg :: Method -> String
methodArg (TurnUp Concurrently) = "up"
methodArg (TurnUp Sequentially) = "up-seq"
methodArg (TurnDown Concurrently) = "down"
methodArg (TurnDown Sequentially) = "down-seq"
methodArg Upkeep = "upkeep"
methodArg Print = "print"
methodArg Dot = "dot"
methodArg CheckDot = "check-dot"
methodArg List = "list"
graphize :: Forest PreOp -> GraphData PreOp OpUniqueId
graphize forest = buildGraph preOpUniqueId forest
opClosureFromB64 :: (Typeable env, Typeable a) => ByteString -> Closure (DevOp env a)
opClosureFromB64 b64 = do
let bstr = B64.decode b64
let encodedClosure = either (error "invalid base64") id bstr
Binary.decode encodedClosure
opClosureToB64 :: (Typeable env, Typeable a) => Closure (DevOp env a) -> ByteString
opClosureToB64 clo =
B64.encode $ Binary.encode clo