nix-thunk-0.7.0.0: Lightweight dependency management with Nix
Safe HaskellNone
LanguageHaskell2010

Nix.Thunk.Internal

Synopsis

Documentation

data ThunkData Source #

Constructors

ThunkData_Packed ThunkSpec ThunkPtr

Packed thunk

ThunkData_Checkout

Checked out thunk that was unpacked from this pointer

data ThunkPtr Source #

A reference to the exact data that a thunk should translate into

data ThunkRev Source #

A specific revision of data; it may be available from multiple sources

data ThunkSource Source #

A location from which a thunk's data can be retrieved

Constructors

ThunkSource_GitHub GitHubSource

A source specialized for GitHub

ThunkSource_Git GitSource

A plain repo source

newtype GitUri Source #

Constructors

GitUri 

Fields

Instances

Instances details
Eq GitUri Source # 
Instance details

Defined in Nix.Thunk.Internal

Ord GitUri Source # 
Instance details

Defined in Nix.Thunk.Internal

Show GitUri Source # 
Instance details

Defined in Nix.Thunk.Internal

newtype ThunkConfig Source #

Constructors

ThunkConfig 

Instances

Instances details
Show ThunkConfig Source # 
Instance details

Defined in Nix.Thunk.Internal

data ThunkCreateSource Source #

The source to be used for creating thunks.

Constructors

ThunkCreateSource_Absolute GitUri

Create a thunk from an absolute reference to a Git repository: URIs like file://, https://, ssh:// etc.

ThunkCreateSource_Relative FilePath

Create a thunk from a local folder. If the folder exists, then it is made absolute using the current working directory and treated as a file:// URL.

forgetGithub :: Bool -> GitHubSource -> GitSource Source #

Convert a GitHub source to a regular Git source. Assumes no submodules.

data ReadThunkError Source #

Constructors

ReadThunkError_UnrecognizedThunk

A generic error that can happen while reading a thunk.

ReadThunkError_UnrecognizedPaths (Maybe ThunkSpec) (NonEmpty FilePath)

The thunk directory has extraneous paths. The Maybe value indicates whether we have matched the rest of the files to a valid specification, and if so, which specification it was.

ReadThunkError_MissingPaths (NonEmpty FilePath)

The thunk directory has missing paths.

ReadThunkError_UnparseablePtr FilePath String

We could not parse the given file as per the thunk specification. The String is a parser-specific error message.

ReadThunkError_FileError FilePath IOError

We encountered an IOError while reading the given file.

ReadThunkError_FileDoesNotMatch FilePath Text

We read the given file just fine, but its contents do not match what was expected for the specification.

ReadThunkError_AmbiguousPackedState ThunkSpec ThunkSpec

We parsed two valid thunk specs for this directory.

prettyReadThunkError :: ReadThunkError -> Text Source #

Pretty-print a ReadThunkError for display to the user

failReadThunkErrorWhile Source #

Arguments

:: MonadError NixThunkError m 
=> Text

String describing what we were doing.

-> ReadThunkError

The error

-> m a 

Fail due to a ReadThunkError with a standardised error message.

didMatchThunkSpec :: ReadThunkError -> Bool Source #

Did we manage to match the thunk directory to one or more known thunk specs before raising this error?

pinnedNixpkgsPath :: FilePath Source #

A path from which our known-good nixpkgs can be fetched. NOTE: This path is hardcoded, and only exists so subsumed thunk specs (v7 specifically) can be parsed.

data ThunkFileSpec Source #

Specification for how a file in a thunk version works.

Constructors

ThunkFileSpec_Ptr (ByteString -> Either String ThunkPtr)

This file specifies ThunkPtr data

ThunkFileSpec_FileMatches Text

This file must match the given content exactly

ThunkFileSpec_CheckoutIndicator

Existence of this directory indicates that the thunk is unpacked

ThunkFileSpec_AttrCache

This directory is an attribute cache

data ThunkSpec Source #

Specification for how a set of files in a thunk version work.

matchThunkSpecToDir Source #

Arguments

:: (MonadError ReadThunkError m, MonadIO m, MonadCatch m) 
=> ThunkSpec

ThunkSpec to match against the given files/directory

-> FilePath

Path to directory

-> Set FilePath

Set of file paths relative to the given directory

