- than .git to be used.
-}
isLinkToAnnex :: S.ByteString -> Bool
-isLinkToAnnex s = p `OS.isInfixOf` (toOsPath s)
+isLinkToAnnex s = p `OS.isInfixOf` s'
#ifdef mingw32_HOST_OS
-- '/' is used inside pointer files on Windows, not the native '\'
- || p' `OS.isInfixOf` s
+ || p' `OS.isInfixOf` s'
#endif
where
+ s' = toOsPath s
p = pathSeparator `OS.cons` objectDir
#ifdef mingw32_HOST_OS
p' = toInternalGitPath p
import Utility.OpenFile
#endif
+#ifndef mingw32_HOST_OS
import Control.Concurrent
+#endif
import Control.Concurrent.STM
import Control.Concurrent.Async
import qualified Data.ByteString as B
( liftIO $ withNullHandle $ \nullh -> do
loghandle <- openLog (fromOsPath logfile)
e <- getEnvironment
- cmd <- programPath
+ cmd <- fromOsPath <$> programPath
ps <- getArgs
let p = (proc cmd ps)
{ env = Just (addEntry flag "1" e)
exitcode <- withCreateProcess p $ \_ _ _ pid ->
waitForProcess pid
exitWith exitcode
- , start (Utility.Daemon.foreground (Just (fromOsPath pidfile))) $
+ , start (Utility.Daemon.foreground (Just pidfile)) $
case startbrowser of
Nothing -> Nothing
Just a -> Just $ a Nothing Nothing
- A build of libmagic will also be included in the installer, if its files\r
- are found in the current directory: \r
- ./magic.mgc ./libmagic-1.dll ./libgnurx-0.dll\r
- - To build git-annex to usse libmagic, it has to be built with the\r
+ - To build git-annex to use libmagic, it has to be built with the\r
- magicmime build flag turned on.\r
-\r
- Copyright 2013-2020 Joey Hess <id@joeyh.name>\r
{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}\r
\r
import Development.NSIS\r
-import System.FilePath\r
import Control.Monad\r
import Control.Applicative\r
import Data.String\r
import Utility.Process\r
import Utility.Exception\r
import Utility.Directory\r
+import Utility.SystemDirectory\r
+import Utility.OsPath\r
import Build.BundledPrograms\r
\r
main = do\r
withTmpDir "nsis-build" $ \tmpdir -> do\r
- let gitannex = tmpdir </> gitannexprogram\r
+ let gitannex = fromOsPath $ tmpdir </> toOsPath gitannexprogram\r
mustSucceed "ln" [File "git-annex.exe", File gitannex]\r
magicDLLs' <- installwhenpresent magicDLLs tmpdir\r
magicShare' <- installwhenpresent magicShare tmpdir\r
- let license = tmpdir </> licensefile\r
+ let license = fromOsPath $ tmpdir </> toOsPath licensefile\r
mustSucceed "sh" [Param "-c", Param $ "zcat standalone/licences.gz > '" ++ license ++ "'"]\r
webappscript <- vbsLauncher tmpdir "git-annex-webapp" "git annex webapp"\r
autostartscript <- vbsLauncher tmpdir "git-annex-autostart" "git annex assistant --autostart"\r
- let htmlhelp = tmpdir </> "git-annex.html"\r
+ let htmlhelp = fromOsPath $ tmpdir </> literalOsPath "git-annex.html"\r
writeFile htmlhelp htmlHelpText\r
- let gitannexcmd = tmpdir </> "git-annex.cmd"\r
+ let gitannexcmd = fromOsPath $ tmpdir </> literalOsPath "git-annex.cmd"\r
writeFile gitannexcmd "git annex %*"\r
writeFile nsifile $ makeInstaller\r
gitannex gitannexcmd license htmlhelp (winPrograms ++ magicDLLs') magicShare'\r
[ webappscript, autostartscript ]\r
mustSucceed "makensis" [File nsifile]\r
- removeFile nsifile -- left behind if makensis fails\r
+ removeFile (toOsPath nsifile) -- left behind if makensis fails\r
where\r
nsifile = "git-annex.nsi"\r
mustSucceed cmd params = do\r
False -> error $ cmd ++ " failed"\r
installwhenpresent fs tmpdir = do\r
fs' <- forM fs $ \f -> do\r
- present <- doesFileExist f\r
+ present <- doesFileExist (toOsPath f)\r
if present\r
then do\r
- mustSucceed "ln" [File f, File (tmpdir </> f)]\r
+ mustSucceed "ln" [File f, File (fromOsPath (tmpdir </> toOsPath f))]\r
return (Just f)\r
else return Nothing\r
return (catMaybes fs')\r
\r
{- Generates a .vbs launcher which runs a command without any visible DOS\r
- box. It expects to be passed the directory where git-annex is installed. -}\r
-vbsLauncher :: FilePath -> String -> String -> IO String\r
+vbsLauncher :: OsPath -> String -> String -> IO String\r
vbsLauncher tmpdir basename cmd = do\r
- let f = tmpdir </> basename ++ ".vbs"\r
+ let f = fromOsPath $ tmpdir </> toOsPath (basename ++ ".vbs")\r
writeFile f $ unlines\r
[ "Set objshell=CreateObject(\"Wscript.Shell\")"\r
, "objShell.CurrentDirectory = Wscript.Arguments.item(0)"\r
removefilesFrom "$INSTDIR" [license, uninstaller]\r
where\r
addfile f = file [] (str f)\r
- removefilesFrom d = mapM_ (\f -> delete [RebootOK] $ fromString $ d ++ "/" ++ takeFileName f)\r
+ removefilesFrom d = mapM_ (\f -> delete [RebootOK] $ fromString $ d ++ "/" ++ fromOsPath (takeFileName (toOsPath f)))\r
\r
winPrograms :: [FilePath]\r
winPrograms = map (\p -> p ++ ".exe") bundledPrograms\r
#ifdef mingw32_HOST_OS
-- git on Windows will write a path to .git/config with "drive:",
-- which is not to be confused with a "host:"
- dosstyle = hasDrive
- dospath = fromRawFilePath . fromInternalGitPath . toRawFilePath
+ dosstyle = hasDrive . toOsPath
+ dospath = fromOsPath . fromInternalGitPath . toOsPath
#endif
insteadOfUrl :: String -> S.ByteString -> RepoFullConfig -> Maybe String
closeFd dupfd
bracketIO open close $ \(h, dupfd) -> do
#else
- let open = openBinaryFile f' ReadMode
+ let open = F.openBinaryFile f ReadMode
let close = hClose
bracketIO open close $ \h -> do
#endif
import qualified Utility.CopyFile
import qualified Utility.MoveFile
import qualified Utility.StatelessOpenPGP
-import qualified Utility.OsString as OS
import qualified Types.Remote
#ifndef mingw32_HOST_OS
+import qualified Utility.OsString as OS
import qualified Remote.Helper.Encryptable
import qualified Types.Crypto
import qualified Utility.Gpg
where
check Nothing = return Nothing
check (Just pid) = do
- v <- lockShared =<< winLockFile pid (fromOsPath pidfile)
+ v <- lockShared =<< winLockFile pid pidfile
case v of
Just h -> do
dropLock h
#else
#if WITH_WIN32NOTIFY
type DirWatcherHandle = Win32Notify.WatchManager
-watchDir :: FilePath -> Pruner -> Bool -> WatchHooks -> (IO Win32Notify.WatchManager -> IO Win32Notify.WatchManager) -> IO DirWatcherHandle
+watchDir :: OsPath -> Pruner -> Bool -> WatchHooks -> (IO Win32Notify.WatchManager -> IO Win32Notify.WatchManager) -> IO DirWatcherHandle
watchDir dir prune scanevents hooks runstartup =
runstartup $ Win32Notify.watchDir dir prune scanevents hooks
#else
import System.Win32.Notify
import System.PosixCompat.Files (isRegularFile)
-watchDir :: FilePath -> (FilePath -> Bool) -> Bool -> WatchHooks -> IO WatchManager
+watchDir :: OsPath -> (OsPath -> Bool) -> Bool -> WatchHooks -> IO WatchManager
watchDir dir ignored scanevents hooks = do
scan dir
wm <- initWatchManager
- void $ watchDirectory wm dir True [Create, Delete, Modify, Move] dispatch
+ void $ watchDirectory wm (fromOsPath dir) True [Create, Delete, Modify, Move] dispatch
return wm
where
dispatch evt
- | ignoredPath ignored (filePath evt) = noop
+ | ignoredPath ignored (toOsPath (filePath evt)) = noop
| otherwise = case evt of
(Deleted _ _)
| isDirectory evt -> runhook delDirHook Nothing
runhook addHook Nothing
runhook modifyHook Nothing
where
- runhook h s = maybe noop (\a -> a (filePath evt) s) (h hooks)
+ runhook h s = maybe noop (\a -> a (toOsPath (filePath evt)) s) (h hooks)
scan d = unless (ignoredPath ignored d) $
- mapM_ (go . fromRawFilePath) =<< emptyWhenDoesNotExist
- (dirContentsRecursiveSkipping (const False) False (toRawFilePath d))
+ mapM_ go =<< emptyWhenDoesNotExist
+ (dirContentsRecursiveSkipping (const False) False d)
where
go f
| ignoredPath ignored f = noop
where
runhook h s = maybe noop (\a -> a f s) (h hooks)
- getstatus = catchMaybeIO . R.getFileStatus . toRawFilePath
+ getstatus = catchMaybeIO . R.getFileStatus . fromOsPath
{- Check each component of the path to see if it's ignored. -}
-ignoredPath :: (FilePath -> Bool) -> FilePath -> Bool
+ignoredPath :: (OsPath -> Bool) -> OsPath -> Bool
ignoredPath ignored = any ignored . map dropTrailingPathSeparator . splitPath
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Directory.Stream (
#ifdef mingw32_HOST_OS
import qualified System.Win32 as Win32
-import System.FilePath
#else
import qualified Data.ByteString as B
import qualified System.Posix.Directory.ByteString as Posix
isopen <- newMVar ()
return (DirectoryHandle isopen dirp)
#else
- (h, fdat) <- Win32.findFirstFile (fromRawFilePath path </> "*")
+ (h, fdat) <- Win32.findFirstFile (fromOsPath (toOsPath path </> literalOsPath "*"))
-- Indicate that the fdat contains a filename that readDirectory
-- has not yet returned, by making the MVar be full.
-- (There's always at least a "." entry.)
-- https://github.com/haskell/file-io/issues/39
import Utility.Path.Windows
import Utility.OsPath
-import System.OsPath
import System.IO (IO, Handle, IOMode)
import Prelude (return)
import qualified System.File.OsPath as O
import Control.Exception (bracket)
import System.IO
import qualified Utility.FileIO as F
-import Utility.OsPath
#else
import System.PosixCompat.Files (fileSize)
+import qualified Utility.RawFilePath as R
#endif
import System.PosixCompat.Files (FileStatus)
-import qualified Utility.RawFilePath as R
import Utility.OsPath
type FileSize = Integer
go (passphrasefd ++ params)
#else
-- store the passphrase in a temp file for gpg
- withTmpFile (toOsPath "gpg") $ \tmpfile h -> do
+ withTmpFile (literalOsPath "gpg") $ \tmpfile h -> do
liftIO $ B.hPutStr h passphrase
liftIO $ hClose h
let passphrasefile = [Param "--passphrase-file", File (fromOsPath tmpfile)]
import Utility.Path.Windows
import Utility.FileSystemEncoding
+import Utility.OsPath
#if MIN_VERSION_Win32(2,13,4)
import Common (tryNonAsync)
#endif
-type LockFile = RawFilePath
+type LockFile = OsPath
type LockHandle = HANDLE
-}
openLock :: ShareMode -> LockFile -> IO (Maybe LockHandle)
openLock sharemode f = do
- f' <- convertToWindowsNativeNamespace f
+ f' <- convertToWindowsNativeNamespace (fromOsPath f)
#if MIN_VERSION_Win32(2,13,4)
r <- tryNonAsync $ createFile_NoRetry (fromRawFilePath f') gENERIC_READ sharemode
Nothing oPEN_ALWAYS fILE_ATTRIBUTE_NORMAL
import System.PosixCompat.Files (isDirectory)
import Control.Monad.IfElse
import Utility.SafeCommand
+import qualified Utility.RawFilePath as R
#endif
import Utility.SystemDirectory
import Utility.Exception
import Utility.Monad
import Utility.OsPath
-import qualified Utility.RawFilePath as R
import Author
{- Moves one filename to another.
#ifdef mingw32_HOST_OS
import Data.Char
-import Utility.FileSystemEncoding
#endif
copyright :: Authored t => t
numcommon = length common
#ifdef mingw32_HOST_OS
normdrive = map toLower
+ . fromOsPath
-- Get just the drive letter, removing any leading
-- path separator, which takeDrive leaves on the drive
-- letter.
- . dropWhileEnd (isPathSeparator . fromIntegral . ord)
- . fromOsPath
+ . OS.dropWhileEnd isPathSeparator
. takeDrive
#endif
indir d = check (d </> command')
check f = firstM doesFileExist
#ifdef mingw32_HOST_OS
- [f, f <> ".exe"]
+ [f, f <> literalOsPath ".exe"]
#else
[f]
#endif
b' <- fromRawFilePath <$> convertToWindowsNativeNamespace b
P.createLink a' b'
-{- On windows, removeLink is not available, so only remove files,
- - not symbolic links. -}
-removeLink :: RawFilePath -> IO ()
-removeLink = D.removeFile . fromRawFilePath
-
getFileStatus :: RawFilePath -> IO FileStatus
getFileStatus p = P.getFileStatus . fromRawFilePath
=<< convertToWindowsNativeNamespace p
#ifdef mingw32_HOST_OS
import qualified System.FilePath.Posix as Posix
+import qualified Utility.OsString as OS
#endif
import Data.Char
rsyncUrlIsPath :: String -> Bool
rsyncUrlIsPath s
#ifdef mingw32_HOST_OS
- | not (null (takeDrive s)) = True
+ | not (OS.null (takeDrive (toOsPath s))) = True
#endif
| rsyncUrlIsShell s = False
| otherwise = ':' `notElem` s
#ifdef mingw32_HOST_OS
toMSYS2Path :: FilePath -> FilePath
toMSYS2Path p
- | null drive = recombine parts
- | otherwise = recombine $ "/" : driveletter drive : parts
+ | OS.null drive = recombine parts
+ | otherwise = recombine $ "/" : driveletter (fromOsPath drive) : parts
where
- (drive, p') = splitDrive p
- parts = splitDirectories p'
+ (drive, p') = splitDrive (toOsPath p)
+ parts = map fromOsPath $ splitDirectories p'
driveletter = map toLower . takeWhile (/= ':')
recombine = fixtrailing . Posix.joinPath
fixtrailing s
- | hasTrailingPathSeparator p = Posix.addTrailingPathSeparator s
+ | hasTrailingPathSeparator (toOsPath p) = Posix.addTrailingPathSeparator s
| otherwise = s
#endif
import Utility.PartialPrelude
#endif
-#ifdef mingw32_HOST_OS
-import System.FilePath
-#endif
-
shellPath :: FilePath
shellPath = "/bin/sh"
Just ('#':'!':rest) -> case words rest of
[] -> defcmd
(c:ps) -> do
- let ps' = map Param ps ++ [File f]
+ let ps' = map Param ps ++ [File (fromOsPath f)]
-- If the command is not inSearchPath,
-- take the base of it, and run eg "sh"
-- which in some cases on windows will work
-- despite it not being inSearchPath.
ok <- inSearchPath c
- return (if ok then c else takeFileName c, ps')
+ return (if ok then c else fromOsPath (takeFileName (toOsPath c)), ps')
_ -> defcmd
#endif
where
go (Just emptydirectory) (passwordfd ++ params)
#else
-- store the password in a temp file
- withTmpFile (toOsPath "sop") $ \tmpfile h -> do
+ withTmpFile (literalOsPath "sop") $ \tmpfile h -> do
liftIO $ B.hPutStr h password
liftIO $ hClose h
let passwordfile = [Param $ "--with-password=" ++ fromOsPath tmpfile]
- of openTempFile, and some extra has been added to make it longer
- than any likely implementation.
-}
+#ifndef mingw32_HOST_OS
templateAddedLength :: Int
templateAddedLength = 20
+#endif
withTmpDir template a = do
topleveltmpdir <- liftIO $
catchDefaultIO (literalOsPath ".") getTemporaryDirectory
- let p = fromOsPath $ topleveltmpdir </> template
#ifndef mingw32_HOST_OS
+ let p = fromOsPath $ topleveltmpdir </> template
-- Use mkdtemp to create a temp directory securely in /tmp.
bracket
(liftIO $ toOsPath <$> mkdtemp p)