sandwich-contexts-0.3.0.0: Contexts for the Sandwich test library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Sandwich.Contexts.Files

Description

This module contains tools for introducing files and making them available to tests. It uses type-level strings, and is mostly intended to be used with -XTypeApplications.

For example:

introduceFile @"grep" "/path/to/grep" $ do
  it "uses grep for something" $ do
    grep <- askFile @"grep"
    results <- readCreateProcess (proc grep ["foo"]) ""
    todo -- Do something with results

For reproducibility, you can leverage a NixContext that's already been introduced to introduce binaries, either by specifying a Nixpkgs package name or by writing out a full derivation.

Synopsis

Introduce a file directly

introduceFile Source #

Arguments

:: forall a context m. (MonadUnliftIO m, KnownSymbol a) 
=> FilePath

Path to the file

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m ()

Child spec

-> SpecFree context m ()

Parent spec

Introduce a file by providing its path.

introduceFile' :: forall a context m. (MonadUnliftIO m, KnownSymbol a) => NodeOptions -> FilePath -> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () -> SpecFree context m () Source #

Same as introduceFile, but allows passing custom NodeOptions.

Introduce a binary from the environment

introduceBinaryViaEnvironment Source #

Arguments

:: forall a context m. (MonadUnliftIO m, KnownSymbol a) 
=> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m ()

Parent spec

-> SpecFree context m ()

Child spec

Introduce a file from the PATH, which must be present when tests are run. Useful when you want to set up your own environment with binaries etc. to use in tests. Throws an exception if the desired file is not available.

introduceBinaryViaEnvironment' :: forall a context m. (MonadUnliftIO m, KnownSymbol a) => NodeOptions -> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () -> SpecFree context m () Source #

Same as introduceBinaryViaEnvironment, but allows you to pass custom NodeOptions.

Introduce a binary from a Nix package

introduceBinaryViaNixPackage Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, KnownSymbol a) 
=> NixPackageName

Nix package name which contains the desired binary. This package will be evaluated using the configured Nixpkgs version of the NixContext. For example, you can use the "hello" binary from the "hello" package like this:

introduceBinaryViaNixPackage' @"hello" "hello"

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Introduce a given EnvironmentFile from the NixContext in scope. It's recommended to use this with -XTypeApplications.

introduceBinaryViaNixPackage' Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, KnownSymbol a) 
=> NodeOptions 
-> NixPackageName

Nix package name which contains the desired binary.

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Same as introduceBinaryViaNixPackage, but allows passing custom NodeOptions.

getBinaryViaNixPackage Source #

Arguments

:: forall a context m. (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLoggerIO m, KnownSymbol a) 
=> NixPackageName

Nix package name which contains the desired binary.

-> m FilePath 

Lower-level version of introduceBinaryViaNixPackage.

getBinaryViaNixPackage' Source #

Arguments

:: forall a context m. (HasBaseContext context, MonadReader context m, MonadLogger m, MonadUnliftIO m, KnownSymbol a) 
=> NixContext

NixContext to use.

-> NixPackageName

Nix package name which contains the desired binary.

-> m FilePath 

Lower-level version of introduceBinaryViaNixPackage.

Introduce file from a Nix package

introduceFileViaNixPackage Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, KnownSymbol a) 
=> NixPackageName

Nix package name which contains the desired file. This package will be evaluated using the configured Nixpkgs version of the NixContext.

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Introduce a given EnvironmentFile from the NixContext in scope. It's recommended to use this with -XTypeApplications.

introduceFileViaNixPackage' Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, KnownSymbol a) 
=> NixPackageName

Nix package name which contains the desired file. This package will be evaluated using the configured Nixpkgs version of the NixContext.

-> (FilePath -> IO FilePath)

Callback to find the desired file within the Nix derivation path. It will be passed the derivation path, and should return the file. For example, tryFindFile "/nix/store/...selenium-server-standalone-3.141.59" may return "/nix/store/...selenium-server-standalone-3.141.59/share/lib/selenium-server-standalone-3.141.59/selenium-server-standalone-3.141.59.jar".

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Same as introduceFileViaNixPackage, but allows you to customize the search callback.

introduceFileViaNixPackage'' Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, KnownSymbol a) 
=> NodeOptions 
-> NixPackageName

Nix package name which contains the desired file.

-> (FilePath -> IO FilePath)

