diff options
author | Joey Hess <id@joeyh.name> | 2013-05-10 15:08:53 -0500 |
---|---|---|
committer | Joey Hess <id@joeyh.name> | 2013-05-10 15:08:53 -0500 |
commit | 493db9a024a89f1f696a858789ce55844a180215 (patch) | |
tree | 3d34bea905c3623156a07406f027bf50e005c881 /Utility | |
parent | 720d0230d6333a3cc3a7d533ef09e921ed6b0d8f (diff) |
stub out posix stuff for Windows
This is enough to let the configure program build.
Diffstat (limited to 'Utility')
-rwxr-xr-x[-rw-r--r--] | Utility/Directory.hs | 8 | ||||
-rwxr-xr-x[-rw-r--r--] | Utility/Misc.hs | 7 | ||||
-rwxr-xr-x[-rw-r--r--] | Utility/Process.hs | 9 | ||||
-rwxr-xr-x[-rw-r--r--] | Utility/TempFile.hs | 12 | ||||
-rwxr-xr-x[-rw-r--r--] | Utility/UserInfo.hs | 16 |
5 files changed, 50 insertions, 2 deletions
diff --git a/Utility/Directory.hs b/Utility/Directory.hs index 7cce4a68f..55d79a825 100644..100755 --- a/Utility/Directory.hs +++ b/Utility/Directory.hs @@ -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. - diff --git a/Utility/Misc.hs b/Utility/Misc.hs index 1bb6de79f..576a6ddbf 100644..100755 --- a/Utility/Misc.hs +++ b/Utility/Misc.hs @@ -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 diff --git a/Utility/Process.hs b/Utility/Process.hs index b2bac99a1..381a14983 100644..100755 --- a/Utility/Process.hs +++ b/Utility/Process.hs @@ -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 diff --git a/Utility/TempFile.hs b/Utility/TempFile.hs index 6dbea693a..e5617d48b 100644..100755 --- a/Utility/TempFile.hs +++ b/Utility/TempFile.hs @@ -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 diff --git a/Utility/UserInfo.hs b/Utility/UserInfo.hs index 916ebb191..6fad3d7b4 100644..100755 --- a/Utility/UserInfo.hs +++ b/Utility/UserInfo.hs @@ -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 |