get rid of __WINDOWS__, use mingw32_HOST_OS
The latter is harder for me to remember, but avoids build failures in code used by the configure program.
This commit is contained in:
		
					parent
					
						
							
								022c3910e9
							
						
					
				
			
			
				commit
				
					
						93f2371e09
					
				
			
		
					 24 changed files with 55 additions and 55 deletions
				
			
		|  | @ -92,14 +92,14 @@ inAnnexSafe = inAnnex' (fromMaybe False) (Just False) go | |||
|   where | ||||
| 	go f = liftIO $ openforlock f >>= check | ||||
| 	openforlock f = catchMaybeIO $ | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		openFd f ReadOnly Nothing defaultFileFlags | ||||
| #else | ||||
| 		return () | ||||
| #endif | ||||
| 	check Nothing = return is_missing | ||||
| 	check (Just h) = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		v <- getLock h (ReadLock, AbsoluteSeek, 0, 0) | ||||
| 		closeFd h | ||||
| 		return $ case v of | ||||
|  | @ -116,7 +116,7 @@ inAnnexSafe = inAnnex' (fromMaybe False) (Just False) go | |||
|  - it. (If the content is not present, no locking is done.) -} | ||||
| lockContent :: Key -> Annex a -> Annex a | ||||
| lockContent key a = do | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| 	a | ||||
| #else | ||||
| 	file <- calcRepo $ gitAnnexLocation key | ||||
|  |  | |||
|  | @ -34,7 +34,7 @@ checkEnvironment = do | |||
| 
 | ||||
| checkEnvironmentIO :: IO () | ||||
| checkEnvironmentIO = | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| 	noop | ||||
| #else | ||||
| 	whenM (null <$> myUserGecos) $ do | ||||
|  |  | |||
|  | @ -87,7 +87,7 @@ lockJournal a = do | |||
| 	bracketIO (lock lockfile mode) unlock (const a) | ||||
|   where | ||||
| 	lock lockfile mode = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		l <- noUmask mode $ createFile lockfile mode | ||||
| 		waitToSetLock l (WriteLock, AbsoluteSeek, 0, 0) | ||||
| 		return l | ||||
|  | @ -95,7 +95,7 @@ lockJournal a = do | |||
| 		writeFile lockfile "" | ||||
| 		return lockfile | ||||
| #endif | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	unlock = closeFd | ||||
| #else | ||||
| 	unlock = removeFile | ||||
|  |  | |||
|  | @ -22,7 +22,7 @@ lockFile file = go =<< fromPool file | |||
|   where | ||||
| 	go (Just _) = noop -- already locked | ||||
| 	go Nothing = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		mode <- annexFileMode | ||||
| 		fd <- liftIO $ noUmask mode $ | ||||
| 			openFd file ReadOnly (Just mode) defaultFileFlags | ||||
|  | @ -37,7 +37,7 @@ unlockFile :: FilePath -> Annex () | |||
| unlockFile file = maybe noop go =<< fromPool file | ||||
|   where | ||||
| 	go fd = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		liftIO $ closeFd fd | ||||
| #endif | ||||
| 		changePool $ M.delete file | ||||
|  |  | |||
|  | @ -98,7 +98,7 @@ sshCleanup = go =<< sshCacheDir | |||
| 			liftIO (catchDefaultIO [] $ dirContents dir) | ||||
| 		forM_ sockets cleanup | ||||
| 	cleanup socketfile = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		-- Drop any shared lock we have, and take an | ||||
| 		-- exclusive lock, without blocking. If the lock | ||||
| 		-- succeeds, nothing is using this ssh, and it can | ||||
|  |  | |||
|  | @ -25,7 +25,7 @@ supportedVersions :: [Version] | |||
| supportedVersions = [defaultVersion, directModeVersion] | ||||
| 
 | ||||
| upgradableVersions :: [Version] | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| upgradableVersions = ["0", "1", "2"] | ||||
| #else | ||||
| upgradableVersions = ["2"] | ||||
|  |  | |||
|  | @ -35,7 +35,7 @@ import Utility.HumanTime | |||
| import Git.FilePath | ||||
| import GitAnnex.Options | ||||
| 
 | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| import System.Posix.Process (getProcessID) | ||||
