22module Network.HTTP.Download.VerifiedSpec where
33
44import Crypto.Hash
5+ import Control.Monad (unless )
56import Control.Monad.Trans.Reader
67import Data.Maybe
78import Network.HTTP.Client.Conduit
@@ -78,6 +79,15 @@ setup = do
7879teardown :: T -> IO ()
7980teardown _ = return ()
8081
82+ shouldNotBe :: (Show a , Eq a ) => a -> a -> Expectation
83+ actual `shouldNotBe` expected =
84+ unless (actual /= expected) (expectationFailure msg)
85+ where
86+ msg = " Value was exactly what it shouldn't be: " ++ show expected
87+
88+ shouldNotReturn :: (Show a , Eq a ) => IO a -> a -> Expectation
89+ action `shouldNotReturn` unexpected = action >>= (`shouldNotBe` unexpected)
90+
8191spec :: Spec
8292spec = beforeAll setup $ afterAll teardown $ do
8393 let exampleProgressHook = return ()
@@ -104,14 +114,17 @@ spec = beforeAll setup $ afterAll teardown $ do
104114 go `shouldReturn` False
105115 doesFileExist exampleFilePath `shouldReturn` True
106116
117+ -- https://github.com/commercialhaskell/stack/issues/372
107118 it " does redownload when the destination file is wrong" $ \ T {.. } -> withTempDir $ \ dir -> do
108119 examplePath <- getExamplePath dir
109120 let exampleFilePath = toFilePath examplePath
110121 writeFile exampleFilePath exampleWrongContent
111122 doesFileExist exampleFilePath `shouldReturn` True
123+ readFile exampleFilePath `shouldReturn` exampleWrongContent
112124 let go = runWith manager $ verifiedDownload exampleReq examplePath exampleProgressHook
113125 go `shouldReturn` True
114126 doesFileExist exampleFilePath `shouldReturn` True
127+ readFile exampleFilePath `shouldNotReturn` exampleWrongContent
115128
116129 it " rejects incorrect content length" $ \ T {.. } -> withTempDir $ \ dir -> do
117130 examplePath <- getExamplePath dir
0 commit comments