Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module contains tools for working with Nix, in order to provide Nix-built artifacts to tests.
The Nix package set (Nixpkgs) is one of the largest package sets in the world, and can be a great way to get artifacts reproducibly. All you need is a nix
binary available on the PATH.
For example, the following will build a Nix environment based on Nixpkgs release 24.05, containing Emacs and Firefox.
introduceNixContext nixpkgsRelease2405 $ introduceNixEnvironment ["emacs", "firefox"] $ do it "uses the environment" $ do envPath <- getContext nixEnvironment emacsVersion <- readCreateProcess (proc (envPath </> "bin" </> "emacs") ["--version"]) "" info [i|Emacs version: #{emacsVersion}|] firefoxVersion <- readCreateProcess (proc (envPath </> "bin" </> "firefox") ["--version"]) "" info [i|Firefox version: #{firefoxVersion}|]
Synopsis
- introduceNixContext :: (MonadUnliftIO m, MonadThrow m) => NixpkgsDerivation -> SpecFree (LabelValue "nixContext" NixContext :> context) m () -> SpecFree context m ()
- introduceNixContext' :: (MonadUnliftIO m, MonadThrow m) => NodeOptions -> NixpkgsDerivation -> SpecFree (LabelValue "nixContext" NixContext :> context) m () -> SpecFree context m ()
- introduceNixContext'' :: (MonadUnliftIO m, MonadThrow m, HasFile context "nix") => NodeOptions -> NixpkgsDerivation -> SpecFree (LabelValue "nixContext" NixContext :> context) m () -> SpecFree context m ()
- introduceNixEnvironment :: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m) => [Text] -> SpecFree (LabelValue "nixEnvironment" FilePath :> context) m () -> SpecFree context m ()
- introduceNixEnvironment' :: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m) => NodeOptions -> [Text] -> SpecFree (LabelValue "nixEnvironment" FilePath :> context) m () -> SpecFree context m ()
- buildNixSymlinkJoin :: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLogger m) => [Text] -> m FilePath
- buildNixSymlinkJoin' :: (HasBaseContextMonad context m, MonadUnliftIO m, MonadLogger m) => NixContext -> [Text] -> m FilePath
- buildNixExpression :: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLogger m) => Text -> m FilePath
- buildNixExpression' :: (HasBaseContextMonad context m, MonadUnliftIO m, MonadLogger m) => NixContext -> Text -> m FilePath
- buildNixCallPackageDerivation :: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLogger m, MonadMask m) => Text -> m FilePath
- buildNixCallPackageDerivation' :: (HasBaseContextMonad context m, MonadUnliftIO m, MonadLogger m, MonadMask m) => NixContext -> Text -> m FilePath
- nixpkgsReleaseDefault :: NixpkgsDerivation
- nixpkgsRelease2405 :: NixpkgsDerivation
- nixpkgsRelease2311 :: NixpkgsDerivation
- nixContext :: Label "nixContext" NixContext
- data NixContext = NixContext {}
- type HasNixContext context = HasLabel context "nixContext" NixContext
- nixEnvironment :: Label "nixEnvironment" FilePath
- type HasNixEnvironment context = HasLabel context "nixEnvironment" FilePath
- data NixpkgsDerivation = NixpkgsDerivationFetchFromGitHub {}
- defaultFileContextVisibilityThreshold :: Int
Nix contexts
:: (MonadUnliftIO m, MonadThrow m) | |
=> NixpkgsDerivation | Nixpkgs derivation to use |
-> SpecFree (LabelValue "nixContext" NixContext :> context) m () | Child spec |
-> SpecFree context m () | Parent spec |
Introduce a NixContext
, which contains information about where to find Nix and what
version of Nixpkgs to use. This can be leveraged to introduce Nix packages in tests.
The NixContext
contains a build cache, so if you build a given derivation more than
once in your tests under this node, runs after the first one will be fast.
This function requires a nix
binary to be in the PATH and will throw an exception if it
isn't found.
:: (MonadUnliftIO m, MonadThrow m) | |
=> NodeOptions | Custom |
-> NixpkgsDerivation | Nixpkgs derivation to use |
-> SpecFree (LabelValue "nixContext" NixContext :> context) m () | Child spec |
-> SpecFree context m () | Parent spec |
Same as introduceNixContext
, but allows passing custom NodeOptions
.
introduceNixContext'' Source #
:: (MonadUnliftIO m, MonadThrow m, HasFile context "nix") | |
=> NodeOptions | Custom |
-> NixpkgsDerivation | Nixpkgs derivation to use |
-> SpecFree (LabelValue "nixContext" NixContext :> context) m () | Child spec |
-> SpecFree context m () | Parent spec |
Same as introduceNixContext'
, but allows specifying the Nix binary via HasFile
.
Nix environments
introduceNixEnvironment Source #
:: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m) | |
=> [Text] | List of package names to include in the Nix environment |
-> SpecFree (LabelValue "nixEnvironment" FilePath :> context) m () | |
-> SpecFree context m () |
Introduce a Nix environment containing the given list of packages, using the current NixContext
.
These packages are mashed together using the Nix symlinkJoin
function. Their binaries will generally
be found in "<environment path>/bin".
introduceNixEnvironment' Source #
:: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m) | |
=> NodeOptions | Custom |
-> [Text] | List of package names to include in the Nix environment |
-> SpecFree (LabelValue "nixEnvironment" FilePath :> context) m () | |
-> SpecFree context m () |
Same as introduceNixEnvironment
, but allows passing custom NodeOptions
.
:: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLogger m) | |
=> [Text] | Package names |
-> m FilePath |
Build a Nix environment, as in introduceNixEnvironment
.
:: (HasBaseContextMonad context m, MonadUnliftIO m, MonadLogger m) | |
=> NixContext | Nix context |
-> [Text] | Package names |
-> m FilePath |
Lower-level version of buildNixSymlinkJoin
.
:: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLogger m) | |
=> Text | Nix expression |
-> m FilePath |
Build a Nix environment containing the given list of packages, using the current NixContext
.
These packages are mashed together using the Nix "symlinkJoin" function. Their binaries will generally
be found in "<environment path>/bin".
:: (HasBaseContextMonad context m, MonadUnliftIO m, MonadLogger m) | |
=> NixContext | Nix expression |
-> Text | |
-> m FilePath |
Lower-level version of buildNixExpression
.
buildNixCallPackageDerivation Source #
:: (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLogger m, MonadMask m) | |
=> Text | Nix derivation |
-> m FilePath |
Build a Nix environment expressed as a derivation expecting a list of dependencies, as in the Nix "callPackage" design pattern. I.e. "{ git, gcc, stdenv, ... }: stdenv.mkDerivation {...}"
buildNixCallPackageDerivation' Source #
:: (HasBaseContextMonad context m, MonadUnliftIO m, MonadLogger m, MonadMask m) | |
=> NixContext | Nix context. |
-> Text | Nix derivation. |
-> m FilePath |
Lower-level version of buildNixCallPackageDerivation
Nixpkgs releases
nixpkgsReleaseDefault :: NixpkgsDerivation Source #
Currently set to nixpkgsRelease2405
.
nixpkgsRelease2405 :: NixpkgsDerivation Source #
Nixpkgs release 24.05, accessed 11/9/2024. You can compute updated values for this release (or others) by running nix-prefetch-github NixOS nixpkgs --rev release-24.05
nixpkgsRelease2311 :: NixpkgsDerivation Source #
Nixpkgs release 23.11, accessed 2/19/2023. You can compute updated values for this release (or others) by running nix-prefetch-github NixOS nixpkgs --rev release-23.11
Types
nixContext :: Label "nixContext" NixContext Source #
data NixContext Source #
Instances
Show NixContext Source # | |
Defined in Test.Sandwich.Contexts.Nix showsPrec :: Int -> NixContext -> ShowS # show :: NixContext -> String # showList :: [NixContext] -> ShowS # |
type HasNixContext context = HasLabel context "nixContext" NixContext Source #
nixEnvironment :: Label "nixEnvironment" FilePath Source #
type HasNixEnvironment context = HasLabel context "nixEnvironment" FilePath Source #
data NixpkgsDerivation Source #
NixpkgsDerivationFetchFromGitHub | |
|
Instances
Show NixpkgsDerivation Source # | |
Defined in Test.Sandwich.Contexts.Nix showsPrec :: Int -> NixpkgsDerivation -> ShowS # show :: NixpkgsDerivation -> String # showList :: [NixpkgsDerivation] -> ShowS # | |
Eq NixpkgsDerivation Source # | |
Defined in Test.Sandwich.Contexts.Nix (==) :: NixpkgsDerivation -> NixpkgsDerivation -> Bool # (/=) :: NixpkgsDerivation -> NixpkgsDerivation -> Bool # |