Skip to content

Commit a571a32

Browse files
authored
Merge pull request #27 from haskell-nix/fewer-deps-3
Remove cryptonite, foundation, basement and memory from all packages
2 parents 63b0c6c + 966aa4a commit a571a32

File tree

8 files changed

+51
-106
lines changed

8 files changed

+51
-106
lines changed

hnix-store-core/hnix-store-core.cabal

Lines changed: 2 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -17,27 +17,22 @@ extra-source-files: ChangeLog.md, README.md
1717
cabal-version: >=1.10
1818

1919
library
20-
exposed-modules: Crypto.Hash.Truncated
21-
, System.Nix.Build
20+
exposed-modules: System.Nix.Build
2221
, System.Nix.Derivation
2322
, System.Nix.GC
23+
, System.Nix.Hash
2424
, System.Nix.Nar
2525
, System.Nix.Path
2626
, System.Nix.Store
2727
, System.Nix.Util
2828
build-depends: base >=4.10 && <4.11
29-
, basement
3029
, bytestring
3130
, binary
3231
, bytestring
3332
, containers
34-
, cryptonite
3533
, directory
3634
, filepath
37-
-- Drop foundation when we can drop cryptonite <0.25
38-
, foundation
3935
, hashable
40-
, memory
4136
, mtl
4237
, regex-base
4338
, regex-tdfa-text

hnix-store-core/src/Crypto/Hash/Truncated.hs

