Skip to content

Commit 6e1e6fc

Browse files
committed
Add System.Nix.StorePath, successor to System.Nix.Path.
The new type acknowledges the store root, and is better named. Future work will migrate all dependents and retire the old module.
1 parent d26c592 commit 6e1e6fc

File tree

3 files changed

+163
-1
lines changed

3 files changed

+163
-1
lines changed

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

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
name: hnix-store-core
2-
version: 0.1.0.0
2+
version: 0.1.1.0
33
synopsis: Core effects for interacting with the Nix store.
44
description:
55
This package contains types and functions needed to describe
@@ -23,10 +23,12 @@ library
2323
, System.Nix.GC
2424
, System.Nix.Hash
2525
, System.Nix.Internal.Hash
26+
, System.Nix.Internal.StorePath
2627
, System.Nix.Nar
2728
, System.Nix.Path
2829
, System.Nix.ReadonlyStore
2930
, System.Nix.Store
31+
, System.Nix.StorePath
3032
, System.Nix.Util
3133
build-depends: base >=4.10 && <5
3234
, base16-bytestring
Lines changed: 141 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,141 @@
1+
{-|
2+
Description : Representation of Nix store paths.
3+
-}
4+
{-# LANGUAGE DataKinds #-}
5+
{-# LANGUAGE OverloadedStrings #-}
6+
{-# LANGUAGE KindSignatures #-}
7+
{-# LANGUAGE ConstraintKinds #-}
8+
{-# LANGUAGE RecordWildCards #-}
9+
module System.Nix.Internal.StorePath where
10+
import System.Nix.Hash (HashAlgorithm(Truncated, SHA256), Digest, encodeBase32)
11+
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
12+
import Text.Regex.TDFA.Text (Regex)
13+
import Data.Text (Text)
14+
import Data.Text.Encoding (encodeUtf8)
15+
import GHC.TypeLits (Symbol, KnownSymbol, symbolVal)
16+
import Data.ByteString (ByteString)
17+
import qualified Data.ByteString as BS
18+
import qualified Data.ByteString.Char8 as BC
19+
20+
-- | A path in a Nix store.
21+
--
22+
-- From the Nix thesis: A store path is the full path of a store
23+
-- object. It has the following anatomy: storeDir/hashPart-name.
24+
--
25+
-- @storeDir@: The root of the Nix store (e.g. \/nix\/store).
26+
--
27+
-- See the 'StoreDir' haddocks for details on why we represent this at
28+
-- the type level.
29+
data StorePath (storeDir :: StoreDir) = StorePath
30+
{ -- | The 160-bit hash digest reflecting the "address" of the name.
31+
-- Currently, this is a truncated SHA256 hash.
32+
storePathHash :: !(Digest StorePathHashAlgo)
33+
, -- | The (typically human readable) name of the path. For packages
34+
-- this is typically the package name and version (e.g.
35+
-- hello-1.2.3).
36+
storePathName :: !StorePathName
37+
}
38+
39+
-- | The name portion of a Nix path.
40+
--
41+
-- 'unStorePathName' must only contain a-zA-Z0-9+._?=-, can't start
42+
-- with a -, and must have at least one character (i.e. it must match
43+
-- 'storePathNameRegex').
44+
newtype StorePathName = StorePathName
45+
{ -- | Extract the contents of the name.
46+
unStorePathName :: Text
47+
}
48+
49+
-- | The hash algorithm used for store path hashes.
50+
type StorePathHashAlgo = 'Truncated 20 'SHA256
51+
52+
-- | A type-level representation of the root directory of a Nix store.
53+
--
54+
-- The extra complexity of type indices requires justification.
55+
-- Fundamentally, this boils down to the fact that there is little
56+
-- meaningful sense in which 'StorePath's rooted at different
57+
-- directories are of the same type, i.e. there are few if any
58+
-- non-trivial non-contrived functions or data types that could
59+
-- equally well accept 'StorePath's from different stores. In current
60+
-- practice, any real application dealing with Nix stores (including,
61+
-- in particular, the Nix expression language) only operates over one
62+
-- store root and only cares about 'StorePath's belonging to that
63+
-- root. One could imagine a use case that cares about multiple store
64+
-- roots at once (e.g. the normal \/nix\/store along with some private
65+
-- store at \/root\/nix\/store to contain secrets), but in that case
66+
-- distinguishing 'StorePath's that belong to one store or the other
67+
-- is even /more/ critical: Most operations will only be correct over
68+
-- one of the stores or another, and it would be an error to mix and
69+
-- match (e.g. a 'StorePath' in one store could not legitimately refer
70+
-- to one in another).
71+
--
72+
-- As of @5886bc5996537fbf00d1fcfbb29595b8ccc9743e@, the C++ Nix
73+
-- codebase contains 30 separate places where we assert that a given
74+
-- store dir is, in fact, in the store we care about; those run-time
75+
-- assertions could be completely removed if we had stronger types
76+
-- there. Moreover, there are dozens of other cases where input coming
77+
-- from the user, from serializations, etc. is parsed and then
78+
-- required to be in the appropriate store; this case is the
79+
-- equivalent of an existentially quantified version of 'StorePath'
80+
-- and, notably, requiring at runtime that the index matches the
81+
-- ambient store directory we're working in. In every case where a
82+
-- path is treated as a store path, there is exactly one legitimate
83+
-- candidate for the store directory it belongs to.
84+
--
85+
-- It may be instructive to consider the example of "chroot stores".
86+
-- Since Nix 2.0, it has been possible to have a store actually live
87+
-- at one directory (say, $HOME\/nix\/store) with a different
88+
-- effective store directory (say, \/nix\/store). Nix can build into
89+
-- a chroot store by running the builds in a mount namespace where the
90+
-- store is at the effective store directory, can download from a
91+
-- binary cache containing paths for the effective store directory,
92+
-- and can run programs in the store that expect to be living at the
93+
-- effective store directory (via nix run). When viewed as store paths
94+
-- (rather than random files in the filesystem), paths in a chroot
95+
-- store have nothing in common with paths in a non-chroot store that
96+
-- lives in the same directory, and a lot in common with paths in a
97+
-- non-chroot store that lives in the effective store directory of the
98+
-- store in question. Store paths in stores with the same effective
99+
-- store directory share the same hashing scheme, can be copied
100+
-- between each other, etc. Store paths in stores with different
101+
-- effective store directories have no relationship to each other that
102+
-- they don't have to arbitrary other files.
103+
type StoreDir = Symbol
104+
105+
-- | Smart constructor for 'StorePathName' that ensures the underlying
106+
-- content invariant is met.
107+
makeStorePathName :: Text -> Maybe StorePathName
108+
makeStorePathName n = case matchTest storePathNameRegex n of
109+
True -> Just $ StorePathName n
110+
False -> Nothing
111+
112+
-- | Regular expression to match valid store path names.
113+
storePathNameRegex :: Regex
114+
storePathNameRegex = makeRegex r
115+
where
116+
r :: String
117+
r = "[a-zA-Z0-9\\+\\-\\_\\?\\=][a-zA-Z0-9\\+\\-\\.\\_\\?\\=]*"
118+
119+
-- | Copied from @RawFilePath@ in the @unix@ package, duplicated here
120+
-- to avoid the dependency.
121+
type RawFilePath = ByteString
122+
123+
-- | Render a 'StorePath' as a 'RawFilePath'.
124+
storePathToRawFilePath
125+
:: (KnownStoreDir storeDir)
126+
=> StorePath storeDir
127+
-> RawFilePath
128+
storePathToRawFilePath s@(StorePath {..}) = BS.concat
129+
[ root
130+
, "/"
131+
, hashPart
132+
, "-"
133+
, name
134+
]
135+
where
136+
root = BC.pack $ symbolVal s
137+
hashPart = encodeUtf8 $ encodeBase32 storePathHash
138+
name = encodeUtf8 $ unStorePathName storePathName
139+
140+
-- | A 'StoreDir' whose value is known at compile time.
141+
type KnownStoreDir = KnownSymbol
Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
{-|
2+
Description : Representation of Nix store paths.
3+
-}
4+
module System.Nix.StorePath
5+
( -- * Basic store path types
6+
StorePath(..)
7+
, StorePathName
8+
, StorePathHashAlgo
9+
, StoreDir
10+
, -- * Manipulating 'StorePathName'
11+
makeStorePathName
12+
, unStorePathName
13+
, storePathNameRegex
14+
, -- * Rendering out 'StorePath's
15+
storePathToRawFilePath
16+
, KnownStoreDir
17+
) where
18+
19+
import System.Nix.Internal.StorePath

0 commit comments

Comments
 (0)