Callback to find the desired file within the Nix derivation path. It will be passed the derivation path, and should return the file. For example, tryFindFile "/nix/store/...selenium-server-standalone-3.141.59" may return "/nix/store/...selenium-server-standalone-3.141.59/share/lib/selenium-server-standalone-3.141.59/selenium-server-standalone-3.141.59.jar".

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Same as introduceFileViaNixPackage', but allows passing custom NodeOptions.

getFileViaNixPackage Source #

Arguments

:: forall context m. (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLoggerIO m) 
=> NixPackageName

Nix package name which contains the desired file.

-> (FilePath -> IO FilePath)

Callback to find the desired file, as in introduceFileViaNixPackage.

-> m FilePath 

Lower-level version of introduceFileViaNixPackage.

Introduce a binary from a Nix derivation

introduceBinaryViaNixDerivation Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, MonadMask m, KnownSymbol a) 
=> Text

Nix derivation as a string.

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Introduce a given EnvironmentFile from the NixContext in scope. It's recommended to use this with -XTypeApplications.

introduceBinaryViaNixDerivation' Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, MonadMask m, KnownSymbol a) 
=> NodeOptions 
-> Text

Nix derivation as a string.

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Same as introduceBinaryViaNixDerivation, but allows passing custom NodeOptions.

getBinaryViaNixDerivation Source #

Arguments

:: forall a context m. (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLoggerIO m, MonadMask m, KnownSymbol a) 
=> Text

Nix derivation as a string.

-> m FilePath 

Lower-level version of introduceBinaryViaNixDerivation.

getBinaryViaNixDerivation' Source #

Arguments

:: forall a context m. (HasBaseContextMonad context m, MonadUnliftIO m, MonadLoggerIO m, MonadMask m, KnownSymbol a) 
=> NixContext

Nix context.

-> Text

Nix derivation as a string.

-> m FilePath 

Lower-level version of getBinaryViaNixDerivation.

Introduce a file from a Nix derivation

introduceFileViaNixDerivation Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, MonadMask m, KnownSymbol a) 
=> Text

Nix derivation as a string.

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Introduce a given EnvironmentFile from the NixContext in scope. It's recommended to use this with -XTypeApplications.

introduceFileViaNixDerivation' Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, MonadMask m, KnownSymbol a) 
=> Text

Nix derivation as a string.

-> (FilePath -> IO FilePath)

Callback to find the desired file.

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Same as introduceFileViaNixDerivation, but allows configuring the file finding callback.

introduceFileViaNixDerivation'' Source #

Arguments

:: forall a context m. (HasBaseContext context, HasNixContext context, MonadUnliftIO m, MonadMask m, KnownSymbol a) 
=> NodeOptions 
-> Text

Nix derivation as a string.

-> (FilePath -> IO FilePath)

Callback to find the desired file.

-> SpecFree (LabelValue (AppendSymbol "file-" a) (EnvironmentFile a) :> context) m () 
-> SpecFree context m () 

Same as introduceFileViaNixDerivation', but allows passing custom NodeOptions.

getFileViaNixDerivation Source #

Arguments

:: forall context m. (HasBaseContextMonad context m, HasNixContext context, MonadUnliftIO m, MonadLoggerIO m, MonadMask m) 
=> Text

Nix derivation as a string.

-> (FilePath -> IO FilePath)

Callback to find the desired file.

-> m FilePath 

Lower-level version of introduceFileViaNixDerivation.

Get a file

askFile :: forall a context m. (MonadReader context m, HasFile context a) => m FilePath Source #

Retrieve a file context.

askFile' :: forall a context m. (MonadReader context m, HasFile context a) => Proxy a -> m FilePath Source #

Variant of askFile that you can use with a Proxy rather than a type application.

Helpers for file-finding callbacks

defaultFindFile :: String -> FilePath -> IO FilePath Source #

Find a file whose name exactly matches a string, using findFirstFile. This calls takeFileName, so it only matches against the name, not the relative path.

findFirstFile :: (FilePath -> IO Bool) -> FilePath -> IO FilePath Source #

Find the first file under the given directory (recursively) which matches the predicate. Note that the callback receives the full relative path to the file from the root dir. Throws using expectationFailure when the file is not found.

Low-level

Types

data EnvironmentFile a Source #

A file path to make available to tests. For example, this can be an external binary like "minikube" if a given test context wants to use it to start a Minikube cluster. But you can use this for any kind of file you want to inject into tests.

type HasFile context a = HasLabel context (AppendSymbol "file-" a) (EnvironmentFile a) Source #

Has-* class for asserting a given file is available.

type FileValue file = LabelValue (AppendSymbol "file-" file) (EnvironmentFile file) Source #

Shorthand for LabelValues containing EnvironmentFiles.