Skip to content
11 changes: 4 additions & 7 deletions hnix-store-core/hnix-store-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -17,33 +17,30 @@ 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
, cryptohash-sha256
, directory
, filepath
-- Drop foundation when we can drop cryptonite <0.25
, foundation
, hashable
, memory
, mtl
, regex-base
, regex-tdfa-text
, text
, unix
, unordered-containers
, vector
hs-source-dirs: src
default-language: Haskell2010

Expand Down
66 changes: 0 additions & 66 deletions hnix-store-core/src/Crypto/Hash/Truncated.hs

This file was deleted.

105 changes: 105 additions & 0 deletions hnix-store-core/src/System/Nix/Hash.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,105 @@
{-|
Description : Nix-style hashes (truncated sha256)
Maintainer : Shea Levy <shea@shealevy.com>
-}

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module System.Nix.Hash (

-- * Introduce hashes for the store
hash
, hashlazy
, fromBase32

-- * cryptohash-sha256 style incremental hash building
, init
, update
, finalize

-- * Internal
, StorePathHash (..)
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

If we want to export these, let's have a System.Nix.Hash.Internal. For a non-internal module, I'd expect to be able to look at the types and assume it's safe to use these to construct my hashes

, truncate52
, toNixBase32

) where

import qualified Crypto.Hash.SHA256 as SHA
import Data.Bits
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import qualified Data.ByteString.Lazy.Builder as BSL
import Data.Char
import qualified Data.Hashable as Hashable
import Data.Semigroup ((<>))
import Data.Word
import qualified Data.Vector.Unboxed as UV
import Prelude hiding (init)

-- | A string, file, or NAR hash in the format
-- used in prefixing files in the nix store
newtype StorePathHash =
StorePathHash { getTruncatedHash :: BS.ByteString }
deriving (Eq, Hashable.Hashable, Ord, Show)


init :: SHA.Ctx
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Can we encapsulate the context type here?

init = SHA.init


update :: SHA.Ctx -> BS.ByteString -> SHA.Ctx
update = SHA.update


finalize :: SHA.Ctx -> StorePathHash
finalize ctx = StorePathHash . truncate52 $ SHA.finalize ctx


hash :: BS.ByteString -> StorePathHash
hash bs = StorePathHash . BSL.toStrict . toNixBase32 . BSL.fromStrict . truncate' $ SHA.hash bs
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Wait, base32 stuff definitely doesn't belong here. Hashes are just numbers, they're not character strings. The result of SHA.hash viewed as a bytestring is a "base-256" representation of that number, not an ascii-based hex encoding.



hashlazy :: BSL.ByteString -> StorePathHash
hashlazy bs = StorePathHash . BSL.toStrict . toNixBase32 . BSL.fromStrict . truncate' $ SHA.hashlazy bs


-- | Import and validate a store path hash
fromBase32 :: BS.ByteString -> Maybe StorePathHash
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

base 32/base 16 questions should just be about presentation, not about internal represenation

fromBase32 = validateRawDigest . StorePathHash
where validateRawDigest = Just
-- TODO: What should we check for? Only valid base32 chars?



truncate52
:: BS.ByteString
-- ^ A sha256 hash
-> BS.ByteString
truncate52 digest =
-- Truncate 52 bits by dropping 6 bytes worth of Word8's,
-- then masking 4 bits off of the 7th Word8
case BS.uncons (BS.drop (52 `div` 8) digest) of
Nothing -> BS.empty -- We received an hash with unexpectedly short length
Just (x,xs) -> BS.cons (mask4bits .&. x) xs
where mask4bits = 2^5 - 1 :: Word8

truncate' :: BS.ByteString -> BS.ByteString
truncate' = BS.take 20


-- | Convert a ByteString to base 32 in the way that Nix does
toNixBase32 :: BSL.ByteString -> BSL.ByteString
toNixBase32 x = BSL.toLazyByteString $ mconcat $ map (BSL.word8 . (symbols UV.!) . fromIntegral) vals
where vals = byteStringToQuintets x
symbols = UV.fromList $ map (fromIntegral . ord) $ filter (`notElem` ("eotu" :: String)) $ ['0'..'9'] <> ['a'..'z']
-- See https://github.com/NixOS/nix/blob/6f1743b1a5116ca57a60b481ee4083c891b7a334/src/libutil/hash.cc#L109
byteStringToQuintets :: BSL.ByteString -> [Word8]
byteStringToQuintets hash = map f [len-1, len-2 .. 0]
where hashSize = fromIntegral $ BSL.length hash
len = (hashSize * 8 - 1) `div` 5 + 1
f n = let b = n * 5
(i, j) = b `divMod` 8
j' = fromIntegral j
--TODO: This is probably pretty slow; replace with something that doesn't use BSL.index
c = ((hash `BSL.index` i) `shift` (-j')) .|. (if i >= hashSize - 1 then 0 else (hash `BSL.index` (i + 1)) `shift` (8 - j'))
in c .&. 0x1f
28 changes: 7 additions & 21 deletions hnix-store-core/src/System/Nix/Path.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,33 +6,28 @@ Maintainer : Shea Levy <shea@shealevy.com>
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module System.Nix.Path
( FilePathPart(..)
, PathHashAlgo
, Path(..)
, PathSet
, SubstitutablePathInfo(..)
, ValidPathInfo(..)
, PathName(..)
, Roots
, filePathPart
, pathName
, Roots
) where