-> m ThunkData 

Attempts to match a ThunkSpec to a given directory.

readThunk :: MonadNixThunk m => FilePath -> m (Either ReadThunkError ThunkData) Source #

Read a packed or unpacked thunk based on predefined thunk specifications.

gitHubThunkSpecs :: NonEmpty ThunkSpec Source #

All recognized github standalone loaders, ordered from newest to oldest. This tool will only ever produce the newest one when it writes a thunk.

gitHubThunkSpecV6 :: ThunkSpec Source #

See gitHubThunkSpecV7.

NOTE: v6 spec thunks are broken! They import the pinned nixpkgs in an incorrect way. GitHub thunks for public repositories with no submodules will still work, but update as soon as possible.

gitHubThunkSpecV7 :: ThunkSpec Source #

Specification for GitHub thunks which use a specific, pinned version of nixpkgs for fetching, rather than using nixpkgs from NIX_PATH. The "v7" specs ensure that thunks can be fetched even when NIX_PATH is unset.

gitHubThunkSpecV8 :: ThunkSpec Source #

Specification for GitHub thunks which use a specific, pinned version of nixpkgs for fetching, rather than using nixpkgs from NIX_PATH.

Unlike gitHubThunKSpecV7, this thunk specification fetches the nixpkgs tarball from GitHub, so it will fail on environments without a network connection.

gitThunkSpecV6 :: ThunkSpec Source #

See gitThunkSpecV7. NOTE: v6 spec thunks are broken! They import the pinned nixpkgs in an incorrect way. GitHub thunks for public repositories with no submodules will still work, but update as soon as possible.

gitThunkSpecV7 :: ThunkSpec Source #

Specification for Git thunks which use a specific, pinned version of nixpkgs for fetching, rather than using nixpkgs from NIX_PATH. The "v7" specs ensure that thunks can be fetched even when NIX_PATH is unset.

gitThunkSpecV8 :: ThunkSpec Source #

Specification for Git thunks which use a specific, pinned version version of nixpkgs for fetching, rather than using nixpkgs from NIX_PATH.

Unlike gitHubThunKSpecV7, this thunk specification fetches the nixpkgs tarball from GitHub, so it will fail on environments without a network connection.

nixBuildThunkAttrWithCache Source #

Arguments

:: (MonadIO m, MonadLog Output m, HasCliConfig NixThunkError m, MonadMask m, MonadError NixThunkError m, MonadFail m) 
=> ThunkSpec 
-> FilePath

Path to directory containing Thunk

-> String

Attribute to build

-> m (Maybe FilePath)

Symlink to cached or built nix output WARNING: If the thunk uses an impure reference such as 'nixpkgs' the caching mechanism will fail as it merely measures the modification time of the cache link and the expression to build.

Checks a cache directory to see if there is a fresh symlink to the result of building an attribute of a thunk. If no cache hit is found, nix-build is called to build the attribute and the result is symlinked into the cache.

nixBuildAttrWithCache Source #

Arguments

:: (MonadLog Output m, HasCliConfig NixThunkError m, MonadIO m, MonadMask m, MonadError NixThunkError m, MonadFail m) 
=> FilePath

Path to directory containing Thunk

-> String

Attribute to build

-> m FilePath

Symlink to cached or built nix output

Build a nix attribute, and cache the result if possible

updateThunk :: MonadNixThunk m => FilePath -> (FilePath -> m a) -> m a Source #

Safely update thunk using a custom action

A temporary working space is used to do any update. When the custom action successfully completes, the resulting (packed) thunk is copied back to the original location.

finalMsg :: Bool -> (a -> Text) -> Maybe (a -> Text) Source #

checkThunkDirectory :: MonadNixThunk m => FilePath -> m () Source #

Check that we are not somewhere inside the thunk directory

gitCloneForThunkUnpack Source #

Arguments

:: MonadNixThunk m 
=> GitSource

Git source to use

-> Ref hash

Commit hash to reset to

-> FilePath

Directory to clone into

-> m () 

readGitProcess :: MonadNixThunk m => FilePath -> [String] -> m Text Source #

Read a git process ignoring the global configuration (according to ignoreGitConfig).

ignoreGitConfig :: ProcessSpec -> ProcessSpec Source #

