stub out posix stuff for Windows
This is enough to let the configure program build.
This commit is contained in:
parent
767a39bd42
commit
a05b4619bb
8 changed files with 62 additions and 3 deletions
6
Build/DesktopFile.hs
Normal file → Executable file
6
Build/DesktopFile.hs
Normal file → Executable file
|
@ -22,18 +22,24 @@ import Assistant.Install.Menu
|
|||
import Control.Applicative
|
||||
import System.Directory
|
||||
import System.Environment
|
||||
#if 0
|
||||
import System.Posix.User
|
||||
import System.Posix.Files
|
||||
#endif
|
||||
import System.FilePath
|
||||
import Data.Maybe
|
||||
|
||||
systemwideInstall :: IO Bool
|
||||
#if 0
|
||||
systemwideInstall = isroot <||> destdirset
|
||||
where
|
||||
isroot = do
|
||||
uid <- fromIntegral <$> getRealUserID
|
||||
return $ uid == (0 :: Int)
|
||||
destdirset = isJust <$> catchMaybeIO (getEnv "DESTDIR")
|
||||
#else
|
||||
systemwideInstall = return False
|
||||
#endif
|
||||
|
||||
inDestDir :: FilePath -> IO FilePath
|
||||
inDestDir f = do
|
||||
|
|
4
Common.hs
Normal file → Executable file
4
Common.hs
Normal file → Executable file
|
@ -1,4 +1,4 @@
|
|||
{-# LANGUAGE PackageImports #-}
|
||||
{-# LANGUAGE PackageImports, CPP #-}
|
||||
|
||||
module Common (module X) where
|
||||
|
||||
|
@ -16,8 +16,10 @@ import "MissingH" System.Path as X
|
|||
import System.FilePath as X
|
||||
import System.Directory as X
|
||||
import System.IO as X hiding (FilePath)
|
||||
#if 0
|
||||
import System.Posix.Files as X
|
||||
import System.Posix.IO as X
|
||||
#endif
|
||||
import System.Exit as X
|
||||
|
||||
import Utility.Misc as X
|
||||
|
|
8
Utility/Directory.hs
Normal file → Executable file
8
Utility/Directory.hs
Normal file → Executable file
|
@ -5,10 +5,14 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
module Utility.Directory where
|
||||
|
||||
import System.IO.Error
|
||||
#if 0
|
||||
import System.Posix.Files
|
||||
#endif
|
||||
import System.Directory
|
||||
import Control.Exception (throw)
|
||||
import Control.Monad
|
||||
|
@ -57,6 +61,7 @@ dirContentsRecursive' (dir:dirs) = unsafeInterleaveIO $ do
|
|||
{- Moves one filename to another.
|
||||
- First tries a rename, but falls back to moving across devices if needed. -}
|
||||
moveFile :: FilePath -> FilePath -> IO ()
|
||||
#if 0
|
||||
moveFile src dest = tryIO (rename src dest) >>= onrename
|
||||
where
|
||||
onrename (Right _) = noop
|
||||
|
@ -84,6 +89,9 @@ moveFile src dest = tryIO (rename src dest) >>= onrename
|
|||
case r of
|
||||
(Left _) -> return False
|
||||
(Right s) -> return $ isDirectory s
|
||||
#else
|
||||
moveFile = error "moveFile TODO"
|
||||
#endif
|
||||
|
||||
{- Removes a file, which may or may not exist.
|
||||
-
|
||||
|
|
7
Utility/Misc.hs
Normal file → Executable file
7
Utility/Misc.hs
Normal file → Executable file
|
@ -5,6 +5,8 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
module Utility.Misc where
|
||||
|
||||
import System.IO
|
||||
|
@ -13,7 +15,9 @@ import Foreign
|
|||
import Data.Char
|
||||
import Data.List
|
||||
import Control.Applicative
|
||||
#if 0
|
||||
import System.Posix.Process (getAnyProcessStatus)
|
||||
#endif
|
||||
|
||||
import Utility.Exception
|
||||
|
||||
|
@ -118,6 +122,7 @@ hGetSomeString h sz = do
|
|||
peekbytes :: Int -> Ptr Word8 -> IO [Word8]
|
||||
peekbytes len buf = mapM (peekElemOff buf) [0..pred len]
|
||||
|
||||
#if 0
|
||||
{- Reaps any zombie git processes.
|
||||
-
|
||||
- Warning: Not thread safe. Anything that was expecting to wait
|
||||
|
@ -128,3 +133,5 @@ reapZombies = do
|
|||
-- throws an exception when there are no child processes
|
||||
catchDefaultIO Nothing (getAnyProcessStatus False True)
|
||||
>>= maybe (return ()) (const reapZombies)
|
||||
|
||||
#endif
|
||||
|
|
9
Utility/Process.hs
Normal file → Executable file
9
Utility/Process.hs
Normal file → Executable file
|
@ -6,7 +6,7 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE Rank2Types #-}
|
||||
{-# LANGUAGE CPP, Rank2Types #-}
|
||||
|
||||
module Utility.Process (
|
||||
module X,
|
||||
|
@ -42,7 +42,9 @@ import Control.Concurrent
|
|||
import qualified Control.Exception as E
|
||||
import Control.Monad
|
||||
import Data.Maybe
|
||||
#if 0
|
||||
import System.Posix.IO
|
||||
#endif
|
||||
|
||||
import Utility.Misc
|
||||
|
||||
|
@ -156,6 +158,7 @@ createBackgroundProcess p a = a =<< createProcess p
|
|||
- returns a transcript combining its stdout and stderr, and
|
||||
- whether it succeeded or failed. -}
|
||||
processTranscript :: String -> [String] -> (Maybe String) -> IO (String, Bool)
|
||||
#if 0
|
||||
processTranscript cmd opts input = do
|
||||
(readf, writef) <- createPipe
|
||||
readh <- fdToHandle readf
|
||||
|
@ -189,7 +192,9 @@ processTranscript cmd opts input = do
|
|||
|
||||
ok <- checkSuccessProcess pid
|
||||
return (transcript, ok)
|
||||
|
||||
#else
|
||||
processTranscript = error "processTranscript TODO"
|
||||
#endif
|
||||
|
||||
{- Runs a CreateProcessRunner, on a CreateProcess structure, that
|
||||
- is adjusted to pipe only from/to a single StdHandle, and passes
|
||||
|
|
12
Utility/TempFile.hs
Normal file → Executable file
12
Utility/TempFile.hs
Normal file → Executable file
|
@ -5,11 +5,15 @@
|
|||
- Licensed under the GNU GPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP #-}
|
||||
|
||||
module Utility.TempFile where
|
||||
|
||||
import Control.Exception (bracket)
|
||||
import System.IO
|
||||
#if 0
|
||||
import System.Posix.Process
|
||||
#endif
|
||||
import System.Directory
|
||||
|
||||
import Utility.Exception
|
||||
|
@ -20,12 +24,16 @@ import System.FilePath
|
|||
- then moving it into place. The temp file is stored in the same
|
||||
- directory as the final file to avoid cross-device renames. -}
|
||||
viaTmp :: (FilePath -> String -> IO ()) -> FilePath -> String -> IO ()
|
||||
#if 0
|
||||
viaTmp a file content = do
|
||||
pid <- getProcessID
|
||||
let tmpfile = file ++ ".tmp" ++ show pid
|
||||
createDirectoryIfMissing True (parentDir file)
|
||||
a tmpfile content
|
||||
renameFile tmpfile file
|
||||
#else
|
||||
viaTmp = error "viaTMP TODO"
|
||||
#endif
|
||||
|
||||
type Template = String
|
||||
|
||||
|
@ -44,6 +52,7 @@ withTempFile template a = bracket create remove use
|
|||
{- Runs an action with a temp directory, then removes the directory and
|
||||
- all its contents. -}
|
||||
withTempDir :: Template -> (FilePath -> IO a) -> IO a
|
||||
#if 0
|
||||
withTempDir template = bracket create remove
|
||||
where
|
||||
remove = removeDirectoryRecursive
|
||||
|
@ -56,3 +65,6 @@ withTempDir template = bracket create remove
|
|||
let dir = tmpdir </> t ++ "." ++ show n
|
||||
r <- tryIO $ createDirectory dir
|
||||
either (const $ makedir tmpdir t $ n + 1) (const $ return dir) r
|
||||
#else
|
||||
withTempDir = error "withTempDir TODO"
|
||||
#endif
|
||||
|
|
16
Utility/UserInfo.hs
Normal file → Executable file
16
Utility/UserInfo.hs
Normal file → Executable file
|
@ -14,29 +14,45 @@ module Utility.UserInfo (
|
|||
) where
|
||||
|
||||
import Control.Applicative
|
||||
#if 0
|
||||
import System.Posix.User
|
||||
import System.Posix.Env
|
||||
#endif
|
||||
|
||||
{- Current user's home directory.
|
||||
-
|
||||
- getpwent will fail on LDAP or NIS, so use HOME if set. -}
|
||||
myHomeDir :: IO FilePath
|
||||
#if 0
|
||||
myHomeDir = myVal ["HOME"] homeDirectory
|
||||
#else
|
||||
myHomeDir = error "myHomeDir TODO"
|
||||
#endif
|
||||
|
||||
{- Current user's user name. -}
|
||||
myUserName :: IO String
|
||||
#if 0
|
||||
myUserName = myVal ["USER", "LOGNAME"] userName
|
||||
#else
|
||||
myUserName = error "myUserName TODO"
|
||||
#endif
|
||||
|
||||
myUserGecos :: IO String
|
||||
#ifdef __ANDROID__
|
||||
myUserGecos = return "" -- userGecos crashes on Android
|
||||
#else
|
||||
#if 0
|
||||
myUserGecos = myVal [] userGecos
|
||||
#else
|
||||
myUserGecos = error "myUserGecos TODO"
|
||||
#endif
|
||||
#endif
|
||||
|
||||
#if 0
|
||||
myVal :: [String] -> (UserEntry -> String) -> IO String
|
||||
myVal envvars extract = maybe (extract <$> getpwent) return =<< check envvars
|
||||
where
|
||||
check [] = return Nothing
|
||||
check (v:vs) = maybe (check vs) (return . Just) =<< getEnv v
|
||||
getpwent = getUserEntryForID =<< getEffectiveUserID
|
||||
#endif
|
||||
|
|
|
@ -86,6 +86,9 @@ Executable git-annex
|
|||
if flag(Production)
|
||||
GHC-Options: -O2
|
||||
|
||||
if os(windows)
|
||||
CPP-Options: -D__WINDOWS__
|
||||
|
||||
if flag(TestSuite)
|
||||
Build-Depends: HUnit
|
||||
CPP-Options: -DWITH_TESTSUITE
|
||||
|
|
Loading…
Reference in a new issue