Skip to content

Commit 2075aae

Browse files
authored
Merge pull request #7 from imalsogreg/master
NAR parser/generator
2 parents 262cdc7 + 7f1928e commit 2075aae

File tree

8 files changed

+773
-54
lines changed

8 files changed

+773
-54
lines changed

hnix-store-core/.ghci

+1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
:set -itests

hnix-store-core/README.md

+6
Original file line numberDiff line numberDiff line change
@@ -7,3 +7,9 @@ See `StoreEffects` in [System.Nix.Store] for the available operations
77
on the store.
88

99
[System.Nix.Store]: ./src/System/Nix/Store.hs
10+
11+
12+
Tests
13+
======
14+
15+
- `ghcid --command "cabal repl test-suite:format-tests" --test="Main.main"`

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

+48-6
Original file line numberDiff line numberDiff line change
@@ -17,11 +17,53 @@ extra-source-files: ChangeLog.md, README.md
1717
cabal-version: >=1.10
1818

1919
library
20-
exposed-modules: Crypto.Hash.Truncated, System.Nix.Store
21-
build-depends: base >=4.10 && <4.11,
22-
-- Drop foundation when we can drop cryptonite <0.25
23-
cryptonite, memory, foundation, basement,
24-
text, regex-base, regex-tdfa-text,
25-
hashable, unordered-containers, bytestring
20+
exposed-modules: Crypto.Hash.Truncated
21+
, System.Nix.Nar
22+
, System.Nix.Path
23+
, System.Nix.Store
24+
build-depends: base >=4.10 && <4.11
25+
, basement
26+
, bytestring
27+
, binary
28+
, bytestring
29+
, containers
30+
, cryptonite
31+
, directory
32+
, filepath
33+
-- Drop foundation when we can drop cryptonite <0.25
34+
, foundation
35+
, hashable
36+
, memory
37+
, mtl
38+
, regex-base
39+
, regex-tdfa-text
40+
, text
41+
, unix
42+
, unordered-containers
2643
hs-source-dirs: src
2744
default-language: Haskell2010
45+
46+
test-suite format-tests
47+
ghc-options: -rtsopts -fprof-auto
48+
type: exitcode-stdio-1.0
49+
main-is: Driver.hs
50+
other-modules:
51+
NarFormat
52+
hs-source-dirs:
53+
tests
54+
build-depends:
55+
hnix-store-core
56+
, base
57+
, base64-bytestring
58+
, binary
59+
, bytestring
60+
, containers
61+
, directory
62+
, process
63+
, tasty
64+
, tasty-discover
65+
, tasty-hspec
66+
, tasty-hunit
67+
, tasty-quickcheck
68+
, text
69+
default-language: Haskell2010

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

