-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Lightweight dependency management with Nix -- -- nix-thunk lets you manage source code dependencies in a lightweight -- and reproducible way, using Nix. Each source repository is represented -- by a stub directory, which refers to the original Git repository. -- nix-thunk can easily update these dependencies. -- -- If you need to make improvements to the original repositories, -- nix-thunk can unpack them in-place, so that changes can be tested -- right away, and then pack them back up when you're done. This makes it -- easy to send a pull request to the upstream repo while your project -- continues on a fork, then switch back to upstream once your pull -- request has been merged. @package nix-thunk @version 0.7.0.1 module Nix.Thunk.Internal type MonadInfallibleNixThunk m = (CliLog m, HasCliConfig NixThunkError m, MonadIO m, MonadMask m) type MonadNixThunk m = (MonadInfallibleNixThunk m, CliThrow NixThunkError m, MonadFail m) data NixThunkError NixThunkError_ProcessFailure :: ProcessFailure -> NixThunkError NixThunkError_Unstructured :: Text -> NixThunkError prettyNixThunkError :: NixThunkError -> Text _NixThunkError_Unstructured :: Prism' NixThunkError Text _NixThunkError_ProcessFailure :: Prism' NixThunkError ProcessFailure data ThunkData -- | Packed thunk ThunkData_Packed :: ThunkSpec -> ThunkPtr -> ThunkData -- | Checked out thunk that was unpacked from this pointer ThunkData_Checkout :: ThunkData -- | A reference to the exact data that a thunk should translate into data ThunkPtr ThunkPtr :: ThunkRev -> ThunkSource -> ThunkPtr [_thunkPtr_rev] :: ThunkPtr -> ThunkRev [_thunkPtr_source] :: ThunkPtr -> ThunkSource type NixSha256 = Text -- | A specific revision of data; it may be available from multiple sources data ThunkRev ThunkRev :: Ref SHA1 -> NixSha256 -> ThunkRev [_thunkRev_commit] :: ThunkRev -> Ref SHA1 [_thunkRev_nixSha256] :: ThunkRev -> NixSha256 -- | A location from which a thunk's data can be retrieved data ThunkSource -- | A source specialized for GitHub ThunkSource_GitHub :: GitHubSource -> ThunkSource -- | A plain repo source ThunkSource_Git :: GitSource -> ThunkSource thunkSourceToGitSource :: ThunkSource -> GitSource data GitHubSource GitHubSource :: Name Owner -> Name Repo -> Maybe (Name Branch) -> Bool -> GitHubSource [_gitHubSource_owner] :: GitHubSource -> Name Owner [_gitHubSource_repo] :: GitHubSource -> Name Repo [_gitHubSource_branch] :: GitHubSource -> Maybe (Name Branch) [_gitHubSource_private] :: GitHubSource -> Bool newtype GitUri GitUri :: URI -> GitUri [unGitUri] :: GitUri -> URI gitUriToText :: GitUri -> Text data GitSource GitSource :: GitUri -> Maybe (Name Branch) -> Bool -> Bool -> GitSource [_gitSource_url] :: GitSource -> GitUri [_gitSource_branch] :: GitSource -> Maybe (Name Branch) [_gitSource_fetchSubmodules] :: GitSource -> Bool [_gitSource_private] :: GitSource -> Bool newtype ThunkConfig ThunkConfig :: Maybe Bool -> ThunkConfig [_thunkConfig_private] :: ThunkConfig -> Maybe Bool data ThunkUpdateConfig ThunkUpdateConfig :: Maybe String -> ThunkConfig -> ThunkUpdateConfig [_thunkUpdateConfig_branch] :: ThunkUpdateConfig -> Maybe String [_thunkUpdateConfig_config] :: ThunkUpdateConfig -> ThunkConfig data ThunkPackConfig ThunkPackConfig :: Bool -> ThunkConfig -> ThunkPackConfig [_thunkPackConfig_force] :: ThunkPackConfig -> Bool [_thunkPackConfig_config] :: ThunkPackConfig -> ThunkConfig -- | The source to be used for creating thunks. data ThunkCreateSource -- | Create a thunk from an absolute reference to a Git repository: URIs -- like file://, https://, ssh:// etc. ThunkCreateSource_Absolute :: GitUri -> ThunkCreateSource -- | 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. ThunkCreateSource_Relative :: FilePath -> ThunkCreateSource data ThunkCreateConfig ThunkCreateConfig :: ThunkCreateSource -> Maybe (Name Branch) -> Maybe (Ref SHA1) -> ThunkConfig -> Maybe FilePath -> ThunkCreateConfig [_thunkCreateConfig_uri] :: ThunkCreateConfig -> ThunkCreateSource [_thunkCreateConfig_branch] :: ThunkCreateConfig -> Maybe (Name Branch) [_thunkCreateConfig_rev] :: ThunkCreateConfig -> Maybe (Ref SHA1) [_thunkCreateConfig_config] :: ThunkCreateConfig -> ThunkConfig [_thunkCreateConfig_destination] :: ThunkCreateConfig -> Maybe FilePath -- | Convert a GitHub source to a regular Git source. Assumes no -- submodules. forgetGithub :: Bool -> GitHubSource -> GitSource commitNameToRef :: Name Commit -> Ref SHA1 getNixSha256ForUriUnpacked :: MonadNixThunk m => GitUri -> m NixSha256 nixPrefetchGit :: MonadNixThunk m => GitUri -> Text -> Bool -> m NixSha256 data ReadThunkError -- | A generic error that can happen while reading a thunk. ReadThunkError_UnrecognizedThunk :: ReadThunkError -- | 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_UnrecognizedPaths :: Maybe ThunkSpec -> NonEmpty FilePath -> ReadThunkError -- | The thunk directory has missing paths. ReadThunkError_MissingPaths :: NonEmpty FilePath -> ReadThunkError -- | We could not parse the given file as per the thunk specification. The -- String is a parser-specific error message. ReadThunkError_UnparseablePtr :: FilePath -> String -> ReadThunkError -- | We encountered an IOError while reading the given file. ReadThunkError_FileError :: FilePath -> IOError -> ReadThunkError -- | We read the given file just fine, but its contents do not match what -- was expected for the specification. ReadThunkError_FileDoesNotMatch :: FilePath -> Text -> ReadThunkError -- | We parsed two valid thunk specs for this directory. ReadThunkError_AmbiguousPackedState :: ThunkSpec -> ThunkSpec -> ReadThunkError -- | Pretty-print a ReadThunkError for display to the user prettyReadThunkError :: ReadThunkError -> Text -- | Fail due to a ReadThunkError with a standardised error message. failReadThunkErrorWhile :: MonadError NixThunkError m => Text -> ReadThunkError -> m a -- | Did we manage to match the thunk directory to one or more known thunk -- specs before raising this error? didMatchThunkSpec :: ReadThunkError -> Bool unpackedDirName :: FilePath attrCacheFileName :: FilePath -- | 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. pinnedNixpkgsPath :: FilePath -- | Specification for how a file in a thunk version works. data ThunkFileSpec -- | This file specifies ThunkPtr data ThunkFileSpec_Ptr :: (ByteString -> Either String ThunkPtr) -> ThunkFileSpec -- | This file must match the given content exactly ThunkFileSpec_FileMatches :: Text -> ThunkFileSpec -- | Existence of this directory indicates that the thunk is unpacked ThunkFileSpec_CheckoutIndicator :: ThunkFileSpec -- | This directory is an attribute cache ThunkFileSpec_AttrCache :: ThunkFileSpec -- | Specification for how a set of files in a thunk version work. data ThunkSpec ThunkSpec :: !Text -> !Map FilePath ThunkFileSpec -> ThunkSpec [_thunkSpec_name] :: ThunkSpec -> !Text [_thunkSpec_files] :: ThunkSpec -> !Map FilePath ThunkFileSpec thunkSpecTypes :: NonEmpty (NonEmpty ThunkSpec) -- | Attempts to match a ThunkSpec to a given directory. matchThunkSpecToDir :: (MonadError ReadThunkError m, MonadIO m, MonadCatch m) => ThunkSpec -> FilePath -> Set FilePath -> m ThunkData readThunkWith :: MonadNixThunk m => NonEmpty (NonEmpty ThunkSpec) -> FilePath -> m (Either ReadThunkError ThunkData) -- | Read a packed or unpacked thunk based on predefined thunk -- specifications. readThunk :: MonadNixThunk m => FilePath -> m (Either ReadThunkError ThunkData) parseThunkPtr :: (Object -> Parser ThunkSource) -> Object -> Parser ThunkPtr parseGitHubSource :: Object -> Parser GitHubSource parseGitSource :: Object -> Parser GitSource overwriteThunk :: MonadNixThunk m => FilePath -> ThunkPtr -> m () thunkPtrToSpec :: ThunkPtr -> ThunkSpec encodeThunkPtrData :: ThunkPtr -> ByteString createThunk' :: MonadNixThunk m => ThunkCreateConfig -> m () createThunk :: MonadNixThunk m => FilePath -> Either ThunkSpec ThunkPtr -> m () updateThunkToLatest :: MonadNixThunk m => ThunkUpdateConfig -> FilePath -> m () setThunk :: MonadNixThunk m => ThunkConfig -> FilePath -> GitSource -> String -> m () -- | All recognized github standalone loaders, ordered from newest to -- oldest. This tool will only ever produce the newest one when it writes -- a thunk. gitHubThunkSpecs :: NonEmpty ThunkSpec gitHubThunkSpecV1 :: ThunkSpec gitHubThunkSpecV2 :: ThunkSpec gitHubThunkSpecV3 :: ThunkSpec gitHubThunkSpecV4 :: ThunkSpec legacyGitHubThunkSpec :: Text -> Text -> ThunkSpec gitHubThunkSpecV5 :: ThunkSpec -- | 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. gitHubThunkSpecV6 :: ThunkSpec -- | 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. gitHubThunkSpecV7 :: ThunkSpec -- | 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. gitHubThunkSpecV8 :: ThunkSpec parseGitHubJsonBytes :: ByteString -> Either String ThunkPtr gitThunkSpecs :: NonEmpty ThunkSpec gitThunkSpecV1 :: ThunkSpec gitThunkSpecV2 :: ThunkSpec gitThunkSpecV3 :: ThunkSpec gitThunkSpecV4 :: ThunkSpec legacyGitThunkSpec :: Text -> Text -> ThunkSpec gitThunkSpecV5 :: ThunkSpec -- | 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. gitThunkSpecV6 :: ThunkSpec -- | 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. gitThunkSpecV7 :: ThunkSpec -- | 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. gitThunkSpecV8 :: ThunkSpec parseGitJsonBytes :: ByteString -> Either String ThunkPtr mkThunkSpec :: Text -> FilePath -> (ByteString -> Either String ThunkPtr) -> Text -> ThunkSpec parseJsonObject :: (Object -> Parser a) -> ByteString -> Either String a -- | 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. nixBuildThunkAttrWithCache :: (MonadIO m, MonadLog Output m, HasCliConfig NixThunkError m, MonadMask m, MonadError NixThunkError m, MonadFail m) => ThunkSpec -> FilePath -> String -> m (Maybe FilePath) -- | Build a nix attribute, and cache the result if possible nixBuildAttrWithCache :: (MonadLog Output m, HasCliConfig NixThunkError m, MonadIO m, MonadMask m, MonadError NixThunkError m, MonadFail m) => FilePath -> String -> m FilePath -- | 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. updateThunk :: MonadNixThunk m => FilePath -> (FilePath -> m a) -> m a finalMsg :: Bool -> (a -> Text) -> Maybe (a -> Text) -- | Check that we are not somewhere inside the thunk directory checkThunkDirectory :: MonadNixThunk m => FilePath -> m () unpackThunk :: MonadNixThunk m => FilePath -> m () unpackThunk' :: MonadNixThunk m => Bool -> FilePath -> m () gitCloneForThunkUnpack :: MonadNixThunk m => GitSource -> Ref hash -> FilePath -> m () -- | Read a git process ignoring the global configuration (according to -- ignoreGitConfig). readGitProcess :: MonadNixThunk m => FilePath -> [String] -> m Text -- | 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. ignoreGitConfig :: ProcessSpec -> ProcessSpec packThunk :: MonadNixThunk m => ThunkPackConfig -> FilePath -> m ThunkPtr packThunk' :: MonadNixThunk m => Bool -> ThunkPackConfig -> FilePath -> m ThunkPtr modifyThunkPtrByConfig :: ThunkConfig -> ThunkPtr -> ThunkPtr data CheckClean -- | Check that the repo is clean, including .gitignored files CheckClean_FullCheck :: CheckClean -- | Check that the repo is clean, not including .gitignored files CheckClean_NotIgnored :: CheckClean -- | Don't check that the repo is clean CheckClean_NoCheck :: CheckClean getThunkPtr :: forall m. MonadNixThunk m => CheckClean -> FilePath -> Maybe Bool -> m ThunkPtr -- | Get the latest revision available from the given source getLatestRev :: MonadNixThunk m => ThunkSource -> m ThunkRev -- | 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. uriThunkPtr :: MonadNixThunk m => GitUri -> Maybe Bool -> Maybe Text -> Maybe Text -> m ThunkPtr -- | Convert a ThunkCreateSource to a ThunkPtr. thunkCreateSourcePtr :: MonadNixThunk m => ThunkCreateSource -> Maybe Bool -> Maybe Text -> Maybe Text -> m ThunkPtr -- | 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. uriToThunkSource :: MonadNixThunk m => GitUri -> Maybe Bool -> Maybe Text -> m ThunkSource guessGitRepoIsPrivate :: MonadNixThunk m => GitUri -> m Bool githubThunkRev :: forall m. MonadNixThunk m => GitHubSource -> Text -> m ThunkRev gitThunkRev :: MonadNixThunk m => GitSource -> Text -> m ThunkRev -- | 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. gitGetCommitBranch :: MonadNixThunk m => GitUri -> Maybe Text -> m (Text, CommitId) parseGitUri :: Text -> Maybe GitUri parseFileURI :: Text -> Maybe URI parseAbsoluteURI :: Text -> Maybe URI parseSshShorthand :: Text -> Maybe URI -- | Represent a git reference (SHA1) newtype Ref hash Ref :: Digest hash -> Ref hash [unRef] :: Ref hash -> Digest hash -- | Invalid Reference exception raised when using something that is not a -- ref as a ref. newtype RefInvalid RefInvalid :: ByteString -> RefInvalid [unRefInvalid] :: RefInvalid -> ByteString refFromHexString :: HashAlgorithm hash => String -> Ref hash refFromHex :: HashAlgorithm hash => ByteString -> Ref hash -- | transform a ref into an hexadecimal string refToHexString :: Ref hash -> String instance Data.Data.Data Nix.Thunk.Internal.RefInvalid instance GHC.Classes.Eq Nix.Thunk.Internal.RefInvalid instance GHC.Show.Show Nix.Thunk.Internal.RefInvalid instance GHC.Classes.Ord Nix.Thunk.Internal.ThunkPtr instance GHC.Classes.Eq Nix.Thunk.Internal.ThunkPtr instance GHC.Show.Show Nix.Thunk.Internal.ThunkPtr instance GHC.Classes.Ord Nix.Thunk.Internal.ThunkRev instance GHC.Classes.Eq Nix.Thunk.Internal.ThunkRev instance GHC.Show.Show Nix.Thunk.Internal.ThunkRev instance GHC.Show.Show Nix.Thunk.Internal.ThunkCreateConfig instance GHC.Classes.Ord (Nix.Thunk.Internal.Ref hash) instance GHC.Classes.Eq (Nix.Thunk.Internal.Ref hash) instance GHC.Show.Show Nix.Thunk.Internal.ThunkCreateSource instance GHC.Show.Show Nix.Thunk.Internal.ThunkPackConfig instance GHC.Show.Show Nix.Thunk.Internal.ThunkUpdateConfig instance GHC.Show.Show Nix.Thunk.Internal.ThunkConfig instance GHC.Classes.Ord Nix.Thunk.Internal.ThunkSource instance GHC.Classes.Eq Nix.Thunk.Internal.ThunkSource instance GHC.Show.Show Nix.Thunk.Internal.ThunkSource instance GHC.Classes.Ord Nix.Thunk.Internal.GitSource instance GHC.Classes.Eq Nix.Thunk.Internal.GitSource instance GHC.Show.Show Nix.Thunk.Internal.GitSource instance GHC.Show.Show Nix.Thunk.Internal.GitUri instance GHC.Classes.Ord Nix.Thunk.Internal.GitUri instance GHC.Classes.Eq Nix.Thunk.Internal.GitUri instance GHC.Classes.Ord Nix.Thunk.Internal.GitHubSource instance GHC.Classes.Eq Nix.Thunk.Internal.GitHubSource instance GHC.Show.Show Nix.Thunk.Internal.GitHubSource instance GHC.Exception.Type.Exception Nix.Thunk.Internal.RefInvalid instance GHC.Show.Show (Nix.Thunk.Internal.Ref hash) instance Cli.Extras.Logging.AsUnstructuredError Nix.Thunk.Internal.NixThunkError instance Cli.Extras.Process.AsProcessFailure Nix.Thunk.Internal.NixThunkError module Nix.Thunk -- | A location from which a thunk's data can be retrieved data ThunkSource -- | A source specialized for GitHub ThunkSource_GitHub :: GitHubSource -> ThunkSource -- | A plain repo source ThunkSource_Git :: GitSource -> ThunkSource data GitHubSource GitHubSource :: Name Owner -> Name Repo -> Maybe (Name Branch) -> Bool -> GitHubSource [_gitHubSource_owner] :: GitHubSource -> Name Owner [_gitHubSource_repo] :: GitHubSource -> Name Repo [_gitHubSource_branch] :: GitHubSource -> Maybe (Name Branch) [_gitHubSource_private] :: GitHubSource -> Bool -- | A specific revision of data; it may be available from multiple sources data ThunkRev ThunkRev :: Ref SHA1 -> NixSha256 -> ThunkRev [_thunkRev_commit] :: ThunkRev -> Ref SHA1 [_thunkRev_nixSha256] :: ThunkRev -> NixSha256 -- | Get the latest revision available from the given source getLatestRev :: MonadNixThunk m => ThunkSource -> m ThunkRev gitCloneForThunkUnpack :: MonadNixThunk m => GitSource -> Ref hash -> FilePath -> m () thunkSourceToGitSource :: ThunkSource -> GitSource -- | A reference to the exact data that a thunk should translate into data ThunkPtr ThunkPtr :: ThunkRev -> ThunkSource -> ThunkPtr [_thunkPtr_rev] :: ThunkPtr -> ThunkRev [_thunkPtr_source] :: ThunkPtr -> ThunkSource data ThunkData -- | Packed thunk ThunkData_Packed :: ThunkSpec -> ThunkPtr -> ThunkData -- | Checked out thunk that was unpacked from this pointer ThunkData_Checkout :: ThunkData -- | Read a packed or unpacked thunk based on predefined thunk -- specifications. readThunk :: MonadNixThunk m => FilePath -> m (Either ReadThunkError ThunkData) data CheckClean -- | Check that the repo is clean, including .gitignored files CheckClean_FullCheck :: CheckClean -- | Check that the repo is clean, not including .gitignored files CheckClean_NotIgnored :: CheckClean -- | Don't check that the repo is clean CheckClean_NoCheck :: 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 :: Bool -> ThunkConfig -> ThunkPackConfig [_thunkPackConfig_force] :: ThunkPackConfig -> Bool [_thunkPackConfig_config] :: ThunkPackConfig -> ThunkConfig newtype ThunkConfig ThunkConfig :: Maybe Bool -> ThunkConfig [_thunkConfig_private] :: ThunkConfig -> Maybe Bool updateThunkToLatest :: MonadNixThunk m => ThunkUpdateConfig -> FilePath -> m () -- | 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. updateThunk :: MonadNixThunk m => FilePath -> (FilePath -> m a) -> m a data ThunkUpdateConfig ThunkUpdateConfig :: Maybe String -> ThunkConfig -> ThunkUpdateConfig [_thunkUpdateConfig_branch] :: ThunkUpdateConfig -> Maybe String [_thunkUpdateConfig_config] :: ThunkUpdateConfig -> ThunkConfig unpackThunk :: MonadNixThunk m => FilePath -> m () -- | Specification for how a set of files in a thunk version work. data ThunkSpec ThunkSpec :: !Text -> !Map FilePath ThunkFileSpec -> ThunkSpec [_thunkSpec_name] :: ThunkSpec -> !Text [_thunkSpec_files] :: ThunkSpec -> !Map FilePath ThunkFileSpec -- | Specification for how a file in a thunk version works. data ThunkFileSpec -- | This file specifies ThunkPtr data ThunkFileSpec_Ptr :: (ByteString -> Either String ThunkPtr) -> ThunkFileSpec -- | This file must match the given content exactly ThunkFileSpec_FileMatches :: Text -> ThunkFileSpec -- | Existence of this directory indicates that the thunk is unpacked ThunkFileSpec_CheckoutIndicator :: ThunkFileSpec -- | This directory is an attribute cache ThunkFileSpec_AttrCache :: ThunkFileSpec data NixThunkError -- | Build a nix attribute, and cache the result if possible 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 -- | The source to be used for creating thunks. data ThunkCreateSource -- | Create a thunk from an absolute reference to a Git repository: URIs -- like file://, https://, ssh:// etc. ThunkCreateSource_Absolute :: GitUri -> ThunkCreateSource -- | 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. ThunkCreateSource_Relative :: FilePath -> ThunkCreateSource data ThunkCreateConfig ThunkCreateConfig :: ThunkCreateSource -> Maybe (Name Branch) -> Maybe (Ref SHA1) -> ThunkConfig -> Maybe FilePath -> ThunkCreateConfig [_thunkCreateConfig_uri] :: ThunkCreateConfig -> ThunkCreateSource [_thunkCreateConfig_branch] :: ThunkCreateConfig -> Maybe (Name Branch) [_thunkCreateConfig_rev] :: ThunkCreateConfig -> Maybe (Ref SHA1) [_thunkCreateConfig_config] :: ThunkCreateConfig -> ThunkConfig [_thunkCreateConfig_destination] :: ThunkCreateConfig -> Maybe FilePath parseGitUri :: Text -> Maybe GitUri newtype GitUri GitUri :: URI -> GitUri [unGitUri] :: GitUri -> URI -- | 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. uriThunkPtr :: MonadNixThunk m => GitUri -> Maybe Bool -> Maybe Text -> Maybe Text -> m ThunkPtr -- | Represent a git reference (SHA1) newtype Ref hash Ref :: Digest hash -> Ref hash [unRef] :: Ref hash -> Digest hash refFromHexString :: HashAlgorithm hash => String -> Ref hash module Nix.Thunk.Command thunkConfig :: Parser ThunkConfig thunkUpdateConfig :: Parser ThunkUpdateConfig thunkPackConfig :: Parser ThunkPackConfig thunkCreateConfig :: Parser ThunkCreateConfig data ThunkCommand ThunkCommand_Update :: ThunkUpdateConfig -> NonEmpty FilePath -> ThunkCommand ThunkCommand_Unpack :: NonEmpty FilePath -> ThunkCommand ThunkCommand_Pack :: ThunkPackConfig -> NonEmpty FilePath -> ThunkCommand ThunkCommand_Create :: ThunkCreateConfig -> ThunkCommand thunkDirList :: Parser (NonEmpty FilePath) thunkCommand :: Parser ThunkCommand runThunkCommand :: (MonadLog Output m, HasCliConfig NixThunkError m, MonadIO m, MonadMask m, MonadError NixThunkError m, MonadFail m) => ThunkCommand -> m () instance GHC.Show.Show Nix.Thunk.Command.ThunkCommand