2014-09-18 08:05:47 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
2014-04-19 06:17:36 +00:00
|
|
|
module Language.Haskell.GhcMod.Utils where
|
2014-04-19 06:20:16 +00:00
|
|
|
|
2014-11-02 18:00:25 +00:00
|
|
|
import Control.Arrow
|
|
|
|
import Data.Char
|
2014-08-28 09:54:01 +00:00
|
|
|
import Language.Haskell.GhcMod.Error
|
2014-08-19 05:56:01 +00:00
|
|
|
import MonadUtils (MonadIO, liftIO)
|
2014-11-01 21:02:47 +00:00
|
|
|
import System.Directory (getCurrentDirectory, setCurrentDirectory, doesFileExist)
|
2014-04-30 23:48:03 +00:00
|
|
|
import System.Exit (ExitCode(..))
|
2014-08-19 05:56:01 +00:00
|
|
|
import System.Process (readProcessWithExitCode)
|
2014-11-02 18:00:25 +00:00
|
|
|
import System.Directory (getTemporaryDirectory)
|
2014-11-02 18:27:40 +00:00
|
|
|
import System.FilePath (splitDrive, pathSeparators)
|
2014-11-02 18:00:25 +00:00
|
|
|
import System.IO.Temp (createTempDirectory)
|
2014-09-18 08:05:47 +00:00
|
|
|
#ifndef SPEC
|
2014-10-06 06:55:16 +00:00
|
|
|
import Control.Applicative ((<$>))
|
2014-09-18 08:05:47 +00:00
|
|
|
import System.Environment
|
2014-10-03 19:21:26 +00:00
|
|
|
import System.FilePath ((</>), takeDirectory)
|
2014-09-18 08:05:47 +00:00
|
|
|
#endif
|
2014-04-30 23:48:03 +00:00
|
|
|
|
2014-04-19 06:20:16 +00:00
|
|
|
-- dropWhileEnd is not provided prior to base 4.5.0.0.
|
|
|
|
dropWhileEnd :: (a -> Bool) -> [a] -> [a]
|
|
|
|
dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
|
2014-04-30 23:54:15 +00:00
|
|
|
|
|
|
|
extractParens :: String -> String
|
|
|
|
extractParens str = extractParens' str 0
|
|
|
|
where
|
|
|
|
extractParens' :: String -> Int -> String
|
|
|
|
extractParens' [] _ = []
|
|
|
|
extractParens' (s:ss) level
|
|
|
|
| s `elem` "([{" = s : extractParens' ss (level+1)
|
|
|
|
| level == 0 = extractParens' ss 0
|
2014-07-17 08:16:44 +00:00
|
|
|
| s `elem` "}])" && level == 1 = [s]
|
2014-04-30 23:54:15 +00:00
|
|
|
| s `elem` "}])" = s : extractParens' ss (level-1)
|
|
|
|
| otherwise = s : extractParens' ss level
|
|
|
|
|
2014-08-28 09:54:01 +00:00
|
|
|
readProcess' :: (MonadIO m, MonadError GhcModError m)
|
2014-08-18 06:06:36 +00:00
|
|
|
=> String
|
|
|
|
-> [String]
|
|
|
|
-> m String
|
2014-04-30 23:48:03 +00:00
|
|
|
readProcess' cmd opts = do
|
2014-08-28 09:54:01 +00:00
|
|
|
(rv,output,err) <- liftIO (readProcessWithExitCode cmd opts "")
|
|
|
|
`modifyError'` GMEProcess ([cmd] ++ opts)
|
2014-04-30 23:48:03 +00:00
|
|
|
case rv of
|
|
|
|
ExitFailure val -> do
|
2014-08-28 09:54:01 +00:00
|
|
|
throwError $ GMEProcess ([cmd] ++ opts) $ strMsg $
|
2014-08-18 06:06:36 +00:00
|
|
|
cmd ++ " " ++ unwords opts ++ " (exit " ++ show val ++ ")"
|
2014-08-19 05:56:01 +00:00
|
|
|
++ "\n" ++ err
|
2014-04-30 23:48:03 +00:00
|
|
|
ExitSuccess ->
|
|
|
|
return output
|
2014-05-01 00:10:42 +00:00
|
|
|
|
2014-08-28 09:54:01 +00:00
|
|
|
withDirectory_ :: (MonadIO m, ExceptionMonad m) => FilePath -> m a -> m a
|
2014-05-01 00:10:42 +00:00
|
|
|
withDirectory_ dir action =
|
2014-08-28 09:54:01 +00:00
|
|
|
gbracket (liftIO getCurrentDirectory) (liftIO . setCurrentDirectory)
|
|
|
|
(\_ -> liftIO (setCurrentDirectory dir) >> action)
|
2014-09-18 08:05:47 +00:00
|
|
|
|
2014-11-02 18:00:25 +00:00
|
|
|
uniqTempDirName :: FilePath -> FilePath
|
|
|
|
uniqTempDirName dir =
|
|
|
|
uncurry (++)
|
|
|
|
$ map escapeDriveChar *** map escapePathChar
|
|
|
|
$ splitDrive dir
|
|
|
|
where
|
|
|
|
escapeDriveChar c
|
|
|
|
| isAlphaNum c = c
|
|
|
|
| otherwise = '-'
|
|
|
|
|
|
|
|
escapePathChar c
|
|
|
|
| c `elem` pathSeparators = '-'
|
|
|
|
| otherwise = c
|
|
|
|
|
|
|
|
newTempDir :: FilePath -> IO FilePath
|
|
|
|
newTempDir dir =
|
|
|
|
flip createTempDirectory (uniqTempDirName dir) =<< getTemporaryDirectory
|
|
|
|
|
2014-11-01 21:02:47 +00:00
|
|
|
mightExist :: FilePath -> IO (Maybe FilePath)
|
|
|
|
mightExist f = do
|
|
|
|
exists <- doesFileExist f
|
|
|
|
return $ if exists then (Just f) else (Nothing)
|
|
|
|
|
2014-09-18 08:05:47 +00:00
|
|
|
-- | Returns the path to the currently running ghc-mod executable. With ghc<7.6
|
|
|
|
-- this is a guess but >=7.6 uses 'getExecutablePath'.
|
|
|
|
ghcModExecutable :: IO FilePath
|
|
|
|
#ifndef SPEC
|
2014-10-03 19:21:26 +00:00
|
|
|
ghcModExecutable = do
|
|
|
|
dir <- getExecutablePath'
|
|
|
|
return $ dir </> "ghc-mod"
|
2014-09-18 08:05:47 +00:00
|
|
|
where
|
2014-10-03 19:21:26 +00:00
|
|
|
getExecutablePath' :: IO FilePath
|
2014-09-18 08:05:47 +00:00
|
|
|
# if __GLASGOW_HASKELL__ >= 706
|
2014-10-03 19:21:26 +00:00
|
|
|
getExecutablePath' = takeDirectory <$> getExecutablePath
|
2014-09-18 08:05:47 +00:00
|
|
|
# else
|
2014-10-03 19:21:26 +00:00
|
|
|
getExecutablePath' = return ""
|
2014-09-18 08:05:47 +00:00
|
|
|
# endif
|
2014-10-06 06:29:05 +00:00
|
|
|
#else
|
|
|
|
ghcModExecutable = return "dist/build/ghc-mod/ghc-mod"
|
|
|
|
#endif
|