[commit: ghc] master: [iserv] drop cryptonite dependency. (5a21003)

git at git.haskell.org git at git.haskell.org
Tue Apr 18 00:35:40 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5a210032d4b9dcc644a5557eb4144445f660ea27/ghc

>---------------------------------------------------------------

commit 5a210032d4b9dcc644a5557eb4144445f660ea27
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date:   Mon Apr 17 12:28:22 2017 -0400

    [iserv] drop cryptonite dependency.
    
    Reviewers: bgamari, austin
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3462


>---------------------------------------------------------------

5a210032d4b9dcc644a5557eb4144445f660ea27
 iserv/iserv-bin.cabal       |  5 ++---
 iserv/proxy-src/Remote.hs   |  3 ++-
 iserv/src/Remote/Message.hs | 16 +++-------------
 iserv/src/Remote/Slave.hs   |  7 ++++---
 4 files changed, 11 insertions(+), 20 deletions(-)

diff --git a/iserv/iserv-bin.cabal b/iserv/iserv-bin.cabal
index f0abf54..8da0c28 100644
--- a/iserv/iserv-bin.cabal
+++ b/iserv/iserv-bin.cabal
@@ -85,8 +85,7 @@ Library
                    bytestring >= 0.10 && < 0.11,
                    containers >= 0.5 && < 0.6,
                    deepseq    >= 1.4 && < 1.5,
-                   cryptonite >= 0.22,
-                   ghci       == 8.1,
+                   ghci       == 8.3,
                    network    >= 2.6 && < 2.7,
                    directory  >= 1.3 && < 1.4,
                    filepath   >= 1.4 && < 1.5
@@ -134,6 +133,6 @@ Executable iserv-proxy
                   bytestring >= 0.10 && < 0.11,
                   containers >= 0.5 && < 0.6,
                   deepseq    >= 1.4 && < 1.5,
-                  ghci       == 8.1,
+                  ghci       == 8.3,
                   network    >= 2.6,
                   iserv-bin
diff --git a/iserv/proxy-src/Remote.hs b/iserv/proxy-src/Remote.hs
index 6b1d528..481d6ac 100644
--- a/iserv/proxy-src/Remote.hs
+++ b/iserv/proxy-src/Remote.hs
@@ -58,6 +58,7 @@ import Control.Monad
 import System.Environment
 import System.Exit
 import Text.Printf
+import GHC.Fingerprint (getFileHash)
 
 import Data.Binary
 import qualified Data.ByteString as BS
@@ -182,7 +183,7 @@ fwdLoadCall verbose _ remote msg = do
           reply =<< BS.readFile path
           loopLoad
         Have path remoteHash -> do
-          localHash <- sha256sum path
+          localHash <- getFileHash path
           reply =<< if localHash == remoteHash
                     then return Nothing
                     else Just <$> BS.readFile path
diff --git a/iserv/src/Remote/Message.hs b/iserv/src/Remote/Message.hs
index faef45d..f174530 100644
--- a/iserv/src/Remote/Message.hs
+++ b/iserv/src/Remote/Message.hs
@@ -3,29 +3,19 @@
 module Remote.Message
   ( SlaveMessage(..)
   , SlaveMsg(..)
-  , sha256sum
   , putSlaveMessage
   , getSlaveMessage )
 where
 
+import GHC.Fingerprint (Fingerprint)
 import Data.Binary
-import Data.ByteString as BS (ByteString, readFile)
-
-import Crypto.Hash
-
-type Sha256Hash = String
-
-sha256 :: ByteString -> Digest SHA256
-sha256 = hash
-
-sha256sum :: FilePath -> IO Sha256Hash
-sha256sum path = (show . sha256) <$> BS.readFile path
+import Data.ByteString (ByteString)
 
 -- | A @SlaveMessage a@ is message from the iserv process on the
 -- target, requesting something from the Proxy of with result type @a at .
 data SlaveMessage a where
   -- sends either a new file, or nothing if the file is acceptable.
-  Have     :: FilePath -> Sha256Hash -> SlaveMessage (Maybe ByteString)
+  Have     :: FilePath -> Fingerprint -> SlaveMessage (Maybe ByteString)
   Missing  :: FilePath -> SlaveMessage ByteString
   Done     :: SlaveMessage ()
 
diff --git a/iserv/src/Remote/Slave.hs b/iserv/src/Remote/Slave.hs
index 2d47a34..e7ff3f2 100644
--- a/iserv/src/Remote/Slave.hs
+++ b/iserv/src/Remote/Slave.hs
@@ -19,6 +19,7 @@ import GHCi.Message (Pipe(..), Msg(..), Message(..), readPipe, writePipe)
 import Foreign.C.String
 
 import Data.Binary
+import GHC.Fingerprint (getFileHash)
 
 import qualified Data.ByteString as BS
 
@@ -59,16 +60,16 @@ startSlave' verbose base_path port = do
 --
 -- If we however already have the requested file we need to make
 -- sure that this file is the same one ghc sees. Hence we
--- calculate the sha256sum of the file and send it back to the
+-- calculate the Fingerprint of the file and send it back to the
 -- host for comparison. The proxy will then send back either @Nothing@
--- indicating that the file on the host has the same sha256sum, or
+-- indicating that the file on the host has the same Fingerprint, or
 -- Maybe ByteString containing the payload to replace the existing
 -- file with.
 handleLoad :: Pipe -> FilePath -> FilePath -> IO ()
 handleLoad pipe path localPath = do
   exists <- doesFileExist localPath
   if exists
-    then sha256sum localPath >>= \hash -> proxyCall (Have path hash) >>= \case
+    then getFileHash localPath >>= \hash -> proxyCall (Have path hash) >>= \case
       Nothing -> return ()
       Just bs -> BS.writeFile localPath bs
     else do



More information about the ghc-commits mailing list