diff --git a/dockmaster.cabal b/dockmaster.cabal index 6ac5630..8112c61 100644 --- a/dockmaster.cabal +++ b/dockmaster.cabal @@ -20,11 +20,10 @@ description: library hs-source-dirs: src exposed-modules: Dockmaster - , Dockmaster.Types - , Dockmaster.Config.Types - other-modules: Dockmaster.Locator , Dockmaster.Parser , Dockmaster.Config.Parser + other-modules: Dockmaster.Types + , Dockmaster.Config.Types , Dockmaster.Utils build-depends: base >= 4.7 && < 5 , yaml @@ -34,6 +33,7 @@ library , text , bytestring , regex-posix + , system-filepath >= 0.4.7 && < 0.5 default-language: Haskell2010 executable dm diff --git a/src/Dockmaster.hs b/src/Dockmaster.hs index 99e30e6..615210b 100644 --- a/src/Dockmaster.hs +++ b/src/Dockmaster.hs @@ -5,14 +5,14 @@ module Dockmaster ( dm ) where +-- Base modules import Data.Either import Data.Monoid ((<>)) import Data.Maybe -- Local modules -import Dockmaster.Locator import Dockmaster.Parser -import Dockmaster.Types +import Dockmaster.Config.Parser -- External modules import Shelly @@ -27,6 +27,7 @@ type DCCommand = T.Text -- See usage docs for more info. Tries to find a dockmaster.yml file based on -- the initial path argument -- TODO monad >>= and >> the shit out of this to remove the casing structure +-- TODO Possibly remove Either return types & just error out whenever -- REMEMBER you can do `when weAreDone exitSuccess` as control flow in do statement dm :: FilePath -> DCCommand -> [T.Text] -> Sh () dm path command args = do diff --git a/src/Dockmaster/Config/Parser.hs b/src/Dockmaster/Config/Parser.hs index b80e4c4..77821c0 100644 --- a/src/Dockmaster/Config/Parser.hs +++ b/src/Dockmaster/Config/Parser.hs @@ -2,8 +2,17 @@ {-# LANGUAGE ExtendedDefaultRules #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} module Dockmaster.Config.Parser - ( config + ( + -- * Getting global config + config , baseConfig + + -- * Resolving relative paths + , getWorkDir + , getWorkDir' + + -- * Re-exported for convenience + , module Dockmaster.Config.Types ) where -- Local modules @@ -16,13 +25,15 @@ import qualified Data.ByteString as BS import Shelly import Prelude hiding (FilePath) import qualified Data.Text as T +import qualified Filesystem.Path.CurrentOS as FP import Data.Monoid ((<>), mconcat, First(..)) import Control.Monad (liftM) default (T.Text) -- | Get global dockmaster config --- If config.yml fails to parse, returns Left error --- If config.yml is not found, returns Right baseConfig (default configuration) +-- +-- If config.yml fails to parse, returns Left error. +-- If config.yml is not found, returns Right baseConfig (default configuration). config :: Sh (Either T.Text Config) config = do mPath <- resolvePath @@ -33,10 +44,15 @@ config = do return $ eitherWrap T.pack id (decodeEither contents :: Either String Config) +-- | Get base config options +baseConfig :: Config +baseConfig = Config { dmcPaths = [] } + -- | Resolves path to dockmaster config.yml in the following order of precedence: --- - DOCKMASTER_CONFIG environment variable --- - $HOME/.dockmaster/config.yml --- - /etc/dockmaster/config.yml +-- +-- (1) DOCKMASTER_CONFIG environment variable +-- (2) $HOME/.dockmaster/config.yml +-- (3) /etc/dockmaster/config.yml resolvePath :: Sh (Maybe FilePath) resolvePath = do envPathT <- get_env "DOCKMASTER_CONFIG" @@ -45,6 +61,50 @@ resolvePath = do return $ getFirst . mconcat $ map First [envPathT >>= (return . fromText), homePath, etcPath] --- | Get base config options -baseConfig :: Config -baseConfig = Config { dmcPaths = [] } +-- | Resolve the appropriate dockmaster workdir. +-- +-- For example, if @$CWD/dockmaster.yml@ exists, then +-- >>> getWorkDir "." +-- Right "." +-- +-- If @$CWD/dockmaster.yml@ does /not/ exist, then +-- >>> getWorkDir "." +-- Left "dockmaster.yml file not found" +-- +-- This function will also try to resolve relative paths against the 'dmcPath' +-- composition listing directories, if any are specified by global config. +-- For example, if: +-- +-- (1) @$HOME/git@ is a PATH specified in global config.yml +-- (2) @$HOME/git/deploybot/dockmaster.yml@ exists +-- (3) @$CWD/deploybot/dockmaster.yml@ does /not/ exist, then +-- >>> getWorkDir "deploybot" +-- Right "$HOME/git/deploybot" +getWorkDir :: FilePath -> Sh (Either T.Text FilePath) +getWorkDir p = undefined + +-- | Same thing as 'getWorkDir' but uses a 'Config' argument instead of +-- resolving one. +getWorkDir' :: Config -> FilePath -> Sh (Either T.Text FilePath) +getWorkDir' cfg p = do + -- If absolute path is given, it is the only one attempted + mPath <- getFirst <$> if FP.absolute p + then tryPath p + else mconcat <$> mapM tryPath (map ( p) $ "." : dmcPaths cfg) + + return $ maybe workDirNotFound Right mPath + +-- | Check if directory @dir@ contains a @dockmaster.yml@ file +-- If it does, return @First dir@, otherwise Nothing +-- Using the @First@ monoid so we can have precedence for composition listings +tryPath :: FilePath -> Sh (First FilePath) +tryPath dir = do + found <- test_e (dir "dockmaster.yml") + return . First $ if found + then Just dir + else Nothing + + +-- | Just a small abstraction to keep error message on its own +workDirNotFound :: Either T.Text b +workDirNotFound = Left "dockmaster.yml file not found" diff --git a/src/Dockmaster/Locator.hs b/src/Dockmaster/Locator.hs deleted file mode 100644 index 12821d3..0000000 --- a/src/Dockmaster/Locator.hs +++ /dev/null @@ -1,32 +0,0 @@ -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ExtendedDefaultRules #-} -{-# OPTIONS_GHC -fno-warn-type-defaults #-} -module Dockmaster.Locator - ( workDirExec - , getWorkDir - , cdWorkDir - ) where - -import Shelly -import Prelude hiding (FilePath) -import qualified Data.Text as T -default (T.Text) - --- | Resolve the appropriate docker-compose workdir (based on path arg) --- TODO This needs to search paths in ~/.dockmaster/config !! - -- aggregate searched dirs for verbosity msg ? -getWorkDir :: FilePath -> Sh (Either T.Text FilePath) -getWorkDir p = do - found <- test_e (p "dockmaster.yml") - return $ if found - then Right p - else Left "dockmaster.yml file not found" - --- | Execute action in workdir (does not affect cwd outside of action) -workDirExec :: FilePath -> Sh a -> Sh (Either T.Text a) -workDirExec = undefined - --- | Cd into workdir --- TODO check if cd retains context when run externally (i.e. do I need to pass action here) -cdWorkDir :: FilePath -> Sh (Either T.Text (Sh ())) -cdWorkDir = undefined diff --git a/src/Dockmaster/Parser.hs b/src/Dockmaster/Parser.hs index 0d55373..dac1c97 100644 --- a/src/Dockmaster/Parser.hs +++ b/src/Dockmaster/Parser.hs @@ -2,12 +2,14 @@ {-# LANGUAGE ExtendedDefaultRules #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} module Dockmaster.Parser - ( - dockmasterYml + ( dockmasterYml + -- * Re-exported for convenience + , module Dockmaster.Types ) where -- Local modules import Dockmaster.Utils (eitherWrap) +import Dockmaster.Config.Parser -- External modules import Data.Yaml @@ -19,6 +21,9 @@ import Prelude hiding (FilePath) import qualified Data.Text as T default (T.Text) +-- | Parse $CWD/dockmaster.yml +-- +-- Note this assumes we are already in the correct dockmaster workdir dockmasterYml :: Sh (Either T.Text Dockmaster) dockmasterYml = do contents <- readBinary "dockmaster.yml" diff --git a/test/Spec.hs b/test/Spec.hs index 9cdc887..9399ced 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -1,12 +1,14 @@ module Main where import Data.Yaml -import Dockmaster.Types +import Dockmaster.Parser import qualified Data.ByteString as BS import Data.Maybe import System.Exit import System.Directory +-- TODO test Dockmaster.Parser.dockmasterYml instead of using this parse function + parseDockmasterYml :: FilePath -> IO Bool parseDockmasterYml "." = return True parseDockmasterYml ".." = return True