Lines changed: 0 additions & 66 deletions
This file was deleted.
Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
{-|
2+
Description : Trunctions of cryptographic hashes.
3+
Maintainer : Shea Levy <[email protected]>
4+
-}
5+
{-# LANGUAGE DataKinds #-}
6+
{-# LANGUAGE TypeApplications #-}
7+
{-# LANGUAGE ScopedTypeVariables #-}
8+
{-# LANGUAGE FlexibleContexts #-}
9+
{-# LANGUAGE TypeFamilies #-}
10+
{-# LANGUAGE TypeOperators #-}
11+
{-# LANGUAGE CPP #-}
12+
module System.Nix.Hash where
13+
14+
import Control.Monad (void)
15+
import Data.Coerce (coerce)
16+
import qualified Data.ByteString as BS
17+
import Data.Hashable (Hashable (..))
18+
import Data.Proxy (Proxy(..))
19+
import Data.Word (Word8)
20+
import GHC.TypeLits (Nat, KnownNat, natVal, type (<=))
21+
import Foreign.Ptr (castPtr, Ptr)
22+
import Foreign.Marshal.Utils (copyBytes)
23+
24+
data HashAlgorithm = TruncatedSHA256 | MD5
25+
26+
newtype Digest (algo :: HashAlgorithm) = Digest { getDigestBytes :: BS.ByteString }
27+
deriving (Eq, Ord, Show)
28+
29+
instance Hashable (Digest algo) where
30+
hashWithSalt s (Digest bytes) = hashWithSalt s bytes

hnix-store-core/src/System/Nix/Path.hs

Lines changed: 8 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -17,10 +17,8 @@ module System.Nix.Path
1717
, Roots
1818
) where
1919

20-
import Crypto.Hash (Digest)
21-
import Crypto.Hash.Algorithms (SHA256)
22-
import Crypto.Hash.Truncated (Truncated)
23-
import qualified Data.ByteArray as B
20+
import System.Nix.Hash (Digest(..),
21+
HashAlgorithm(TruncatedSHA256))
2422
import qualified Data.ByteString as BS
2523
import qualified Data.ByteString.Char8 as BSC
2624
import Data.Hashable (Hashable (..), hashPtrWithSalt)
@@ -33,6 +31,9 @@ import System.IO.Unsafe (unsafeDupablePerformIO)
3331
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
3432
import Text.Regex.TDFA.Text (Regex)
3533

34+
-- | The hash algorithm used for store path hashes.
35+
type PathHashAlgo = TruncatedSHA256
36+
3637
-- | The name portion of a Nix path.
3738
--
3839
-- Must be composed of a-z, A-Z, 0-9, +, -, ., _, ?, and =, can't
@@ -52,26 +53,10 @@ pathName n = case matchTest nameRegex n of
5253
True -> Just $ PathName n
5354
False -> Nothing
5455

55-
-- | The hash algorithm used for store path hashes.
56-
type PathHashAlgo = Truncated SHA256 20
57-
5856
-- | A path in a store.
5957
data Path = Path !(Digest PathHashAlgo) !PathName
6058
deriving (Eq, Ord, Show)
6159

62-
-- | Wrapper to defined a 'Hashable' instance for 'Digest'.
63-
newtype HashableDigest a = HashableDigest (Digest a)
64-
65-
instance Hashable (HashableDigest a) where
66-
hashWithSalt s (HashableDigest d) = unsafeDupablePerformIO $
67-
B.withByteArray d $ \ptr -> hashPtrWithSalt ptr (B.length d) s
68-
69-
instance Hashable Path where
70-
hashWithSalt s (Path digest name) =
71-
s `hashWithSalt`
72-
(HashableDigest digest) `hashWithSalt` name
73-
74-
7560
type PathSet = HashSet Path
7661

7762
-- | Information about substitutes for a 'Path'.
@@ -130,3 +115,6 @@ filePathPart p = case BSC.any (`elem` ['/', '\NUL']) p of
130115
True -> Nothing
131116

132117
type Roots = Map Path Path
118+
119+
instance Hashable Path where
120+
hashWithSalt s (Path hash name) = s `hashWithSalt` hash `hashWithSalt` name

hnix-store-core/src/System/Nix/Store.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -11,11 +11,7 @@ module System.Nix.Store
1111
, SubstitutablePathInfo(..)
1212
) where
1313

14-
import Crypto.Hash (Digest)
15-
import Crypto.Hash.Truncated (Truncated)
16-
import Crypto.Hash.Algorithms (SHA256)
1714
import qualified Data.ByteString.Lazy as BS
18-
import qualified Data.ByteArray as B
1915
import Data.Text (Text)
2016
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
2117
import Text.Regex.TDFA.Text (Regex)
@@ -24,6 +20,7 @@ import Data.HashSet (HashSet)
2420
import Data.HashMap.Strict (HashMap)
2521
import System.IO.Unsafe (unsafeDupablePerformIO)
2622

23+
import System.Nix.Hash (Digest)
2724
import System.Nix.Path
2825
import System.Nix.Nar
2926

hnix-store-remote/hnix-store-remote.cabal

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -29,9 +29,7 @@ library
2929
, unix
3030
, network
3131
, mtl
32-
, cryptonite
3332
, unordered-containers
34-
, memory
3533
-- , pretty-simple
3634
-- , base16-bytestring
3735
-- , base32-bytestring

hnix-store-remote/src/System/Nix/Store/Remote.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,6 @@ module System.Nix.Store.Remote (
3030
) where
3131

3232
import Data.Maybe
33-
import Data.ByteArray (convert)
3433
import qualified Data.ByteString.Lazy as LBS
3534
import qualified Data.Map.Strict as M
3635

@@ -39,15 +38,14 @@ import Control.Monad
3938
import qualified System.Nix.Build as Build
4039
import qualified System.Nix.Derivation as Drv
4140
import qualified System.Nix.GC as GC
41+
import System.Nix.Hash (Digest, HashAlgorithm)
4242
import System.Nix.Path
4343
import System.Nix.Util
4444

4545
import System.Nix.Store.Remote.Types
4646
import System.Nix.Store.Remote.Protocol
4747
import System.Nix.Store.Remote.Util
4848

49-
import Crypto.Hash
50-
5149
type RepairFlag = Bool
5250
type CheckFlag = Bool
5351
type CheckSigsFlag = Bool
@@ -151,15 +149,18 @@ queryDerivationOutputNames p = do
151149
queryPathFromHashPart :: Digest PathHashAlgo -> MonadStore (Maybe Path)
152150
queryPathFromHashPart d = do
153151
runOpArgs QueryPathFromHashPart $
154-
putByteStringLen $ LBS.fromStrict $ convert d
152+
-- TODO: replace `undefined` with digest encoding function when
153+
-- [issue 24](https://github.com/haskell-nix/hnix-store/issues/24) is
154+
-- closed
155+
putByteStringLen $ LBS.fromStrict $ undefined d
155156
sockGetPath
156157

157158
type Source = () -- abstract binary source
158159
addToStoreNar :: ValidPathInfo -> Source -> RepairFlag -> CheckSigsFlag -> MonadStore ()
159160
addToStoreNar = undefined -- XXX
160161

161162
type PathFilter = Path -> Bool
162-
addToStore :: LBS.ByteString -> Path -> Bool -> PathHashAlgo -> PathFilter -> RepairFlag -> MonadStore Path
163+
addToStore :: LBS.ByteString -> Path -> Bool -> HashAlgorithm -> PathFilter -> RepairFlag -> MonadStore Path
163164
addToStore name pth recursive hashAlgo pfilter repair = undefined -- XXX
164165

165166
addTextToStore :: LBS.ByteString -> LBS.ByteString -> PathSet -> RepairFlag -> MonadStore (Maybe Path)

hnix-store-remote/src/System/Nix/Store/Remote/Util.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,6 @@ import System.Nix.Store.Remote.Types
1818
import System.Nix.Path
1919
import System.Nix.Util
2020

21-
import Crypto.Hash
2221

2322
genericIncremental :: (MonadIO m) => m (Maybe B.ByteString) -> Get a -> m a
2423
genericIncremental getsome parser = go decoder
@@ -71,7 +70,10 @@ textToLBS = LBS.fromStrict . BSC.pack . T.unpack
7170
-- XXX: needs work
7271
mkPath :: LBS.ByteString -> Maybe Path
7372
mkPath p = case (pathName $ lBSToText p) of
74-
Just x -> Just $ Path (hash $ LBS.toStrict p) x --XXX: hash
73+
-- TODO: replace `undefined` with digest encoding function when
74+
-- [issue 24](https://github.com/haskell-nix/hnix-store/issues/24)
75+
-- is closed
76+
Just x -> Just $ Path (undefined $ LBS.toStrict p) x --XXX: hash
7577
Nothing -> Nothing
7678

7779
-- WOOT

0 commit comments

Comments
 (0)