{-# options_haddock prune #-}

-- |Description: Executable helpers, Internal
module Polysemy.Process.Executable where

import Path (Abs, File, Path, Rel, toFilePath)
import qualified Path.IO as Path
import Path.IO (executable, getPermissions)

checkExecutable ::
  Member (Embed IO) r =>
  Text ->
  Path Abs File ->
  Sem r (Either Text (Path Abs File))
checkExecutable :: forall (r :: EffectRow).
Member (Embed IO) r =>
Text -> Path Abs File -> Sem r (Either Text (Path Abs File))
checkExecutable Text
name Path Abs File
path =
  IO Permissions -> Sem r (Either Text Permissions)
forall (r :: EffectRow) a.
Member (Embed IO) r =>
IO a -> Sem r (Either Text a)
tryIOError (Path Abs File -> IO Permissions
forall (m :: * -> *) b t. MonadIO m => Path b t -> m Permissions
getPermissions Path Abs File
path) Sem r (Either Text Permissions)
-> (Either Text Permissions -> Either Text (Path Abs File))
-> Sem r (Either Text (Path Abs File))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
    Right (Permissions -> Bool
executable -> Bool
True) ->
      Path Abs File -> Either Text (Path Abs File)
forall a b. b -> Either a b
Right Path Abs File
path
    Right Permissions
_ ->
      Text -> Either Text (Path Abs File)
forall a b. a -> Either a b
Left (Text -> Text
message Text
"executable")
    Left Text
_ ->
      Text -> Either Text (Path Abs File)
forall a b. a -> Either a b
Left (Text -> Text
message Text
"a readable file")
  where
    message :: Text -> Text
message Text
what =
      Text
"specified path for `" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"` is not " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
what Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
": " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
pathText
    pathText :: Text
pathText =
      FilePath -> Text
forall a. ToText a => a -> Text
toText (Path Abs File -> FilePath
forall b t. Path b t -> FilePath
toFilePath Path Abs File
path)

-- |Find a file in @$PATH@, verifying that it is executable by this process.
resolveExecutable ::
  Member (Embed IO) r =>
  -- |Executable name, for @$PATH@ lookup and error messages
  Path Rel File ->
  -- |Explicit override to be checked for adequate permissions
  Maybe (Path Abs File) ->
  Sem r (Either Text (Path Abs File))
resolveExecutable :: forall (r :: EffectRow).
Member (Embed IO) r =>
Path Rel File
-> Maybe (Path Abs File) -> Sem r (Either Text (Path Abs File))
resolveExecutable Path Rel File
exe = \case
  Just Path Abs File
path ->
    Text -> Path Abs File -> Sem r (Either Text (Path Abs File))
forall (r :: EffectRow).
Member (Embed IO) r =>
Text -> Path Abs File -> Sem r (Either Text (Path Abs File))
checkExecutable Text
name Path Abs File
path
  Maybe (Path Abs File)
Nothing ->
    IO (Maybe (Path Abs File))
-> Sem r (Either Text (Maybe (Path Abs File)))
forall (r :: EffectRow) a.
Member (Embed IO) r =>
IO a -> Sem r (Either Text a)
tryIOError (Path Rel File -> IO (Maybe (Path Abs File))
forall (m :: * -> *).
MonadIO m =>
Path Rel File -> m (Maybe (Path Abs File))
Path.findExecutable Path Rel File
exe) Sem r (Either Text (Maybe (Path Abs File)))
-> (Either Text (Maybe (Path Abs File))
    -> Either Text (Path Abs File))
-> Sem r (Either Text (Path Abs File))
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
      Right (Just Path Abs File
path) ->
        Path Abs File -> Either Text (Path Abs File)
forall a b. b -> Either a b
Right Path Abs File
path
      Either Text (Maybe (Path Abs File))
_ ->
        Text -> Either Text (Path Abs File)
forall a b. a -> Either a b
Left (Text
"could not find executable `" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
name Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"` in `$PATH`.")
  where
    name :: Text
name =
      FilePath -> Text
forall a. ToText a => a -> Text
toText (Path Rel File -> FilePath
forall b t. Path b t -> FilePath
toFilePath Path Rel File
exe)