summaryrefslogtreecommitdiff
path: root/Utility/ThreadScheduler.hs
diff options
context:
space:
mode:
authorJoey Hess <joey@kitenet.net>2013-11-20 20:20:14 -0400
committerJoey Hess <joey@kitenet.net>2013-11-20 20:23:37 -0400
commitac491b4fac4e83f0319e0da7c82f86d81a5b7030 (patch)
tree33ee787767831234e1d775d589844b66af4ea311 /Utility/ThreadScheduler.hs
parent7d21450e862ed30d0e7dc35ffb818bf7ac6e4687 (diff)
downloadgit-repair-ac491b4fac4e83f0319e0da7c82f86d81a5b7030.tar.gz
fix cat-file stall bug
Apparently some corruption to an object can cause cat-file to say it's N bytes long, but only output N-M bytes of data. This causes Git.CatFile to stall waiting for the rest. To fix, add a 1 minute timeout to the cat-file, which should be enough time to read any reasonable object.
Diffstat (limited to 'Utility/ThreadScheduler.hs')
-rw-r--r--Utility/ThreadScheduler.hs69
1 files changed, 69 insertions, 0 deletions
diff --git a/Utility/ThreadScheduler.hs b/Utility/ThreadScheduler.hs
new file mode 100644
index 0000000..c3e871c
--- /dev/null
+++ b/Utility/ThreadScheduler.hs
@@ -0,0 +1,69 @@
+{- thread scheduling
+ -
+ - Copyright 2012, 2013 Joey Hess <joey@kitenet.net>
+ - Copyright 2011 Bas van Dijk & Roel van Dijk
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+{-# LANGUAGE CPP #-}
+
+module Utility.ThreadScheduler where
+
+import Common
+
+import Control.Concurrent
+#ifndef mingw32_HOST_OS
+import System.Posix.Signals
+#ifndef __ANDROID__
+import System.Posix.Terminal
+#endif
+#endif
+
+newtype Seconds = Seconds { fromSeconds :: Int }
+ deriving (Eq, Ord, Show)
+
+type Microseconds = Integer
+
+{- Runs an action repeatedly forever, sleeping at least the specified number
+ - of seconds in between. -}
+runEvery :: Seconds -> IO a -> IO a
+runEvery n a = forever $ do
+ threadDelaySeconds n
+ a
+
+threadDelaySeconds :: Seconds -> IO ()
+threadDelaySeconds (Seconds n) = unboundDelay (fromIntegral n * oneSecond)
+
+{- Like threadDelay, but not bounded by an Int.
+ -
+ - There is no guarantee that the thread will be rescheduled promptly when the
+ - delay has expired, but the thread will never continue to run earlier than
+ - specified.
+ -
+ - Taken from the unbounded-delay package to avoid a dependency for 4 lines
+ - of code.
+ -}
+unboundDelay :: Microseconds -> IO ()
+unboundDelay time = do
+ let maxWait = min time $ toInteger (maxBound :: Int)
+ threadDelay $ fromInteger maxWait
+ when (maxWait /= time) $ unboundDelay (time - maxWait)
+
+{- Pauses the main thread, letting children run until program termination. -}
+waitForTermination :: IO ()
+waitForTermination = do
+ lock <- newEmptyMVar
+#ifndef mingw32_HOST_OS
+ let check sig = void $
+ installHandler sig (CatchOnce $ putMVar lock ()) Nothing
+ check softwareTermination
+#ifndef __ANDROID__
+ whenM (queryTerminal stdInput) $
+ check keyboardSignal
+#endif
+#endif
+ takeMVar lock
+
+oneSecond :: Microseconds
+oneSecond = 1000000