@@ -16,12 +16,13 @@ import System.Nix.Hash
1616 ( HashAlgorithm (Truncated , SHA256 )
1717 , Digest
1818 , encodeBase32
19+ , decodeBase32
1920 , SomeNamedDigest
2021 )
21- import Text.Regex.Base.RegexLike (makeRegex , matchTest )
22- import Text.Regex.TDFA.Text (Regex )
22+
2323import Data.Text (Text )
2424import Data.Text.Encoding (encodeUtf8 )
25+ import qualified Data.Text as T
2526import GHC.TypeLits (Symbol , KnownSymbol , symbolVal )
2627import Data.ByteString (ByteString )
2728import qualified Data.ByteString as BS
@@ -30,6 +31,9 @@ import Data.Hashable (Hashable(..))
3031import Data.HashSet (HashSet )
3132import Data.Proxy (Proxy (.. ))
3233
34+ import System.FilePath (splitFileName )
35+
36+ import Data.Char
3337-- | A path in a Nix store.
3438--
3539-- From the Nix thesis: A store path is the full path of a store
@@ -39,20 +43,25 @@ import Data.Proxy (Proxy(..))
3943--
4044-- See the 'StoreDir' haddocks for details on why we represent this at
4145-- the type level.
42- data StorePath ( storeDir :: StoreDir ) = StorePath
46+ data StorePath = StorePath
4347 { -- | The 160-bit hash digest reflecting the "address" of the name.
4448 -- Currently, this is a truncated SHA256 hash.
4549 storePathHash :: ! (Digest StorePathHashAlgo )
4650 , -- | The (typically human readable) name of the path. For packages
4751 -- this is typically the package name and version (e.g.
4852 -- hello-1.2.3).
4953 storePathName :: ! StorePathName
54+ , -- | Root of the store
55+ storePathRoot :: ! FilePath
5056 } deriving (Eq , Ord )
5157
52- instance Hashable ( StorePath storeDir ) where
58+ instance Hashable StorePath where
5359 hashWithSalt s (StorePath {.. }) =
5460 s `hashWithSalt` storePathHash `hashWithSalt` storePathName
5561
62+ instance Show StorePath where
63+ show p = BC. unpack $ storePathToRawFilePath p
64+
5665-- | The name portion of a Nix path.
5766--
5867-- 'unStorePathName' must only contain a-zA-Z0-9+._?=-, can't start
@@ -67,7 +76,7 @@ newtype StorePathName = StorePathName
6776type StorePathHashAlgo = 'Truncated 20 'SHA256
6877
6978-- | A set of 'StorePath's.
70- type StorePathSet storeDir = HashSet ( StorePath storeDir )
79+ type StorePathSet = HashSet StorePath
7180
7281-- | An address for a content-addressable store path, i.e. one whose
7382-- store path hash is purely a function of its contents (as opposed to
@@ -99,103 +108,67 @@ data NarHashMode
99108 -- file if so desired.
100109 Recursive
101110
102- -- | A type-level representation of the root directory of a Nix store.
103- --
104- -- The extra complexity of type indices requires justification.
105- -- Fundamentally, this boils down to the fact that there is little
106- -- meaningful sense in which 'StorePath's rooted at different
107- -- directories are of the same type, i.e. there are few if any
108- -- non-trivial non-contrived functions or data types that could
109- -- equally well accept 'StorePath's from different stores. In current
110- -- practice, any real application dealing with Nix stores (including,
111- -- in particular, the Nix expression language) only operates over one
112- -- store root and only cares about 'StorePath's belonging to that
113- -- root. One could imagine a use case that cares about multiple store
114- -- roots at once (e.g. the normal \/nix\/store along with some private
115- -- store at \/root\/nix\/store to contain secrets), but in that case
116- -- distinguishing 'StorePath's that belong to one store or the other
117- -- is even /more/ critical: Most operations will only be correct over
118- -- one of the stores or another, and it would be an error to mix and
119- -- match (e.g. a 'StorePath' in one store could not legitimately refer
120- -- to one in another).
121- --
122- -- As of @5886bc5996537fbf00d1fcfbb29595b8ccc9743e@, the C++ Nix
123- -- codebase contains 30 separate places where we assert that a given
124- -- store dir is, in fact, in the store we care about; those run-time
125- -- assertions could be completely removed if we had stronger types
126- -- there. Moreover, there are dozens of other cases where input coming
127- -- from the user, from serializations, etc. is parsed and then
128- -- required to be in the appropriate store; this case is the
129- -- equivalent of an existentially quantified version of 'StorePath'
130- -- and, notably, requiring at runtime that the index matches the
131- -- ambient store directory we're working in. In every case where a
132- -- path is treated as a store path, there is exactly one legitimate
133- -- candidate for the store directory it belongs to.
134- --
135- -- It may be instructive to consider the example of "chroot stores".
136- -- Since Nix 2.0, it has been possible to have a store actually live
137- -- at one directory (say, $HOME\/nix\/store) with a different
138- -- effective store directory (say, \/nix\/store). Nix can build into
139- -- a chroot store by running the builds in a mount namespace where the
140- -- store is at the effective store directory, can download from a
141- -- binary cache containing paths for the effective store directory,
142- -- and can run programs in the store that expect to be living at the
143- -- effective store directory (via nix run). When viewed as store paths
144- -- (rather than random files in the filesystem), paths in a chroot
145- -- store have nothing in common with paths in a non-chroot store that
146- -- lives in the same directory, and a lot in common with paths in a
147- -- non-chroot store that lives in the effective store directory of the
148- -- store in question. Store paths in stores with the same effective
149- -- store directory share the same hashing scheme, can be copied
150- -- between each other, etc. Store paths in stores with different
151- -- effective store directories have no relationship to each other that
152- -- they don't have to arbitrary other files.
153- type StoreDir = Symbol
154-
155- -- | Smart constructor for 'StorePathName' that ensures the underlying
156- -- content invariant is met.
157- makeStorePathName :: Text -> Maybe StorePathName
158- makeStorePathName n = case matchTest storePathNameRegex n of
159- True -> Just $ StorePathName n
160- False -> Nothing
161-
162- -- | Regular expression to match valid store path names.
163- storePathNameRegex :: Regex
164- storePathNameRegex = makeRegex r
111+ makeStorePathName :: Text -> Either String StorePathName
112+ makeStorePathName n = case validStorePathName n of
113+ True -> Right $ StorePathName n
114+ False -> Left $ reasonInvalid n
115+
116+ reasonInvalid n | n == " " = " Empty name"
117+ reasonInvalid n | (T. length n > 211 ) = " Path too long"
118+ reasonInvalid n | (T. head n == ' .' ) = " Leading dot"
119+ reasonInvalid n | otherwise = " Invalid character"
120+
121+ validStorePathName " " = False
122+ validStorePathName n = (T. length n <= 211 )
123+ && T. head n /= ' .'
124+ && T. all validChar n
165125 where
166- r :: String
167- r = " [a-zA-Z0-9\\ +\\ -\\ _\\ ?\\ =][a-zA-Z0-9\\ +\\ -\\ .\\ _\\ ?\\ =]*"
126+ validChar c = any ($ c) $
127+ [ isAsciiLower -- 'a'..'z'
128+ , isAsciiUpper -- 'A'..'Z'
129+ , isDigit
130+ ] ++
131+ map (==) " +-._?="
168132
169133-- | Copied from @RawFilePath@ in the @unix@ package, duplicated here
170134-- to avoid the dependency.
171135type RawFilePath = ByteString
172136
173137-- | Render a 'StorePath' as a 'RawFilePath'.
174138storePathToRawFilePath
175- :: forall storeDir . (KnownStoreDir storeDir )
176- => StorePath storeDir
139+ :: StorePath
177140 -> RawFilePath
178- storePathToRawFilePath ( StorePath {.. }) = BS. concat
141+ storePathToRawFilePath StorePath {.. } = BS. concat
179142 [ root
180143 , " /"
181144 , hashPart
182145 , " -"
183146 , name
184147 ]
185148 where
186- root = storeDirVal @ storeDir
149+ root = BC. pack storePathRoot
187150 hashPart = encodeUtf8 $ encodeBase32 storePathHash
188151 name = encodeUtf8 $ unStorePathName storePathName
189152
190- -- | Get a value-level representation of a 'KnownStoreDir'
191- storeDirVal :: forall storeDir . ( KnownStoreDir storeDir )
192- => ByteString
193- storeDirVal = BC. pack $ symbolVal @ storeDir Proxy
153+ storePathToNarinfo StorePath { .. } = BS. concat
154+ [ encodeUtf8 $ encodeBase32 storePathHash
155+ , " .narinfo "
156+ ]
194157
195- -- | A 'StoreDir' whose value is known at compile time.
196- --
197- -- A valid instance of 'KnownStoreDir' should represent a valid path,
198- -- i.e. all "characters" fit into bytes (as determined by the logic of
199- -- 'BC.pack') and there are no 0 "characters". Currently this is not
200- -- enforced, but it should be.
201- type KnownStoreDir = KnownSymbol
158+ -- | Parse `StorePath` from `BC.ByteString`, checking
159+ -- that store directory matches `expectedRoot`.
160+ parsePath :: FilePath -> BC. ByteString -> Either String StorePath
161+ parsePath expectedRoot x =
162+ let
163+ (rootDir, fname) = splitFileName . BC. unpack $ x
164+ (digestPart, namePart) = T. breakOn " -" $ T. pack fname
165+ digest = decodeBase32 digestPart
166+ name = makeStorePathName . T. drop 1 $ namePart
167+ -- rootDir' = dropTrailingPathSeparator rootDir
168+ -- cannot use ^^ as it drops multiple slashes /a/b/// -> /a/b
169+ rootDir' = init rootDir
170+ storeDir = if expectedRoot == rootDir'
171+ then Right rootDir'
172+ else Left $ unwords $ [ " Root store dir mismatch, expected " , expectedRoot, " got" , rootDir']
173+ in
174+ StorePath <$> digest <*> name <*> storeDir
0 commit comments