libnix-0.4.1.0: Bindings to the nix package manager
CopyrightProfpatsch 2018–2021
LicenseGPL-3
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Foreign.Nix.Shellout.Types

Description

 
Synopsis

Store paths

newtype StorePath a Source #

A path in the nix store. It carries a phantom a to differentiate between Derivation files and Realized paths.

Constructors

StorePath 

Instances

Instances details
Eq (StorePath a) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

(==) :: StorePath a -> StorePath a -> Bool #

(/=) :: StorePath a -> StorePath a -> Bool #

Show (StorePath a) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

data Derivation Source #

A nix derivation is a complete build instruction that can be realized.

data Realized Source #

Once a derivation is realized, the finished output can be used.

NixAction

runNixAction :: RunOptions m -> NixAction e m a -> m (Either (NixActionError e) a) Source #

Run a NixAction, given runtime options. See defaultRunOptions.

newtype NixAction e m a Source #

Calls a command that returns an error and the whole stderr on failure.

Constructors

NixAction 

Instances

Instances details
MonadTrans (NixAction e) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

lift :: Monad m => m a -> NixAction e m a #

Monad m => MonadReader (RunOptions m) (NixAction e m) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

ask :: NixAction e m (RunOptions m) #

local :: (RunOptions m -> RunOptions m) -> NixAction e m a -> NixAction e m a #

reader :: (RunOptions m -> a) -> NixAction e m a #

Monad m => MonadError (NixActionError e) (NixAction e m) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

throwError :: NixActionError e -> NixAction e m a #

catchError :: NixAction e m a -> (NixActionError e -> NixAction e m a) -> NixAction e m a #

Monad m => Monad (NixAction e m) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

(>>=) :: NixAction e m a -> (a -> NixAction e m b) -> NixAction e m b #

(>>) :: NixAction e m a -> NixAction e m b -> NixAction e m b #

return :: a -> NixAction e m a #

Functor m => Functor (NixAction e m) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

fmap :: (a -> b) -> NixAction e m a -> NixAction e m b #

(<$) :: a -> NixAction e m b -> NixAction e m a #

Monad m => Applicative (NixAction e m) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

pure :: a -> NixAction e m a #

(<*>) :: NixAction e m (a -> b) -> NixAction e m a -> NixAction e m b #

liftA2 :: (a -> b -> c) -> NixAction e m a -> NixAction e m b -> NixAction e m c #

(*>) :: NixAction e m a -> NixAction e m b -> NixAction e m b #

(<*) :: NixAction e m a -> NixAction e m b -> NixAction e m a #

MonadIO m => MonadIO (NixAction e m) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

liftIO :: IO a -> NixAction e m a #

data RunOptions m Source #

Options that modify how a NixAction executes.

Might get more fields in the future, use defaultRunOptions to be backwards-compatbile.

Constructors

RunOptions 

Fields

Instances

Instances details
Monad m => MonadReader (RunOptions m) (NixAction e m) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

ask :: NixAction e m (RunOptions m) #

local :: (RunOptions m -> RunOptions m) -> NixAction e m a -> NixAction e m a #

reader :: (RunOptions m -> a) -> NixAction e m a #

defaultRunOptions :: Monad m => RunOptions m Source #

logFn = nothing is done/logged
executable = all executables are taken from PATH

newtype LogFn m Source #

Logging function to call before running a command. This can be used to provide debugging output.

The first argument is the executable name, the second argument is the list of arguments.

Constructors

LogFn (Text -> [Text] -> m ()) 

data Executables Source #

All executables this library might need.

If you set an executable to Just filepath, the internal code will use the given path instead of looking up the executable name in PATH. This is useful if you want to ensure that the executables always exist before calling into this library.

NixAction functions document the executables they use in their docstrings.

If an executable can’t be found, an IOException is thrown (by the process spawn function).

Constructors

Executables 

Fields

defaultExecutables :: Executables Source #

all executables are taken from PATH

data NixActionError e Source #

Combines the standard error of running a command with a more semantic error type one should match on first.

Constructors

NixActionError 

Fields

Instances

Instances details
Functor NixActionError Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

fmap :: (a -> b) -> NixActionError a -> NixActionError b #

(<$) :: a -> NixActionError b -> NixActionError a #

Show e => Show (NixActionError e) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Monad m => MonadError (NixActionError e) (NixAction e m) Source # 
Instance details

Defined in Foreign.Nix.Shellout.Types

Methods

throwError :: NixActionError e -> NixAction e m a #

catchError :: NixAction e m a -> (NixActionError e -> NixAction e m a) -> NixAction e m a #

mapActionError :: Functor m => (a1 -> e) -> NixAction a1 m a2 -> NixAction e m a2 Source #

Map over the e in a NixActionError.