diff options
Diffstat (limited to 'Command')
-rw-r--r-- | Command/Add.hs | 2 | ||||
-rw-r--r-- | Command/Assistant.hs | 3 | ||||
-rw-r--r-- | Command/Fix.hs | 2 | ||||
-rw-r--r-- | Command/FromKey.hs | 2 | ||||
-rw-r--r-- | Command/Fsck.hs | 18 | ||||
-rw-r--r-- | Command/Import.hs | 2 | ||||
-rw-r--r-- | Command/Indirect.hs | 2 | ||||
-rw-r--r-- | Command/ReKey.hs | 2 | ||||
-rw-r--r-- | Command/RecvKey.hs | 2 | ||||
-rw-r--r-- | Command/Status.hs | 1 | ||||
-rw-r--r-- | Command/Unannex.hs | 6 | ||||
-rw-r--r-- | Command/WebApp.hs | 7 |
12 files changed, 43 insertions, 6 deletions
diff --git a/Command/Add.hs b/Command/Add.hs index 68a894d30..95af72a6f 100644 --- a/Command/Add.hs +++ b/Command/Add.hs @@ -9,6 +9,8 @@ module Command.Add where +import System.PosixCompat.Files + import Common.Annex import Annex.Exception import Command diff --git a/Command/Assistant.hs b/Command/Assistant.hs index 32c9c7a15..c40c9e5e9 100644 --- a/Command/Assistant.hs +++ b/Command/Assistant.hs @@ -15,7 +15,6 @@ import Init import Config.Files import System.Environment -import System.Posix.Directory def :: [Command] def = [noRepo checkAutoStart $ dontCheck repoExists $ @@ -64,5 +63,5 @@ autoStart = do ) where go program dir = do - changeWorkingDirectory dir + setCurrentDirectory dir boolSystem program [Param "assistant"] diff --git a/Command/Fix.hs b/Command/Fix.hs index 6aedbad6e..c6b4df257 100644 --- a/Command/Fix.hs +++ b/Command/Fix.hs @@ -7,6 +7,8 @@ module Command.Fix where +import System.PosixCompat.Files + import Common.Annex import Command import qualified Annex.Queue diff --git a/Command/FromKey.hs b/Command/FromKey.hs index 30b491478..c3d2daafe 100644 --- a/Command/FromKey.hs +++ b/Command/FromKey.hs @@ -7,6 +7,8 @@ module Command.FromKey where +import System.PosixCompat.Files + import Common.Annex import Command import qualified Annex.Queue diff --git a/Command/Fsck.hs b/Command/Fsck.hs index 1c9af0d34..fe1d35162 100644 --- a/Command/Fsck.hs +++ b/Command/Fsck.hs @@ -5,8 +5,12 @@ - Licensed under the GNU GPL version 3 or higher. -} +{-# LANGUAGE CPP #-} + module Command.Fsck where +import System.PosixCompat.Files + import Common.Annex import Command import qualified Annex @@ -28,7 +32,11 @@ import qualified Option import Types.Key import Utility.HumanTime +#ifndef __WINDOWS__ import System.Posix.Process (getProcessID) +#else +import System.Random (getStdRandom, random) +#endif import Data.Time.Clock.POSIX import Data.Time import System.Posix.Types (EpochTime) @@ -138,10 +146,14 @@ performRemote key file backend numcopies remote = , checkKeyNumCopies key file numcopies ] withtmp a = do - pid <- liftIO getProcessID +#ifndef __WINDOWS__ + v <- liftIO getProcessID +#else + v <- liftIO (getStdRandom random :: IO Int) +#endif t <- fromRepo gitAnnexTmpDir createAnnexDirectory t - let tmp = t </> "fsck" ++ show pid ++ "." ++ keyFile key + let tmp = t </> "fsck" ++ show v ++ "." ++ keyFile key let cleanup = liftIO $ catchIO (removeFile tmp) (const noop) cleanup cleanup `after` a tmp @@ -449,7 +461,9 @@ recordFsckTime key = do parent <- parentDir <$> calcRepo (gitAnnexLocation key) liftIO $ void $ tryIO $ do touchFile parent +#ifndef __WINDOWS__ setSticky parent +#endif getFsckTime :: Key -> Annex (Maybe EpochTime) getFsckTime key = do diff --git a/Command/Import.hs b/Command/Import.hs index d86b44b80..cadf8fa2e 100644 --- a/Command/Import.hs +++ b/Command/Import.hs @@ -7,6 +7,8 @@ module Command.Import where +import System.PosixCompat.Files + import Common.Annex import Command import qualified Annex diff --git a/Command/Indirect.hs b/Command/Indirect.hs index 668bebefb..bf1509944 100644 --- a/Command/Indirect.hs +++ b/Command/Indirect.hs @@ -7,6 +7,8 @@ module Command.Indirect where +import System.PosixCompat.Files + import Common.Annex import Command import qualified Git diff --git a/Command/ReKey.hs b/Command/ReKey.hs index bc4a9fac9..05fd73f1b 100644 --- a/Command/ReKey.hs +++ b/Command/ReKey.hs @@ -7,6 +7,8 @@ module Command.ReKey where +import System.PosixCompat.Files + import Common.Annex import Command import qualified Annex diff --git a/Command/RecvKey.hs b/Command/RecvKey.hs index 840fd34cb..c316e2ca5 100644 --- a/Command/RecvKey.hs +++ b/Command/RecvKey.hs @@ -7,6 +7,8 @@ module Command.RecvKey where +import System.PosixCompat.Files + import Common.Annex import Command import CmdLine diff --git a/Command/Status.hs b/Command/Status.hs index 0009ff075..6a50c1ab5 100644 --- a/Command/Status.hs +++ b/Command/Status.hs @@ -13,6 +13,7 @@ import "mtl" Control.Monad.State.Strict import qualified Data.Map as M import Text.JSON import Data.Tuple +import System.PosixCompat.Files import Common.Annex import qualified Types.Backend as B diff --git a/Command/Unannex.hs b/Command/Unannex.hs index 53b593f20..6674b37d2 100644 --- a/Command/Unannex.hs +++ b/Command/Unannex.hs @@ -5,6 +5,8 @@ - Licensed under the GNU GPL version 3 or higher. -} +{-# LANGUAGE CPP #-} + module Command.Unannex where import Common.Annex @@ -58,6 +60,9 @@ cleanup file key = do return True where +#ifdef __WINDOWS__ + goFast = go +#else goFast = do -- fast mode: hard link to content in annex src <- calcRepo $ gitAnnexLocation key @@ -66,6 +71,7 @@ cleanup file key = do ( thawContent file , go ) +#endif go = do fromAnnex key file logStatus key InfoMissing diff --git a/Command/WebApp.hs b/Command/WebApp.hs index b4307a21f..d15319078 100644 --- a/Command/WebApp.hs +++ b/Command/WebApp.hs @@ -28,7 +28,6 @@ import qualified Annex import Config.Files import qualified Option -import System.Posix.Directory import Control.Concurrent import Control.Concurrent.STM import System.Process (env, std_out, std_err) @@ -97,7 +96,7 @@ startNoRepo = do case dirs of [] -> firstRun listenhost (d:_) -> do - changeWorkingDirectory d + setCurrentDirectory d state <- Annex.new =<< Git.CurrentRepo.get void $ Annex.eval state $ doCommand $ start' False listenhost @@ -158,7 +157,11 @@ firstRun listenhost = do sendurlback v _origout _origerr url _htmlshim = putMVar v url openBrowser :: Maybe FilePath -> FilePath -> String -> Maybe Handle -> Maybe Handle -> IO () +#ifdef __ANDROID__ openBrowser mcmd htmlshim realurl outh errh = do +#else +openBrowser mcmd htmlshim _realurl outh errh = do +#endif hPutStrLn (fromMaybe stdout outh) $ "Launching web browser on " ++ url hFlush stdout environ <- cleanEnvironment |