{-# LANGUAGE ScopedTypeVariables #-}
module General.Extra(
getProcessorCount,
findGcc,
withResultType,
whenLeft,
randomElem,
wrapQuote, showBracket,
withs,
maximum', maximumBy',
fastAt,
forkFinallyUnmasked,
isAsyncException,
doesFileExist_,
removeFile_, createDirectoryRecursive,
catchIO, tryIO, handleIO
) where
import Control.Exception
import Data.Char
import Data.List
import System.Environment.Extra
import System.IO.Extra
import System.IO.Unsafe
import System.Info.Extra
import System.FilePath
import System.Random
import System.Directory
import System.Exit
import Control.Concurrent
import Data.Maybe
import Data.Functor
import Data.Primitive.Array
import Control.Applicative
import Control.Monad
import Control.Monad.ST
import GHC.Conc(getNumProcessors)
import Prelude
maximumBy' :: (a -> a -> Ordering) -> [a] -> a
maximumBy' cmp = foldl1' $ \x y -> if cmp x y == GT then x else y
maximum' :: Ord a => [a] -> a
maximum' = maximumBy' compare
wrapQuote :: String -> String
wrapQuote xs | any isSpace xs = "\"" ++ concatMap (\x -> if x == '\"' then "\"\"" else [x]) xs ++ "\""
| otherwise = xs
wrapBracket :: String -> String
wrapBracket xs | any isSpace xs = "(" ++ xs ++ ")"
| otherwise = xs
showBracket :: Show a => a -> String
showBracket = wrapBracket . show
fastAt :: [a] -> (Int -> Maybe a)
fastAt xs = \i -> if i < 0 || i >= n then Nothing else Just $ indexArray arr i
where
n = length xs
arr = runST $ do
let n = length xs
arr <- newArray n undefined
forM_ (zip [0..] xs) $ \(i,x) ->
writeArray arr i x
unsafeFreezeArray arr
{-# NOINLINE getProcessorCount #-}
getProcessorCount :: IO Int
getProcessorCount = let res = unsafePerformIO act in return res
where
act =
if rtsSupportsBoundThreads then
fromIntegral <$> getNumProcessors
else do
env <- lookupEnv "NUMBER_OF_PROCESSORS"
case env of
Just s | [(i,"")] <- reads s -> return i
_ -> do
src <- readFile' "/proc/cpuinfo" `catchIO` \_ -> return ""
return $! max 1 $ length [() | x <- lines src, "processor" `isPrefixOf` x]
findGcc :: IO (Bool, Maybe FilePath)
findGcc = do
v <- findExecutable "gcc"
case v of
Nothing | isWindows -> do
ghc <- findExecutable "ghc"
case ghc of
Just ghc -> do
let gcc = takeDirectory (takeDirectory ghc) </> "mingw/bin/gcc.exe"
b <- doesFileExist_ gcc
return $ if b then (True, Just $ takeDirectory gcc) else (False, Nothing)
_ -> return (False, Nothing)
_ -> return (isJust v, Nothing)
randomElem :: [a] -> IO a
randomElem xs = do
when (null xs) $ fail "General.Extra.randomElem called with empty list, can't pick a random element"
i <- randomRIO (0, length xs - 1)
return $ xs !! i
withs :: [(a -> r) -> r] -> ([a] -> r) -> r
withs [] act = act []
withs (f:fs) act = f $ \a -> withs fs $ \as -> act $ a:as
forkFinallyUnmasked :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
forkFinallyUnmasked act cleanup =
mask_ $ forkIOWithUnmask $ \unmask ->
try (unmask act) >>= cleanup
isAsyncException :: SomeException -> Bool
isAsyncException e
| Just (_ :: AsyncException) <- fromException e = True
| Just (_ :: ExitCode) <- fromException e = True
| otherwise = False
catchIO :: IO a -> (IOException -> IO a) -> IO a
catchIO = Control.Exception.catch
tryIO :: IO a -> IO (Either IOException a)
tryIO = try
handleIO :: (IOException -> IO a) -> IO a -> IO a
handleIO = flip catchIO
doesFileExist_ :: FilePath -> IO Bool
doesFileExist_ x = doesFileExist x `catchIO` \_ -> return False
removeFile_ :: FilePath -> IO ()
removeFile_ x = removeFile x `catchIO` \_ -> return ()
createDirectoryRecursive :: FilePath -> IO ()
createDirectoryRecursive dir = do
x <- tryIO $ doesDirectoryExist dir
when (x /= Right True) $ createDirectoryIfMissing True dir
whenLeft :: Applicative m => Either a b -> (a -> m ()) -> m ()
whenLeft x f = either f (const $ pure ()) x
withResultType :: (Maybe a -> a) -> a
withResultType f = f Nothing