git-annex/Utility/FileMode.hs

188 lines
5.6 KiB
Haskell
Raw Normal View History

2011-09-23 22:13:24 +00:00
{- File mode utilities.
-
- Copyright 2010-2023 Joey Hess <id@joeyh.name>
2011-09-23 22:13:24 +00:00
-
- License: BSD-2-clause
2011-09-23 22:13:24 +00:00
-}
2013-05-10 21:29:59 +00:00
{-# LANGUAGE CPP #-}
2020-09-07 19:10:09 +00:00
{-# OPTIONS_GHC -fno-warn-tabs #-}
2013-05-10 21:29:59 +00:00
2015-10-08 18:26:21 +00:00
module Utility.FileMode (
2015-10-12 19:08:17 +00:00
module Utility.FileMode,
2015-10-08 18:26:21 +00:00
FileMode,
) where
2011-09-23 22:13:24 +00:00
import System.IO
import Control.Monad
import System.PosixCompat.Types
2023-03-27 16:17:55 +00:00
import System.PosixCompat.Files (unionFileModes, intersectFileModes, stdFileMode, nullFileMode, groupReadMode, ownerReadMode, ownerWriteMode, ownerExecuteMode, groupWriteMode, groupExecuteMode, otherReadMode, otherWriteMode, otherExecuteMode, fileMode)
2023-03-21 22:22:41 +00:00
#ifndef mingw32_HOST_OS
import System.PosixCompat.Files (setFileCreationMask)
#endif
import Control.Monad.IO.Class
2011-09-23 22:13:24 +00:00
import Foreign (complement)
2015-11-12 22:03:49 +00:00
import Control.Monad.Catch
2011-09-23 22:13:24 +00:00
import Utility.Exception
import Utility.FileSystemEncoding
import qualified Utility.RawFilePath as R
{- Applies a conversion function to a file's mode. -}
modifyFileMode :: RawFilePath -> (FileMode -> FileMode) -> IO ()
modifyFileMode f convert = void $ modifyFileMode' f convert
modifyFileMode' :: RawFilePath -> (FileMode -> FileMode) -> IO FileMode
modifyFileMode' f convert = do
s <- R.getFileStatus f
let old = fileMode s
let new = convert old
when (new /= old) $
R.setFileMode f new
return old
{- Runs an action after changing a file's mode, then restores the old mode. -}
withModifiedFileMode :: RawFilePath -> (FileMode -> FileMode) -> IO a -> IO a
withModifiedFileMode file convert a = bracket setup cleanup go
where
setup = modifyFileMode' file convert
cleanup oldmode = modifyFileMode file (const oldmode)
go _ = a
2012-04-21 20:01:56 +00:00
{- Adds the specified FileModes to the input mode, leaving the rest
- unchanged. -}
addModes :: [FileMode] -> FileMode -> FileMode
addModes ms m = combineModes (m:ms)
{- Removes the specified FileModes from the input mode. -}
removeModes :: [FileMode] -> FileMode -> FileMode
removeModes ms m = m `intersectFileModes` complement (combineModes ms)
writeModes :: [FileMode]
writeModes = [ownerWriteMode, groupWriteMode, otherWriteMode]
readModes :: [FileMode]
readModes = [ownerReadMode, groupReadMode, otherReadMode]
2011-09-23 22:13:24 +00:00
executeModes :: [FileMode]
executeModes = [ownerExecuteMode, groupExecuteMode, otherExecuteMode]
2014-04-01 00:15:16 +00:00
otherGroupModes :: [FileMode]
otherGroupModes =
[ groupReadMode, otherReadMode
, groupWriteMode, otherWriteMode
, groupExecuteMode, otherExecuteMode
2014-04-01 00:15:16 +00:00
]
2011-09-23 22:13:24 +00:00
{- Removes the write bits from a file. -}
preventWrite :: RawFilePath -> IO ()
2012-04-21 20:01:56 +00:00
preventWrite f = modifyFileMode f $ removeModes writeModes
2011-09-23 22:13:24 +00:00
2012-04-21 20:01:56 +00:00
{- Turns a file's owner write bit back on. -}
allowWrite :: RawFilePath -> IO ()
2012-04-21 20:01:56 +00:00
allowWrite f = modifyFileMode f $ addModes [ownerWriteMode]
2013-11-20 17:42:13 +00:00
{- Turns a file's owner read bit back on. -}
allowRead :: RawFilePath -> IO ()
2013-11-20 17:42:13 +00:00
allowRead f = modifyFileMode f $ addModes [ownerReadMode]
{- Allows owner and group to read and write to a file. -}
groupSharedModes :: [FileMode]
groupSharedModes =
2012-04-21 20:01:56 +00:00
[ ownerWriteMode, groupWriteMode
, ownerReadMode, groupReadMode
]
groupWriteRead :: RawFilePath -> IO ()
groupWriteRead f = modifyFileMode f $ addModes groupSharedModes
checkMode :: FileMode -> FileMode -> Bool
checkMode checkfor mode = checkfor `intersectFileModes` mode == checkfor
2012-03-14 16:17:38 +00:00
{- Checks if a file has any executable bits set. -}
isExecutable :: FileMode -> Bool
isExecutable mode = combineModes executeModes `intersectFileModes` mode /= 0
2012-04-21 20:01:56 +00:00
data ModeSetter = ModeSetter FileMode (RawFilePath -> IO ())
{- Runs an action which should create the file, passing it the desired
- initial file mode. Then runs the ModeSetter's action on the file, which
- can adjust the initial mode if umask prevented the file from being
- created with the right mode. -}
applyModeSetter :: Maybe ModeSetter -> RawFilePath -> (Maybe FileMode -> IO a) -> IO a
applyModeSetter (Just (ModeSetter mode modeaction)) file a = do
r <- a (Just mode)
void $ tryIO $ modeaction file
return r
applyModeSetter Nothing _ a =
a Nothing
2015-11-12 22:03:49 +00:00
withUmask :: (MonadIO m, MonadMask m) => FileMode -> m a -> m a
#ifndef mingw32_HOST_OS
withUmask umask a = bracket setup cleanup go
2012-12-13 04:24:19 +00:00
where
2015-11-12 22:03:49 +00:00
setup = liftIO $ setFileCreationMask umask
cleanup = liftIO . setFileCreationMask
2012-12-13 04:24:19 +00:00
go _ = a
2013-05-10 21:29:59 +00:00
#else
withUmask _ a = a
2013-05-10 21:29:59 +00:00
#endif
getUmask :: IO FileMode
#ifndef mingw32_HOST_OS
getUmask = bracket setup cleanup return
where
setup = setFileCreationMask nullFileMode
cleanup = setFileCreationMask
#else
getUmask = return nullFileMode
#endif
defaultFileMode :: IO FileMode
defaultFileMode = do
umask <- getUmask
return $ intersectFileModes (complement umask) stdFileMode
2012-04-21 20:01:56 +00:00
combineModes :: [FileMode] -> FileMode
2015-04-29 18:15:08 +00:00
combineModes [] = 0
2012-04-21 20:01:56 +00:00
combineModes [m] = m
combineModes (m:ms) = foldl unionFileModes m ms
isSticky :: FileMode -> Bool
#ifdef mingw32_HOST_OS
isSticky _ = False
2013-05-10 21:29:59 +00:00
#else
isSticky = checkMode stickyMode
stickyMode :: FileMode
stickyMode = 512
setSticky :: RawFilePath -> IO ()
setSticky f = modifyFileMode f $ addModes [stickyMode]
#endif
{- Writes a file, ensuring that its modes do not allow it to be read
- or written by anyone other than the current user,
- before any content is written.
-
- When possible, this is done using the umask.
-
- On a filesystem that does not support file permissions, this is the same
- as writeFile.
-}
writeFileProtected :: RawFilePath -> String -> IO ()
writeFileProtected file content = writeFileProtected' file
(\h -> hPutStr h content)
writeFileProtected' :: RawFilePath -> (Handle -> IO ()) -> IO ()
writeFileProtected' file writer = bracket setup cleanup writer
where
setup = do
h <- protectedOutput $ openFile (fromRawFilePath file) WriteMode
void $ tryIO $ modifyFileMode file $ removeModes otherGroupModes
return h
cleanup = hClose
protectedOutput :: IO a -> IO a
protectedOutput = withUmask 0o0077