Safe Haskell | None |
---|---|
Language | Haskell2010 |
Nix.Thunk
Synopsis
- data ThunkSource
- = ThunkSource_GitHub GitHubSource
- | ThunkSource_Git GitSource
- data GitHubSource = GitHubSource {}
- data ThunkRev = ThunkRev {
- _thunkRev_commit :: Ref SHA1
- _thunkRev_nixSha256 :: NixSha256
- 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 :: forall m. MonadNixThunk m => CheckClean -> FilePath -> Maybe Bool -> m ThunkPtr
- packThunk :: MonadNixThunk m => ThunkPackConfig -> FilePath -> m ThunkPtr
- createThunk :: MonadNixThunk m => FilePath -> Either ThunkSpec ThunkPtr -> m ()
- createThunk' :: MonadNixThunk m => ThunkCreateConfig -> m ()
- data ThunkPackConfig = ThunkPackConfig {}
- newtype ThunkConfig = ThunkConfig {}
- updateThunkToLatest :: MonadNixThunk m => ThunkUpdateConfig -> FilePath -> m ()
- data ThunkUpdateConfig = ThunkUpdateConfig {}
- unpackThunk :: MonadNixThunk m => FilePath -> m ()
- data ThunkSpec = ThunkSpec {}
- data ThunkFileSpec
- data NixThunkError
- nixBuildAttrWithCache :: (MonadLog Output m, HasCliConfig m, MonadIO m, MonadMask m, MonadError NixThunkError m, MonadFail m) => FilePath -> String -> m FilePath
- attrCacheFileName :: FilePath
- prettyNixThunkError :: NixThunkError -> Text
- data ThunkCreateConfig = ThunkCreateConfig {}
- parseGitUri :: Text -> Maybe GitUri
- newtype GitUri = GitUri {}
- uriThunkPtr :: MonadNixThunk m => GitUri -> Maybe Bool -> Maybe Text -> Maybe Text -> m ThunkPtr
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
Eq ThunkSource Source # | |
Defined in Nix.Thunk | |
Ord ThunkSource Source # | |
Defined in Nix.Thunk 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 # | |
Show ThunkSource Source # | |
Defined in Nix.Thunk Methods showsPrec :: Int -> ThunkSource -> ShowS # show :: ThunkSource -> String # showList :: [ThunkSource] -> ShowS # |
data GitHubSource Source #
Constructors
GitHubSource | |
Fields |
Instances
Eq GitHubSource Source # | |
Defined in Nix.Thunk | |
Ord GitHubSource Source # | |
Defined in Nix.Thunk 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 # | |
Show GitHubSource Source # | |
Defined in Nix.Thunk Methods showsPrec :: Int -> GitHubSource -> ShowS # show :: GitHubSource -> String # showList :: [GitHubSource] -> ShowS # |
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
thunkSourceToGitSource :: ThunkSource -> GitSource Source #
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 thunk and validate that it is exactly a packed thunk. If additional data is present, fail.
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 :: forall m. MonadNixThunk m => CheckClean -> FilePath -> Maybe Bool -> m ThunkPtr Source #
createThunk' :: MonadNixThunk m => ThunkCreateConfig -> m () Source #
data ThunkPackConfig Source #
Constructors
ThunkPackConfig | |
Fields |
Instances
Show ThunkPackConfig Source # | |
Defined in Nix.Thunk 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 Methods showsPrec :: Int -> ThunkConfig -> ShowS # show :: ThunkConfig -> String # showList :: [ThunkConfig] -> ShowS # |
updateThunkToLatest :: MonadNixThunk m => ThunkUpdateConfig -> FilePath -> m () Source #
data ThunkUpdateConfig Source #
Constructors
ThunkUpdateConfig | |
Instances
Show ThunkUpdateConfig Source # | |
Defined in Nix.Thunk 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
AsProcessFailure NixThunkError Source # | |
Defined in Nix.Thunk Methods | |
AsUnstructuredError NixThunkError Source # | |
Defined in Nix.Thunk Methods |
nixBuildAttrWithCache Source #
Arguments
:: (MonadLog Output m, HasCliConfig 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 ThunkCreateConfig Source #
Constructors
ThunkCreateConfig | |
Instances
Show ThunkCreateConfig Source # | |
Defined in Nix.Thunk 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.