-- Copyright (C) 2005 Tomasz Zielonka -- -- This program is free software; you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation; either version 2, or (at your option) -- any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with this program; see the file COPYING. If not, write to -- the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, -- Boston, MA 02110-1301, USA. {-# LANGUAGE CPP #-} -- | This was originally Tomasz Zielonka's AtExit module, slightly generalised -- to include global variables. Here, we attempt to cover broad, global -- features, such as exit handlers. These features slightly break the Haskellian -- purity of darcs, in favour of programming convenience. module Darcs.Global ( atexit, withAtexit, SshSettings(..), defaultSsh, timingsMode, setTimingsMode, whenDebugMode, withDebugMode, setDebugMode, debugMessage, debugFail, putTiming, addCRCWarning, getCRCWarnings, resetCRCWarnings, addBadSource, getBadSourcesList, isBadSource, darcsdir, isReachableSource, addReachableSource, windows ) where import Control.Applicative ( (<$>), (<*>) ) import Control.Monad ( when ) import Control.Concurrent.MVar import Control.Exception.Extensible ( bracket_, catch, catchJust, SomeException , block, unblock ) import Data.IORef ( IORef, newIORef, readIORef, writeIORef ) import Data.IORef ( modifyIORef ) import Data.List ( isPrefixOf ) import System.Info ( os ) import System.IO.Unsafe (unsafePerformIO) import System.IO (hPutStrLn, hPutStr, stderr) import System.IO.Error ( ioeGetErrorType, isDoesNotExistErrorType ) import System.Process ( readProcessWithExitCode ) import System.Time ( calendarTimeToString, toCalendarTime, getClockTime ) import System.Environment ( getEnv ) import System.Exit ( ExitCode(..) ) import Prelude hiding (catch) windows :: Bool windows = "mingw" `isPrefixOf` os {-# NOINLINE atexitActions #-} atexitActions :: MVar (Maybe [IO ()]) atexitActions = unsafePerformIO (newMVar (Just [])) -- | Registers an IO action to run just before darcs exits. Useful -- for removing temporary files and directories, for example. atexit :: IO () -> IO () atexit action = do modifyMVar_ atexitActions $ \ml -> do case ml of Just l -> do return (Just (action : l)) Nothing -> do hPutStrLn stderr "It's too late to use atexit" return Nothing withAtexit :: IO a -> IO a withAtexit prog = do bracket_ (return ()) exit prog where exit = block $ do Just actions <- swapMVar atexitActions Nothing -- from now on atexit will not register new actions mapM_ runAction actions runAction action = do catch (unblock action) $ \(exn :: SomeException) -> do hPutStrLn stderr $ "Exception thrown by an atexit registered action:" hPutStrLn stderr $ show exn -- Write-once-read-many global variables make it easier to implement flags, such -- as --no-ssh-cm. Using global variables reduces the number of parameters -- that we have to pass around, but it is rather unsafe and should be used sparingly. {-# NOINLINE _debugMode #-} _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++": ") {-# NOINLINE _timingsMode #-} _timingsMode :: IORef Bool _timingsMode = unsafePerformIO $ newIORef False setTimingsMode :: IO () setTimingsMode = writeIORef _timingsMode True {-# NOINLINE timingsMode #-} timingsMode :: Bool timingsMode = unsafePerformIO $ readIORef _timingsMode data SshSettings = SshSettings { ssh :: String , scp :: String , sftp :: String } deriving (Show, Eq) _defaultSsh :: IORef SshSettings _defaultSsh = unsafePerformIO $ newIORef =<< detectSsh -- expected properties: -- -- * only ever runs once in the lifetime of the program -- * environment variables override all -- * tries Putty first on Windows -- * falls back to plain old ssh detectSsh :: IO SshSettings detectSsh = do whenDebugMode (putStrLn "Detecting SSH settings") vanilla <- if windows then do plinkStr <- (snd3 <$> readProcessWithExitCode "plink" [] "") `catch` \(e :: SomeException) -> return (show e) whenDebugMode $ putStrLn $ "SSH settings (plink): " ++ (concat . take 1 . lines $ plinkStr) if "PuTTY" `isPrefixOf` plinkStr then return (SshSettings "plink" "pscp -q" "psftp") else return rawVanilla else return rawVanilla settings <- SshSettings <$> fromEnv (ssh vanilla) "DARCS_SSH" <*> fromEnv (scp vanilla) "DARCS_SCP" <*> fromEnv (sftp vanilla) "DARCS_SFTP" whenDebugMode (putStrLn $ "SSH settings: " ++ show settings) return settings where snd3 (_, x, _) = x rawVanilla = SshSettings "ssh" "scp -q" "sftp" fromEnv :: String -> String -> IO String fromEnv d v = catchJust notFound (getEnv v) (const (return d)) notFound e = if isDoesNotExistErrorType (ioeGetErrorType e) then Just () else Nothing defaultSsh :: SshSettings defaultSsh = unsafePerformIO $ readIORef _defaultSsh type CRCWarningList = [FilePath] {-# NOINLINE _crcWarningList #-} _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 [] {- NOINLINE _badSourcesList -} _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) {- NOINLINE _reachableSourcesList -} _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"