Safe Haskell | None |
---|---|
Language | Haskell2010 |
Nix.Thunk
Synopsis
- data ThunkSource
- data GitHubSource = GitHubSource {}
- data ThunkRev = ThunkRev {}
- getLatestRev :: MonadNixThunk m => ThunkSource -> m ThunkRev
- gitCloneForThunkUnpack :: MonadNixThunk m => GitSource -> Ref hash -> FilePath -> m ()
- thunkSourceToGitSource :: ThunkSource -> GitSource
- data ThunkPtr = ThunkPtr {}
- data ThunkData
- readThunk :: MonadNixThunk m => FilePath -> m (Either ReadThunkError ThunkData)
- data CheckClean
- getThunkPtr :: MonadNixThunk m => CheckClean -> FilePath -> Maybe Bool -> m (ThunkPtr, Bool)
- packThunk :: MonadNixThunk m => ThunkPackConfig -> FilePath -> m ThunkPtr
- createThunk :: MonadNixThunk m => FilePath -> Either ThunkSpec ThunkPtr -> m ()
- createThunk' :: MonadNixThunk m => ThunkCreateConfig -> m ()
- createWorktree :: MonadNixThunk m => FilePath -> FilePath -> CreateWorktreeConfig -> m ()
- data CreateWorktreeConfig = CreateWorktreeConfig {}
- data ThunkPackConfig = ThunkPackConfig {}
- newtype ThunkConfig = ThunkConfig {}
- updateThunkToLatest :: MonadNixThunk m => ThunkUpdateConfig -> FilePath -> m ()
- updateThunk :: MonadNixThunk m => FilePath -> (FilePath -> m a) -> m a
- data ThunkUpdateConfig = ThunkUpdateConfig {}
- unpackThunk :: MonadNixThunk m => FilePath -> m ()
- data ThunkSpec = ThunkSpec {}
- data ThunkFileSpec
- data NixThunkError
- nixBuildAttrWithCache :: (MonadLog Output m, HasCliConfig NixThunkError m, MonadIO m, MonadMask m, MonadError NixThunkError m, MonadFail m) => FilePath -> String -> m FilePath
- attrCacheFileName :: FilePath
- prettyNixThunkError :: NixThunkError -> Text
- data ThunkCreateSource
- data ThunkCreateConfig = ThunkCreateConfig {}
- parseGitUri :: Text -> Maybe GitUri
- newtype GitUri = GitUri {}
- uriThunkPtr :: MonadNixThunk m => GitUri -> Maybe Bool -> Maybe Text -> Maybe Text -> m ThunkPtr
- newtype Ref hash = Ref {}
- refFromHexString :: HashAlgorithm hash => String -> Ref hash
Documentation
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 |
Instances
Show ThunkSource Source # | |
Defined in Nix.Thunk.Internal Methods showsPrec :: Int -> ThunkSource -> ShowS # show :: ThunkSource -> String # showList :: [ThunkSource] -> ShowS # | |
Eq ThunkSource Source # | |
Defined in Nix.Thunk.Internal | |
Ord ThunkSource Source # | |
Defined in Nix.Thunk.Internal Methods compare :: ThunkSource -> ThunkSource -> Ordering # (<) :: ThunkSource -> ThunkSource -> Bool # (<=) :: ThunkSource -> ThunkSource -> Bool # (>) :: ThunkSource -> ThunkSource -> Bool # (>=) :: ThunkSource -> ThunkSource -> Bool # max :: ThunkSource -> ThunkSource -> ThunkSource # min :: ThunkSource -> ThunkSource -> ThunkSource # |
data GitHubSource Source #
Constructors
GitHubSource | |
Fields |
Instances
Show GitHubSource Source # | |
Defined in Nix.Thunk.Internal Methods showsPrec :: Int -> GitHubSource -> ShowS # show :: GitHubSource -> String # showList :: [GitHubSource] -> ShowS # | |
Eq GitHubSource Source # | |
Defined in Nix.Thunk.Internal | |
Ord GitHubSource Source # | |
Defined in Nix.Thunk.Internal Methods compare :: GitHubSource -> GitHubSource -> Ordering # (<) :: GitHubSource -> GitHubSource -> Bool # (<=) :: GitHubSource -> GitHubSource -> Bool # (>) :: GitHubSource -> GitHubSource -> Bool # (>=) :: GitHubSource -> GitHubSource -> Bool # max :: GitHubSource -> GitHubSource -> GitHubSource # min :: GitHubSource -> GitHubSource -> GitHubSource # |
A specific revision of data; it may be available from multiple sources
Constructors
ThunkRev | |
Fields |
getLatestRev :: MonadNixThunk m => ThunkSource -> m ThunkRev Source #
Get the latest revision available from the given source
gitCloneForThunkUnpack Source #
Arguments
:: MonadNixThunk m | |
=> GitSource | Git source to use |
-> Ref hash | Commit hash to reset to |
-> FilePath | Directory to clone into |
-> m () |
A reference to the exact data that a thunk should translate into
Constructors
ThunkPtr | |
Fields |
Constructors
ThunkData_Packed ThunkSpec ThunkPtr | Packed thunk |
ThunkData_Checkout | Checked out thunk that was unpacked from this pointer |
readThunk :: MonadNixThunk m => FilePath -> m (Either ReadThunkError ThunkData) Source #
Read a packed or unpacked thunk based on predefined thunk specifications.
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 |
getThunkPtr :: MonadNixThunk m => CheckClean -> FilePath -> Maybe Bool -> m (ThunkPtr, Bool) Source #
packThunk :: MonadNixThunk m => ThunkPackConfig -> FilePath -> m ThunkPtr Source #
createThunk :: MonadNixThunk m => FilePath -> Either ThunkSpec ThunkPtr -> m () Source #
createThunk' :: MonadNixThunk m => ThunkCreateConfig -> m () Source #
createWorktree :: MonadNixThunk m => FilePath -> FilePath -> CreateWorktreeConfig -> m () Source #
data CreateWorktreeConfig Source #
Constructors
CreateWorktreeConfig | |
Instances
Show CreateWorktreeConfig Source # | |
Defined in Nix.Thunk.Internal Methods showsPrec :: Int -> CreateWorktreeConfig -> ShowS # show :: CreateWorktreeConfig -> String # showList :: [CreateWorktreeConfig] -> ShowS # |
data ThunkPackConfig Source #
Constructors
ThunkPackConfig | |
Fields |
Instances
Show ThunkPackConfig Source # | |
Defined in Nix.Thunk.Internal Methods showsPrec :: Int -> ThunkPackConfig -> ShowS # show :: ThunkPackConfig -> String # showList :: [ThunkPackConfig] -> ShowS # |
newtype ThunkConfig Source #
Constructors
ThunkConfig | |
Fields |
Instances
Show ThunkConfig Source # | |
Defined in Nix.Thunk.Internal Methods showsPrec :: Int -> ThunkConfig -> ShowS # show :: ThunkConfig -> String # showList :: [ThunkConfig] -> ShowS # |
updateThunkToLatest :: MonadNixThunk m => ThunkUpdateConfig -> FilePath -> m () Source #
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.
data ThunkUpdateConfig Source #
Constructors
ThunkUpdateConfig | |
Instances
Show ThunkUpdateConfig Source # | |
Defined in Nix.Thunk.Internal Methods showsPrec :: Int -> ThunkUpdateConfig -> ShowS # show :: ThunkUpdateConfig -> String # showList :: [ThunkUpdateConfig] -> ShowS # |
unpackThunk :: MonadNixThunk m => FilePath -> m () Source #
Specification for how a set of files in a thunk version work.
Constructors
ThunkSpec | |
Fields
|
data ThunkFileSpec Source #
Specification for how a file in a thunk version works.
Constructors
ThunkFileSpec_Ptr (ByteString -> Either String ThunkPtr) | This file specifies |
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 NixThunkError Source #
Instances
AsUnstructuredError NixThunkError Source # | |
Defined in Nix.Thunk.Internal Methods | |
AsProcessFailure NixThunkError Source # | |
Defined in Nix.Thunk.Internal Methods |
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
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 |
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 |
Instances
Show ThunkCreateSource Source # | |
Defined in Nix.Thunk.Internal Methods showsPrec :: Int -> ThunkCreateSource -> ShowS # show :: ThunkCreateSource -> String # showList :: [ThunkCreateSource] -> ShowS # |
data ThunkCreateConfig Source #
Constructors
ThunkCreateConfig | |
Instances
Show ThunkCreateConfig Source # | |
Defined in Nix.Thunk.Internal Methods showsPrec :: Int -> ThunkCreateConfig -> ShowS # show :: ThunkCreateConfig -> String # showList :: [ThunkCreateConfig] -> ShowS # |
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.
Represent a git reference (SHA1)
refFromHexString :: HashAlgorithm hash => String -> Ref hash Source #