-- Copyright (C) 2011 Robert Helgesson -- -- This program is free software: you can redistribute it and/or -- modify it under the terms of the GNU General Public License as -- published by the Free Software Foundation, either version 3 of the -- License, or (at your option) any later version. -- -- This program is distributed in the hope that it will be useful, but -- WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU -- General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see -- . module Main (main) where import Paths_pwstore_cli (version) import Control.Monad (when, unless) import Crypto.PasswordStore ( genSaltIO , makeSalt , makePasswordSalt , isPasswordFormatValid , verifyPassword , strengthenPassword ) import Data.Text (Text) import Data.ByteString (ByteString) import qualified Data.Text as T import qualified Data.Text.Encoding as T import qualified Data.Text.IO as T import Data.Version (showVersion) import System.Console.CmdArgs import System.Environment (getProgName) import System.Exit (exitFailure) import System.IO (stdin, stdout, hFlush, hIsTerminalDevice, hSetEcho) -- | The modes of operations supported by this program. data Modes = Generate { strength :: Int , salt :: Maybe String } | Verify { hash :: String } | Strengthen { hash :: String , strength :: Int } deriving (Show, Data, Typeable) -- | Build the parser for the generator mode options. optGen :: Modes optGen = Generate { strength = 12 &= help "Strength value, default is 12" , salt = Nothing &= help "Hash salt, a random salt is used if missing" &= typ "SALT" &= explicit &= name "salt" } &= auto &= help "Generates a password hash. The password will be read from\ \ standard input. Note, passwords and salts will be\ \ converted to UTF-8 before hashing." -- | Build the parser for the verify mode options. optVerify :: Modes optVerify = Verify { hash = def &= typ "HASH" &= argPos 0 } &= help "Verify a given hash against a password." -- | Build the parser for the strengthen mode options. optStrengthen :: Modes optStrengthen = Strengthen { strength = 12 &= help "The new hash strength" , hash = def &= typ "HASH" &= argPos 0 } &= help "Strengthens the given hash." -- | Command line options for the pwstore command. optAll :: String -> Modes optAll progname = modes [optGen, optVerify, optStrengthen] &= program progname &= summary (progname ++ " " ++ showVersion version) &= help "The program provides a simple command line interface\ \ to Peter Scott's pwstore library." -- | Prompts without echoing the response. silentPrompt :: String -> IO Text silentPrompt p = do putStr p hFlush stdout hSetEcho stdin False l <- T.getLine hSetEcho stdin True putStrLn "" return l -- | IO action that reads a password from standard input. Terminal -- echoing is disabled while reading interactively. If not reading -- interactively we simply read without prompting. getPassword :: Bool -> IO Text getPassword verify = do isTerminal <- hIsTerminalDevice stdin case (isTerminal, verify) of (True, True) -> readVerify (True, False) -> silentPrompt "Password: " (False, _) -> T.getLine where readVerify :: IO Text readVerify = do a <- silentPrompt "Password: " b <- silentPrompt "Repeat password: " if a /= b then putStrLn "Try again!" >> readVerify else return a -- | Converts a string to a hash byte string. If the given string is -- not in a valid format then an error message will be printed and the -- program exited. strToHash :: String -> IO ByteString strToHash hash = do let hash' = T.encodeUtf8 . T.pack $ hash unless (isPasswordFormatValid hash') $ putStrLn "Invalid password hash format." >> exitFailure return hash' -- | Performs the appropriate actions based on the given options -- argument. runMode :: Modes -> IO () runMode Generate {..} = do when (strength < 1) $ putStrLn "Strength must be positive." >> exitFailure when (maybe False ((< 8) . length) salt) $ putStrLn "The salt must be 8 characters or longer." >> exitFailure password <- fmap T.encodeUtf8 $ getPassword True salt' <- maybe genSaltIO (return . makeSalt . T.encodeUtf8 . T.pack) salt T.putStrLn . T.decodeUtf8 $ makePasswordSalt password salt' strength runMode Verify {..} = do hash' <- strToHash hash password <- getPassword False if verifyPassword (T.encodeUtf8 password) hash' then putStrLn "good password" else putStrLn "bad password" runMode Strengthen {..} = do hash' <- strToHash hash T.putStrLn . T.decodeUtf8 $ strengthenPassword hash' strength main :: IO () main = getProgName >>= cmdArgs . optAll >>= runMode