noop
This commit is contained in:
		
					parent
					
						
							
								bee420bd2d
							
						
					
				
			
			
				commit
				
					
						ed79596b75
					
				
			
		
					 27 changed files with 56 additions and 52 deletions
				
			
		| 
						 | 
					@ -98,7 +98,7 @@ lockContent key a = do
 | 
				
			||||||
			case v of
 | 
								case v of
 | 
				
			||||||
				Left _ -> error "content is locked"
 | 
									Left _ -> error "content is locked"
 | 
				
			||||||
				Right _ -> return $ Just fd
 | 
									Right _ -> return $ Just fd
 | 
				
			||||||
		unlock Nothing = return ()
 | 
							unlock Nothing = noop
 | 
				
			||||||
		unlock (Just l) = closeFd l
 | 
							unlock (Just l) = closeFd l
 | 
				
			||||||
 | 
					
 | 
				
			||||||
{- Calculates the relative path to use to link a file to a key. -}
 | 
					{- Calculates the relative path to use to link a file to a key. -}
 | 
				
			||||||
| 
						 | 
					@ -237,10 +237,10 @@ cleanObjectLoc key = do
 | 
				
			||||||
	file <- inRepo $ gitAnnexLocation key
 | 
						file <- inRepo $ gitAnnexLocation key
 | 
				
			||||||
	liftIO $ removeparents file (3 :: Int)
 | 
						liftIO $ removeparents file (3 :: Int)
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		removeparents _ 0 = return ()
 | 
							removeparents _ 0 = noop
 | 
				
			||||||
		removeparents file n = do
 | 
							removeparents file n = do
 | 
				
			||||||
			let dir = parentDir file
 | 
								let dir = parentDir file
 | 
				
			||||||
			maybe (return ()) (const $ removeparents dir (n-1))
 | 
								maybe noop (const $ removeparents dir (n-1))
 | 
				
			||||||
				=<< catchMaybeIO (removeDirectory dir)
 | 
									=<< catchMaybeIO (removeDirectory dir)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
{- Removes a key's file from .git/annex/objects/ -}
 | 
					{- Removes a key's file from .git/annex/objects/ -}
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -18,7 +18,7 @@ import Annex.Perms
 | 
				
			||||||
lockFile :: FilePath -> Annex ()
 | 
					lockFile :: FilePath -> Annex ()
 | 
				
			||||||
lockFile file = go =<< fromPool file
 | 
					lockFile file = go =<< fromPool file
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		go (Just _) = return () -- already locked
 | 
							go (Just _) = noop -- already locked
 | 
				
			||||||
		go Nothing = do
 | 
							go Nothing = do
 | 
				
			||||||
			mode <- annexFileMode
 | 
								mode <- annexFileMode
 | 
				
			||||||
			fd <- liftIO $ noUmask mode $
 | 
								fd <- liftIO $ noUmask mode $
 | 
				
			||||||
| 
						 | 
					@ -27,10 +27,9 @@ lockFile file = go =<< fromPool file
 | 
				
			||||||
			changePool $ M.insert file fd
 | 
								changePool $ M.insert file fd
 | 
				
			||||||
 | 
					
 | 
				
			||||||
unlockFile :: FilePath -> Annex ()
 | 
					unlockFile :: FilePath -> Annex ()
 | 
				
			||||||
unlockFile file = go =<< fromPool file
 | 
					unlockFile file = maybe noop go =<< fromPool file
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		go Nothing = return ()
 | 
							go fd = do
 | 
				
			||||||
		go (Just fd) = do
 | 
					 | 
				
			||||||
			liftIO $ closeFd fd
 | 
								liftIO $ closeFd fd
 | 
				
			||||||
			changePool $ M.delete file
 | 
								changePool $ M.delete file
 | 
				
			||||||
 | 
					
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -37,7 +37,7 @@ setAnnexPerm file = withShared $ liftIO . go
 | 
				
			||||||
		go GroupShared = groupWriteRead file
 | 
							go GroupShared = groupWriteRead file
 | 
				
			||||||
		go AllShared = modifyFileMode file $ addModes $
 | 
							go AllShared = modifyFileMode file $ addModes $
 | 
				
			||||||
			[ ownerWriteMode, groupWriteMode ] ++ readModes
 | 
								[ ownerWriteMode, groupWriteMode ] ++ readModes
 | 
				
			||||||
		go _ = return ()
 | 
							go _ = noop
 | 
				
			||||||
 | 
					
 | 
				
			||||||
{- Gets the appropriate mode to use for creating a file in the annex
 | 
					{- Gets the appropriate mode to use for creating a file in the annex
 | 
				
			||||||
 - (other than content files, which are locked down more). -}
 | 
					 - (other than content files, which are locked down more). -}
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -81,7 +81,7 @@ sshCleanup = do
 | 
				
			||||||
			v <- liftIO $ tryIO $
 | 
								v <- liftIO $ tryIO $
 | 
				
			||||||
				setLock fd (WriteLock, AbsoluteSeek, 0, 0)
 | 
									setLock fd (WriteLock, AbsoluteSeek, 0, 0)
 | 
				
			||||||
			case v of
 | 
								case v of
 | 
				
			||||||
				Left _ -> return ()
 | 
									Left _ -> noop
 | 
				
			||||||
				Right _ -> stopssh socketfile
 | 
									Right _ -> stopssh socketfile
 | 
				
			||||||
			liftIO $ closeFd fd
 | 
								liftIO $ closeFd fd
 | 
				
			||||||
		stopssh socketfile = do
 | 
							stopssh socketfile = do
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -35,7 +35,7 @@ setVersion = setConfig versionField defaultVersion
 | 
				
			||||||
 | 
					
 | 
				
			||||||
checkVersion :: Version -> Annex ()
 | 
					checkVersion :: Version -> Annex ()
 | 
				
			||||||
checkVersion v
 | 
					checkVersion v
 | 
				
			||||||
	| v `elem` supportedVersions = return ()
 | 
						| v `elem` supportedVersions = noop
 | 
				
			||||||
	| v `elem` upgradableVersions = err "Upgrade this repository: git-annex upgrade"
 | 
						| v `elem` upgradableVersions = err "Upgrade this repository: git-annex upgrade"
 | 
				
			||||||
	| otherwise = err "Upgrade git-annex."
 | 
						| otherwise = err "Upgrade git-annex."
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -88,7 +88,7 @@ tryRun = tryRun' 0
 | 
				
			||||||
tryRun' :: Integer -> Annex.AnnexState -> Command -> [CommandCleanup] -> IO ()
 | 
					tryRun' :: Integer -> Annex.AnnexState -> Command -> [CommandCleanup] -> IO ()
 | 
				
			||||||
tryRun' errnum _ cmd []
 | 
					tryRun' errnum _ cmd []
 | 
				
			||||||
	| errnum > 0 = error $ cmdname cmd ++ ": " ++ show errnum ++ " failed"
 | 
						| errnum > 0 = error $ cmdname cmd ++ ": " ++ show errnum ++ " failed"
 | 
				
			||||||
	| otherwise = return ()
 | 
						| otherwise = noop
 | 
				
			||||||
tryRun' errnum state cmd (a:as) = do
 | 
					tryRun' errnum state cmd (a:as) = do
 | 
				
			||||||
	r <- run
 | 
						r <- run
 | 
				
			||||||
	handle $! r
 | 
						handle $! r
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -85,7 +85,7 @@ performRemote key file backend numcopies remote =
 | 
				
			||||||
			t <- fromRepo gitAnnexTmpDir
 | 
								t <- fromRepo gitAnnexTmpDir
 | 
				
			||||||
			let tmp = t </> "fsck" ++ show pid ++ "." ++ keyFile key
 | 
								let tmp = t </> "fsck" ++ show pid ++ "." ++ keyFile key
 | 
				
			||||||
			liftIO $ createDirectoryIfMissing True t
 | 
								liftIO $ createDirectoryIfMissing True t
 | 
				
			||||||
			let cleanup = liftIO $ catchIO (removeFile tmp) (const $ return ())
 | 
								let cleanup = liftIO $ catchIO (removeFile tmp) (const noop)
 | 
				
			||||||
			cleanup
 | 
								cleanup
 | 
				
			||||||
			cleanup `after` a tmp
 | 
								cleanup `after` a tmp
 | 
				
			||||||
		getfile tmp =
 | 
							getfile tmp =
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -108,12 +108,11 @@ nojson :: StatState String -> String -> StatState String
 | 
				
			||||||
nojson a _ = a
 | 
					nojson a _ = a
 | 
				
			||||||
 | 
					
 | 
				
			||||||
showStat :: Stat -> StatState ()
 | 
					showStat :: Stat -> StatState ()
 | 
				
			||||||
showStat s = calc =<< s
 | 
					showStat s = maybe noop calc =<< s
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		calc (Just (desc, a)) = do
 | 
							calc (desc, a) = do
 | 
				
			||||||
			(lift . showHeader) desc
 | 
								(lift . showHeader) desc
 | 
				
			||||||
			lift . showRaw =<< a
 | 
								lift . showRaw =<< a
 | 
				
			||||||
		calc Nothing = return ()
 | 
					 | 
				
			||||||
 | 
					
 | 
				
			||||||
supported_backends :: Stat
 | 
					supported_backends :: Stat
 | 
				
			||||||
supported_backends = stat "supported backends" $ json unwords $
 | 
					supported_backends = stat "supported backends" $ json unwords $
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -268,7 +268,7 @@ withKeysReferencedInGitRef a ref = do
 | 
				
			||||||
	showAction $ "checking " ++ Git.Ref.describe ref
 | 
						showAction $ "checking " ++ Git.Ref.describe ref
 | 
				
			||||||
	go =<< inRepo (LsTree.lsTree ref)
 | 
						go =<< inRepo (LsTree.lsTree ref)
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		go [] = return ()
 | 
							go [] = noop
 | 
				
			||||||
		go (l:ls)
 | 
							go (l:ls)
 | 
				
			||||||
			| isSymLink (LsTree.mode l) = do
 | 
								| isSymLink (LsTree.mode l) = do
 | 
				
			||||||
				content <- L.decodeUtf8 <$> catFile ref (LsTree.file l)
 | 
									content <- L.decodeUtf8 <$> catFile ref (LsTree.file l)
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -46,9 +46,9 @@ perform remotemap key = do
 | 
				
			||||||
		untrustedheader = "The following untrusted locations may also have copies:\n"
 | 
							untrustedheader = "The following untrusted locations may also have copies:\n"
 | 
				
			||||||
 | 
					
 | 
				
			||||||
performRemote :: Key -> Remote -> Annex () 
 | 
					performRemote :: Key -> Remote -> Annex () 
 | 
				
			||||||
performRemote key remote = case whereisKey remote of
 | 
					performRemote key remote = maybe noop go $ whereisKey remote
 | 
				
			||||||
	Nothing -> return ()
 | 
						where
 | 
				
			||||||
	Just a -> do
 | 
							go a = do
 | 
				
			||||||
		ls <- a key
 | 
								ls <- a key
 | 
				
			||||||
		unless (null ls) $ showLongNote $
 | 
								unless (null ls) $ showLongNote $ unlines $
 | 
				
			||||||
			unlines $ map (\l -> name remote ++ ": " ++ l) ls
 | 
									map (\l -> name remote ++ ": " ++ l) ls
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -79,5 +79,5 @@ pipeNullSplit params repo =
 | 
				
			||||||
reap :: IO ()
 | 
					reap :: IO ()
 | 
				
			||||||
reap = do
 | 
					reap = do
 | 
				
			||||||
	-- throws an exception when there are no child processes
 | 
						-- throws an exception when there are no child processes
 | 
				
			||||||
	r <- catchDefaultIO (getAnyProcessStatus False True) Nothing
 | 
						catchDefaultIO (getAnyProcessStatus False True) Nothing
 | 
				
			||||||
	maybe (return ()) (const reap) r
 | 
							>>= maybe noop (const reap)
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -48,7 +48,7 @@ import qualified Git.Url as Url
 | 
				
			||||||
fromCurrent :: IO Repo
 | 
					fromCurrent :: IO Repo
 | 
				
			||||||
fromCurrent = do
 | 
					fromCurrent = do
 | 
				
			||||||
	r <- maybe fromCwd fromPath =<< getEnv "GIT_DIR"
 | 
						r <- maybe fromCwd fromPath =<< getEnv "GIT_DIR"
 | 
				
			||||||
	maybe (return ()) changeWorkingDirectory =<< getEnv "GIT_WORK_TREE"
 | 
						maybe noop changeWorkingDirectory =<< getEnv "GIT_WORK_TREE"
 | 
				
			||||||
	unsetEnv "GIT_DIR"
 | 
						unsetEnv "GIT_DIR"
 | 
				
			||||||
	unsetEnv "GIT_WORK_TREE"
 | 
						unsetEnv "GIT_WORK_TREE"
 | 
				
			||||||
	return r
 | 
						return r
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -97,7 +97,7 @@ calc_merge :: CatFileHandle -> [String] -> Repo -> Streamer
 | 
				
			||||||
calc_merge ch differ repo streamer = gendiff >>= go
 | 
					calc_merge ch differ repo streamer = gendiff >>= go
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		gendiff = pipeNullSplit (map Param differ) repo
 | 
							gendiff = pipeNullSplit (map Param differ) repo
 | 
				
			||||||
		go [] = return ()
 | 
							go [] = noop
 | 
				
			||||||
		go (info:file:rest) = mergeFile info file ch repo >>=
 | 
							go (info:file:rest) = mergeFile info file ch repo >>=
 | 
				
			||||||
			maybe (go rest) (\l -> streamer l >> go rest)
 | 
								maybe (go rest) (\l -> streamer l >> go rest)
 | 
				
			||||||
		go (_:[]) = error "calc_merge parse error"
 | 
							go (_:[]) = error "calc_merge parse error"
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -52,7 +52,7 @@ options = Option.common ++
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		checkuuid expected = getUUID >>= check
 | 
							checkuuid expected = getUUID >>= check
 | 
				
			||||||
			where
 | 
								where
 | 
				
			||||||
				check u | u == toUUID expected = return ()
 | 
									check u | u == toUUID expected = noop
 | 
				
			||||||
				check NoUUID = unexpected "uninitialized repository"
 | 
									check NoUUID = unexpected "uninitialized repository"
 | 
				
			||||||
				check u = unexpected $ "UUID " ++ fromUUID u
 | 
									check u = unexpected $ "UUID " ++ fromUUID u
 | 
				
			||||||
				unexpected s = error $
 | 
									unexpected s = error $
 | 
				
			||||||
| 
						 | 
					@ -107,7 +107,7 @@ checkNotLimited = checkEnv "GIT_ANNEX_SHELL_LIMITED"
 | 
				
			||||||
 | 
					
 | 
				
			||||||
checkNotReadOnly :: String -> IO ()
 | 
					checkNotReadOnly :: String -> IO ()
 | 
				
			||||||
checkNotReadOnly cmd
 | 
					checkNotReadOnly cmd
 | 
				
			||||||
	| cmd `elem` map cmdname cmds_readonly = return ()
 | 
						| cmd `elem` map cmdname cmds_readonly = noop
 | 
				
			||||||
	| otherwise = checkEnv "GIT_ANNEX_SHELL_READONLY"
 | 
						| otherwise = checkEnv "GIT_ANNEX_SHELL_READONLY"
 | 
				
			||||||
 | 
					
 | 
				
			||||||
checkEnv :: String -> IO ()
 | 
					checkEnv :: String -> IO ()
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -30,7 +30,7 @@ import Logs.Presence
 | 
				
			||||||
{- Log a change in the presence of a key's value in a repository. -}
 | 
					{- Log a change in the presence of a key's value in a repository. -}
 | 
				
			||||||
logChange :: Key -> UUID -> LogStatus -> Annex ()
 | 
					logChange :: Key -> UUID -> LogStatus -> Annex ()
 | 
				
			||||||
logChange key (UUID u) s = addLog (logFile key) =<< logNow s u
 | 
					logChange key (UUID u) s = addLog (logFile key) =<< logNow s u
 | 
				
			||||||
logChange _ NoUUID _ = return ()
 | 
					logChange _ NoUUID _ = noop
 | 
				
			||||||
 | 
					
 | 
				
			||||||
{- Returns a list of repository UUIDs that, according to the log, have
 | 
					{- Returns a list of repository UUIDs that, according to the log, have
 | 
				
			||||||
 - the value of a key.
 | 
					 - the value of a key.
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -73,7 +73,7 @@ recordUUID u = go . M.lookup u =<< uuidMap
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		go (Just "") = set
 | 
							go (Just "") = set
 | 
				
			||||||
		go Nothing = set
 | 
							go Nothing = set
 | 
				
			||||||
		go _ = return ()
 | 
							go _ = noop
 | 
				
			||||||
		set = describeUUID u ""
 | 
							set = describeUUID u ""
 | 
				
			||||||
 | 
					
 | 
				
			||||||
{- Read the uuidLog into a simple Map.
 | 
					{- Read the uuidLog into a simple Map.
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -72,8 +72,8 @@ metered key a = Annex.getState Annex.output >>= go (keySize key)
 | 
				
			||||||
				incrP progress n
 | 
									incrP progress n
 | 
				
			||||||
				displayMeter stdout meter
 | 
									displayMeter stdout meter
 | 
				
			||||||
			liftIO $ clearMeter stdout meter
 | 
								liftIO $ clearMeter stdout meter
 | 
				
			||||||
			return r	
 | 
								return r
 | 
				
			||||||
                go _ _ = a (const $ return ())
 | 
					                go _ _ = a (const noop)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
showSideAction :: String -> Annex ()
 | 
					showSideAction :: String -> Annex ()
 | 
				
			||||||
showSideAction s = handle q $
 | 
					showSideAction s = handle q $
 | 
				
			||||||
| 
						 | 
					@ -160,7 +160,7 @@ handle json normal = Annex.getState Annex.output >>= go
 | 
				
			||||||
		go Annex.JSONOutput = liftIO $ flushed json
 | 
							go Annex.JSONOutput = liftIO $ flushed json
 | 
				
			||||||
 | 
					
 | 
				
			||||||
q :: Monad m => m ()
 | 
					q :: Monad m => m ()
 | 
				
			||||||
q = return ()
 | 
					q = noop
 | 
				
			||||||
 | 
					
 | 
				
			||||||
flushed :: IO () -> IO ()
 | 
					flushed :: IO () -> IO ()
 | 
				
			||||||
flushed a = a >> hFlush stdout
 | 
					flushed a = a >> hFlush stdout
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -194,7 +194,7 @@ showLocations key exclude = do
 | 
				
			||||||
		message rs us = message rs [] ++ message [] us
 | 
							message rs us = message rs [] ++ message [] us
 | 
				
			||||||
 | 
					
 | 
				
			||||||
showTriedRemotes :: [Remote] -> Annex ()
 | 
					showTriedRemotes :: [Remote] -> Annex ()
 | 
				
			||||||
showTriedRemotes [] = return ()	
 | 
					showTriedRemotes [] = noop
 | 
				
			||||||
showTriedRemotes remotes =
 | 
					showTriedRemotes remotes =
 | 
				
			||||||
	showLongNote $ "Unable to access these remotes: " ++
 | 
						showLongNote $ "Unable to access these remotes: " ++
 | 
				
			||||||
		join ", " (map name remotes)
 | 
							join ", " (map name remotes)
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -195,7 +195,8 @@ meteredWriteFile' meterupdate dest startstate feeder =
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		feed state [] h = do
 | 
							feed state [] h = do
 | 
				
			||||||
			(state', cs) <- feeder state
 | 
								(state', cs) <- feeder state
 | 
				
			||||||
			if null cs then return () else feed state' cs h
 | 
								unless (null cs) $
 | 
				
			||||||
 | 
									feed state' cs h
 | 
				
			||||||
		feed state (c:cs) h = do
 | 
							feed state (c:cs) h = do
 | 
				
			||||||
			S.hPut h c
 | 
								S.hPut h c
 | 
				
			||||||
			meterupdate $ toInteger $ S.length c
 | 
								meterupdate $ toInteger $ S.length c
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -46,7 +46,7 @@ runHooks r starthook stophook a = do
 | 
				
			||||||
	a
 | 
						a
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		remoteid = show (uuid r)
 | 
							remoteid = show (uuid r)
 | 
				
			||||||
		run Nothing = return ()
 | 
							run Nothing = noop
 | 
				
			||||||
		run (Just command) = void $ liftIO $
 | 
							run (Just command) = void $ liftIO $
 | 
				
			||||||
			boolSystem "sh" [Param "-c", Param command]
 | 
								boolSystem "sh" [Param "-c", Param command]
 | 
				
			||||||
		firstrun lck = do
 | 
							firstrun lck = do
 | 
				
			||||||
| 
						 | 
					@ -81,7 +81,7 @@ runHooks r starthook stophook a = do
 | 
				
			||||||
			v <- liftIO $ tryIO $
 | 
								v <- liftIO $ tryIO $
 | 
				
			||||||
				setLock fd (WriteLock, AbsoluteSeek, 0, 0)
 | 
									setLock fd (WriteLock, AbsoluteSeek, 0, 0)
 | 
				
			||||||
			case v of
 | 
								case v of
 | 
				
			||||||
				Left _ -> return ()
 | 
									Left _ -> noop
 | 
				
			||||||
				Right _ -> run stophook
 | 
									Right _ -> run stophook
 | 
				
			||||||
			liftIO $ closeFd fd
 | 
								liftIO $ closeFd fd
 | 
				
			||||||
 | 
					
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -93,7 +93,7 @@ s3Setup u c = handlehost $ M.lookup "host" c
 | 
				
			||||||
 | 
					
 | 
				
			||||||
		archiveorg = do
 | 
							archiveorg = do
 | 
				
			||||||
			showNote "Internet Archive mode"
 | 
								showNote "Internet Archive mode"
 | 
				
			||||||
			maybe (error "specify bucket=") (const $ return ()) $
 | 
								maybe (error "specify bucket=") (const noop) $
 | 
				
			||||||
				M.lookup "bucket" archiveconfig
 | 
									M.lookup "bucket" archiveconfig
 | 
				
			||||||
			use archiveconfig
 | 
								use archiveconfig
 | 
				
			||||||
			where
 | 
								where
 | 
				
			||||||
| 
						 | 
					@ -237,13 +237,13 @@ genBucket c = do
 | 
				
			||||||
	showAction "checking bucket"
 | 
						showAction "checking bucket"
 | 
				
			||||||
	loc <- liftIO $ getBucketLocation conn bucket 
 | 
						loc <- liftIO $ getBucketLocation conn bucket 
 | 
				
			||||||
	case loc of
 | 
						case loc of
 | 
				
			||||||
		Right _ -> return ()
 | 
							Right _ -> noop
 | 
				
			||||||
		Left err@(NetworkError _) -> s3Error err
 | 
							Left err@(NetworkError _) -> s3Error err
 | 
				
			||||||
		Left (AWSError _ _) -> do
 | 
							Left (AWSError _ _) -> do
 | 
				
			||||||
			showAction $ "creating bucket in " ++ datacenter
 | 
								showAction $ "creating bucket in " ++ datacenter
 | 
				
			||||||
			res <- liftIO $ createBucketIn conn bucket datacenter
 | 
								res <- liftIO $ createBucketIn conn bucket datacenter
 | 
				
			||||||
			case res of
 | 
								case res of
 | 
				
			||||||
				Right _ -> return ()
 | 
									Right _ -> noop
 | 
				
			||||||
				Left err -> s3Error err
 | 
									Left err -> s3Error err
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		bucket = fromJust $ M.lookup "bucket" c
 | 
							bucket = fromJust $ M.lookup "bucket" c
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -89,7 +89,7 @@ updateSymlinks = do
 | 
				
			||||||
		fixlink f = do
 | 
							fixlink f = do
 | 
				
			||||||
			r <- lookupFile1 f
 | 
								r <- lookupFile1 f
 | 
				
			||||||
			case r of
 | 
								case r of
 | 
				
			||||||
				Nothing -> return ()
 | 
									Nothing -> noop
 | 
				
			||||||
				Just (k, _) -> do
 | 
									Just (k, _) -> do
 | 
				
			||||||
					link <- calcGitLink f k
 | 
										link <- calcGitLink f k
 | 
				
			||||||
					liftIO $ removeFile f
 | 
										liftIO $ removeFile f
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -19,6 +19,7 @@ import Control.Applicative
 | 
				
			||||||
import Utility.SafeCommand
 | 
					import Utility.SafeCommand
 | 
				
			||||||
import Utility.TempFile
 | 
					import Utility.TempFile
 | 
				
			||||||
import Utility.Exception
 | 
					import Utility.Exception
 | 
				
			||||||
 | 
					import Utility.Monad
 | 
				
			||||||
 | 
					
 | 
				
			||||||
{- Lists the contents of a directory.
 | 
					{- Lists the contents of a directory.
 | 
				
			||||||
 - Unlike getDirectoryContents, paths are not relative to the directory. -}
 | 
					 - Unlike getDirectoryContents, paths are not relative to the directory. -}
 | 
				
			||||||
| 
						 | 
					@ -34,7 +35,7 @@ dirContents d = map (d </>) . filter notcruft <$> getDirectoryContents d
 | 
				
			||||||
moveFile :: FilePath -> FilePath -> IO ()
 | 
					moveFile :: FilePath -> FilePath -> IO ()
 | 
				
			||||||
moveFile src dest = tryIO (rename src dest) >>= onrename
 | 
					moveFile src dest = tryIO (rename src dest) >>= onrename
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		onrename (Right _) = return ()
 | 
							onrename (Right _) = noop
 | 
				
			||||||
		onrename (Left e)
 | 
							onrename (Left e)
 | 
				
			||||||
			| isPermissionError e = rethrow
 | 
								| isPermissionError e = rethrow
 | 
				
			||||||
			| isDoesNotExistError e = rethrow
 | 
								| isDoesNotExistError e = rethrow
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -56,7 +56,7 @@ watchDir' scan i test add del dir = do
 | 
				
			||||||
		then void $ do
 | 
							then void $ do
 | 
				
			||||||
			_ <- addWatch i watchevents dir go
 | 
								_ <- addWatch i watchevents dir go
 | 
				
			||||||
			mapM walk =<< dirContents dir
 | 
								mapM walk =<< dirContents dir
 | 
				
			||||||
		else return ()
 | 
							else noop
 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		watchevents
 | 
							watchevents
 | 
				
			||||||
			| isJust add && isJust del =
 | 
								| isJust add && isJust del =
 | 
				
			||||||
| 
						 | 
					@ -68,19 +68,19 @@ watchDir' scan i test add del dir = do
 | 
				
			||||||
		recurse = watchDir' scan i test add del
 | 
							recurse = watchDir' scan i test add del
 | 
				
			||||||
		walk f = ifM (catchBoolIO $ Files.isDirectory <$> getFileStatus f)
 | 
							walk f = ifM (catchBoolIO $ Files.isDirectory <$> getFileStatus f)
 | 
				
			||||||
			( recurse f
 | 
								( recurse f
 | 
				
			||||||
			, if scan && isJust add then fromJust add f else return ()
 | 
								, when (scan && isJust add) $ fromJust add f
 | 
				
			||||||
			)
 | 
								)
 | 
				
			||||||
 | 
					
 | 
				
			||||||
		go (Created { isDirectory = False }) = return ()
 | 
							go (Created { isDirectory = False }) = noop
 | 
				
			||||||
		go (Created { filePath = subdir }) = Just recurse <@> subdir
 | 
							go (Created { filePath = subdir }) = Just recurse <@> subdir
 | 
				
			||||||
		go (Closed { maybeFilePath = Just f }) = add <@> f
 | 
							go (Closed { maybeFilePath = Just f }) = add <@> f
 | 
				
			||||||
		go (MovedIn { isDirectory = False, filePath = f }) = add <@> f
 | 
							go (MovedIn { isDirectory = False, filePath = f }) = add <@> f
 | 
				
			||||||
		go (MovedOut { isDirectory = False, filePath = f }) = del <@> f
 | 
							go (MovedOut { isDirectory = False, filePath = f }) = del <@> f
 | 
				
			||||||
		go (Deleted { isDirectory = False, filePath = f }) = del <@> f
 | 
							go (Deleted { isDirectory = False, filePath = f }) = del <@> f
 | 
				
			||||||
		go _ = return ()
 | 
							go _ = noop
 | 
				
			||||||
		
 | 
							
 | 
				
			||||||
		Just a <@> f = a $ dir </> f
 | 
							Just a <@> f = a $ dir </> f
 | 
				
			||||||
		Nothing <@> _ = return ()
 | 
							Nothing <@> _ = noop
 | 
				
			||||||
 | 
					
 | 
				
			||||||
{- Pauses the main thread, letting children run until program termination. -}
 | 
					{- Pauses the main thread, letting children run until program termination. -}
 | 
				
			||||||
waitForTermination :: IO ()
 | 
					waitForTermination :: IO ()
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -49,3 +49,7 @@ observe observer a = do
 | 
				
			||||||
{- b `after` a runs first a, then b, and returns the value of a -}
 | 
					{- b `after` a runs first a, then b, and returns the value of a -}
 | 
				
			||||||
after :: Monad m => m b -> m a -> m a
 | 
					after :: Monad m => m b -> m a -> m a
 | 
				
			||||||
after = observe . const
 | 
					after = observe . const
 | 
				
			||||||
 | 
					
 | 
				
			||||||
 | 
					{- do nothing -}
 | 
				
			||||||
 | 
					noop :: Monad m => m ()
 | 
				
			||||||
 | 
					noop = return ()
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -106,9 +106,8 @@ touchBoth file atime mtime follow =
 | 
				
			||||||
	withFilePath file $ \f -> do
 | 
						withFilePath file $ \f -> do
 | 
				
			||||||
		pokeArray ptr [atime, mtime]
 | 
							pokeArray ptr [atime, mtime]
 | 
				
			||||||
		r <- syscall f ptr
 | 
							r <- syscall f ptr
 | 
				
			||||||
		if (r /= 0)
 | 
							when (r /= 0) $
 | 
				
			||||||
			then throwErrno "touchBoth"
 | 
								throwErrno "touchBoth"
 | 
				
			||||||
			else return ()
 | 
					 | 
				
			||||||
	where
 | 
						where
 | 
				
			||||||
		syscall = if follow
 | 
							syscall = if follow
 | 
				
			||||||
			then c_lutimes
 | 
								then c_lutimes
 | 
				
			||||||
| 
						 | 
					@ -116,6 +115,6 @@ touchBoth file atime mtime follow =
 | 
				
			||||||
 | 
					
 | 
				
			||||||
#else
 | 
					#else
 | 
				
			||||||
#warning "utimensat and lutimes not available; building without symlink timestamp preservation support"
 | 
					#warning "utimensat and lutimes not available; building without symlink timestamp preservation support"
 | 
				
			||||||
touchBoth _ _ _ _ = return ()
 | 
					touchBoth _ _ _ _ = noop
 | 
				
			||||||
#endif
 | 
					#endif
 | 
				
			||||||
#endif
 | 
					#endif
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
| 
						 | 
					@ -17,6 +17,7 @@ import Common
 | 
				
			||||||
import qualified Network.Browser as Browser
 | 
					import qualified Network.Browser as Browser
 | 
				
			||||||
import Network.HTTP
 | 
					import Network.HTTP
 | 
				
			||||||
import Network.URI
 | 
					import Network.URI
 | 
				
			||||||
 | 
					import Utility.Monad
 | 
				
			||||||
 | 
					
 | 
				
			||||||
type URLString = String
 | 
					type URLString = String
 | 
				
			||||||
 | 
					
 | 
				
			||||||
| 
						 | 
					@ -95,7 +96,7 @@ request url requesttype = go 5 url
 | 
				
			||||||
			case rspCode rsp of
 | 
								case rspCode rsp of
 | 
				
			||||||
				(3,0,x) | x /= 5 -> redir (n - 1) u rsp
 | 
									(3,0,x) | x /= 5 -> redir (n - 1) u rsp
 | 
				
			||||||
				_ -> return rsp
 | 
									_ -> return rsp
 | 
				
			||||||
		ignore = const $ return ()
 | 
							ignore = const noop
 | 
				
			||||||
		redir n u rsp = case retrieveHeaders HdrLocation rsp of
 | 
							redir n u rsp = case retrieveHeaders HdrLocation rsp of
 | 
				
			||||||
			[] -> return rsp
 | 
								[] -> return rsp
 | 
				
			||||||
			(Header _ newu:_) ->
 | 
								(Header _ newu:_) ->
 | 
				
			||||||
| 
						 | 
					
 | 
				
			||||||
		Loading…
	
	Add table
		Add a link
		
	
		Reference in a new issue