Merge pull request #27 from haskell-nix/fewer-deps-3

Remove cryptonite, foundation, basement and memory from all packages
This commit is contained in:
Greg Hale 2018-10-23 08:53:07 -04:00 committed by GitHub
commit a571a32871
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
8 changed files with 51 additions and 106 deletions

View File

@ -17,27 +17,22 @@ extra-source-files: ChangeLog.md, README.md
cabal-version: >=1.10
library
exposed-modules: Crypto.Hash.Truncated
, System.Nix.Build
exposed-modules: System.Nix.Build
, System.Nix.Derivation
, System.Nix.GC
, System.Nix.Hash
, System.Nix.Nar
, System.Nix.Path
, System.Nix.Store
, System.Nix.Util
build-depends: base >=4.10 && <4.11
, basement
, bytestring
, binary
, bytestring
, containers
, cryptonite
, directory
, filepath
-- Drop foundation when we can drop cryptonite <0.25
, foundation
, hashable
, memory
, mtl
, regex-base
, regex-tdfa-text

View File

@ -1,66 +0,0 @@
{-|
Description : Trunctions of cryptographic hashes.
Maintainer : Shea Levy <shea@shealevy.com>
-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE CPP #-}
module Crypto.Hash.Truncated where
import Control.Monad (void)
import Data.Coerce (coerce)
import Data.Proxy (Proxy(..))
import Data.Word (Word8)
import GHC.TypeLits (Nat, KnownNat, natVal, type (<=))
import Crypto.Hash (Digest)
import Crypto.Hash.IO (HashAlgorithm(..),)
import Data.ByteArray (alloc)
import Foreign.Ptr (castPtr, Ptr)
import Foreign.Marshal.Utils (copyBytes)
#if MIN_VERSION_cryptonite(0,25,0)
import Basement.Block.Mutable (Block)
#else
import Foundation.Array (UArray)
#endif
-- | Hash algorithm 'algo' truncated to 'size' bytes.
newtype Truncated algo (size :: Nat) = Truncated algo
-- | The underlying type of a 'Digest'.
#if MIN_VERSION_cryptonite(0,25,0)
type DigestUnwrapped = Block Word8
#else
type DigestUnwrapped = UArray Word8
#endif
-- | Use the 'HashAlgorithm' instance of 'algo' and truncate the final
-- digest.
--
-- The implementation of finalization does some pointer munging that
-- relies on the representational equivalence of a 'Digest' and
-- 'DigestUnwrapped', but there is no way for that to be enforced by
-- the type system. Until/unless cryptonite exports this, we will have
-- to be vigilant to changes in the type.
instance ( HashAlgorithm algo, KnownNat (HashDigestSize algo)
, KnownNat size, size <= HashDigestSize algo
) => HashAlgorithm (Truncated algo size) where
type HashBlockSize (Truncated algo size) = HashBlockSize algo
type HashDigestSize (Truncated algo size) = size
type HashInternalContextSize (Truncated algo size) =
HashInternalContextSize algo
hashBlockSize = hashBlockSize @algo . coerce
hashDigestSize _ = fromIntegral $ natVal @size Proxy
hashInternalContextSize = hashInternalContextSize @algo . coerce
hashInternalInit = hashInternalInit @algo . coerce
hashInternalUpdate = hashInternalUpdate @algo . coerce
hashInternalFinalize cptr dptr = void @_ @DigestUnwrapped $
alloc (fromIntegral $ natVal @(HashDigestSize algo) Proxy) go
where
go :: Ptr (Digest algo) -> IO ()
go p = do
hashInternalFinalize (coerce cptr) p
copyBytes dptr (castPtr p) (fromIntegral $ natVal @size Proxy)

View File

@ -0,0 +1,30 @@
{-|
Description : Trunctions of cryptographic hashes.
Maintainer : Shea Levy <shea@shealevy.com>
-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE CPP #-}
module System.Nix.Hash where
import Control.Monad (void)
import Data.Coerce (coerce)
import qualified Data.ByteString as BS
import Data.Hashable (Hashable (..))
import Data.Proxy (Proxy(..))
import Data.Word (Word8)
import GHC.TypeLits (Nat, KnownNat, natVal, type (<=))
import Foreign.Ptr (castPtr, Ptr)
import Foreign.Marshal.Utils (copyBytes)
data HashAlgorithm = TruncatedSHA256 | MD5
newtype Digest (algo :: HashAlgorithm) = Digest { getDigestBytes :: BS.ByteString }
deriving (Eq, Ord, Show)
instance Hashable (Digest algo) where
hashWithSalt s (Digest bytes) = hashWithSalt s bytes

View File

@ -17,10 +17,8 @@ module System.Nix.Path
, Roots
) where
import Crypto.Hash (Digest)
import Crypto.Hash.Algorithms (SHA256)
import Crypto.Hash.Truncated (Truncated)
import qualified Data.ByteArray as B
import System.Nix.Hash (Digest(..),
HashAlgorithm(TruncatedSHA256))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import Data.Hashable (Hashable (..), hashPtrWithSalt)
@ -33,6 +31,9 @@ import System.IO.Unsafe (unsafeDupablePerformIO)
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
import Text.Regex.TDFA.Text (Regex)
-- | The hash algorithm used for store path hashes.
type PathHashAlgo = TruncatedSHA256
-- | The name portion of a Nix path.
--
-- Must be composed of a-z, A-Z, 0-9, +, -, ., _, ?, and =, can't
@ -52,26 +53,10 @@ pathName n = case matchTest nameRegex n of
True -> Just $ PathName n
False -> Nothing
-- | The hash algorithm used for store path hashes.
type PathHashAlgo = Truncated SHA256 20
-- | A path in a store.
data Path = Path !(Digest PathHashAlgo) !PathName
deriving (Eq, Ord, Show)
-- | Wrapper to defined a 'Hashable' instance for 'Digest'.
newtype HashableDigest a = HashableDigest (Digest a)
instance Hashable (HashableDigest a) where
hashWithSalt s (HashableDigest d) = unsafeDupablePerformIO $
B.withByteArray d $ \ptr -> hashPtrWithSalt ptr (B.length d) s
instance Hashable Path where
hashWithSalt s (Path digest name) =
s `hashWithSalt`
(HashableDigest digest) `hashWithSalt` name
type PathSet = HashSet Path
-- | Information about substitutes for a 'Path'.
@ -130,3 +115,6 @@ filePathPart p = case BSC.any (`elem` ['/', '\NUL']) p of
True -> Nothing
type Roots = Map Path Path
instance Hashable Path where
hashWithSalt s (Path hash name) = s `hashWithSalt` hash `hashWithSalt` name

View File

@ -11,11 +11,7 @@ module System.Nix.Store
, SubstitutablePathInfo(..)
) where
import Crypto.Hash (Digest)
import Crypto.Hash.Truncated (Truncated)
import Crypto.Hash.Algorithms (SHA256)
import qualified Data.ByteString.Lazy as BS
import qualified Data.ByteArray as B
import Data.Text (Text)
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
import Text.Regex.TDFA.Text (Regex)
@ -24,6 +20,7 @@ import Data.HashSet (HashSet)
import Data.HashMap.Strict (HashMap)
import System.IO.Unsafe (unsafeDupablePerformIO)
import System.Nix.Hash (Digest)
import System.Nix.Path
import System.Nix.Nar

