{-# LANGUAGE OverloadedStrings #-} module Main (main) where import qualified Data.ByteString.Char8 as B import Data.List (isPrefixOf) import qualified Crypto.PasswordStore as P import System.Process (readProcess) import Test.HUnit import Test.Hspec import Test.Hspec.HUnit -- | Runs the pwstore command with the given arguments and standard -- input. runPwstore :: [String] -> String -> IO String runPwstore = readProcess "dist/build/pwstore/pwstore" -- | A valid hunter2 hash. hunter2hash :: String hunter2hash = "sha256|12|YmBsCrO7FQIcrbMt23jnOA==|E8FZPaJnwa/dakuXOnz1A9OL2qj3nlzwDE02olsXMy0=" specs :: IO Specs specs = describe "pwstore-cli" [ it "verifies hash with good password" $ do actual <- runPwstore ["verify", hunter2hash] "hunter2" "good password\n" @=? actual , it "does not verify hash with bad password" $ do actual <- runPwstore ["verify", hunter2hash] "badpass" "bad password\n" @=? actual , it "generates hash with given salt" $ do actual <- runPwstore ["generate", "--salt=72cd18b5ebfe6e96"] "hunter2" "sha256|12|NzJjZDE4YjVlYmZlNmU5Ng==|M17VU2ciK8VaKyyDfVeGHS5eiLAuiStg/Y647B+Y4aE=\n" @=? actual , it "generates hash without given salt" $ do hash' <- runPwstore ["generate"] "hunter2" let hash = init hash' -- Remove trailing \n assertBool "" $ P.verifyPassword "hunter2" (B.pack hash) , it "generates hash with given strength" $ do hash' <- runPwstore ["generate", "--strength=15"] "hunter2" let hash = init hash' -- Remove trailing \n assertBool "" $ P.verifyPassword "hunter2" (B.pack hash) assertBool "" $ "sha256|15|" `isPrefixOf` hash , it "strengthens hashes" $ do actual <- runPwstore ["strengthen", "-s15", hunter2hash] "" "sha256|15|YmBsCrO7FQIcrbMt23jnOA==|6ugvNWDF6KznLSsNC6AGXEObUalzx60UKauaivGkPkU=\n" @=? actual , it "does not weaken hashes" $ do actual <- runPwstore ["strengthen", "-s11", hunter2hash] "" hunter2hash ++ "\n" @=? actual ] main :: IO () main = hspecX specs