import Crypto.Hash (Digest)
import Crypto.Hash.Algorithms (SHA256)
import Crypto.Hash.Truncated (Truncated)
import qualified Data.ByteArray as B
import qualified Data.ByteString as BS

import qualified Data.ByteString.Char8 as BSC
import Data.Hashable (Hashable (..), hashPtrWithSalt)
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet)
import Data.Map.Strict (Map)
import Data.Text (Text)
import qualified Data.Text as T
import System.IO.Unsafe (unsafeDupablePerformIO)
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
import Text.Regex.TDFA.Text (Regex)

import System.Nix.Hash (StorePathHash, toNixBase32)

-- | The name portion of a Nix path.
--
-- Must be composed of a-z, A-Z, 0-9, +, -, ., _, ?, and =, can't
Expand All @@ -52,24 +47,15 @@ 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
data Path = Path !StorePathHash !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
digest `hashWithSalt` name


type PathSet = HashSet Path
Expand All @@ -87,7 +73,7 @@ data SubstitutablePathInfo = SubstitutablePathInfo
narSize :: !Integer
} deriving (Eq, Ord, Show)

-- | Information about @Path@
-- | Information about 'Path'.
data ValidPathInfo = ValidPathInfo
{ -- | Path itself
path :: !Path
Expand Down
9 changes: 3 additions & 6 deletions hnix-store-core/src/System/Nix/Store.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,16 +6,12 @@ Maintainer : Shea Levy <shea@shealevy.com>
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module System.Nix.Store
( PathName, pathNameContents, pathName
, PathHashAlgo, Path(..)
, Path(..)
, StoreEffects(..)
, 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)
Expand All @@ -24,6 +20,7 @@ import Data.HashSet (HashSet)
import Data.HashMap.Strict (HashMap)
import System.IO.Unsafe (unsafeDupablePerformIO)

import System.Nix.Hash
import System.Nix.Path
import System.Nix.Nar

Expand Down Expand Up @@ -63,7 +60,7 @@ data StoreEffects rootedPath validPath m =
, -- | Get the output names of the derivation at a 'Path'.
derivationOutputNames :: !(validPath -> m (HashSet Text))
, -- | Get a full 'Path' corresponding to a given 'Digest'.
pathFromHashPart :: !(Digest PathHashAlgo -> m Path)
pathFromHashPart :: !(StorePathHash -> m Path)
, -- | Add a non-nar file to the store
addFile :: !(BS.ByteString -> m validPath)
}
22 changes: 22 additions & 0 deletions hnix-store-core/tests/Hash.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
{-# LANGUAGE OverloadedStrings #-}

module Hash where

import qualified Data.ByteString.Char8 as BSC
import Data.Foldable
import Data.Semigroup
import Test.Tasty.Hspec
import Test.Tasty.HUnit
import System.Nix.Hash

spec_hashBase32truncateParity :: Spec
spec_hashBase32truncateParity = describe "hashBase32" $
for_ testCases $ \(testCase, expectation) ->
it ("computes correct base32 hash for string " <> BSC.unpack testCase) $
getTruncatedHash (hash testCase) `shouldBe` expectation
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

No it shouldn't 😉

where
testCases :: [(BSC.ByteString, BSC.ByteString)]
testCases = []
-- [ ("hello", "hcv22wi9b082i6qy160jgi9cvw3am153") ]
-- TODO: This test fails.
-- See [issue #24](https://github.com/haskell-nix/hnix-store/issues/24)
4 changes: 0 additions & 4 deletions hnix-store-remote/hnix-store-remote.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -29,12 +29,8 @@ library
, unix
, network
, mtl
, cryptonite
, unordered-containers
, memory
-- , pretty-simple
-- , base16-bytestring
-- , base32-bytestring
, hnix-store-core
hs-source-dirs: src
default-language: Haskell2010
Expand Down
10 changes: 5 additions & 5 deletions hnix-store-remote/src/System/Nix/Store/Remote.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,14 +39,14 @@ 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
import System.Nix.Path
import System.Nix.Util

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
Expand Down Expand Up @@ -148,19 +148,19 @@ queryDerivationOutputNames p = do
sockGetPaths

-- XXX: this is broken as I don't know how to get hashes from paths (fix mkPath)
queryPathFromHashPart :: Digest PathHashAlgo -> MonadStore (Maybe Path)
queryPathFromHashPart :: StorePathHash -> MonadStore (Maybe Path)
queryPathFromHashPart d = do
runOpArgs QueryPathFromHashPart $
putByteStringLen $ LBS.fromStrict $ convert d
putByteStringLen $ LBS.fromStrict $ getTruncatedHash d
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

here we do need to convert to base32, since we're talking to the daemon.

sockGetPath

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

type PathFilter = Path -> Bool
addToStore :: LBS.ByteString -> Path -> Bool -> PathHashAlgo -> PathFilter -> RepairFlag -> MonadStore Path
addToStore name pth recursive hashAlgo pfilter repair = undefined -- XXX
addToStore :: LBS.ByteString -> Path -> Bool -> PathFilter -> RepairFlag -> MonadStore Path
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Why is this argument dropped? We should be able to pass different hash algorithms to this operation, we can add things to the store based on e.g. md5 or sha512 hash

addToStore name pth recursive pfilter repair = undefined -- XXX

addTextToStore :: LBS.ByteString -> LBS.ByteString -> PathSet -> RepairFlag -> MonadStore (Maybe Path)
addTextToStore name text references' repair = do
Expand Down
Loading