+267
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,267 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE KindSignatures #-}
3+
{-# LANGUAGE OverloadedStrings #-}
4+
{-# LANGUAGE ScopedTypeVariables #-}
5+
{-# LANGUAGE TupleSections #-}
6+
{-# LANGUAGE TypeApplications #-}
7+
8+
{-|
9+
Description : Allowed effects for interacting with Nar files.
10+
Maintainer : Shea Levy <[email protected]>
11+
|-}
12+
module System.Nix.Nar (
13+
FileSystemObject(..)
14+
, IsExecutable (..)
15+
, Nar(..)
16+
, getNar
17+
, localPackNar
18+
, localUnpackNar
19+
, narEffectsIO
20+
, putNar
21+
) where
22+
23+
import Control.Applicative
24+
import Control.Monad (replicateM, replicateM_, (<=<))
25+
import qualified Data.Binary as B
26+
import qualified Data.Binary.Get as B
27+
import qualified Data.Binary.Put as B
28+
import Data.Bool (bool)
29+
import qualified Data.ByteString as BS
30+
import qualified Data.ByteString.Char8 as BSC
31+
import qualified Data.ByteString.Lazy as BSL
32+
import Data.Foldable (forM_)
33+
import qualified Data.Map as Map
34+
import Data.Maybe (fromMaybe)
35+
import Data.Monoid ((<>))
36+
import qualified Data.Text as T
37+
import qualified Data.Text.Encoding as E
38+
import Data.Traversable (forM)
39+
import GHC.Int (Int64)
40+
import System.Directory
41+
import System.FilePath
42+
import System.Posix.Files (createSymbolicLink, fileSize, getFileStatus,
43+
isDirectory, readSymbolicLink)
44+
45+
import System.Nix.Path
46+
47+
data NarEffects (m :: * -> *) = NarEffects {
48+
narReadFile :: FilePath -> m BSL.ByteString
49+
, narWriteFile :: FilePath -> BSL.ByteString -> m ()
50+
, narListDir :: FilePath -> m [FilePath]
51+
, narCreateDir :: FilePath -> m ()
52+
, narCreateLink :: FilePath -> FilePath -> m ()
53+
, narGetPerms :: FilePath -> m Permissions
54+
, narSetPerms :: FilePath -> Permissions -> m ()
55+
, narIsDir :: FilePath -> m Bool
56+
, narIsSymLink :: FilePath -> m Bool
57+
, narFileSize :: FilePath -> m Int64
58+
, narReadLink :: FilePath -> m FilePath
59+
}
60+
61+
62+
-- Directly taken from Eelco thesis
63+
-- https://nixos.org/%7Eeelco/pubs/phd-thesis.pdf
64+
65+
data Nar = Nar { narFile :: FileSystemObject }
66+
deriving (Eq, Show)
67+
68+
-- | A FileSystemObject (FSO) is an anonymous entity that can be NAR archived
69+
data FileSystemObject =
70+
Regular IsExecutable Int64 BSL.ByteString
71+
-- ^ Reguar file, with its executable state, size (bytes) and contents
72+
| Directory (Map.Map FilePathPart FileSystemObject)
73+
-- ^ Directory with mapping of filenames to sub-FSOs
74+
| SymLink T.Text
75+
-- ^ Symbolic link target
76+
deriving (Eq, Show)
77+
78+
79+
data IsExecutable = NonExecutable | Executable
80+
deriving (Eq, Show)
81+
82+
83+
instance B.Binary Nar where
84+
get = getNar
85+
put = putNar
86+
87+
------------------------------------------------------------------------------
88+
-- | Serialize Nar to lazy ByteString
89+
putNar :: Nar -> B.Put
90+
putNar (Nar file) = header <> parens (putFile file)
91+
where
92+
93+
header = str "nix-archive-1"
94+
95+
putFile (Regular isExec fSize contents) =
96+
strs ["type", "regular"]
97+
>> (if isExec == Executable
98+
then strs ["executable", ""]
99+
else return ())
100+
>> putContents fSize contents
101+
102+
putFile (SymLink target) =
103+
strs ["type", "symlink", "target", BSL.fromStrict $ E.encodeUtf8 target]
104+
105+
-- toList sorts the entries by FilePathPart before serializing
106+
putFile (Directory entries) =
107+
strs ["type", "directory"]
108+
<> mapM_ putEntry (Map.toList entries)
109+
110+
putEntry (FilePathPart name, fso) = do
111+
str "entry"
112+
parens $ do
113+
str "name"
114+
str (BSL.fromStrict name)
115+
str "node"
116+
parens (putFile fso)
117+
118+
parens m = str "(" >> m >> str ")"
119+
120+
-- Do not use this for file contents
121+
str :: BSL.ByteString -> B.Put
122+
str t = let len = BSL.length t
123+
in int len <> pad len t
124+
125+
putContents :: Int64 -> BSL.ByteString -> B.Put
126+
putContents fSize bs = str "contents" <> int fSize <> (pad fSize bs)
127+
-- putContents fSize bs = str "contents" <> int (BSL.length bs) <> (pad fSize bs)
128+
129+
int :: Integral a => a -> B.Put
130+
int n = B.putInt64le $ fromIntegral n
131+
132+
pad :: Int64 -> BSL.ByteString -> B.Put
133+
pad strSize bs = do
134+
B.putLazyByteString bs
135+
B.putLazyByteString (BSL.replicate (padLen strSize) 0)
136+
137+
strs :: [BSL.ByteString] -> B.Put
138+
strs = mapM_ str
139+
140+
141+
------------------------------------------------------------------------------
142+
-- | Deserialize a Nar from lazy ByteString
143+
getNar :: B.Get Nar
144+
getNar = fmap Nar $ header >> parens getFile
145+
where
146+
147+
header = assertStr "nix-archive-1"
148+
149+
150+
-- Fetch a FileSystemObject
151+
getFile = getRegularFile <|> getDirectory <|> getSymLink
152+
153+
getRegularFile = do
154+
assertStr "type"
155+
assertStr "regular"
156+
mExecutable <- optional $ Executable <$ (assertStr "executable"
157+
>> assertStr "")
158+
assertStr "contents"
159+
(fSize, contents) <- sizedStr
160+
return $ Regular (fromMaybe NonExecutable mExecutable) fSize contents
161+
162+
getDirectory = do
163+
assertStr "type"
164+
assertStr "directory"
165+
fs <- many getEntry
166+
return $ Directory (Map.fromList fs)
167+
168+
getSymLink = do
169+
assertStr "type"
170+
assertStr "symlink"
171+
assertStr "target"
172+
fmap (SymLink . E.decodeUtf8 . BSL.toStrict) str
173+
174+
getEntry = do
175+
assertStr "entry"
176+
parens $ do
177+
assertStr "name"
178+
name <- E.decodeUtf8 . BSL.toStrict <$> str
179+
assertStr "node"
180+
file <- parens getFile
181+
maybe (fail $ "Bad FilePathPart: " ++ show name)
182+
(return . (,file))
183+
(filePathPart $ E.encodeUtf8 name)
184+
185+
-- Fetch a length-prefixed, null-padded string
186+
str = fmap snd sizedStr
187+
188+
sizedStr = do
189+
n <- B.getInt64le
190+
s <- B.getLazyByteString n
191+
p <- B.getByteString . fromIntegral $ padLen n
192+
return (n,s)
193+
194+
parens m = assertStr "(" *> m <* assertStr ")"
195+
196+
assertStr s = do
197+
s' <- str
198+
if s == s'
199+
then return s
200+
else fail "No"
201+
202+
203+
-- | Distance to the next multiple of 8
204+
padLen :: Int64 -> Int64
205+
padLen n = (8 - n) `mod` 8
206+
207+
208+
-- | Unpack a NAR into a non-nix-store directory (e.g. for testing)
209+
localUnpackNar :: Monad m => NarEffects m -> FilePath -> Nar -> m ()
210+
localUnpackNar effs basePath (Nar fso) = localUnpackFSO basePath fso
211+
212+
where
213+
214+
localUnpackFSO basePath fso = case fso of
215+
216+
Regular isExec _ bs -> do
217+
(narWriteFile effs) basePath bs
218+
p <- narGetPerms effs basePath
219+
(narSetPerms effs) basePath (p {executable = isExec == Executable})
220+
221+
SymLink targ -> narCreateLink effs (T.unpack targ) basePath
222+
223+
Directory contents -> do
224+
narCreateDir effs basePath
225+
forM_ (Map.toList contents) $ \(FilePathPart path', fso) ->
226+
localUnpackFSO (basePath </> BSC.unpack path') fso
227+
228+
229+
-- | Pack a NAR from a filepath
230+
localPackNar :: Monad m => NarEffects m -> FilePath -> m Nar
231+
localPackNar effs basePath = Nar <$> localPackFSO basePath
232+
233+
where
234+
235+
localPackFSO path' = do
236+
fType <- (,) <$> narIsDir effs path' <*> narIsSymLink effs path'
237+
case fType of
238+
(_, True) -> SymLink . T.pack <$> narReadLink effs path'
239+
(False, _) -> Regular <$> isExecutable effs path'
240+
<*> narFileSize effs path'
241+
<*> narReadFile effs path'
242+
(True , _) -> fmap (Directory . Map.fromList) $ do
243+
fs <- narListDir effs path'
244+
forM fs $ \fp ->
245+
(FilePathPart (BSC.pack $ fp),) <$> localPackFSO (path' </> fp)
246+
247+
248+
249+
narEffectsIO :: NarEffects IO
250+
narEffectsIO = NarEffects {
251+
narReadFile = BSL.readFile
252+
, narWriteFile = BSL.writeFile
253+
, narListDir = listDirectory
254+
, narCreateDir = createDirectory
255+
, narCreateLink = createSymbolicLink
256+
, narGetPerms = getPermissions
257+
, narSetPerms = setPermissions
258+
, narIsDir = fmap isDirectory <$> getFileStatus
259+
, narIsSymLink = pathIsSymbolicLink
260+
, narFileSize = fmap (fromIntegral . fileSize) <$> getFileStatus
261+
, narReadLink = readSymbolicLink
262+
}
263+
264+
265+
isExecutable :: Functor m => NarEffects m -> FilePath -> m IsExecutable
266+
isExecutable effs fp =
267+
bool NonExecutable Executable . executable <$> narGetPerms effs fp

0 commit comments

Comments
 (0)