View File

@ -29,9 +29,7 @@ library
, unix
, network
, mtl
, cryptonite
, unordered-containers
, memory
-- , pretty-simple
-- , base16-bytestring
-- , base32-bytestring

View File

@ -30,7 +30,6 @@ module System.Nix.Store.Remote (
) where
import Data.Maybe
import Data.ByteArray (convert)
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Map.Strict as M
@ -39,6 +38,7 @@ import Control.Monad
import qualified System.Nix.Build as Build
import qualified System.Nix.Derivation as Drv
import qualified System.Nix.GC as GC
import System.Nix.Hash (Digest, HashAlgorithm)
import System.Nix.Path
import System.Nix.Util
@ -46,8 +46,6 @@ import System.Nix.Store.Remote.Types
import System.Nix.Store.Remote.Protocol
import System.Nix.Store.Remote.Util
import Crypto.Hash
type RepairFlag = Bool
type CheckFlag = Bool
type CheckSigsFlag = Bool
@ -151,7 +149,10 @@ queryDerivationOutputNames p = do
queryPathFromHashPart :: Digest PathHashAlgo -> MonadStore (Maybe Path)
queryPathFromHashPart d = do
runOpArgs QueryPathFromHashPart $
putByteStringLen $ LBS.fromStrict $ convert d
-- TODO: replace `undefined` with digest encoding function when
-- [issue 24](https://github.com/haskell-nix/hnix-store/issues/24) is
-- closed
putByteStringLen $ LBS.fromStrict $ undefined d
sockGetPath
type Source = () -- abstract binary source
@ -159,7 +160,7 @@ addToStoreNar :: ValidPathInfo -> Source -> RepairFlag -> CheckSigsFlag -> Monad
addToStoreNar = undefined -- XXX
type PathFilter = Path -> Bool
addToStore :: LBS.ByteString -> Path -> Bool -> PathHashAlgo -> PathFilter -> RepairFlag -> MonadStore Path
addToStore :: LBS.ByteString -> Path -> Bool -> HashAlgorithm -> PathFilter -> RepairFlag -> MonadStore Path
addToStore name pth recursive hashAlgo pfilter repair = undefined -- XXX
addTextToStore :: LBS.ByteString -> LBS.ByteString -> PathSet -> RepairFlag -> MonadStore (Maybe Path)

View File

@ -18,7 +18,6 @@ import System.Nix.Store.Remote.Types
import System.Nix.Path
import System.Nix.Util
import Crypto.Hash
genericIncremental :: (MonadIO m) => m (Maybe B.ByteString) -> Get a -> m a
genericIncremental getsome parser = go decoder
@ -71,7 +70,10 @@ textToLBS = LBS.fromStrict . BSC.pack . T.unpack
-- XXX: needs work
mkPath :: LBS.ByteString -> Maybe Path
mkPath p = case (pathName $ lBSToText p) of
Just x -> Just $ Path (hash $ LBS.toStrict p) x --XXX: hash
-- TODO: replace `undefined` with digest encoding function when
-- [issue 24](https://github.com/haskell-nix/hnix-store/issues/24)
-- is closed
Just x -> Just $ Path (undefined $ LBS.toStrict p) x --XXX: hash
Nothing -> Nothing
-- WOOT