| Copyright | (c) 2021-2022 berberman |
|---|---|
| License | MIT |
| Maintainer | berberman <berberman@yandex.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
NvFetcher.Types
Description
Types used in this program.
Synopsis
- newtype Version = Version Text
- newtype Checksum = Checksum Text
- newtype ContainerDigest = ContainerDigest Text
- newtype Branch = Branch (Maybe Text)
- type NixExpr = Text
- data VersionChange = VersionChange {}
- newtype WithPackageKey k = WithPackageKey (k, PackageKey)
- data VersionSortMethod
- data ListOptions = ListOptions {}
- data VersionSource
- = GitHubRelease { }
- | GitHubTag {
- _owner :: Text
- _repo :: Text
- _listOptions :: ListOptions
- | Git { }
- | Pypi { }
- | ArchLinux { }
- | Aur { }
- | Manual { }
- | Repology { }
- | Webpage {
- _vurl :: Text
- _regex :: Text
- _listOptions :: ListOptions
- | HttpHeader {
- _vurl :: Text
- _regex :: Text
- _listOptions :: ListOptions
- | OpenVsx {
- _ovPublisher :: Text
- _ovExtName :: Text
- | VscodeMarketplace {
- _vsmPublisher :: Text
- _vsmExtName :: Text
- | Cmd { }
- | Container { }
- data NvcheckerResult = NvcheckerResult {}
- data NvcheckerRaw
- data CheckVersion = CheckVersion VersionSource NvcheckerOptions
- data NvcheckerOptions = NvcheckerOptions {}
- data UseStaleVersion
- data RunFetch = RunFetch ForceFetch (NixFetcher Fresh)
- data ForceFetch
- data NixFetcher (k :: FetchStatus)
- = FetchGit {
- _furl :: Text
- _rev :: Version
- _deepClone :: Bool
- _fetchSubmodules :: Bool
- _leaveDotGit :: Bool
- _sparseCheckout :: [Text]
- _name :: Maybe Text
- _sha256 :: FetchResult Checksum k
- | FetchGitHub {
- _fowner :: Text
- _frepo :: Text
- _rev :: Version
- _deepClone :: Bool
- _fetchSubmodules :: Bool
- _leaveDotGit :: Bool
- _sparseCheckout :: [Text]
- _name :: Maybe Text
- _sha256 :: FetchResult Checksum k
- | FetchUrl { }
- | FetchTarball {
- _furl :: Text
- _sha256 :: FetchResult Checksum k
- | FetchDocker {
- _imageName :: Text
- _imageTag :: Text
- _imageDigest :: FetchResult ContainerDigest k
- _sha256 :: FetchResult Checksum k
- _fos :: Maybe Text
- _farch :: Maybe Text
- _finalImageName :: Maybe Text
- _finalImageTag :: Maybe Text
- _tlsVerify :: Maybe Bool
- = FetchGit {
- type family FetchResult a (k :: FetchStatus) where ...
- data FetchStatus
- data ExtractSrcQ = ExtractSrcQ (NixFetcher Fetched) (NonEmpty FilePath)
- data FetchRustGitDepsQ = FetchRustGitDepsQ (NixFetcher Fetched) FilePath
- newtype DateFormat = DateFormat (Maybe Text)
- data GetGitCommitDate = GetGitCommitDate {}
- data Core = Core
- type PackageName = Text
- type PackageFetcher = Version -> NixFetcher Fresh
- newtype PackageExtractSrc = PackageExtractSrc (NonEmpty FilePath)
- newtype PackageCargoLockFiles = PackageCargoLockFiles (NonEmpty FilePath)
- newtype PackagePassthru = PackagePassthru (HashMap Text Text)
- data Package = Package {}
- newtype PackageKey = PackageKey PackageName
- data PackageResult = PackageResult {}
Common types
Package version
Instances
| FromJSON Version Source # | |
Defined in NvFetcher.Types | |
| ToJSON Version Source # | |
| IsString Version Source # | |
Defined in NvFetcher.Types Methods fromString :: String -> Version # | |
| Monoid Version Source # | |
| Semigroup Version Source # | |
| Generic Version Source # | |
| Show Version Source # | |
| Binary Version Source # | |
| NFData Version Source # | |
Defined in NvFetcher.Types | |
| Eq Version Source # | |
| Ord Version Source # | |
| Hashable Version Source # | |
Defined in NvFetcher.Types | |
| ToNixExpr Version Source # | |
| Pretty Version Source # | |
Defined in NvFetcher.Types | |
| type Rep Version Source # | |
Defined in NvFetcher.Types | |
Check sum, sha256, sri or base32, etc.
Instances
| FromJSON Checksum Source # | |
Defined in NvFetcher.Types | |
| ToJSON Checksum Source # | |
| Generic Checksum Source # | |
| Show Checksum Source # | |
| Binary Checksum Source # | |
| NFData Checksum Source # | |
Defined in NvFetcher.Types | |
| Eq Checksum Source # | |
| Ord Checksum Source # | |
Defined in NvFetcher.Types | |
| Hashable Checksum Source # | |
Defined in NvFetcher.Types | |
| Pretty Checksum Source # | |
Defined in NvFetcher.Types | |
| type Rep Checksum Source # | |
Defined in NvFetcher.Types | |
newtype ContainerDigest Source #
Digest of a (Docker) container
Constructors
| ContainerDigest Text |
Instances
Git branch (Nothing: master)
Instances
| Generic Branch Source # | |
| Show Branch Source # | |
| Binary Branch Source # | |
| Default Branch Source # | |
Defined in NvFetcher.Types | |
| NFData Branch Source # | |
Defined in NvFetcher.Types | |
| Eq Branch Source # | |
| Ord Branch Source # | |
| Hashable Branch Source # | |
Defined in NvFetcher.Types | |
| Pretty Branch Source # | |
Defined in NvFetcher.Types | |
| type Rep Branch Source # | |
data VersionChange Source #
Version change of a package
>>>VersionChange "foo" Nothing "2.3.3"foo: ∅ → 2.3.3
>>>VersionChange "bar" (Just "2.2.2") "2.3.3"bar: 2.2.2 → 2.3.3
Constructors
| VersionChange | |
Instances
| Show VersionChange Source # | |
Defined in NvFetcher.Types Methods showsPrec :: Int -> VersionChange -> ShowS # show :: VersionChange -> String # showList :: [VersionChange] -> ShowS # | |
| Eq VersionChange Source # | |
Defined in NvFetcher.Types Methods (==) :: VersionChange -> VersionChange -> Bool # (/=) :: VersionChange -> VersionChange -> Bool # | |
newtype WithPackageKey k Source #
Decorate a rule's key with PackageKey
Constructors
| WithPackageKey (k, PackageKey) |
Instances
| Show k => Show (WithPackageKey k) Source # | |
Defined in NvFetcher.Types Methods showsPrec :: Int -> WithPackageKey k -> ShowS # show :: WithPackageKey k -> String # showList :: [WithPackageKey k] -> ShowS # | |
| Binary k => Binary (WithPackageKey k) Source # | |
Defined in NvFetcher.Types Methods put :: WithPackageKey k -> Put # get :: Get (WithPackageKey k) # putList :: [WithPackageKey k] -> Put # | |
| NFData k => NFData (WithPackageKey k) Source # | |
Defined in NvFetcher.Types Methods rnf :: WithPackageKey k -> () # | |
| Eq k => Eq (WithPackageKey k) Source # | |
Defined in NvFetcher.Types Methods (==) :: WithPackageKey k -> WithPackageKey k -> Bool # (/=) :: WithPackageKey k -> WithPackageKey k -> Bool # | |
| Hashable k => Hashable (WithPackageKey k) Source # | |
Defined in NvFetcher.Types | |
| type RuleResult (WithPackageKey k) Source # | |
Defined in NvFetcher.Types | |
Nvchecker types
data VersionSortMethod Source #
Constructors
| ParseVersion | |
| Vercmp |
Instances
data ListOptions Source #
Filter-like configuration for some version sources. See https://nvchecker.readthedocs.io/en/latest/usage.html#list-options for details.
Constructors
| ListOptions | |
Fields | |
Instances
data VersionSource Source #
Upstream version source for nvchecker to check
Constructors
| GitHubRelease | |
| GitHubTag | |
Fields
| |
| Git | |
| Pypi | |
| ArchLinux | |
| Aur | |
| Manual | |
| Repology | |
| Webpage | |
Fields
| |
| HttpHeader | |
Fields
| |
| OpenVsx | |
Fields
| |
| VscodeMarketplace | |
Fields
| |
| Cmd | |
| Container | |
Fields | |
Instances
data NvcheckerResult Source #
The result of nvchecker rule
Constructors
| NvcheckerResult | |
Instances
data NvcheckerRaw Source #
Parsed JSON output from nvchecker
Constructors
| NvcheckerSuccess Version | |
| NvcheckerError Text |
Instances
| FromJSON NvcheckerRaw Source # | |
Defined in NvFetcher.Types | |
| Generic NvcheckerRaw Source # | |
Defined in NvFetcher.Types Associated Types type Rep NvcheckerRaw :: Type -> Type # | |
| Show NvcheckerRaw Source # | |
Defined in NvFetcher.Types Methods showsPrec :: Int -> NvcheckerRaw -> ShowS # show :: NvcheckerRaw -> String # showList :: [NvcheckerRaw] -> ShowS # | |
| Eq NvcheckerRaw Source # | |
Defined in NvFetcher.Types | |
| type Rep NvcheckerRaw Source # | |
Defined in NvFetcher.Types type Rep NvcheckerRaw = D1 ('MetaData "NvcheckerRaw" "NvFetcher.Types" "nvfetcher-0.7.0.0-A35nVRCksvb3leatD1NVDI" 'False) (C1 ('MetaCons "NvcheckerSuccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version)) :+: C1 ('MetaCons "NvcheckerError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
data CheckVersion Source #
The input of nvchecker
Constructors
| CheckVersion VersionSource NvcheckerOptions |
Instances
data NvcheckerOptions Source #
Configuration available for evey version sourece. See https://nvchecker.readthedocs.io/en/latest/usage.html#global-options for details.
Constructors
| NvcheckerOptions | |
Fields
| |
Instances
data UseStaleVersion Source #
Using stale value indicates that we will NOT check for new versions if there is a known version recovered from json file or last use of the rule. Normally you don't want a stale version unless you need pin a package.
Constructors
| PermanentStale | Specified in configuration file |
| TemporaryStale | Specified by |
| NoStale |
Instances
Nix fetcher types
The input of prefetch rule
Constructors
| RunFetch ForceFetch (NixFetcher Fresh) |
Instances
| Generic RunFetch Source # | |
| Show RunFetch Source # | |
| Binary RunFetch Source # | |
| NFData RunFetch Source # | |
Defined in NvFetcher.Types | |
| Eq RunFetch Source # | |
| Ord RunFetch Source # | |
Defined in NvFetcher.Types | |
| Hashable RunFetch Source # | |
Defined in NvFetcher.Types | |
| type Rep RunFetch Source # | |
Defined in NvFetcher.Types type Rep RunFetch = D1 ('MetaData "RunFetch" "NvFetcher.Types" "nvfetcher-0.7.0.0-A35nVRCksvb3leatD1NVDI" 'False) (C1 ('MetaCons "RunFetch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ForceFetch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NixFetcher 'Fresh)))) | |
| type RuleResult RunFetch Source # | |
Defined in NvFetcher.Types | |
data ForceFetch Source #
Whether to cache the fetched sha256
ForceFetch indicates alwaysRerun the fetcher rule
Constructors
| ForceFetch | |
| NoForceFetch |
Instances
data NixFetcher (k :: FetchStatus) Source #
If the package is prefetched, then we can obtain the SHA256
Constructors
| FetchGit | |
Fields
| |
| FetchGitHub | |
Fields
| |
| FetchUrl | |
| FetchTarball | |
Fields
| |
| FetchDocker | |
Fields
| |
Instances
type family FetchResult a (k :: FetchStatus) where ... Source #
Prefetched fetchers hold hashes
Equations
| FetchResult _ Fresh = () | |
| FetchResult a Fetched = a |
ExtractSrc Types
data ExtractSrcQ Source #
Extract file contents from package source
e.g. Cargo.lock
Constructors
| ExtractSrcQ (NixFetcher Fetched) (NonEmpty FilePath) |
Instances
FetchRustGitDeps types
data FetchRustGitDepsQ Source #
Fetch outputHashes for git dependencies in Cargo.lock.
See https://github.com/NixOS/nixpkgs/blob/master/doc/languages-frameworks/rust.section.md#importing-a-cargolock-file for details.
We need fetched source and the file path to Cargo.lock.
Constructors
| FetchRustGitDepsQ (NixFetcher Fetched) FilePath |
Instances
GetGitCommitDate types
newtype DateFormat Source #
strftime format
Nothing defaults to %Y-%m-%d
Constructors
| DateFormat (Maybe Text) |
Instances
data GetGitCommitDate Source #
Get the commit date by using shallow clone
_gformat is in.
Note: Requires git >= 2.5
Constructors
| GetGitCommitDate | |
Instances
Core types
The key type of nvfetcher rule. See NvFetcher.Core
Constructors
| Core |
Package types
type PackageName = Text Source #
Package name, used in generating nix expr
type PackageFetcher = Version -> NixFetcher Fresh Source #
How to create package source fetcher given a version
newtype PackageExtractSrc Source #
Constructors
| PackageExtractSrc (NonEmpty FilePath) |
newtype PackageCargoLockFiles Source #
Constructors
| PackageCargoLockFiles (NonEmpty FilePath) |
newtype PackagePassthru Source #
Constructors
| PackagePassthru (HashMap Text Text) |
Instances
| Monoid PackagePassthru Source # | |
Defined in NvFetcher.Types Methods mappend :: PackagePassthru -> PackagePassthru -> PackagePassthru # mconcat :: [PackagePassthru] -> PackagePassthru # | |
| Semigroup PackagePassthru Source # | |
Defined in NvFetcher.Types Methods (<>) :: PackagePassthru -> PackagePassthru -> PackagePassthru # sconcat :: NonEmpty PackagePassthru -> PackagePassthru # stimes :: Integral b => b -> PackagePassthru -> PackagePassthru # | |
A package is defined with:
- its name
- how to track its version
- how to fetch it as we have the version
- optional file paths to extract (dump to build dir)
- optional
Cargo.lockpath (if it's a rust package) - an optional pass through map
- if the package version was pinned
- optional git date format (if the version source is git)
- whether to always fetch a package regardless of the version changing
INVARIANT:
Versionpassed toPackageFetcherMUST be used textually, i.e. can only be concatenated with other strings, in case we can't check the equality between fetcher functions.
Constructors
| Package | |
newtype PackageKey Source #
Package key is the name of a package. We use this type to index packages.
Constructors
| PackageKey PackageName |
Instances
data PackageResult Source #
Result type of Core
Constructors
| PackageResult | |
Fields
| |