Skip to content

Commit

Permalink
Merge pull request #21 from bjaress/optional-auth
Browse files Browse the repository at this point in the history
Make username and password optional.
  • Loading branch information
dogonthehorizon authored Dec 7, 2016
2 parents 5adcaf8 + fd648c2 commit 7704791
Show file tree
Hide file tree
Showing 4 changed files with 30 additions and 22 deletions.
17 changes: 11 additions & 6 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -72,7 +72,7 @@ bindOption a failMessage =
return a

-- | Execute the given command with the given username and jenkins instance.
executeCommand :: Command -> User -> JenkinsInstance -> IO ()
executeCommand :: Command -> Maybe User -> JenkinsInstance -> IO ()
executeCommand cmd usr jenkinsInstance =
case cmd of
Info jobPaths ->
Expand All @@ -96,14 +96,19 @@ run (Options username jenkinsInstance profile cmd) = do
jenkins <- bindOption (jenkinsInstance <|> cfgJenkins)
(Just "Could not determine the Jenkins instance to use.")

shouldStorePassword <- fromMaybe False <$> C.getStorePassword cfg
cfgUser <- C.getUsername cfg
usr <- bindOption (username <|> cfgUser)
(Just "Could not determine username to use.")
usr <- userWithPassword (username <|> cfgUser)
(selectPassword shouldStorePassword profileName)

shouldStorePassword <- fromMaybe False <$> C.getStorePassword cfg
pwd <- selectPassword shouldStorePassword profileName usr
executeCommand cmd usr jenkins

executeCommand cmd (User usr pwd) jenkins
-- There is probably a better way to do this
userWithPassword :: Maybe Username -> (Username -> IO Password) -> IO (Maybe User)
userWithPassword Nothing _ = return Nothing
userWithPassword (Just username) getPwd = do
password <- getPwd username
return $ Just (User username password)

main :: IO ()
main = run =<< execParser (parseOptions `withInfo` "")
13 changes: 7 additions & 6 deletions src/Bartlett/Actions/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,8 @@ import Bartlett.Network (execRequest)
import Bartlett.Types
import qualified Bartlett.Util as BU

import Control.Lens ((?~), (^.), (&))
import Control.Lens (set, (^.), (&))
import Data.Maybe (Maybe)
import Data.Aeson.Encode.Pretty (encodePretty)
import qualified Data.ByteString.Lazy.Char8 as BL
import Network.Wreq (Options, responseStatus, auth)
Expand All @@ -34,15 +35,15 @@ consBuildType (Just jobParameters) =

-- | Trigger a build for the given job with optional build parameters.
postBuild ::
BasicAuthUser b => b -- ^ The user to authenticate with.
-> JenkinsInstance -- ^ The Jenkins instance to make requests against.
-> JobPath -- ^ The job to trigger a build against.
-> Maybe JobParameters -- ^ Optional set of job parameters to trigger with.
BasicAuthUser b => Maybe b -- ^ The user to authenticate with.
-> JenkinsInstance -- ^ The Jenkins instance to make requests against.
-> JobPath -- ^ The job to trigger a build against.
-> Maybe JobParameters -- ^ Optional set of job parameters to trigger with.
-> IO ()
postBuild user base path parameters = do
resp <- execRequest Post reqOpts reqUri Nothing
BL.putStrLn . encodePretty . BU.toResponseStatus $
resp ^. responseStatus
where (suffix, buildOpts) = consBuildType parameters
reqOpts = buildOpts & auth ?~ getBasicAuth user
reqOpts = buildOpts & set auth (getBasicAuth <$> user)
reqUri = BU.mkUrl base path suffix
11 changes: 6 additions & 5 deletions src/Bartlett/Actions/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,8 @@ import Bartlett.Network (execRequest)
import Bartlett.Types
import Bartlett.Util (toResponseStatus, mkUrl)

import Control.Lens ((^.), (?~), (&))
import Control.Lens (set, (^.), (&))
import Data.Maybe (Maybe)
import Data.Aeson.Encode.Pretty (encodePretty)
import qualified Data.ByteString.Lazy.Char8 as BL
import Network.Wreq (responseStatus, responseBody, defaults, auth)
Expand All @@ -26,18 +27,18 @@ configUri base path =

-- | Retrieve the XML configuration for the given job.
getConfig :: BasicAuthUser a =>
a -- The user to authenticate with.
Maybe a -- The user to authenticate with.
-> JenkinsInstance -- The Jenkins instance to interact with.
-> JobPath -- The Job for the given Jenkins instance to interact with.
-> IO () -- The XML configuration for the given job.
getConfig user base path = do
resp <- execRequest Get reqOpts (configUri base path) Nothing
BL.putStrLn $ resp ^. responseBody
where reqOpts = defaults & auth ?~ getBasicAuth user
where reqOpts = defaults & set auth (getBasicAuth <$> user)

-- | Update the XML configuration for the given job.
updateConfig :: BasicAuthUser a =>
a -- The user to authenticate with.
Maybe a -- The user to authenticate with.
-> JenkinsInstance -- The Jenkins instance to interact with.
-> JobPath -- The Job for the given Jenkins instance to interact with.
-> ConfigPath -- Path to the XML configuration to upload to Jenkins.
Expand All @@ -46,4 +47,4 @@ updateConfig user base path configPath = do
configFile <- BL.readFile configPath
resp <- execRequest Post reqOpts (configUri base path) (Just configFile)
BL.putStrLn . encodePretty . toResponseStatus $ resp ^. responseStatus
where reqOpts = defaults & auth ?~ getBasicAuth user
where reqOpts = defaults & set auth (getBasicAuth <$> user)
11 changes: 6 additions & 5 deletions src/Bartlett/Actions/Info.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,8 @@ import Bartlett.Network (execRequest)
import Bartlett.Types
import Bartlett.Util (toPrettyJson, mkUrl)

import Control.Lens ((^.), (?~), (&))
import Control.Lens (set, (^.), (&))
import Data.Maybe (Maybe)
import qualified Data.ByteString.Lazy.Char8 as BL
import Network.Wreq (responseBody, defaults, auth)

Expand All @@ -27,14 +28,14 @@ import Network.Wreq (responseBody, defaults, auth)
-- 'JenkinsInstance'. If not protocol is specified it will attempt to contact
-- Jenkins over SSL.
getInfo ::
BasicAuthUser b => b -- ^ The user to authenticate with.
-> JenkinsInstance -- ^ The Jenkins instance to authenticate against.
-> [JobPath] -- ^ The jobs to get information from.
BasicAuthUser b => Maybe b -- ^ The user to authenticate with.
-> JenkinsInstance -- ^ The Jenkins instance to authenticate against.
-> [JobPath] -- ^ The jobs to get information from.
-> IO ()
getInfo user base [] = return ()
getInfo user base (path:paths) = do
resp <- execRequest Get reqOpts reqUri Nothing
BL.putStrLn . toPrettyJson $ resp ^. responseBody
getInfo user base paths
where reqOpts = defaults & auth ?~ getBasicAuth user
where reqOpts = defaults & set auth (getBasicAuth <$> user)
reqUri = mkUrl base path "/api/json"

0 comments on commit 7704791

Please sign in to comment.