| Copyright | (c) Julian Ospald 2020 |
|---|---|
| License | LGPL-3.0 |
| Maintainer | hasufell@hasufell.de |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
GHCup.Utils.File
Description
This module handles file and executable handling. Some of these functions use sophisticated logging.
Synopsis
- data ProcessError
- data CapturedProcess = CapturedProcess {}
- stdOut :: Lens' CapturedProcess ByteString
- stdErr :: Lens' CapturedProcess ByteString
- exitCode :: Lens' CapturedProcess ExitCode
- findExecutable :: Path Rel -> IO (Maybe (Path Abs))
- executeOut :: Path b -> [ByteString] -> Maybe (Path Abs) -> IO CapturedProcess
- execLogged :: (MonadReader AppState m, MonadIO m, MonadThrow m) => ByteString -> Bool -> [ByteString] -> Path Rel -> Maybe (Path Abs) -> Maybe [(ByteString, ByteString)] -> m (Either ProcessError ())
- captureOutStreams :: IO a -> IO CapturedProcess
- actionWithPipes :: ((Fd, Fd) -> IO b) -> IO b
- cleanup :: [Fd] -> IO ()
- createRegularFileFd :: FileMode -> Path b -> IO Fd
- exec :: ByteString -> Bool -> [ByteString] -> Maybe (Path Abs) -> Maybe [(ByteString, ByteString)] -> IO (Either ProcessError ())
- toProcessError :: ByteString -> [ByteString] -> Maybe ProcessStatus -> Either ProcessError ()
- searchPath :: [Path Abs] -> Path Rel -> IO (Maybe (Path Abs))
- isShadowed :: Path Abs -> IO (Maybe (Path Abs))
- isInPath :: Path Abs -> IO Bool
- findFiles :: Path Abs -> Regex -> IO [Path Rel]
- findFiles' :: Path Abs -> Parsec Void Text () -> IO [Path Rel]
- isBrokenSymlink :: Path Abs -> IO Bool
- chmod_755 :: (MonadLogger m, MonadIO m) => Path a -> m ()
Documentation
data ProcessError Source #
Constructors
| NonZeroExit Int ByteString [ByteString] | |
| PTerminated ByteString [ByteString] | |
| PStopped ByteString [ByteString] | |
| NoSuchPid ByteString [ByteString] |
Instances
| Show ProcessError Source # | |
Defined in GHCup.Utils.File Methods showsPrec :: Int -> ProcessError -> ShowS # show :: ProcessError -> String # showList :: [ProcessError] -> ShowS # | |
| Pretty ProcessError Source # | |
Defined in GHCup.Utils.File Methods pPrintPrec :: PrettyLevel -> Rational -> ProcessError -> Doc # pPrint :: ProcessError -> Doc # pPrintList :: PrettyLevel -> [ProcessError] -> Doc # | |
data CapturedProcess Source #
Constructors
| CapturedProcess | |
Fields
| |
Instances
| Eq CapturedProcess Source # | |
Defined in GHCup.Utils.File Methods (==) :: CapturedProcess -> CapturedProcess -> Bool # (/=) :: CapturedProcess -> CapturedProcess -> Bool # | |
| Show CapturedProcess Source # | |
Defined in GHCup.Utils.File Methods showsPrec :: Int -> CapturedProcess -> ShowS # show :: CapturedProcess -> String # showList :: [CapturedProcess] -> ShowS # | |
findExecutable :: Path Rel -> IO (Maybe (Path Abs)) Source #
Find the given executable by searching all *absolute* PATH components. Relative paths in PATH are ignored.
This shouldn't throw IO exceptions, unless getting the environment variable PATH does.
Arguments
| :: Path b | command as filename, e.g. |
| -> [ByteString] | arguments to the command |
| -> Maybe (Path Abs) | chdir to this path |
| -> IO CapturedProcess |
Execute the given command and collect the stdout, stderr and the exit code. The command is run in a subprocess.
Arguments
| :: (MonadReader AppState m, MonadIO m, MonadThrow m) | |
| => ByteString | thing to execute |
| -> Bool | whether to search PATH for the thing |
| -> [ByteString] | args for the thing |
| -> Path Rel | log filename |
| -> Maybe (Path Abs) | optionally chdir into this |
| -> Maybe [(ByteString, ByteString)] | optional environment |
| -> m (Either ProcessError ()) |
Arguments
| :: IO a | the action to execute in a subprocess |
| -> IO CapturedProcess |
Capture the stdout and stderr of the given action, which
is run in a subprocess. Stdin is closed. You might want to
race this to make sure it terminates.
createRegularFileFd :: FileMode -> Path b -> IO Fd Source #
Create a new regular file in write-only mode. The file must not exist.
Arguments
| :: ByteString | thing to execute |
| -> Bool | whether to search PATH for the thing |
| -> [ByteString] | args for the thing |
| -> Maybe (Path Abs) | optionally chdir into this |
| -> Maybe [(ByteString, ByteString)] | optional environment |
| -> IO (Either ProcessError ()) |
Thin wrapper around executeFile.
toProcessError :: ByteString -> [ByteString] -> Maybe ProcessStatus -> Either ProcessError () Source #
searchPath :: [Path Abs] -> Path Rel -> IO (Maybe (Path Abs)) Source #
Search for a file in the search paths.
Catches PermissionDenied and NoSuchThing and returns Nothing.
isShadowed :: Path Abs -> IO (Maybe (Path Abs)) Source #
Check wether a binary is shadowed by another one that comes before it in PATH. Returns the path to said binary, if any.