Skip to content

Commit

Permalink
Merge pull request #282 from sandydoo/fix-executable-perms
Browse files Browse the repository at this point in the history
nar: fix executable permissions logic
  • Loading branch information
sorki authored Jul 30, 2024
2 parents 1525aef + b6ab60c commit c105037
Show file tree
Hide file tree
Showing 3 changed files with 71 additions and 8 deletions.
1 change: 1 addition & 0 deletions hnix-store-nar/hnix-store-nar.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ test-suite nar
tasty-discover:tasty-discover
build-depends:
base
, cryptonite
, hnix-store-nar
, base64-bytestring
, cereal
Expand Down
49 changes: 43 additions & 6 deletions hnix-store-nar/src/System/Nix/Nar/Effects.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,8 @@ module System.Nix.Nar.Effects
( NarEffects(..)
, narEffectsIO
, IsExecutable(..)
, isExecutable
, setExecutable
) where

import Control.Monad.Trans.Control (MonadBaseControl)
Expand All @@ -19,10 +21,21 @@ import qualified Data.ByteString
import qualified Data.ByteString.Lazy as Bytes.Lazy
import qualified System.Directory as Directory
import System.Posix.Files ( createSymbolicLink
, fileMode
, fileSize
, FileStatus
, getFileStatus
, getSymbolicLinkStatus
, groupExecuteMode
, intersectFileModes
, isDirectory
, isRegularFile
, nullFileMode
, otherExecuteMode
, ownerExecuteMode
, readSymbolicLink
, setFileMode
, unionFileModes
)
import qualified System.IO as IO
import qualified Control.Exception.Lifted as Exception.Lifted
Expand Down Expand Up @@ -59,13 +72,13 @@ narEffectsIO = NarEffects {
narReadFile = liftIO . Bytes.Lazy.readFile
, narWriteFile = \f e c -> liftIO $ do
Bytes.Lazy.writeFile f c
p <- Directory.getPermissions f
Directory.setPermissions f (p { Directory.executable = e == Executable })
Control.Monad.when (e == Executable) $
setExecutable f
, narStreamFile = streamStringOutIO
, narListDir = liftIO . Directory.listDirectory
, narCreateDir = liftIO . Directory.createDirectory
, narCreateLink = \f -> liftIO . createSymbolicLink f
, narIsExec = liftIO . (fmap (bool NonExecutable Executable . Directory.executable)) . Directory.getPermissions
, narIsExec = liftIO . fmap (bool NonExecutable Executable . isExecutable) . getSymbolicLinkStatus
, narIsDir = fmap isDirectory . liftIO . getFileStatus
, narIsSymLink = liftIO . Directory.pathIsSymbolicLink
, narFileSize = fmap (fromIntegral . fileSize) . liftIO . getFileStatus
Expand Down Expand Up @@ -102,10 +115,34 @@ streamStringOutIO f executable getChunk =
liftIO $ Data.ByteString.hPut handle c
go handle
updateExecutablePermissions =
Control.Monad.when (executable == Executable) $ do
p <- Directory.getPermissions f
Directory.setPermissions f (p { Directory.executable = True })
Control.Monad.when (executable == Executable) $
setExecutable f
cleanupException (e :: Exception.Lifted.SomeException) = do
liftIO $ Directory.removeFile f
Control.Monad.fail $
"Failed to stream string to " <> f <> ": " <> show e

-- | Check whether the file is executable by the owner.
--
-- Matches the logic used by Nix.
--
-- access() should not be used for this purpose on macOS.
-- It returns false for executables when placed in certain directories.
-- For example, when in an app bundle: App.app/Contents/Resources/en.lproj/myexecutable.strings
isExecutable :: FileStatus -> Bool
isExecutable st =
isRegularFile st
&& fileMode st `intersectFileModes` ownerExecuteMode /= nullFileMode

-- | Set the file to be executable by the owner, group, and others.
--
-- Matches the logic used by Nix.
setExecutable :: FilePath -> IO ()
setExecutable f = do
st <- getSymbolicLinkStatus f
let p =
fileMode st
`unionFileModes` ownerExecuteMode
`unionFileModes` groupExecuteMode
`unionFileModes` otherExecuteMode
setFileMode f p
29 changes: 27 additions & 2 deletions hnix-store-nar/tests/NarFormat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ import Control.Applicative (many, optional, (<|>))
import qualified Control.Concurrent as Concurrent
import Control.Exception (SomeException, try)
import Control.Monad (replicateM, void, forM_, when)
import Crypto.Hash (hash, Digest, SHA256)
import Data.Serialize (Serialize(..))
import Data.Serialize (Get, getByteString,
getInt64le,
Expand Down Expand Up @@ -35,6 +36,7 @@ import System.Environment (getEnv)
import System.FilePath ((<.>), (</>))
import qualified System.IO as IO
import qualified System.IO.Temp as Temp
import qualified System.Posix.Files as Unix
import qualified System.Posix.Process as Unix
import qualified System.Process as P
import Test.Tasty as T
Expand Down Expand Up @@ -142,11 +144,19 @@ unit_nixStoreDirectory = filesystemNixStore "directory" (Nar sampleDirectory)
unit_nixStoreDirectory' :: HU.Assertion
unit_nixStoreDirectory' = filesystemNixStore "directory'" (Nar sampleDirectory')

-- | Test that the executable permissions are handled correctly in app bundles on macOS.
-- In this case, access() returns false for a file under this specific path, even when the executable bit is set.
-- NAR implementations should avoid this syscall on macOS.
test_nixStoreMacOSAppBundle :: TestTree
test_nixStoreMacOSAppBundle = packThenExtract "App.app" $ \ baseDir -> do
let testDir = baseDir </> "App.app" </> "Resources" </> "en.lproj"
Directory.createDirectoryIfMissing True testDir
mkExecutableFile (testDir </> "test.strings")

test_nixStoreBigFile :: TestTree
test_nixStoreBigFile = packThenExtract "bigfile" $ \baseDir -> do
mkBigFile (baseDir </> "bigfile")


test_nixStoreBigDir :: TestTree
test_nixStoreBigDir = packThenExtract "bigdir" $ \baseDir -> do
let testDir = baseDir </> "bigdir"
Expand Down Expand Up @@ -350,7 +360,16 @@ packThenExtract testName setup =
IO.withFile hnixNarFile IO.WriteMode $ \h ->
buildNarIO narEffectsIO narFilePath h

-- BSL.writeFile hnixNarFile narBS
-- Compare the hash digests of the two NARs
nixHash :: Digest SHA256 <- hash <$> BS.readFile nixNarFile
hnixHash :: Digest SHA256 <- hash <$> BS.readFile hnixNarFile
step $ unlines
[ "Compare SHA256 digests between NARs:"
, " nix: " <> show nixHash
, " hnix: " <> show hnixHash
]

HU.assertEqual "Hash mismatch between NARs" nixHash hnixHash

step $ "Unpack NAR to " <> outputFile
_narHandle <- IO.withFile nixNarFile IO.ReadMode $ \h ->
Expand Down Expand Up @@ -567,6 +586,12 @@ mkBigFile path = do
fsize <- getBigFileSize
BSL.writeFile path (BSL.take fsize $ BSL.cycle "Lorem ipsum")

mkExecutableFile :: FilePath -> IO ()
mkExecutableFile path = do
BSL.writeFile path ""
st <- Unix.getSymbolicLinkStatus path
let p = Unix.fileMode st `Unix.unionFileModes` Unix.ownerExecuteMode
Unix.setFileMode path p

-- | Construct FilePathPart from Text by checking that there
-- are no '/' or '\\NUL' characters
Expand Down

0 comments on commit c105037

Please sign in to comment.