module Darcs.Util.Global
(
timingsMode
, setTimingsMode
, whenDebugMode
, withDebugMode
, setDebugMode
, debugMessage
, debugFail
, putTiming
, addCRCWarning
, getCRCWarnings
, resetCRCWarnings
, addBadSource
, getBadSourcesList
, isBadSource
, darcsdir
, darcsLastMessage
, darcsSendMessage
, darcsSendMessageFinal
, defaultRemoteDarcsCmd
, isReachableSource
, addReachableSource
) where
import Prelude ()
import Darcs.Prelude
import Control.Monad ( when )
import Data.IORef ( modifyIORef, IORef, newIORef, readIORef, writeIORef )
import System.IO.Unsafe (unsafePerformIO)
import System.IO ( hPutStrLn, hPutStr, stderr )
import System.Time ( calendarTimeToString, toCalendarTime, getClockTime )
import System.FilePath.Posix ( combine, (<.>) )
_debugMode :: IORef Bool
_debugMode = unsafePerformIO $ newIORef False
setDebugMode :: IO ()
setDebugMode = writeIORef _debugMode True
whenDebugMode :: IO () -> IO ()
whenDebugMode j = do b <- readIORef _debugMode
when b j
withDebugMode :: (Bool -> IO a) -> IO a
withDebugMode j = readIORef _debugMode >>= j
debugMessage :: String -> IO ()
debugMessage m = whenDebugMode $ do putTiming; hPutStrLn stderr m
debugFail :: String -> IO a
debugFail m = debugMessage m >> fail m
putTiming :: IO ()
putTiming = when timingsMode $ do
t <- getClockTime >>= toCalendarTime
hPutStr stderr (calendarTimeToString t++": ")
_timingsMode :: IORef Bool
_timingsMode = unsafePerformIO $ newIORef False
setTimingsMode :: IO ()
setTimingsMode = writeIORef _timingsMode True
timingsMode :: Bool
timingsMode = unsafePerformIO $ readIORef _timingsMode
type CRCWarningList = [FilePath]
_crcWarningList :: IORef CRCWarningList
_crcWarningList = unsafePerformIO $ newIORef []
addCRCWarning :: FilePath -> IO ()
addCRCWarning fp = modifyIORef _crcWarningList (fp:)
getCRCWarnings :: IO [FilePath]
getCRCWarnings = readIORef _crcWarningList
resetCRCWarnings :: IO ()
resetCRCWarnings = writeIORef _crcWarningList []
_badSourcesList :: IORef [String]
_badSourcesList = unsafePerformIO $ newIORef []
addBadSource :: String -> IO ()
addBadSource cache = modifyIORef _badSourcesList (cache:)
getBadSourcesList :: IO [String]
getBadSourcesList = readIORef _badSourcesList
isBadSource :: IO (String -> Bool)
isBadSource = do
badSources <- getBadSourcesList
return (`elem` badSources)
_reachableSourcesList :: IORef [String]
_reachableSourcesList = unsafePerformIO $ newIORef []
addReachableSource :: String -> IO ()
addReachableSource src = modifyIORef _reachableSourcesList (src:)
getReachableSources :: IO [String]
getReachableSources = readIORef _reachableSourcesList
isReachableSource :: IO (String -> Bool)
isReachableSource = do
reachableSources <- getReachableSources
return (`elem` reachableSources)
darcsdir :: String
darcsdir = "_darcs"
defaultRemoteDarcsCmd :: String
defaultRemoteDarcsCmd = "darcs"
darcsLastMessage :: String
darcsLastMessage = combine darcsdir "patch_description.txt"
darcsSendMessage :: String
darcsSendMessage = combine darcsdir "darcs-send"
darcsSendMessageFinal :: String
darcsSendMessageFinal = darcsSendMessage <.> "final"