| #else | ||||
| import System.Random (getStdRandom, random) | ||||
|  | @ -151,7 +151,7 @@ performRemote key file backend numcopies remote = | |||
| 		, checkKeyNumCopies key file numcopies | ||||
| 		] | ||||
| 	withtmp a = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		v <- liftIO getProcessID | ||||
| #else | ||||
| 		v <- liftIO (getStdRandom random :: IO Int) | ||||
|  | @ -458,7 +458,7 @@ recordFsckTime key = do | |||
| 	parent <- parentDir <$> calcRepo (gitAnnexLocation key) | ||||
| 	liftIO $ void $ tryIO $ do | ||||
| 		touchFile parent | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		setSticky parent | ||||
| #endif | ||||
| 
 | ||||
|  |  | |||
|  | @ -66,7 +66,7 @@ cleanupIndirect file key = do | |||
| 		) | ||||
| 	return True | ||||
|   where | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| 	goFast = go | ||||
| #else | ||||
| 	goFast = do | ||||
|  |  | |||
|  | @ -25,7 +25,7 @@ module Git.Construct ( | |||
| 
 | ||||
| {-# LANGUAGE CPP #-} | ||||
| 
 | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| import System.Posix.User | ||||
| #else | ||||
| import Git.FilePath | ||||
|  | @ -146,7 +146,7 @@ fromRemoteLocation :: String -> Repo -> IO Repo | |||
| fromRemoteLocation s repo = gen $ calcloc s | ||||
|   where | ||||
| 	gen v	 | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| 		| dosstyle v = fromRemotePath (dospath v) repo | ||||
| #endif | ||||
| 		| scpstyle v = fromUrl $ scptourl v | ||||
|  | @ -182,7 +182,7 @@ fromRemoteLocation s repo = gen $ calcloc s | |||
| 			| "/" `isPrefixOf` d = d | ||||
| 			| "~" `isPrefixOf` d = '/':d | ||||
| 			| otherwise = "/~/" ++ d | ||||
| #ifdef __WINDOWS__ | ||||
| #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 | ||||
|  | @ -208,7 +208,7 @@ repoAbsPath d = do | |||
| 	return $ h </> d' | ||||
| 
 | ||||
| expandTilde :: FilePath -> IO FilePath | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| expandTilde = return | ||||
| #else | ||||
| expandTilde = expandt True | ||||
|  |  | |||
|  | @ -41,7 +41,7 @@ get = do | |||
| 			return $ addworktree wt r | ||||
|   where | ||||
| 	pathenv s = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		v <- getEnv s | ||||
| 		case v of | ||||
| 			Just d -> do | ||||
|  |  | |||
|  | @ -44,14 +44,14 @@ asTopFilePath file = TopFilePath file | |||
| type InternalGitPath = String | ||||
| 
 | ||||
| toInternalGitPath :: FilePath -> InternalGitPath | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| toInternalGitPath = id | ||||
| #else | ||||
| toInternalGitPath = replace "\\" "/" | ||||
| #endif | ||||
| 
 | ||||
| fromInternalGitPath :: InternalGitPath -> FilePath | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| fromInternalGitPath = id | ||||
| #else | ||||
| fromInternalGitPath = replace "/" "\\" | ||||
|  |  | |||
|  | @ -130,7 +130,7 @@ runTransfer t file shouldretry a = do | |||
| 			return ok | ||||
|   where | ||||
| 	prep tfile mode info = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		mfd <- catchMaybeIO $ | ||||
| 			openFd (transferLockFile tfile) ReadWrite (Just mode) | ||||
| 				defaultFileFlags { trunc = True } | ||||
|  | @ -154,7 +154,7 @@ runTransfer t file shouldretry a = do | |||
| 	cleanup tfile (Just fd) = do | ||||
| 		void $ tryIO $ removeFile tfile | ||||
| 		void $ tryIO $ removeFile $ transferLockFile tfile | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 		closeFd fd | ||||
| #endif | ||||
| 	retry oldinfo metervar run = do | ||||
|  | @ -214,7 +214,7 @@ startTransferInfo file = TransferInfo | |||
| checkTransfer :: Transfer -> Annex (Maybe TransferInfo) | ||||
| checkTransfer t = do | ||||
| 	tfile <- fromRepo $ transferFile t | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	mode <- annexFileMode | ||||
| 	mfd <- liftIO $ catchMaybeIO $ | ||||
| 		openFd (transferLockFile tfile) ReadOnly (Just mode) defaultFileFlags | ||||
|  |  | |||
|  | @ -219,7 +219,7 @@ retrieveEncrypted d chunksize (cipher, enck) k f p = metered (Just p) k $ \meter | |||
| 
 | ||||
| retrieveCheap :: FilePath -> ChunkSize -> Key -> FilePath -> Annex Bool | ||||
| retrieveCheap _ (Just _) _ _ = return False -- no cheap retrieval for chunks | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| retrieveCheap d _ k f = liftIO $ withStoredFiles Nothing d k go | ||||
|   where | ||||
| 	go [file] = catchBoolIO $ createSymbolicLink file f >> return True | ||||
|  |  | |||
|  | @ -267,7 +267,7 @@ keyUrls :: Git.Repo -> Key -> [String] | |||
| keyUrls r key = map tourl locs | ||||
|   where | ||||
| 	tourl l = Git.repoLocation r ++ "/" ++ l | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	locs = annexLocations key | ||||
| #else | ||||
| 	locs = map (replace "\\" "/") (annexLocations key) | ||||
|  | @ -361,7 +361,7 @@ copyFromRemote' r key file dest | |||
| 
 | ||||
| copyFromRemoteCheap :: Remote -> Key -> FilePath -> Annex Bool | ||||
| copyFromRemoteCheap r key file | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	| not $ Git.repoIsUrl (repo r) = guardUsable (repo r) False $ do | ||||
| 		loc <- liftIO $ gitAnnexLocation key (repo r) $ | ||||
| 			fromJust $ remoteGitConfig $ gitconfig r | ||||
|  | @ -418,7 +418,7 @@ rsyncHelper callback params = do | |||
|  - filesystem. Then cp could be faster. -} | ||||
| rsyncOrCopyFile :: [CommandParam] -> FilePath -> FilePath -> MeterUpdate -> Annex Bool | ||||
| rsyncOrCopyFile rsyncparams src dest p = | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| 	dorsync | ||||
|   where | ||||
| #else | ||||
|  |  | |||
|  | @ -11,7 +11,7 @@ module Remote.Rsync (remote) where | |||
| 
 | ||||
| import qualified Data.ByteString.Lazy as L | ||||
| import qualified Data.Map as M | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| import System.Posix.Process (getProcessID) | ||||
| #else | ||||
| import System.Random (getStdRandom, random) | ||||
|  | @ -221,7 +221,7 @@ sendParams = ifM crippledFileSystem | |||
|  - up trees for rsync. -} | ||||
| withRsyncScratchDir :: (FilePath -> Annex Bool) -> Annex Bool | ||||
| withRsyncScratchDir a = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	v <- liftIO getProcessID | ||||
| #else | ||||
| 	v <- liftIO (getStdRandom random :: IO Int) | ||||
|  |  | |||
|  | @ -88,6 +88,6 @@ rawMode ch = do | |||
|   where | ||||
|   	raw h = do | ||||
| 		fileEncoding h | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| 		hSetNewlineMode h noNewlineTranslation | ||||
| #endif | ||||
|  |  | |||
|  | @ -36,7 +36,7 @@ copyFileExternal src dest = do | |||
| {- Create a hard link if the filesystem allows it, and fall back to copying | ||||
|  - the file. -} | ||||
| createLinkOrCopy :: FilePath -> FilePath -> IO Bool | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| createLinkOrCopy src dest = go `catchIO` const fallback | ||||
|   where | ||||
|   	go = do | ||||
|  |  | |||
|  | @ -12,7 +12,7 @@ module Utility.Daemon where | |||
| import Common | ||||
| import Utility.LogFile | ||||
| 
 | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| import System.Posix | ||||
