{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.Distributed.Utils
( parseNetConfig
, log
, logSucc
, logWarn
, listDeps
, getBestPid
, encodePath
, decodePath
, timeIt
, runStackBuild
, runStackBuildT
) where
import Network.Distributed.Types
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.ByteString (ByteString)
import qualified Data.Configurator as C
import Data.List (intersect)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Filesystem.Path (FilePath)
import Filesystem.Path.CurrentOS (fromText, toText)
import Prelude hiding (FilePath, log)
import System.Clock
import System.Console.ANSI
import System.Directory (getCurrentDirectory)
import System.Exit (ExitCode (..))
import System.IO (BufferMode (..), hGetContents,
hSetBuffering)
import System.Process
parseNetConfig :: IO NetworkConfig
parseNetConfig = do
cfg <- C.load [C.Required "network.config"]
NetworkConfig <$> C.require cfg "net.host" <*> C.require cfg "net.port"
log :: MonadIO m => String -> m ()
log = log' [[SetColor Foreground Vivid Black]]
logSucc :: MonadIO m => String -> m ()
logSucc = log' [[SetColor Foreground Vivid Green]]
logWarn :: MonadIO m => String -> m ()
logWarn = log' [[SetColor Foreground Dull Red]]
log' :: MonadIO m => [[SGR]] -> String -> m ()
log' styles msg =
liftIO $ do
mapM_ setSGR styles
putStrLn msg
setSGR [Reset]
listDeps :: MonadIO m => m [String]
listDeps =
liftIO $ do
path <- getCurrentDirectory
(_, Just hStdout, _, p) <-
System.Process.createProcess
(proc "stack" ["list-dependencies", "--stack-root", path ++ "/root"])
{std_out = CreatePipe, std_err = Inherit}
hSetBuffering hStdout NoBuffering
exit_code <- waitForProcess p
case exit_code of
ExitSuccess -> lines <$> hGetContents hStdout
ExitFailure _ -> logWarn "Error calculating dependencies" >> pure []
getBestPid ::
[(Deps, Node)]
-> Deps
-> (Maybe Node, Int)
-> Maybe Node
getBestPid [] _ best = fst best
getBestPid ((curDeps, curPid):xs) cmpDeps curBest
| curLen > snd curBest = recurse (Just curPid, curLen)
| otherwise = recurse curBest
where
curLen = length (curDeps `intersect` cmpDeps)
recurse = getBestPid xs cmpDeps
fromEither :: Either a a -> a
fromEither (Right a) = a
fromEither (Left a) = a
encodePath :: FilePath -> ByteString
encodePath = encodeUtf8 . fromEither . toText
decodePath :: ByteString -> FilePath
decodePath = fromText . decodeUtf8
runStackBuildT :: IO ()
runStackBuildT = timeIt runStackBuild
runStackBuild :: IO ()
runStackBuild = do
log "Build invoked..."
path <- getCurrentDirectory
callProcess "stack" ["build", "--stack-root", path ++ "/root"]
logSucc "Build Succesfully Completed."
timeIt ::
MonadIO m
=> m a
-> m a
timeIt action = do
start <- liftIO $ getTime Monotonic
res <- action
end <- liftIO $ getTime Monotonic
logSucc $ "Time: " ++ show (sec $ diffTimeSpec start end) ++ " seconds"
pure res