Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
HIE.Bios.Process
Synopsis
- data CreateProcess = CreateProcess {
- cmdspec :: CmdSpec
- cwd :: Maybe FilePath
- env :: Maybe [(String, String)]
- std_in :: StdStream
- std_out :: StdStream
- std_err :: StdStream
- close_fds :: Bool
- create_group :: Bool
- delegate_ctlc :: Bool
- detach_console :: Bool
- create_new_console :: Bool
- new_session :: Bool
- child_group :: Maybe GroupID
- child_user :: Maybe UserID
- use_process_jobs :: Bool
- readProcessWithCwd :: LogAction IO (WithSeverity Log) -> FilePath -> FilePath -> [String] -> String -> IO (CradleLoadResult String)
- readProcessWithCwd_ :: LogAction IO (WithSeverity Log) -> FilePath -> FilePath -> [String] -> String -> CradleLoadResultT IO String
- readProcessWithCwd' :: LogAction IO (WithSeverity Log) -> CreateProcess -> String -> CradleLoadResultT IO String
- readProcessWithOutputs :: Outputs -> LogAction IO (WithSeverity Log) -> FilePath -> CreateProcess -> IO (ExitCode, [String], [String], [(OutputName, Maybe [String])])
- getCleanEnvironment :: IO [(String, String)]
- cacheFile :: FilePath -> String -> (FilePath -> IO ()) -> IO FilePath
- findFileUpwards :: FilePath -> FilePath -> MaybeT IO FilePath
- findFileUpwardsPredicate :: (FilePath -> Bool) -> FilePath -> MaybeT IO FilePath
- findFile :: (FilePath -> Bool) -> FilePath -> IO [FilePath]
Documentation
data CreateProcess #
Constructors
CreateProcess | |
Fields
|
Instances
Show CreateProcess | |
Defined in System.Process.Common Methods showsPrec :: Int -> CreateProcess -> ShowS # show :: CreateProcess -> String # showList :: [CreateProcess] -> ShowS # | |
Eq CreateProcess | |
Defined in System.Process.Common Methods (==) :: CreateProcess -> CreateProcess -> Bool # (/=) :: CreateProcess -> CreateProcess -> Bool # |
Run processes with extra environment variables
readProcessWithCwd :: LogAction IO (WithSeverity Log) -> FilePath -> FilePath -> [String] -> String -> IO (CradleLoadResult String) Source #
Wrapper around readCreateProcess
that sets the working directory and
clears the environment, suitable for invoking cabal/stack and raw ghc commands.
readProcessWithCwd_ :: LogAction IO (WithSeverity Log) -> FilePath -> FilePath -> [String] -> String -> CradleLoadResultT IO String Source #
readProcessWithCwd' :: LogAction IO (WithSeverity Log) -> CreateProcess -> String -> CradleLoadResultT IO String Source #
Wrapper around readCreateProcessWithExitCode
, wrapping the result in
a CradleLoadResult
. Provides better error messages than raw readCreateProcess
.
readProcessWithOutputs Source #
Arguments
:: Outputs | Names of the outputs produced by this process |
-> LogAction IO (WithSeverity Log) | Output of the process is emitted as logs. |
-> FilePath | Working directory. Process is executed in this directory. |
-> CreateProcess | Parameters for the process to be executed. |
-> IO (ExitCode, [String], [String], [(OutputName, Maybe [String])]) |
Call a given process with temp files for the process to write to. * The process can discover the temp files paths by reading the environment. * The contents of the temp files are returned by this function, if any. * The logging function is called every time the process emits anything to stdout or stderr. it can be used to report progress of the process to a user. * The process is executed in the given directory.
getCleanEnvironment :: IO [(String, String)] Source #
Some environments (e.g. stack exec) include GHC_PACKAGE_PATH. Cabal v2 *will* complain, even though or precisely because it ignores them. Unset them from the environment to sidestep this
File Caching
cacheFile :: FilePath -> String -> (FilePath -> IO ()) -> IO FilePath Source #
Create and cache a file in hie-bios's cache directory.
. cacheFile
fpName srcHash populatefpName
is the pattern name of the
cached file you want to create. srcHash
is the hash that is appended to
the file pattern and is expected to change whenever you want to invalidate
the cache.
If the cached file's srcHash
changes, then a new file is created, but
the old cached file name will not be deleted.
If the file does not exist yet, populate
is invoked with cached file
location and it is expected that the caller persists the given filepath in
the File System.
Find file utilities
findFileUpwards :: FilePath -> FilePath -> MaybeT IO FilePath Source #
Searches upwards for the first directory containing a file.
findFileUpwardsPredicate :: (FilePath -> Bool) -> FilePath -> MaybeT IO FilePath Source #
Searches upwards for the first directory containing a file to match the predicate.
- WARNING*, this scans all the files of all the directories upward. If
appliable, prefer to use
findFileUpwards