| #else | ||||
| import System.PosixCompat | ||||
|  | @ -26,7 +26,7 @@ import System.Posix.Types | |||
|  - | ||||
|  - When successful, does not return. -} | ||||
| daemonize :: Fd -> Maybe FilePath -> Bool -> IO () -> IO () | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| daemonize logfd pidfile changedirectory a = do | ||||
| 	maybe noop checkalreadyrunning pidfile | ||||
| 	_ <- forkProcess child1 | ||||
|  | @ -58,7 +58,7 @@ daemonize = error "daemonize is not implemented on Windows" -- TODO | |||
| lockPidFile :: FilePath -> IO () | ||||
| lockPidFile file = do | ||||
| 	createDirectoryIfMissing True (parentDir file) | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	fd <- openFd file ReadWrite (Just stdFileMode) defaultFileFlags | ||||
| 	locked <- catchMaybeIO $ setLock fd (WriteLock, AbsoluteSeek, 0, 0) | ||||
| 	fd' <- openFd newfile ReadWrite (Just stdFileMode) defaultFileFlags | ||||
|  | @ -85,7 +85,7 @@ alreadyRunning = error "Daemon is already running." | |||
|  - | ||||
|  - If it's running, returns its pid. -} | ||||
| checkDaemon :: FilePath -> IO (Maybe ProcessID) | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| checkDaemon pidfile = do | ||||
| 	v <- catchMaybeIO $ | ||||
| 		openFd pidfile ReadOnly (Just stdFileMode) defaultFileFlags | ||||
|  | @ -110,7 +110,7 @@ checkDaemon pidfile = maybe Nothing readish <$> catchMaybeIO (readFile pidfile) | |||
| 
 | ||||
