module EndOfExe where import qualified System.Directory as D (findExecutable) import Data.Maybe (isJust,isNothing) import System.IO.Unsafe (unsafePerformIO) -- | Function that is used instead of 'System.Info.os' to check whether the executable ends in .exe. The function returns @IO Nothing@ if there is neither @ys@ nor @(ys ++ ".exe")@ names for executables in the -- variable @PATH@ endOfExecutable :: String -> IO (Maybe String) endOfExecutable ys = do xs <- D.findExecutable ys if isJust xs then return $ fmap (ys ++) (Just "") else do zs <- D.findExecutable (ys ++ ".exe") if isJust zs then return $ fmap (ys ++) (Just ".exe") else error ("Please, install the executable " ++ ys ++ " into the directory in the PATH variable!") -- | Function to get the proper name of the executable in the system (it must be seen in the directories in the @PATH@ variable). -- You can use 'showE' \"nameOfExecutable\" to get @Just \"nameOfExecutable\"@ if it is present on the system. Further you can adopt it to be used -- inside the 'System.Process.callCommand' as the name of the executable showE :: String -> Maybe String showE xs | null xs = error "No executable specified!" | otherwise = let r = unsafePerformIO . endOfExecutable $ xs in if isJust r then r else Nothing -- | Function that being given a list of names of executables (without .exe suffix) looks up for them in the specified list order till the first existing occurrence. -- If there is no such occurrence (the specified executables are not installed in the directories mentioned in the variable @PATH@) then the function returns @Nothing@. findSysExes :: [String] -> Maybe String findSysExes xss | null (dropWhile isNothing . map showE $ xss) = Nothing | otherwise = head (dropWhile isNothing . map showE $ xss)