Skip to content

Commit 0ea7647

Browse files
vaibhavsagarshlevy
andcommitted
Replace permissions with narIsExec effect
Co-Authored-By: Shea Levy <[email protected]>
1 parent 11797c6 commit 0ea7647

File tree

3 files changed

+23
-34
lines changed

3 files changed

+23
-34
lines changed

hnix-store-nar/src/System/Nix/Nar/Effects.hs

Lines changed: 18 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -3,11 +3,13 @@
33
module System.Nix.Nar.Effects
44
( NarEffects(..)
55
, narEffectsIO
6+
, IsExecutable(..)
67
) where
78

89
import Control.Monad.Trans.Control (MonadBaseControl)
910
import Control.Monad.IO.Class (MonadIO(liftIO))
1011
import Data.ByteString (ByteString)
12+
import Data.Bool (bool)
1113
import Data.Int (Int64)
1214
import Data.Kind (Type)
1315
import System.IO (Handle, IOMode(WriteMode))
@@ -25,15 +27,17 @@ import System.Posix.Files ( createSymbolicLink
2527
import qualified System.IO as IO
2628
import qualified Control.Exception.Lifted as Exception.Lifted
2729

30+
data IsExecutable = NonExecutable | Executable
31+
deriving (Eq, Show)
32+
2833
data NarEffects (m :: Type -> Type) = NarEffects {
2934
narReadFile :: FilePath -> m Bytes.Lazy.ByteString
30-
, narWriteFile :: FilePath -> Bytes.Lazy.ByteString -> m ()
31-
, narStreamFile :: FilePath -> m (Maybe ByteString) -> m ()
35+
, narWriteFile :: FilePath -> IsExecutable -> Bytes.Lazy.ByteString -> m ()
36+
, narStreamFile :: FilePath -> IsExecutable -> m (Maybe ByteString) -> m ()
3237
, narListDir :: FilePath -> m [FilePath]
3338
, narCreateDir :: FilePath -> m ()
3439
, narCreateLink :: FilePath -> FilePath -> m ()
35-
, narGetPerms :: FilePath -> m Directory.Permissions
36-
, narSetPerms :: FilePath -> Directory.Permissions -> m ()
40+
, narIsExec :: FilePath -> m IsExecutable
3741
, narIsDir :: FilePath -> m Bool
3842
, narIsSymLink :: FilePath -> m Bool
3943
, narFileSize :: FilePath -> m Int64
@@ -53,13 +57,15 @@ narEffectsIO
5357
=> NarEffects m
5458
narEffectsIO = NarEffects {
5559
narReadFile = liftIO . Bytes.Lazy.readFile
56-
, narWriteFile = \a -> liftIO . Bytes.Lazy.writeFile a
60+
, narWriteFile = \f e c -> liftIO $ do
61+
Bytes.Lazy.writeFile f c
62+
p <- Directory.getPermissions f
63+
Directory.setPermissions f (p { Directory.executable = e == Executable })
5764
, narStreamFile = streamStringOutIO
5865
, narListDir = liftIO . Directory.listDirectory
5966
, narCreateDir = liftIO . Directory.createDirectory
6067
, narCreateLink = \f -> liftIO . createSymbolicLink f
61-
, narGetPerms = liftIO . Directory.getPermissions
62-
, narSetPerms = \f -> liftIO . Directory.setPermissions f
68+
, narIsExec = liftIO . (fmap (bool NonExecutable Executable . Directory.executable)) . Directory.getPermissions
6369
, narIsDir = fmap isDirectory . liftIO . getFileStatus
6470
, narIsSymLink = liftIO . Directory.pathIsSymbolicLink
6571
, narFileSize = fmap (fromIntegral . fileSize) . liftIO . getFileStatus
@@ -76,9 +82,10 @@ streamStringOutIO
7682
, MonadBaseControl IO m
7783
)
7884
=> FilePath
85+
-> IsExecutable
7986
-> m (Maybe ByteString)
8087
-> m ()
81-
streamStringOutIO f getChunk =
88+
streamStringOutIO f executable getChunk =
8289
Exception.Lifted.bracket
8390
(liftIO $ IO.openFile f WriteMode)
8491
(liftIO . IO.hClose)
@@ -93,6 +100,9 @@ streamStringOutIO f getChunk =
93100
Nothing -> pure ()
94101
Just c -> do
95102
liftIO $ Data.ByteString.hPut handle c
103+
Control.Monad.when (executable == Executable) $ liftIO $ do
104+
p <- Directory.getPermissions f
105+
Directory.setPermissions f (p { Directory.executable = True })
96106
go handle
97107
cleanupException (e :: Exception.Lifted.SomeException) = do
98108
liftIO $ Directory.removeFile f

hnix-store-nar/src/System/Nix/Nar/Parser.hs

Lines changed: 2 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -268,13 +268,8 @@ parseFile = do
268268

269269
target <- currentFile
270270
streamFile <- getNarEffect Nar.narStreamFile
271-
Trans.lift (streamFile target getChunk)
272-
273-
when (s == "executable") $ do
274-
effs :: Nar.NarEffects m <- getNarEffects
275-
Trans.lift $ do
276-
p <- Nar.narGetPerms effs target
277-
Nar.narSetPerms effs target (p { Directory.executable = True })
271+
let isExecutable = bool Nar.NonExecutable Nar.Executable (s == "executable")
272+
Trans.lift (streamFile target isExecutable getChunk)
278273

279274
expectRawString (Bytes.replicate (padLen $ fromIntegral fSize) 0)
280275

hnix-store-nar/src/System/Nix/Nar/Streamer.hs

Lines changed: 3 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ module System.Nix.Nar.Streamer
77
, dumpPath
88
, streamNarIO
99
, streamNarIOWithOptions
10-
, IsExecutable(..)
10+
, Nar.IsExecutable(..)
1111
) where
1212

1313
import Data.ByteString (ByteString)
@@ -18,15 +18,13 @@ import Control.Monad ( forM_
1818
, when
1919
)
2020
import qualified Control.Monad.IO.Class as IO
21-
import Data.Bool ( bool )
2221
import qualified Data.ByteString as Bytes
2322
import qualified Data.ByteString.Lazy as Bytes.Lazy
2423
import qualified Data.Foldable
2524
import qualified Data.List
2625
import qualified Data.Serialize as Serial
2726
import qualified Data.Text as T (pack, breakOn)
2827
import qualified Data.Text.Encoding as TE (encodeUtf8)
29-
import qualified System.Directory as Directory
3028
import System.FilePath ((</>))
3129

3230
import qualified System.Nix.Nar.Effects as Nar
@@ -107,9 +105,9 @@ streamNarIOWithOptions opts effs basePath yield = do
107105
yield $ strs ["name", serializedPath, "node"]
108106
parens $ go fullName
109107
else do
110-
isExec <- IO.liftIO $ isExecutable effs path
108+
isExec <- IO.liftIO $ Nar.narIsExec effs path
111109
yield $ strs ["type", "regular"]
112-
when (isExec == Executable) $ yield $ strs ["executable", ""]
110+
when (isExec == Nar.Executable) $ yield $ strs ["executable", ""]
113111
fSize <- IO.liftIO $ Nar.narFileSize effs path
114112
yield $ str "contents"
115113
yield $ int fSize
@@ -127,20 +125,6 @@ streamNarIOWithOptions opts effs basePath yield = do
127125
mapM_ yield . Bytes.Lazy.toChunks =<< IO.liftIO (Nar.narReadFile effs path)
128126
yield $ Bytes.replicate (padLen $ fromIntegral fsize) 0
129127

130-
data IsExecutable = NonExecutable | Executable
131-
deriving (Eq, Show)
132-
133-
isExecutable
134-
:: Functor m
135-
=> Nar.NarEffects m
136-
-> FilePath
137-
-> m IsExecutable
138-
isExecutable effs fp =
139-
bool
140-
NonExecutable
141-
Executable
142-
. Directory.executable <$> Nar.narGetPerms effs fp
143-
144128
-- | Distance to the next multiple of 8
145129
padLen :: Int -> Int
146130
padLen n = (8 - n) `mod` 8

0 commit comments

Comments
 (0)