| {- Stops the daemon, safely. -} | ||||
| stopDaemon :: FilePath -> IO () | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| stopDaemon pidfile = go =<< checkDaemon pidfile | ||||
|   where | ||||
| 	go Nothing = noop | ||||
|  |  | |||
|  | @ -13,7 +13,7 @@ import Common | |||
| 
 | ||||
| import Control.Exception (bracket) | ||||
| import System.PosixCompat.Types | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| import System.Posix.Files | ||||
| #endif | ||||
| import Foreign (complement) | ||||
|  | @ -76,7 +76,7 @@ checkMode checkfor mode = checkfor `intersectFileModes` mode == checkfor | |||
| 
 | ||||
| {- Checks if a file mode indicates it's a symlink. -} | ||||
| isSymLink :: FileMode -> Bool | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| isSymLink _ = False | ||||
| #else | ||||
| isSymLink = checkMode symbolicLinkMode | ||||
|  | @ -89,7 +89,7 @@ isExecutable mode = combineModes executeModes `intersectFileModes` mode /= 0 | |||
| {- Runs an action without that pesky umask influencing it, unless the | ||||
|  - passed FileMode is the standard one. -} | ||||
| noUmask :: FileMode -> IO a -> IO a | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| noUmask mode a | ||||
| 	| mode == stdFileMode = a | ||||
| 	| otherwise = bracket setup cleanup go | ||||
|  | @ -107,7 +107,7 @@ combineModes [m] = m | |||
| combineModes (m:ms) = foldl unionFileModes m ms | ||||
| 
 | ||||
| isSticky :: FileMode -> Bool | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| isSticky _ = False | ||||
| #else | ||||
| isSticky = checkMode stickyMode | ||||
|  |  | |||
|  | @ -29,7 +29,7 @@ gpgcmd = fromMaybe "gpg" SysConfig.gpg | |||
| 
 | ||||
| stdParams :: [CommandParam] -> IO [String] | ||||
| stdParams params = do | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	-- Enable batch mode if GPG_AGENT_INFO is set, to avoid extraneous | ||||
| 	-- gpg output about password prompts. GPG_BATCH is set by the test | ||||
| 	-- suite for a similar reason. | ||||
|  | @ -77,7 +77,7 @@ pipeStrict params input = do | |||
|  - Note that to avoid deadlock with the cleanup stage, | ||||
|  - the reader must fully consume gpg's input before returning. -} | ||||
| feedRead :: [CommandParam] -> String -> (Handle -> IO ()) -> (Handle -> IO a) -> IO a | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| feedRead params passphrase feeder reader = do | ||||
| 	-- pipe the passphrase into gpg on a fd | ||||
| 	(frompipe, topipe) <- createPipe | ||||
|  |  | |||
|  | @ -14,7 +14,7 @@ import Common | |||
| import System.Posix.Types | ||||
| 
 | ||||
| openLog :: FilePath -> IO Fd | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| openLog logfile = do | ||||
| 	rotateLog logfile | ||||
| 	openFd logfile WriteOnly (Just stdFileMode) | ||||
|  | @ -50,7 +50,7 @@ maxLogs :: Int | |||
| maxLogs = 9 | ||||
| 
 | ||||
| redirLog :: Fd -> IO () | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| redirLog logfd = do | ||||
| 	mapM_ (redir logfd) [stdOutput, stdError] | ||||
| 	closeFd logfd | ||||
|  | @ -58,7 +58,7 @@ redirLog logfd = do | |||
| redirLog _ = error "redirLog TODO" | ||||
| #endif | ||||
| 
 | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| redir :: Fd -> Fd -> IO () | ||||
| redir newh h = do | ||||
| 	closeFd h | ||||
|  |  | |||
|  | @ -16,7 +16,7 @@ import Data.List | |||
| import Data.Maybe | ||||
| import Control.Applicative | ||||
| 
 | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| import Data.Char | ||||
| import qualified System.FilePath.Posix as Posix | ||||
| #else | ||||
|  | @ -38,7 +38,7 @@ import Utility.UserInfo | |||
|  - no normalization is done. | ||||
|  -} | ||||
| absNormPath :: FilePath -> FilePath -> Maybe FilePath | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| absNormPath dir path = MissingH.absNormPath dir path | ||||
| #else | ||||
| absNormPath dir path = Just $ combine dir path | ||||
|  | @ -183,7 +183,7 @@ searchPath command | |||
|   where | ||||
| 	indir d = check $ d </> command | ||||
| 	check f = firstM doesFileExist | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| 		[f, f ++ ".exe"] | ||||
| #else | ||||
| 		[f] | ||||
|  | @ -203,7 +203,7 @@ dotfile file | |||
| {- Converts a DOS style path to a Cygwin style path. Only on Windows. | ||||
|  - Any trailing '\' is preserved as a trailing '/' -} | ||||
| toCygPath :: FilePath -> FilePath | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| toCygPath = id | ||||
| #else | ||||
| toCygPath p | ||||
|  | @ -226,7 +226,7 @@ toCygPath p | |||
|  - limit. | ||||
|  -} | ||||
| fileNameLengthLimit :: FilePath -> IO Int | ||||
| #ifdef __WINDOWS__ | ||||
| #ifdef mingw32_HOST_OS | ||||
| fileNameLengthLimit _ = return 255 | ||||
| #else | ||||
| fileNameLengthLimit dir = do | ||||
|  |  | |||
|  | @ -13,7 +13,7 @@ module Utility.ThreadScheduler where | |||
| import Common | ||||
| 
 | ||||