Prevent the called process from reading Git configuration. This isn't as locked-down as isolateGitProc to make sure the Git process can still interact with the user (e.g. ssh-askpass), but it still ignores enough of the configuration to ensure that thunks are reproducible.

data CheckClean Source #

Constructors

CheckClean_FullCheck

Check that the repo is clean, including .gitignored files

CheckClean_NotIgnored

Check that the repo is clean, not including .gitignored files

CheckClean_NoCheck

Don't check that the repo is clean

getLatestRev :: MonadNixThunk m => ThunkSource -> m ThunkRev Source #

Get the latest revision available from the given source

uriThunkPtr :: MonadNixThunk m => GitUri -> Maybe Bool -> Maybe Text -> Maybe Text -> m ThunkPtr Source #

Convert a URI to a thunk

If the URL is a github URL, we try to just download an archive for performance. If that doesn't work (e.g. authentication issue), we fall back on just doing things the normal way for git repos in general, and save it as a regular git thunk.

thunkCreateSourcePtr Source #

Arguments

:: MonadNixThunk m 
=> ThunkCreateSource

Where is the repository?

-> Maybe Bool

Is it private?

-> Maybe Text

Shall we fetch a specific branch?

-> Maybe Text

Shall we check out a specific commit?

-> m ThunkPtr 

Convert a ThunkCreateSource to a ThunkPtr.

uriToThunkSource :: MonadNixThunk m => GitUri -> Maybe Bool -> Maybe Text -> m ThunkSource Source #

N.B. Cannot infer all fields.

If the thunk is a GitHub thunk and fails, we do *not* fall back like with uriThunkPtr. Unlike a plain URL, a thunk src explicitly states which method should be employed, and so we respect that.

gitGetCommitBranch :: MonadNixThunk m => GitUri -> Maybe Text -> m (Text, CommitId) Source #

Given the URI to a git remote, and an optional branch name, return the name of the branch along with the hash of the commit at tip of that branch.

If the branch name is passed in, it is returned exactly as-is. If it is not passed it, the default branch of the repo is used instead.

newtype Ref hash Source #

Represent a git reference (SHA1)

Constructors

Ref 

Fields

Instances

Instances details
Eq (Ref hash) Source # 
Instance details

Defined in Nix.Thunk.Internal

Methods

(==) :: Ref hash -> Ref hash -> Bool Source #

(/=) :: Ref hash -> Ref hash -> Bool Source #

Ord (Ref hash) Source # 
Instance details

Defined in Nix.Thunk.Internal

Methods

compare :: Ref hash -> Ref hash -> Ordering Source #

(<) :: Ref hash -> Ref hash -> Bool Source #

(<=) :: Ref hash -> Ref hash -> Bool Source #

(>) :: Ref hash -> Ref hash -> Bool Source #

(>=) :: Ref hash -> Ref hash -> Bool Source #

max :: Ref hash -> Ref hash -> Ref hash Source #

min :: Ref hash -> Ref hash -> Ref hash Source #

Show (Ref hash) Source # 
Instance details

Defined in Nix.Thunk.Internal

Methods

showsPrec :: Int -> Ref hash -> ShowS Source #

show :: Ref hash -> String Source #

showList :: [Ref hash] -> ShowS Source #

newtype RefInvalid Source #

Invalid Reference exception raised when using something that is not a ref as a ref.

Constructors

RefInvalid 

Instances

Instances details
Eq RefInvalid Source # 
Instance details

Defined in Nix.Thunk.Internal

Data RefInvalid Source # 
Instance details

Defined in Nix.Thunk.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RefInvalid -> c RefInvalid Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RefInvalid Source #

toConstr :: RefInvalid -> Constr Source #

dataTypeOf :: RefInvalid -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RefInvalid) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RefInvalid) Source #

gmapT :: (forall b. Data b => b -> b) -> RefInvalid -> RefInvalid Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RefInvalid -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RefInvalid -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RefInvalid -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RefInvalid -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RefInvalid -> m RefInvalid Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RefInvalid -> m RefInvalid Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RefInvalid -> m RefInvalid Source #

Show RefInvalid Source # 
Instance details

Defined in Nix.Thunk.Internal

Exception RefInvalid Source # 
Instance details

Defined in Nix.Thunk.Internal

refToHexString :: Ref hash -> String Source #

transform a ref into an hexadecimal string