{-# LANGUAGE OverloadedStrings, TemplateHaskell #-}
module System.Which where
import qualified Shelly as Sh
import qualified Data.Text as T
import Language.Haskell.TH (Exp, Q, reportError, runIO)
import Data.Monoid ((<>))
import Data.List (isPrefixOf)
which :: FilePath -> IO (Maybe FilePath)
which f = fmap (fmap (T.unpack . Sh.toTextIgnore)) $ Sh.shelly $ Sh.which $ Sh.fromText $ T.pack f
staticWhich :: FilePath -> Q Exp
staticWhich f = do
mf' <- runIO $ which f
case mf' of
Nothing -> compileError $ "Could not find executable for " <> show f
Just f'
| "/nix/store/" `isPrefixOf` f' -> [| f' |]
| otherwise -> compileError $ "Path to executable " <> show f <> " was found in " <> show f' <> " which is not in /nix/store. Be sure to add the relevant package to 'backendTools' in default.nix."
where
compileError msg' = do
let msg = "staticWhich: " <> msg'
reportError msg
[| error msg |]