| import Control.Concurrent | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| import System.Posix.Signals | ||||
| #ifndef __ANDROID__ | ||||
| import System.Posix.Terminal | ||||
|  | @ -54,7 +54,7 @@ unboundDelay time = do | |||
| waitForTermination :: IO () | ||||
| waitForTermination = do | ||||
| 	lock <- newEmptyMVar | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	let check sig = void $ | ||||
| 		installHandler sig (CatchOnce $ putMVar lock ()) Nothing | ||||
| 	check softwareTermination | ||||
|  |  | |||
|  | @ -24,7 +24,7 @@ import Utility.Env | |||
| myHomeDir :: IO FilePath | ||||
| myHomeDir = myVal env homeDirectory | ||||
|   where | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	env = ["HOME"] | ||||
| #else | ||||
| 	env = ["USERPROFILE", "HOME"] -- HOME is used in Cygwin | ||||
|  | @ -34,7 +34,7 @@ myHomeDir = myVal env homeDirectory | |||
| myUserName :: IO String | ||||
| myUserName = myVal env userName | ||||
|   where | ||||
| #ifndef __WINDOWS__ | ||||
| #ifndef mingw32_HOST_OS | ||||
| 	env = ["USER", "LOGNAME"] | ||||
| #else | ||||
| 	env = ["USERNAME", "USER", "LOGNAME"] | ||||
|  |  | |||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue
	
	 Joey Hess
				Joey Hess