1+ {-# LANGUAGE TypeApplications #-}
12{-|
23Description : Representation of Nix store paths.
34-}
@@ -10,15 +11,10 @@ Description : Representation of Nix store paths.
1011{-# LANGUAGE TypeInType #-} -- Needed for GHC 8.4.4 for some reason
1112
1213module System.Nix.Internal.StorePath where
13- import System.Nix.Hash ( HashAlgorithm
14- ( Truncated
15- , SHA256
16- )
14+ import System.Nix.Internal.Hash ( HashAlgorithm (SHA256 )
1715 , Digest
18- , BaseEncoding (.. )
19- , encodeDigestWith
20- , decodeDigestWith
2116 , SomeNamedDigest
17+ , mkStorePathHash
2218 )
2319
2420
@@ -39,6 +35,11 @@ import qualified Data.Attoparsec.Text.Lazy as Parser.Text.Lazy
3935import qualified System.FilePath as FilePath
4036import Data.Hashable ( Hashable (.. ) )
4137import Data.HashSet ( HashSet )
38+ import System.Nix.Internal.Base ( BaseEncoding (.. )
39+ , encodeWith
40+ , decodeWith
41+ )
42+ import Data.Coerce ( coerce )
4243
4344-- | A path in a Nix store.
4445--
@@ -52,7 +53,7 @@ import Data.HashSet ( HashSet )
5253data StorePath = StorePath
5354 { -- | The 160-bit hash digest reflecting the "address" of the name.
5455 -- Currently, this is a truncated SHA256 hash.
55- storePathHash :: ! ( Digest StorePathHashAlgo )
56+ storePathHash :: ! StorePathHashPart
5657 , -- | The (typically human readable) name of the path. For packages
5758 -- this is typically the package name and version (e.g.
5859 -- hello-1.2.3).
@@ -80,7 +81,11 @@ newtype StorePathName = StorePathName
8081 } deriving (Eq , Hashable , Ord )
8182
8283-- | The hash algorithm used for store path hashes.
83- type StorePathHashAlgo = 'Truncated 20 'SHA256
84+ newtype StorePathHashPart = StorePathHashPart ByteString
85+ deriving (Eq , Hashable , Ord , Show )
86+
87+ mkStorePathHashPart :: ByteString -> StorePathHashPart
88+ mkStorePathHashPart = coerce . mkStorePathHash @ 'SHA256
8489
8590-- | A set of 'StorePath's.
8691type StorePathSet = HashSet StorePath
@@ -154,7 +159,7 @@ storePathToRawFilePath StorePath{..} =
154159 root <> " /" <> hashPart <> " -" <> name
155160 where
156161 root = Bytes.Char8. pack storePathRoot
157- hashPart = Text. encodeUtf8 $ encodeDigestWith NixBase32 storePathHash
162+ hashPart = Text. encodeUtf8 $ encodeWith NixBase32 $ coerce storePathHash
158163 name = Text. encodeUtf8 $ unStorePathName storePathName
159164
160165-- | Render a 'StorePath' as a 'FilePath'.
@@ -169,16 +174,16 @@ storePathToText = Text.pack . Bytes.Char8.unpack . storePathToRawFilePath
169174-- can be used to query binary caches.
170175storePathToNarInfo :: StorePath -> Bytes.Char8. ByteString
171176storePathToNarInfo StorePath {.. } =
172- Text. encodeUtf8 $ encodeDigestWith NixBase32 storePathHash <> " .narinfo"
177+ Text. encodeUtf8 $ encodeWith NixBase32 (coerce storePathHash) <> " .narinfo"
173178
174179-- | Parse `StorePath` from `Bytes.Char8.ByteString`, checking
175180-- that store directory matches `expectedRoot`.
176181parsePath :: FilePath -> Bytes.Char8. ByteString -> Either String StorePath
177182parsePath expectedRoot x =
178183 let
179184 (rootDir, fname) = FilePath. splitFileName . Bytes.Char8. unpack $ x
180- (digestPart , namePart) = Text. breakOn " -" $ Text. pack fname
181- digest = decodeDigestWith NixBase32 digestPart
185+ (storeBasedHashPart , namePart) = Text. breakOn " -" $ Text. pack fname
186+ storeHash = decodeWith NixBase32 storeBasedHashPart
182187 name = makeStorePathName . Text. drop 1 $ namePart
183188 -- rootDir' = dropTrailingPathSeparator rootDir
184189 -- cannot use ^^ as it drops multiple slashes /a/b/// -> /a/b
@@ -188,7 +193,7 @@ parsePath expectedRoot x =
188193 then Right rootDir'
189194 else Left $ " Root store dir mismatch, expected" <> expectedRoot <> " got" <> rootDir'
190195 in
191- StorePath <$> digest <*> name <*> storeDir
196+ StorePath <$> coerce storeHash <*> name <*> storeDir
192197
193198pathParser :: FilePath -> Parser StorePath
194199pathParser expectedRoot = do
@@ -200,7 +205,7 @@ pathParser expectedRoot = do
200205 <?> " Expecting path separator"
201206
202207 digest <-
203- decodeDigestWith NixBase32
208+ decodeWith NixBase32
204209 <$> Parser.Text.Lazy. takeWhile1 (`elem` Nix.Base32. digits32)
205210 <?> " Invalid Base32 part"
206211
@@ -219,4 +224,4 @@ pathParser expectedRoot = do
219224 either
220225 fail
221226 pure
222- (StorePath <$> digest <*> name <*> pure expectedRoot)
227+ (StorePath <$> coerce digest <*> name <*> pure expectedRoot)
0 commit comments