Copyright | (c) 2021-2022 berberman |
---|---|
License | MIT |
Maintainer | berberman <berberman@yandex.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Types used in this program.
Synopsis
- newtype Version = Version Text
- newtype Checksum = Checksum 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 { }
- data NvcheckerResult = NvcheckerResult {}
- newtype NvcheckerRaw = NvcheckerRaw Version
- data CheckVersion = CheckVersion VersionSource NvcheckerOptions
- data NvcheckerOptions = NvcheckerOptions {}
- data UseStaleVersion
- data NixFetcher (k :: FetchStatus)
- = FetchGit {
- _furl :: Text
- _rev :: Version
- _deepClone :: Bool
- _fetchSubmodules :: Bool
- _leaveDotGit :: Bool
- _name :: Maybe Text
- _sha256 :: FetchResult k
- | FetchGitHub {
- _fowner :: Text
- _frepo :: Text
- _rev :: Version
- _deepClone :: Bool
- _fetchSubmodules :: Bool
- _leaveDotGit :: Bool
- _name :: Maybe Text
- _sha256 :: FetchResult k
- | FetchUrl { }
- | FetchTarball {
- _furl :: Text
- _sha256 :: FetchResult k
- = FetchGit {
- type family FetchResult (k :: FetchStatus) where ...
- data FetchStatus
- data ExtractSrcQ = ExtractSrcQ (NixFetcher Fetched) (NonEmpty FilePath)
- data FetchRustGitDepsQ = FetchRustGitDepsQ (NixFetcher Fetched) FilePath
- 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
Eq Version Source # | |
Ord Version Source # | |
Show Version Source # | |
IsString Version Source # | |
Defined in NvFetcher.Types fromString :: String -> Version # | |
Generic Version Source # | |
Semigroup Version Source # | |
Monoid Version Source # | |
Hashable Version Source # | |
Defined in NvFetcher.Types | |
ToJSON Version Source # | |
Defined in NvFetcher.Types | |
FromJSON Version Source # | |
Binary Version Source # | |
NFData Version Source # | |
Defined in NvFetcher.Types | |
Pretty Version Source # | |
Defined in NvFetcher.Types | |
ToNixExpr Version Source # | |
type Rep Version Source # | |
Defined in NvFetcher.Types |
Check sum, sha256, sri or base32, etc.
Instances
Eq Checksum Source # | |
Ord Checksum Source # | |
Defined in NvFetcher.Types | |
Show Checksum Source # | |
Generic Checksum Source # | |
Hashable Checksum Source # | |
Defined in NvFetcher.Types | |
ToJSON Checksum Source # | |
Defined in NvFetcher.Types | |
FromJSON Checksum Source # | |
Binary Checksum Source # | |
NFData Checksum Source # | |
Defined in NvFetcher.Types | |
Pretty Checksum Source # | |
Defined in NvFetcher.Types | |
type Rep Checksum Source # | |
Defined in NvFetcher.Types |
Git branch (Nothing
: master)
Instances
Eq Branch Source # | |
Ord Branch Source # | |
Show Branch Source # | |
Generic Branch Source # | |
Hashable Branch Source # | |
Defined in NvFetcher.Types | |
Binary Branch Source # | |
Default Branch Source # | |
Defined in NvFetcher.Types | |
NFData 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
Instances
Eq VersionChange Source # | |
Defined in NvFetcher.Types (==) :: VersionChange -> VersionChange -> Bool # (/=) :: VersionChange -> VersionChange -> Bool # | |
Show VersionChange Source # | |
Defined in NvFetcher.Types showsPrec :: Int -> VersionChange -> ShowS # show :: VersionChange -> String # showList :: [VersionChange] -> ShowS # |
newtype WithPackageKey k Source #
Decorate a rule's key with PackageKey
WithPackageKey (k, PackageKey) |
Instances
Eq k => Eq (WithPackageKey k) Source # | |
Defined in NvFetcher.Types (==) :: WithPackageKey k -> WithPackageKey k -> Bool # (/=) :: WithPackageKey k -> WithPackageKey k -> Bool # | |
Show k => Show (WithPackageKey k) Source # | |
Defined in NvFetcher.Types showsPrec :: Int -> WithPackageKey k -> ShowS # show :: WithPackageKey k -> String # showList :: [WithPackageKey k] -> ShowS # | |
Hashable k => Hashable (WithPackageKey k) Source # | |
Defined in NvFetcher.Types hashWithSalt :: Int -> WithPackageKey k -> Int # hash :: WithPackageKey k -> Int # | |
Binary k => Binary (WithPackageKey k) Source # | |
Defined in NvFetcher.Types put :: WithPackageKey k -> Put # get :: Get (WithPackageKey k) # putList :: [WithPackageKey k] -> Put # | |
NFData k => NFData (WithPackageKey k) Source # | |
Defined in NvFetcher.Types rnf :: WithPackageKey k -> () # | |
type RuleResult (WithPackageKey k) Source # | |
Defined in NvFetcher.Types |
Nvchecker types
data VersionSortMethod Source #
Instances
data ListOptions Source #
Filter-like configuration for some version sources. See https://nvchecker.readthedocs.io/en/latest/usage.html#list-options for details.
Instances
data VersionSource Source #
Upstream version source for nvchecker to check
GitHubRelease | |
GitHubTag | |
| |
Git | |
Pypi | |
ArchLinux | |
Aur | |
Manual | |
Repology | |
Webpage | |
| |
HttpHeader | |
| |
OpenVsx | |
| |
VscodeMarketplace | |
| |
Cmd | |
Instances
data NvcheckerResult Source #
The result of nvchecker rule
Instances
newtype NvcheckerRaw Source #
Parsed JSON output from nvchecker
Instances
Eq NvcheckerRaw Source # | |
Defined in NvFetcher.Types (==) :: NvcheckerRaw -> NvcheckerRaw -> Bool # (/=) :: NvcheckerRaw -> NvcheckerRaw -> Bool # | |
Show NvcheckerRaw Source # | |
Defined in NvFetcher.Types showsPrec :: Int -> NvcheckerRaw -> ShowS # show :: NvcheckerRaw -> String # showList :: [NvcheckerRaw] -> ShowS # | |
Generic NvcheckerRaw Source # | |
Defined in NvFetcher.Types type Rep NvcheckerRaw :: Type -> Type # from :: NvcheckerRaw -> Rep NvcheckerRaw x # to :: Rep NvcheckerRaw x -> NvcheckerRaw # | |
FromJSON NvcheckerRaw Source # | |
Defined in NvFetcher.Types parseJSON :: Value -> Parser NvcheckerRaw # parseJSONList :: Value -> Parser [NvcheckerRaw] # | |
type Rep NvcheckerRaw Source # | |
Defined in NvFetcher.Types type Rep NvcheckerRaw = D1 ('MetaData "NvcheckerRaw" "NvFetcher.Types" "nvfetcher-0.5.0.0-3yJjetg0q7IBedlVdRRp6j" 'True) (C1 ('MetaCons "NvcheckerRaw" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Version))) |
data CheckVersion Source #
The input of nvchecker
Instances
data NvcheckerOptions Source #
Configuration available for evey version sourece. See https://nvchecker.readthedocs.io/en/latest/usage.html#global-options for details.
Instances
data UseStaleVersion Source #
Using stale value indicates that we will NOT check for new versions if there is a known version recoverd from json file or last use of the rule. Normally you don't want a stale version unless you need pin a package.
PermanentStale | Specified in configuration file |
TemporaryStale | Specified by |
NoStale |
Instances
Nix fetcher types
data NixFetcher (k :: FetchStatus) Source #
If the package is prefetched, then we can obtain the SHA256
FetchGit | |
| |
FetchGitHub | |
| |
FetchUrl | |
FetchTarball | |
|
Instances
type family FetchResult (k :: FetchStatus) where ... Source #
Prefetched fetchers hold hashes
FetchResult Fresh = () | |
FetchResult Fetched = Checksum |
ExtractSrc Types
data ExtractSrcQ Source #
Extract file contents from package source
e.g. Cargo.lock
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
.
Instances
Core types
The key type of nvfetcher rule. See NvFetcher.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 PackagePassthru Source #
Instances
Semigroup PackagePassthru Source # | |
Defined in NvFetcher.Types (<>) :: PackagePassthru -> PackagePassthru -> PackagePassthru # sconcat :: NonEmpty PackagePassthru -> PackagePassthru # stimes :: Integral b => b -> PackagePassthru -> PackagePassthru # | |
Monoid PackagePassthru Source # | |
Defined in NvFetcher.Types mappend :: PackagePassthru -> PackagePassthru -> PackagePassthru # mconcat :: [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.lock
path (if it's a rust package) - an optional pass through map
- if the package version was pinned
INVARIANT: Version
passed to PackageFetcher
MUST be used textually,
i.e. can only be concatenated with other strings,
in case we can't check the equality between fetcher functions.
newtype PackageKey Source #
Package key is the name of a package. We use this type to index packages.
Instances
data PackageResult Source #
Result type of Core
PackageResult | |
|