Skip to content

Commit

Permalink
ref: Modify initConfig to pass a custom getLine
Browse files Browse the repository at this point in the history
  • Loading branch information
CristhianMotoche committed Feb 7, 2024
1 parent e8ec435 commit b344cd3
Show file tree
Hide file tree
Showing 5 changed files with 124 additions and 38 deletions.
2 changes: 1 addition & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -144,7 +144,7 @@ main = do
Maintenance _ ->
runHapCmd opts $ \C.Config{..} _ ->
Hap.deleteMaintenanceFile configDeployPath configMaintenanceDirectory configMaintenanceFileName
InitConfig -> Hap.initConfig getLine
InitConfig -> Hap.initConfig

runHapCmd :: Opts -> (C.Config -> C.ExecutionMode -> Hapistrano ()) -> IO ()
runHapCmd Opts{..} hapCmd = do
Expand Down
1 change: 1 addition & 0 deletions hapistrano.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -48,6 +48,7 @@ library
, System.Hapistrano.Commands
, System.Hapistrano.Config
, System.Hapistrano.Core
, System.Hapistrano.Internal
, System.Hapistrano.Types
, System.Hapistrano.Commands.Internal
, System.Hapistrano.Maintenance
Expand Down
30 changes: 27 additions & 3 deletions spec/System/Hapistrano/InitSpec.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,41 @@
{-# LANGUAGE LambdaCase #-}

module System.Hapistrano.InitSpec (spec) where

import Data.List (isInfixOf)

import Test.Hspec

import System.Directory (doesFileExist, getCurrentDirectory, withCurrentDirectory)
import System.FilePath ((</>))
import System.Hapistrano (initConfig)
import System.Hapistrano.Internal (initConfig')
import System.IO.Temp (withSystemTempDirectory)

getLine' :: String -> IO String
getLine' = return . go
where
go s
| "repo" `isInfixOf` s = show "git@github.com:stackbuilders/hapistrano.git"
| "revision" `isInfixOf` s = show "origin/master"
| "host" `isInfixOf` s = show "user@localhost.com"
| "port" `isInfixOf` s = "22"
| "restart Command" `isInfixOf` s = show "n"
| otherwise = show s

spec :: Spec
spec = do
spec =
describe "initConfig" $ do
it "should create a file when missing" $
withSystemTempDirectory "hapistrano-spec-initConfig-missing" $ \tempDir ->
withCurrentDirectory tempDir $ do
configFilePath <- (</> "hap.yml") <$> getCurrentDirectory
initConfig $ return ""
initConfig' $ const . return $ ""
doesFileExist configFilePath `shouldReturn` True

it "should create a file when missing" $
withSystemTempDirectory "hapistrano-spec-initConfig-missing" $ \tempDir ->
withCurrentDirectory tempDir $ do
configFilePath <- (</> "hap.yml") <$> getCurrentDirectory
initConfig' getLine'
content <- readFile configFilePath
content `shouldContain` "user@localhost.com"
70 changes: 36 additions & 34 deletions src/System/Hapistrano.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,8 @@ import Path.IO
import qualified System.Directory as Directory
import System.Exit (exitFailure)
import qualified System.FilePath as FilePath

import System.Hapistrano.Internal (initConfig')
import System.Hapistrano.Commands
import qualified System.Hapistrano.Config as HC
import System.Hapistrano.Config (BuildCommand (..), CopyThing (..),
Expand Down Expand Up @@ -271,40 +273,40 @@ playScriptLocally cmds =

-- | Create a file with an initial config file by getting information from the
-- user.
initConfig :: IO String -> IO ()
initConfig getLine' = do
configFilePath <- (FilePath.</> "hap.yml") <$> Directory.getCurrentDirectory
alreadyExisting <- Directory.doesFileExist configFilePath
when alreadyExisting $ do
T.hPutStrLn stderr "'hap.yml' already exists"
exitFailure
putStrLn "Creating 'hap.yml'"
defaults <- defaultInitTemplateConfig
let prompt :: Read a => T.Text -> a -> IO a
prompt title d = do
T.putStrLn $ title <> "?: "
x <- getLine'
return $
if null x
then d
else read x
prompt' :: Read a => T.Text -> (InitTemplateConfig -> T.Text) -> (InitTemplateConfig -> a) -> IO a
prompt' title f fd = prompt (title <> " (default: " <> f defaults <> ")") (fd defaults)

let yesNo :: a -> a -> T.Text -> a
yesNo t f x = if x == "y" then t else f

config <-
InitTemplateConfig
<$> prompt' "repo" repo repo
<*> prompt' "revision" revision revision
<*> prompt' "host" host host
<*> prompt' "port" (T.pack . show . port) port
<*> return (buildScript defaults)
<*> fmap (yesNo (restartCommand defaults) Nothing) (prompt' "Include restart command" (const "Y/n") (const "y"))

Yaml.encodeFile configFilePath config
putStrLn $ "Configuration written at " <> configFilePath
initConfig :: IO ()
initConfig = initConfig' (const getLine)
-- configFilePath <- (FilePath.</> "hap.yml") <$> Directory.getCurrentDirectory
-- alreadyExisting <- Directory.doesFileExist configFilePath
-- when alreadyExisting $ do
-- T.hPutStrLn stderr "'hap.yml' already exists"
-- exitFailure
-- putStrLn "Creating 'hap.yml'"
-- defaults <- defaultInitTemplateConfig
-- let prompt :: Read a => T.Text -> a -> IO a
-- prompt title d = do
-- T.putStrLn $ title <> "?: "
-- x <- getLine'
-- return $
-- if null x
-- then d
-- else read x
-- prompt' :: Read a => T.Text -> (InitTemplateConfig -> T.Text) -> (InitTemplateConfig -> a) -> IO a
-- prompt' title f fd = prompt (title <> " (default: " <> f defaults <> ")") (fd defaults)

-- let yesNo :: a -> a -> T.Text -> a
-- yesNo t f x = if x == "y" then t else f

-- config <-
-- InitTemplateConfig
-- <$> prompt' "repo" repo repo
-- <*> prompt' "revision" revision revision
-- <*> prompt' "host" host host
-- <*> prompt' "port" (T.pack . show . port) port
-- <*> return (buildScript defaults)
-- <*> fmap (yesNo (restartCommand defaults) Nothing) (prompt' "Include restart command" (const "Y/n") (const "y"))

-- Yaml.encodeFile configFilePath config
-- putStrLn $ "Configuration written at " <> configFilePath

----------------------------------------------------------------------------
-- Helpers
Expand Down
59 changes: 59 additions & 0 deletions src/System/Hapistrano/Internal.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

module System.Hapistrano.Internal (initConfig') where

import Control.Monad (when)
import Control.Monad.IO.Class (MonadIO(..))

import qualified Data.Text as T
import qualified Data.Text.IO as T

import qualified Data.Yaml as Yaml

import System.IO (stderr)
import System.Exit (exitFailure)
import qualified System.FilePath as FilePath
import qualified System.Directory as Directory

import System.Hapistrano.Types (InitTemplateConfig(..), defaultInitTemplateConfig)


-- | Create a file with an initial config file by getting information from the
-- user.
initConfig' :: forall m. MonadIO m => (String -> m String) -> m ()
initConfig' getLine' = do
configFilePath <- (FilePath.</> "hap.yml") <$> liftIO Directory.getCurrentDirectory
alreadyExisting <- liftIO $ Directory.doesFileExist configFilePath
when alreadyExisting $ liftIO $ do
T.hPutStrLn stderr "'hap.yml' already exists"
exitFailure
liftIO $ putStrLn "Creating 'hap.yml'"
defaults <- liftIO defaultInitTemplateConfig
let prompt :: Read a => String -> a -> m a
prompt title d = do
liftIO $ T.putStrLn $ T.pack $ title <> "?: "
x <- getLine' title
liftIO $ putStrLn $ "Value of X: " <> x
return $
if null x
then d
else read x
prompt' :: Read a => String -> (InitTemplateConfig -> T.Text) -> (InitTemplateConfig -> a) -> m a
prompt' title f fd = prompt title (fd defaults)

let yesNo :: a -> a -> T.Text -> a
yesNo t f x = if x == "y" then t else f

config <-
InitTemplateConfig
<$> prompt' "repo" repo repo
<*> prompt' "revision" revision revision
<*> prompt' "host" host host
<*> prompt' "port" (T.pack . show . port) port
<*> return (buildScript defaults)
<*> fmap (yesNo (restartCommand defaults) Nothing) (prompt' "Include restart command" (const "Y/n") (const "y"))

liftIO $ do
Yaml.encodeFile configFilePath config
putStrLn $ "Configuration written at " <> configFilePath

0 comments on commit b344cd3

Please sign in to comment.