Skip to content

Commit 8fa0119

Browse files
committed
ReadonlyStore: Update to use new StorePath module.
1 parent aabde18 commit 8fa0119

File tree

3 files changed

+29
-21
lines changed

3 files changed

+29
-21
lines changed

hnix-store-core/src/System/Nix/Internal/StorePath.hs

Lines changed: 12 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,9 @@ Description : Representation of Nix store paths.
77
{-# LANGUAGE ConstraintKinds #-}
88
{-# LANGUAGE RecordWildCards #-}
99
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
10+
{-# LANGUAGE TypeApplications #-}
11+
{-# LANGUAGE ScopedTypeVariables #-}
12+
{-# LANGUAGE AllowAmbiguousTypes #-}
1013
module System.Nix.Internal.StorePath where
1114
import System.Nix.Hash (HashAlgorithm(Truncated, SHA256), Digest, encodeBase32)
1215
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
@@ -19,6 +22,7 @@ import qualified Data.ByteString as BS
1922
import qualified Data.ByteString.Char8 as BC
2023
import Data.Hashable (Hashable(..))
2124
import Data.HashSet (HashSet)
25+
import Data.Proxy (Proxy(..))
2226

2327
-- | A path in a Nix store.
2428
--
@@ -132,20 +136,25 @@ type RawFilePath = ByteString
132136

133137
-- | Render a 'StorePath' as a 'RawFilePath'.
134138
storePathToRawFilePath
135-
:: (KnownStoreDir storeDir)
139+
:: forall storeDir . (KnownStoreDir storeDir)
136140
=> StorePath storeDir
137141
-> RawFilePath
138-
storePathToRawFilePath s@(StorePath {..}) = BS.concat
142+
storePathToRawFilePath (StorePath {..}) = BS.concat
139143
[ root
140144
, "/"
141145
, hashPart
142146
, "-"
143147
, name
144148
]
145149
where
146-
root = BC.pack $ symbolVal s
150+
root = storeDirVal @storeDir
147151
hashPart = encodeUtf8 $ encodeBase32 storePathHash
148152
name = encodeUtf8 $ unStorePathName storePathName
149153

154+
-- | Get a value-level representation of a 'KnownStoreDir'
155+
storeDirVal :: forall storeDir . (KnownStoreDir storeDir)
156+
=> ByteString
157+
storeDirVal = BC.pack $ symbolVal @storeDir Proxy
158+
150159
-- | A 'StoreDir' whose value is known at compile time.
151160
type KnownStoreDir = KnownSymbol
Lines changed: 16 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,34 +1,32 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE OverloadedStrings #-}
33
{-# LANGUAGE TypeApplications #-}
4-
4+
{-# LANGUAGE ScopedTypeVariables #-}
55
module System.Nix.ReadonlyStore where
66

77
import Data.ByteString (ByteString)
8-
import Data.ByteString.Base16 as Base16
8+
import qualified Data.ByteString as BS
99
import qualified Data.HashSet as HS
10-
import Data.Text (Text)
11-
import qualified Data.Text as T
1210
import Data.Text.Encoding
1311
import System.Nix.Hash
14-
import System.Nix.Path
12+
import System.Nix.StorePath
1513

16-
makeStorePath :: Text -> Text -> Digest 'SHA256 -> Text -> Path
17-
makeStorePath storeDir ty h nm = Path storeHash (PathName nm)
14+
makeStorePath :: forall storeDir . (KnownStoreDir storeDir) => ByteString -> Digest 'SHA256 -> StorePathName -> StorePath storeDir
15+
makeStorePath ty h nm = StorePath storeHash nm
1816
where
19-
s = T.intercalate ":"
17+
s = BS.intercalate ":"
2018
[ ty
21-
, algoName @'SHA256
22-
, encodeBase16 h
23-
, storeDir
24-
, nm
19+
, encodeUtf8 $ algoName @'SHA256
20+
, encodeUtf8 $ encodeBase16 h
21+
, storeDirVal @storeDir
22+
, encodeUtf8 $ unStorePathName nm
2523
]
26-
storeHash = hash $ encodeUtf8 s
24+
storeHash = hash s
2725

28-
makeTextPath :: Text -> Text -> Digest 'SHA256 -> PathSet -> Path
29-
makeTextPath storeDir nm h refs = makeStorePath storeDir ty h nm
26+
makeTextPath :: (KnownStoreDir storeDir) => StorePathName -> Digest 'SHA256 -> StorePathSet storeDir -> StorePath storeDir
27+
makeTextPath nm h refs = makeStorePath ty h nm
3028
where
31-
ty = T.intercalate ":" ("text" : map (pathToText storeDir) (HS.toList refs))
29+
ty = BS.intercalate ":" ("text" : map storePathToRawFilePath (HS.toList refs))
3230

33-
computeStorePathForText :: Text -> Text -> ByteString -> PathSet -> Path
34-
computeStorePathForText storeDir nm s refs = makeTextPath storeDir nm (hash s) refs
31+
computeStorePathForText :: (KnownStoreDir storeDir) => StorePathName -> ByteString -> StorePathSet storeDir -> StorePath storeDir
32+
computeStorePathForText nm s refs = makeTextPath nm (hash s) refs

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module System.Nix.StorePath
1414
, storePathNameRegex
1515
, -- * Rendering out 'StorePath's
1616
storePathToRawFilePath
17+
, storeDirVal
1718
, KnownStoreDir
1819
) where
1920

0 commit comments

Comments
 (0)