{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}

-- | Copyright: (c) 2021-2022 berberman
-- SPDX-License-Identifier: MIT
-- Maintainer: berberman <berberman@yandex.com>
-- Stability: experimental
-- Portability: portable
--
-- Types used in this program.
module NvFetcher.Types
  ( -- * Common types
    Version (..),
    Checksum (..),
    ContainerDigest (..),
    Branch (..),
    NixExpr,
    VersionChange (..),
    WithPackageKey (..),

    -- * Nvchecker types
    VersionSortMethod (..),
    ListOptions (..),
    VersionSource (..),
    NvcheckerResult (..),
    NvcheckerRaw (..),
    CheckVersion (..),
    NvcheckerOptions (..),
    UseStaleVersion (..),

    -- * Nix fetcher types
    RunFetch (..),
    ForceFetch (..),
    NixFetcher (..),
    FetchResult,
    FetchStatus (..),

    -- * ExtractSrc Types
    ExtractSrcQ (..),

    -- * FetchRustGitDeps types
    FetchRustGitDepsQ (..),

    -- * GetGitCommitDate types
    DateFormat (..),
    GetGitCommitDate (..),

    -- * Core types
    Core (..),

    -- * Package types
    PackageName,
    PackageFetcher,
    PackageExtractSrc (..),
    PackageCargoLockFiles (..),
    PackagePassthru (..),
    Package (..),
    PackageKey (..),
    PackageResult (..),
  )
where

import qualified Data.Aeson as A
import Data.Coerce (coerce)
import Data.Default
import Data.HashMap.Strict (HashMap)
import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromMaybe, isNothing)
import Data.String (IsString)
import Data.Text (Text)
import qualified Data.Text as T
import Development.Shake
import Development.Shake.Classes
import GHC.Generics (Generic)
import Prettyprinter

--------------------------------------------------------------------------------

-- | Package version
newtype Version = Version Text
  deriving newtype (Version -> Version -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Version -> Version -> Bool
$c/= :: Version -> Version -> Bool
== :: Version -> Version -> Bool
$c== :: Version -> Version -> Bool
Eq, Int -> Version -> ShowS
[Version] -> ShowS
Version -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Version] -> ShowS
$cshowList :: [Version] -> ShowS
show :: Version -> FilePath
$cshow :: Version -> FilePath
showsPrec :: Int -> Version -> ShowS
$cshowsPrec :: Int -> Version -> ShowS
Show, Eq Version
Version -> Version -> Bool
Version -> Version -> Ordering
Version -> Version -> Version
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Version -> Version -> Version
$cmin :: Version -> Version -> Version
max :: Version -> Version -> Version
$cmax :: Version -> Version -> Version
>= :: Version -> Version -> Bool
$c>= :: Version -> Version -> Bool
> :: Version -> Version -> Bool
$c> :: Version -> Version -> Bool
<= :: Version -> Version -> Bool
$c<= :: Version -> Version -> Bool
< :: Version -> Version -> Bool
$c< :: Version -> Version -> Bool
compare :: Version -> Version -> Ordering
$ccompare :: Version -> Version -> Ordering
Ord, FilePath -> Version
forall a. (FilePath -> a) -> IsString a
fromString :: FilePath -> Version
$cfromString :: FilePath -> Version
IsString, NonEmpty Version -> Version
Version -> Version -> Version
forall b. Integral b => b -> Version -> Version
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> Version -> Version
$cstimes :: forall b. Integral b => b -> Version -> Version
sconcat :: NonEmpty Version -> Version
$csconcat :: NonEmpty Version -> Version
<> :: Version -> Version -> Version
$c<> :: Version -> Version -> Version
Semigroup, Semigroup Version
Version
[Version] -> Version
Version -> Version -> Version
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [Version] -> Version
$cmconcat :: [Version] -> Version
mappend :: Version -> Version -> Version
$cmappend :: Version -> Version -> Version
mempty :: Version
$cmempty :: Version
Monoid, Value -> Parser [Version]
Value -> Parser Version
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Version]
$cparseJSONList :: Value -> Parser [Version]
parseJSON :: Value -> Parser Version
$cparseJSON :: Value -> Parser Version
A.FromJSON, [Version] -> Encoding
[Version] -> Value
Version -> Encoding
Version -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Version] -> Encoding
$ctoEncodingList :: [Version] -> Encoding
toJSONList :: [Version] -> Value
$ctoJSONList :: [Version] -> Value
toEncoding :: Version -> Encoding
$ctoEncoding :: Version -> Encoding
toJSON :: Version -> Value
$ctoJSON :: Version -> Value
A.ToJSON, forall ann. [Version] -> Doc ann
forall ann. Version -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [Version] -> Doc ann
$cprettyList :: forall ann. [Version] -> Doc ann
pretty :: forall ann. Version -> Doc ann
$cpretty :: forall ann. Version -> Doc ann
Pretty)
  deriving stock (Typeable, forall x. Rep Version x -> Version
forall x. Version -> Rep Version x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Version x -> Version
$cfrom :: forall x. Version -> Rep Version x
Generic)
  deriving anyclass (Eq Version
Int -> Version -> Int
Version -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Version -> Int
$chash :: Version -> Int
hashWithSalt :: Int -> Version -> Int
$chashWithSalt :: Int -> Version -> Int
Hashable, Get Version
[Version] -> Put
Version -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Version] -> Put
$cputList :: [Version] -> Put
get :: Get Version
$cget :: Get Version
put :: Version -> Put
$cput :: Version -> Put
Binary, Version -> ()
forall a. (a -> ()) -> NFData a
rnf :: Version -> ()
$crnf :: Version -> ()
NFData)

-- | Check sum, sha256, sri or base32, etc.
newtype Checksum = Checksum Text
  deriving newtype (Int -> Checksum -> ShowS
[Checksum] -> ShowS
Checksum -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Checksum] -> ShowS
$cshowList :: [Checksum] -> ShowS
show :: Checksum -> FilePath
$cshow :: Checksum -> FilePath
showsPrec :: Int -> Checksum -> ShowS
$cshowsPrec :: Int -> Checksum -> ShowS
Show, Checksum -> Checksum -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Checksum -> Checksum -> Bool
$c/= :: Checksum -> Checksum -> Bool
== :: Checksum -> Checksum -> Bool
$c== :: Checksum -> Checksum -> Bool
Eq, Eq Checksum
Checksum -> Checksum -> Bool
Checksum -> Checksum -> Ordering
Checksum -> Checksum -> Checksum
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Checksum -> Checksum -> Checksum
$cmin :: Checksum -> Checksum -> Checksum
max :: Checksum -> Checksum -> Checksum
$cmax :: Checksum -> Checksum -> Checksum
>= :: Checksum -> Checksum -> Bool
$c>= :: Checksum -> Checksum -> Bool
> :: Checksum -> Checksum -> Bool
$c> :: Checksum -> Checksum -> Bool
<= :: Checksum -> Checksum -> Bool
$c<= :: Checksum -> Checksum -> Bool
< :: Checksum -> Checksum -> Bool
$c< :: Checksum -> Checksum -> Bool
compare :: Checksum -> Checksum -> Ordering
$ccompare :: Checksum -> Checksum -> Ordering
Ord, Value -> Parser [Checksum]
Value -> Parser Checksum
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Checksum]
$cparseJSONList :: Value -> Parser [Checksum]
parseJSON :: Value -> Parser Checksum
$cparseJSON :: Value -> Parser Checksum
A.FromJSON, [Checksum] -> Encoding
[Checksum] -> Value
Checksum -> Encoding
Checksum -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Checksum] -> Encoding
$ctoEncodingList :: [Checksum] -> Encoding
toJSONList :: [Checksum] -> Value
$ctoJSONList :: [Checksum] -> Value
toEncoding :: Checksum -> Encoding
$ctoEncoding :: Checksum -> Encoding
toJSON :: Checksum -> Value
$ctoJSON :: Checksum -> Value
A.ToJSON, forall ann. [Checksum] -> Doc ann
forall ann. Checksum -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [Checksum] -> Doc ann
$cprettyList :: forall ann. [Checksum] -> Doc ann
pretty :: forall ann. Checksum -> Doc ann
$cpretty :: forall ann. Checksum -> Doc ann
Pretty)
  deriving stock (Typeable, forall x. Rep Checksum x -> Checksum
forall x. Checksum -> Rep Checksum x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Checksum x -> Checksum
$cfrom :: forall x. Checksum -> Rep Checksum x
Generic)
  deriving anyclass (Eq Checksum
Int -> Checksum -> Int
Checksum -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Checksum -> Int
$chash :: Checksum -> Int
hashWithSalt :: Int -> Checksum -> Int
$chashWithSalt :: Int -> Checksum -> Int
Hashable, Get Checksum
[Checksum] -> Put
Checksum -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Checksum] -> Put
$cputList :: [Checksum] -> Put
get :: Get Checksum
$cget :: Get Checksum
put :: Checksum -> Put
$cput :: Checksum -> Put
Binary, Checksum -> ()
forall a. (a -> ()) -> NFData a
rnf :: Checksum -> ()
$crnf :: Checksum -> ()
NFData)

-- | Digest of a (Docker) container
newtype ContainerDigest = ContainerDigest Text
  deriving newtype (Int -> ContainerDigest -> ShowS
[ContainerDigest] -> ShowS
ContainerDigest -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ContainerDigest] -> ShowS
$cshowList :: [ContainerDigest] -> ShowS
show :: ContainerDigest -> FilePath
$cshow :: ContainerDigest -> FilePath
showsPrec :: Int -> ContainerDigest -> ShowS
$cshowsPrec :: Int -> ContainerDigest -> ShowS
Show, ContainerDigest -> ContainerDigest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContainerDigest -> ContainerDigest -> Bool
$c/= :: ContainerDigest -> ContainerDigest -> Bool
== :: ContainerDigest -> ContainerDigest -> Bool
$c== :: ContainerDigest -> ContainerDigest -> Bool
Eq, Eq ContainerDigest
ContainerDigest -> ContainerDigest -> Bool
ContainerDigest -> ContainerDigest -> Ordering
ContainerDigest -> ContainerDigest -> ContainerDigest
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ContainerDigest -> ContainerDigest -> ContainerDigest
$cmin :: ContainerDigest -> ContainerDigest -> ContainerDigest
max :: ContainerDigest -> ContainerDigest -> ContainerDigest
$cmax :: ContainerDigest -> ContainerDigest -> ContainerDigest
>= :: ContainerDigest -> ContainerDigest -> Bool
$c>= :: ContainerDigest -> ContainerDigest -> Bool
> :: ContainerDigest -> ContainerDigest -> Bool
$c> :: ContainerDigest -> ContainerDigest -> Bool
<= :: ContainerDigest -> ContainerDigest -> Bool
$c<= :: ContainerDigest -> ContainerDigest -> Bool
< :: ContainerDigest -> ContainerDigest -> Bool
$c< :: ContainerDigest -> ContainerDigest -> Bool
compare :: ContainerDigest -> ContainerDigest -> Ordering
$ccompare :: ContainerDigest -> ContainerDigest -> Ordering
Ord, Value -> Parser [ContainerDigest]
Value -> Parser ContainerDigest
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ContainerDigest]
$cparseJSONList :: Value -> Parser [ContainerDigest]
parseJSON :: Value -> Parser ContainerDigest
$cparseJSON :: Value -> Parser ContainerDigest
A.FromJSON, [ContainerDigest] -> Encoding
[ContainerDigest] -> Value
ContainerDigest -> Encoding
ContainerDigest -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ContainerDigest] -> Encoding
$ctoEncodingList :: [ContainerDigest] -> Encoding
toJSONList :: [ContainerDigest] -> Value
$ctoJSONList :: [ContainerDigest] -> Value
toEncoding :: ContainerDigest -> Encoding
$ctoEncoding :: ContainerDigest -> Encoding
toJSON :: ContainerDigest -> Value
$ctoJSON :: ContainerDigest -> Value
A.ToJSON, forall ann. [ContainerDigest] -> Doc ann
forall ann. ContainerDigest -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [ContainerDigest] -> Doc ann
$cprettyList :: forall ann. [ContainerDigest] -> Doc ann
pretty :: forall ann. ContainerDigest -> Doc ann
$cpretty :: forall ann. ContainerDigest -> Doc ann
Pretty)
  deriving stock (Typeable, forall x. Rep ContainerDigest x -> ContainerDigest
forall x. ContainerDigest -> Rep ContainerDigest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContainerDigest x -> ContainerDigest
$cfrom :: forall x. ContainerDigest -> Rep ContainerDigest x
Generic)
  deriving anyclass (Eq ContainerDigest
Int -> ContainerDigest -> Int
ContainerDigest -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ContainerDigest -> Int
$chash :: ContainerDigest -> Int
hashWithSalt :: Int -> ContainerDigest -> Int
$chashWithSalt :: Int -> ContainerDigest -> Int
Hashable, Get ContainerDigest
[ContainerDigest] -> Put
ContainerDigest -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [ContainerDigest] -> Put
$cputList :: [ContainerDigest] -> Put
get :: Get ContainerDigest
$cget :: Get ContainerDigest
put :: ContainerDigest -> Put
$cput :: ContainerDigest -> Put
Binary, ContainerDigest -> ()
forall a. (a -> ()) -> NFData a
rnf :: ContainerDigest -> ()
$crnf :: ContainerDigest -> ()
NFData)

-- | Git branch ('Nothing': master)
newtype Branch = Branch (Maybe Text)
  deriving newtype (Int -> Branch -> ShowS
[Branch] -> ShowS
Branch -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Branch] -> ShowS
$cshowList :: [Branch] -> ShowS
show :: Branch -> FilePath
$cshow :: Branch -> FilePath
showsPrec :: Int -> Branch -> ShowS
$cshowsPrec :: Int -> Branch -> ShowS
Show, Branch -> Branch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Branch -> Branch -> Bool
$c/= :: Branch -> Branch -> Bool
== :: Branch -> Branch -> Bool
$c== :: Branch -> Branch -> Bool
Eq, Eq Branch
Branch -> Branch -> Bool
Branch -> Branch -> Ordering
Branch -> Branch -> Branch
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Branch -> Branch -> Branch
$cmin :: Branch -> Branch -> Branch
max :: Branch -> Branch -> Branch
$cmax :: Branch -> Branch -> Branch
>= :: Branch -> Branch -> Bool
$c>= :: Branch -> Branch -> Bool
> :: Branch -> Branch -> Bool
$c> :: Branch -> Branch -> Bool
<= :: Branch -> Branch -> Bool
$c<= :: Branch -> Branch -> Bool
< :: Branch -> Branch -> Bool
$c< :: Branch -> Branch -> Bool
compare :: Branch -> Branch -> Ordering
$ccompare :: Branch -> Branch -> Ordering
Ord, Branch
forall a. a -> Default a
def :: Branch
$cdef :: Branch
Default, forall ann. [Branch] -> Doc ann
forall ann. Branch -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [Branch] -> Doc ann
$cprettyList :: forall ann. [Branch] -> Doc ann
pretty :: forall ann. Branch -> Doc ann
$cpretty :: forall ann. Branch -> Doc ann
Pretty)
  deriving stock (Typeable, forall x. Rep Branch x -> Branch
forall x. Branch -> Rep Branch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Branch x -> Branch
$cfrom :: forall x. Branch -> Rep Branch x
Generic)
  deriving anyclass (Eq Branch
Int -> Branch -> Int
Branch -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Branch -> Int
$chash :: Branch -> Int
hashWithSalt :: Int -> Branch -> Int
$chashWithSalt :: Int -> Branch -> Int
Hashable, Get Branch
[Branch] -> Put
Branch -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Branch] -> Put
$cputList :: [Branch] -> Put
get :: Get Branch
$cget :: Get Branch
put :: Branch -> Put
$cput :: Branch -> Put
Binary, Branch -> ()
forall a. (a -> ()) -> NFData a
rnf :: Branch -> ()
$crnf :: Branch -> ()
NFData)

-- | 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
data VersionChange = VersionChange
  { VersionChange -> Text
vcName :: PackageName,
    VersionChange -> Maybe Version
vcOld :: Maybe Version,
    VersionChange -> Version
vcNew :: Version
  }
  deriving (VersionChange -> VersionChange -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionChange -> VersionChange -> Bool
$c/= :: VersionChange -> VersionChange -> Bool
== :: VersionChange -> VersionChange -> Bool
$c== :: VersionChange -> VersionChange -> Bool
Eq)

instance Show VersionChange where
  show :: VersionChange -> FilePath
show VersionChange {Maybe Version
Text
Version
vcNew :: Version
vcOld :: Maybe Version
vcName :: Text
vcNew :: VersionChange -> Version
vcOld :: VersionChange -> Maybe Version
vcName :: VersionChange -> Text
..} =
    Text -> FilePath
T.unpack forall a b. (a -> b) -> a -> b
$ Text
vcName forall a. Semigroup a => a -> a -> a
<> Text
": " forall a. Semigroup a => a -> a -> a
<> forall a. a -> Maybe a -> a
fromMaybe Text
"∅" (coerce :: forall a b. Coercible a b => a -> b
coerce Maybe Version
vcOld) forall a. Semigroup a => a -> a -> a
<> Text
" → " forall a. Semigroup a => a -> a -> a
<> coerce :: forall a b. Coercible a b => a -> b
coerce Version
vcNew

-- | Nix expression
type NixExpr = Text

--------------------------------------------------------------------------------

data VersionSortMethod = ParseVersion | Vercmp
  deriving (Typeable, VersionSortMethod -> VersionSortMethod -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionSortMethod -> VersionSortMethod -> Bool
$c/= :: VersionSortMethod -> VersionSortMethod -> Bool
== :: VersionSortMethod -> VersionSortMethod -> Bool
$c== :: VersionSortMethod -> VersionSortMethod -> Bool
Eq, Eq VersionSortMethod
VersionSortMethod -> VersionSortMethod -> Bool
VersionSortMethod -> VersionSortMethod -> Ordering
VersionSortMethod -> VersionSortMethod -> VersionSortMethod
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VersionSortMethod -> VersionSortMethod -> VersionSortMethod
$cmin :: VersionSortMethod -> VersionSortMethod -> VersionSortMethod
max :: VersionSortMethod -> VersionSortMethod -> VersionSortMethod
$cmax :: VersionSortMethod -> VersionSortMethod -> VersionSortMethod
>= :: VersionSortMethod -> VersionSortMethod -> Bool
$c>= :: VersionSortMethod -> VersionSortMethod -> Bool
> :: VersionSortMethod -> VersionSortMethod -> Bool
$c> :: VersionSortMethod -> VersionSortMethod -> Bool
<= :: VersionSortMethod -> VersionSortMethod -> Bool
$c<= :: VersionSortMethod -> VersionSortMethod -> Bool
< :: VersionSortMethod -> VersionSortMethod -> Bool
$c< :: VersionSortMethod -> VersionSortMethod -> Bool
compare :: VersionSortMethod -> VersionSortMethod -> Ordering
$ccompare :: VersionSortMethod -> VersionSortMethod -> Ordering
Ord, Int -> VersionSortMethod
VersionSortMethod -> Int
VersionSortMethod -> [VersionSortMethod]
VersionSortMethod -> VersionSortMethod
VersionSortMethod -> VersionSortMethod -> [VersionSortMethod]
VersionSortMethod
-> VersionSortMethod -> VersionSortMethod -> [VersionSortMethod]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VersionSortMethod
-> VersionSortMethod -> VersionSortMethod -> [VersionSortMethod]
$cenumFromThenTo :: VersionSortMethod
-> VersionSortMethod -> VersionSortMethod -> [VersionSortMethod]
enumFromTo :: VersionSortMethod -> VersionSortMethod -> [VersionSortMethod]
$cenumFromTo :: VersionSortMethod -> VersionSortMethod -> [VersionSortMethod]
enumFromThen :: VersionSortMethod -> VersionSortMethod -> [VersionSortMethod]
$cenumFromThen :: VersionSortMethod -> VersionSortMethod -> [VersionSortMethod]
enumFrom :: VersionSortMethod -> [VersionSortMethod]
$cenumFrom :: VersionSortMethod -> [VersionSortMethod]
fromEnum :: VersionSortMethod -> Int
$cfromEnum :: VersionSortMethod -> Int
toEnum :: Int -> VersionSortMethod
$ctoEnum :: Int -> VersionSortMethod
pred :: VersionSortMethod -> VersionSortMethod
$cpred :: VersionSortMethod -> VersionSortMethod
succ :: VersionSortMethod -> VersionSortMethod
$csucc :: VersionSortMethod -> VersionSortMethod
Enum, forall x. Rep VersionSortMethod x -> VersionSortMethod
forall x. VersionSortMethod -> Rep VersionSortMethod x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VersionSortMethod x -> VersionSortMethod
$cfrom :: forall x. VersionSortMethod -> Rep VersionSortMethod x
Generic, Eq VersionSortMethod
Int -> VersionSortMethod -> Int
VersionSortMethod -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: VersionSortMethod -> Int
$chash :: VersionSortMethod -> Int
hashWithSalt :: Int -> VersionSortMethod -> Int
$chashWithSalt :: Int -> VersionSortMethod -> Int
Hashable, Get VersionSortMethod
[VersionSortMethod] -> Put
VersionSortMethod -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [VersionSortMethod] -> Put
$cputList :: [VersionSortMethod] -> Put
get :: Get VersionSortMethod
$cget :: Get VersionSortMethod
put :: VersionSortMethod -> Put
$cput :: VersionSortMethod -> Put
Binary, VersionSortMethod -> ()
forall a. (a -> ()) -> NFData a
rnf :: VersionSortMethod -> ()
$crnf :: VersionSortMethod -> ()
NFData)

instance Show VersionSortMethod where
  show :: VersionSortMethod -> FilePath
show = \case
    VersionSortMethod
ParseVersion -> FilePath
"parse_version"
    VersionSortMethod
Vercmp -> FilePath
"vercmp"

instance Pretty VersionSortMethod where
  pretty :: forall ann. VersionSortMethod -> Doc ann
pretty VersionSortMethod
ParseVersion = Doc ann
"ParseVersion"
  pretty VersionSortMethod
Vercmp = Doc ann
"Vercmp"

instance Default VersionSortMethod where
  def :: VersionSortMethod
def = VersionSortMethod
ParseVersion

-- | Filter-like configuration for some version sources.
-- See <https://nvchecker.readthedocs.io/en/latest/usage.html#list-options> for details.
data ListOptions = ListOptions
  { ListOptions -> Maybe Text
_includeRegex :: Maybe Text,
    ListOptions -> Maybe Text
_excludeRegex :: Maybe Text,
    ListOptions -> Maybe VersionSortMethod
_sortVersionKey :: Maybe VersionSortMethod,
    ListOptions -> Maybe Text
_ignored :: Maybe Text
  }
  deriving (Int -> ListOptions -> ShowS
[ListOptions] -> ShowS
ListOptions -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ListOptions] -> ShowS
$cshowList :: [ListOptions] -> ShowS
show :: ListOptions -> FilePath
$cshow :: ListOptions -> FilePath
showsPrec :: Int -> ListOptions -> ShowS
$cshowsPrec :: Int -> ListOptions -> ShowS
Show, Typeable, ListOptions -> ListOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListOptions -> ListOptions -> Bool
$c/= :: ListOptions -> ListOptions -> Bool
== :: ListOptions -> ListOptions -> Bool
$c== :: ListOptions -> ListOptions -> Bool
Eq, Eq ListOptions
ListOptions -> ListOptions -> Bool
ListOptions -> ListOptions -> Ordering
ListOptions -> ListOptions -> ListOptions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ListOptions -> ListOptions -> ListOptions
$cmin :: ListOptions -> ListOptions -> ListOptions
max :: ListOptions -> ListOptions -> ListOptions
$cmax :: ListOptions -> ListOptions -> ListOptions
>= :: ListOptions -> ListOptions -> Bool
$c>= :: ListOptions -> ListOptions -> Bool
> :: ListOptions -> ListOptions -> Bool
$c> :: ListOptions -> ListOptions -> Bool
<= :: ListOptions -> ListOptions -> Bool
$c<= :: ListOptions -> ListOptions -> Bool
< :: ListOptions -> ListOptions -> Bool
$c< :: ListOptions -> ListOptions -> Bool
compare :: ListOptions -> ListOptions -> Ordering
$ccompare :: ListOptions -> ListOptions -> Ordering
Ord, forall x. Rep ListOptions x -> ListOptions
forall x. ListOptions -> Rep ListOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListOptions x -> ListOptions
$cfrom :: forall x. ListOptions -> Rep ListOptions x
Generic, Eq ListOptions
Int -> ListOptions -> Int
ListOptions -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ListOptions -> Int
$chash :: ListOptions -> Int
hashWithSalt :: Int -> ListOptions -> Int
$chashWithSalt :: Int -> ListOptions -> Int
Hashable, Get ListOptions
[ListOptions] -> Put
ListOptions -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [ListOptions] -> Put
$cputList :: [ListOptions] -> Put
get :: Get ListOptions
$cget :: Get ListOptions
put :: ListOptions -> Put
$cput :: ListOptions -> Put
Binary, ListOptions -> ()
forall a. (a -> ()) -> NFData a
rnf :: ListOptions -> ()
$crnf :: ListOptions -> ()
NFData, ListOptions
forall a. a -> Default a
def :: ListOptions
$cdef :: ListOptions
Default)

isEmptyListOptions :: ListOptions -> Bool
isEmptyListOptions :: ListOptions -> Bool
isEmptyListOptions ListOptions {Maybe Text
Maybe VersionSortMethod
_ignored :: Maybe Text
_sortVersionKey :: Maybe VersionSortMethod
_excludeRegex :: Maybe Text
_includeRegex :: Maybe Text
_ignored :: ListOptions -> Maybe Text
_sortVersionKey :: ListOptions -> Maybe VersionSortMethod
_excludeRegex :: ListOptions -> Maybe Text
_includeRegex :: ListOptions -> Maybe Text
..} =
  forall a. Maybe a -> Bool
isNothing Maybe Text
_includeRegex
    Bool -> Bool -> Bool
&& forall a. Maybe a -> Bool
isNothing Maybe Text
_excludeRegex
    Bool -> Bool -> Bool
&& forall a. Maybe a -> Bool
isNothing Maybe VersionSortMethod
_sortVersionKey
    Bool -> Bool -> Bool
&& forall a. Maybe a -> Bool
isNothing Maybe Text
_includeRegex

instance Pretty ListOptions where
  pretty :: forall ann. ListOptions -> Doc ann
pretty ListOptions {Maybe Text
Maybe VersionSortMethod
_ignored :: Maybe Text
_sortVersionKey :: Maybe VersionSortMethod
_excludeRegex :: Maybe Text
_includeRegex :: Maybe Text
_ignored :: ListOptions -> Maybe Text
_sortVersionKey :: ListOptions -> Maybe VersionSortMethod
_excludeRegex :: ListOptions -> Maybe Text
_includeRegex :: ListOptions -> Maybe Text
..} =
    Doc ann
"ListOptions"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
              [ forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"includeRegex" Maybe Text
_includeRegex,
                forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"excludeRegex" Maybe Text
_excludeRegex,
                forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"sortVersionKey" Maybe VersionSortMethod
_sortVersionKey,
                forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"ignored" Maybe Text
_includeRegex
              ]
        )

-- | Configuration available for evey version sourece.
-- See <https://nvchecker.readthedocs.io/en/latest/usage.html#global-options> for details.
data NvcheckerOptions = NvcheckerOptions
  { NvcheckerOptions -> Maybe Text
_stripPrefix :: Maybe Text,
    NvcheckerOptions -> Maybe Text
_fromPattern :: Maybe Text,
    NvcheckerOptions -> Maybe Text
_toPattern :: Maybe Text
  }
  deriving (Int -> NvcheckerOptions -> ShowS
[NvcheckerOptions] -> ShowS
NvcheckerOptions -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [NvcheckerOptions] -> ShowS
$cshowList :: [NvcheckerOptions] -> ShowS
show :: NvcheckerOptions -> FilePath
$cshow :: NvcheckerOptions -> FilePath
showsPrec :: Int -> NvcheckerOptions -> ShowS
$cshowsPrec :: Int -> NvcheckerOptions -> ShowS
Show, Typeable, NvcheckerOptions -> NvcheckerOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NvcheckerOptions -> NvcheckerOptions -> Bool
$c/= :: NvcheckerOptions -> NvcheckerOptions -> Bool
== :: NvcheckerOptions -> NvcheckerOptions -> Bool
$c== :: NvcheckerOptions -> NvcheckerOptions -> Bool
Eq, Eq NvcheckerOptions
NvcheckerOptions -> NvcheckerOptions -> Bool
NvcheckerOptions -> NvcheckerOptions -> Ordering
NvcheckerOptions -> NvcheckerOptions -> NvcheckerOptions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NvcheckerOptions -> NvcheckerOptions -> NvcheckerOptions
$cmin :: NvcheckerOptions -> NvcheckerOptions -> NvcheckerOptions
max :: NvcheckerOptions -> NvcheckerOptions -> NvcheckerOptions
$cmax :: NvcheckerOptions -> NvcheckerOptions -> NvcheckerOptions
>= :: NvcheckerOptions -> NvcheckerOptions -> Bool
$c>= :: NvcheckerOptions -> NvcheckerOptions -> Bool
> :: NvcheckerOptions -> NvcheckerOptions -> Bool
$c> :: NvcheckerOptions -> NvcheckerOptions -> Bool
<= :: NvcheckerOptions -> NvcheckerOptions -> Bool
$c<= :: NvcheckerOptions -> NvcheckerOptions -> Bool
< :: NvcheckerOptions -> NvcheckerOptions -> Bool
$c< :: NvcheckerOptions -> NvcheckerOptions -> Bool
compare :: NvcheckerOptions -> NvcheckerOptions -> Ordering
$ccompare :: NvcheckerOptions -> NvcheckerOptions -> Ordering
Ord, forall x. Rep NvcheckerOptions x -> NvcheckerOptions
forall x. NvcheckerOptions -> Rep NvcheckerOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NvcheckerOptions x -> NvcheckerOptions
$cfrom :: forall x. NvcheckerOptions -> Rep NvcheckerOptions x
Generic, Eq NvcheckerOptions
Int -> NvcheckerOptions -> Int
NvcheckerOptions -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: NvcheckerOptions -> Int
$chash :: NvcheckerOptions -> Int
hashWithSalt :: Int -> NvcheckerOptions -> Int
$chashWithSalt :: Int -> NvcheckerOptions -> Int
Hashable, Get NvcheckerOptions
[NvcheckerOptions] -> Put
NvcheckerOptions -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [NvcheckerOptions] -> Put
$cputList :: [NvcheckerOptions] -> Put
get :: Get NvcheckerOptions
$cget :: Get NvcheckerOptions
put :: NvcheckerOptions -> Put
$cput :: NvcheckerOptions -> Put
Binary, NvcheckerOptions -> ()
forall a. (a -> ()) -> NFData a
rnf :: NvcheckerOptions -> ()
$crnf :: NvcheckerOptions -> ()
NFData, NvcheckerOptions
forall a. a -> Default a
def :: NvcheckerOptions
$cdef :: NvcheckerOptions
Default)

isEmptyNvcheckerOptions :: NvcheckerOptions -> Bool
isEmptyNvcheckerOptions :: NvcheckerOptions -> Bool
isEmptyNvcheckerOptions NvcheckerOptions {Maybe Text
_toPattern :: Maybe Text
_fromPattern :: Maybe Text
_stripPrefix :: Maybe Text
_toPattern :: NvcheckerOptions -> Maybe Text
_fromPattern :: NvcheckerOptions -> Maybe Text
_stripPrefix :: NvcheckerOptions -> Maybe Text
..} =
  forall a. Maybe a -> Bool
isNothing Maybe Text
_stripPrefix
    Bool -> Bool -> Bool
&& forall a. Maybe a -> Bool
isNothing Maybe Text
_fromPattern
    Bool -> Bool -> Bool
&& forall a. Maybe a -> Bool
isNothing Maybe Text
_toPattern

instance Pretty NvcheckerOptions where
  pretty :: forall ann. NvcheckerOptions -> Doc ann
pretty NvcheckerOptions {Maybe Text
_toPattern :: Maybe Text
_fromPattern :: Maybe Text
_stripPrefix :: Maybe Text
_toPattern :: NvcheckerOptions -> Maybe Text
_fromPattern :: NvcheckerOptions -> Maybe Text
_stripPrefix :: NvcheckerOptions -> Maybe Text
..} =
    Doc ann
"NvcheckerOptions"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
              [ forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"stripPrefix" Maybe Text
_stripPrefix,
                forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"fromPattern" Maybe Text
_fromPattern,
                forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"toPattern" Maybe Text
_toPattern
              ]
        )

ppField :: Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField :: forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
_ Maybe a
Nothing = []
ppField Doc ann
s (Just a
x) = [Doc ann
s forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty a
x]

-- | Upstream version source for nvchecker to check
data VersionSource
  = GitHubRelease {VersionSource -> Text
_owner :: Text, VersionSource -> Text
_repo :: Text}
  | GitHubTag {_owner :: Text, _repo :: Text, VersionSource -> ListOptions
_listOptions :: ListOptions}
  | Git {VersionSource -> Text
_vurl :: Text, VersionSource -> Branch
_vbranch :: Branch}
  | Pypi {VersionSource -> Text
_pypi :: Text}
  | ArchLinux {VersionSource -> Text
_archpkg :: Text}
  | Aur {VersionSource -> Text
_aur :: Text}
  | Manual {VersionSource -> Text
_manual :: Text}
  | Repology {VersionSource -> Text
_repology :: Text, _repo :: Text}
  | Webpage {_vurl :: Text, VersionSource -> Text
_regex :: Text, _listOptions :: ListOptions}
  | HttpHeader {_vurl :: Text, _regex :: Text, _listOptions :: ListOptions}
  | OpenVsx {VersionSource -> Text
_ovPublisher :: Text, VersionSource -> Text
_ovExtName :: Text}
  | VscodeMarketplace {VersionSource -> Text
_vsmPublisher :: Text, VersionSource -> Text
_vsmExtName :: Text}
  | Cmd {VersionSource -> Text
_vcmd :: Text}
  | Container {VersionSource -> Text
_vcontainer :: Text, _listOptions :: ListOptions}
  deriving (Int -> VersionSource -> ShowS
[VersionSource] -> ShowS
VersionSource -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [VersionSource] -> ShowS
$cshowList :: [VersionSource] -> ShowS
show :: VersionSource -> FilePath
$cshow :: VersionSource -> FilePath
showsPrec :: Int -> VersionSource -> ShowS
$cshowsPrec :: Int -> VersionSource -> ShowS
Show, Typeable, VersionSource -> VersionSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VersionSource -> VersionSource -> Bool
$c/= :: VersionSource -> VersionSource -> Bool
== :: VersionSource -> VersionSource -> Bool
$c== :: VersionSource -> VersionSource -> Bool
Eq, Eq VersionSource
VersionSource -> VersionSource -> Bool
VersionSource -> VersionSource -> Ordering
VersionSource -> VersionSource -> VersionSource
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VersionSource -> VersionSource -> VersionSource
$cmin :: VersionSource -> VersionSource -> VersionSource
max :: VersionSource -> VersionSource -> VersionSource
$cmax :: VersionSource -> VersionSource -> VersionSource
>= :: VersionSource -> VersionSource -> Bool
$c>= :: VersionSource -> VersionSource -> Bool
> :: VersionSource -> VersionSource -> Bool
$c> :: VersionSource -> VersionSource -> Bool
<= :: VersionSource -> VersionSource -> Bool
$c<= :: VersionSource -> VersionSource -> Bool
< :: VersionSource -> VersionSource -> Bool
$c< :: VersionSource -> VersionSource -> Bool
compare :: VersionSource -> VersionSource -> Ordering
$ccompare :: VersionSource -> VersionSource -> Ordering
Ord, forall x. Rep VersionSource x -> VersionSource
forall x. VersionSource -> Rep VersionSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VersionSource x -> VersionSource
$cfrom :: forall x. VersionSource -> Rep VersionSource x
Generic, Eq VersionSource
Int -> VersionSource -> Int
VersionSource -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: VersionSource -> Int
$chash :: VersionSource -> Int
hashWithSalt :: Int -> VersionSource -> Int
$chashWithSalt :: Int -> VersionSource -> Int
Hashable, Get VersionSource
[VersionSource] -> Put
VersionSource -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [VersionSource] -> Put
$cputList :: [VersionSource] -> Put
get :: Get VersionSource
$cget :: Get VersionSource
put :: VersionSource -> Put
$cput :: VersionSource -> Put
Binary, VersionSource -> ()
forall a. (a -> ()) -> NFData a
rnf :: VersionSource -> ()
$crnf :: VersionSource -> ()
NFData)

instance Pretty VersionSource where
  pretty :: forall ann. VersionSource -> Doc ann
pretty GitHubRelease {Text
_repo :: Text
_owner :: Text
_repo :: VersionSource -> Text
_owner :: VersionSource -> Text
..} =
    Doc ann
"CheckGitHubRelease"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep
            [ Doc ann
"owner" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_owner,
              Doc ann
"repo" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_repo
            ]
        )
  pretty GitHubTag {Text
ListOptions
_listOptions :: ListOptions
_repo :: Text
_owner :: Text
_listOptions :: VersionSource -> ListOptions
_repo :: VersionSource -> Text
_owner :: VersionSource -> Text
..} =
    Doc ann
"CheckGitHubTag"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            [ Doc ann
"owner" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_owner,
              Doc ann
"repo" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_repo
            ]
              forall a. Semigroup a => a -> a -> a
<> [Doc ann
"listOptions" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty ListOptions
_listOptions | Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ ListOptions -> Bool
isEmptyListOptions ListOptions
_listOptions]
        )
  pretty Git {Text
Branch
_vbranch :: Branch
_vurl :: Text
_vbranch :: VersionSource -> Branch
_vurl :: VersionSource -> Text
..} =
    Doc ann
"CheckGit"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep
            [ Doc ann
"url" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_vurl,
              Doc ann
"branch" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Branch
_vbranch
            ]
        )
  pretty Pypi {Text
_pypi :: Text
_pypi :: VersionSource -> Text
..} =
    Doc ann
"CheckPypi" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_pypi
  pretty ArchLinux {Text
_archpkg :: Text
_archpkg :: VersionSource -> Text
..} =
    Doc ann
"CheckArchLinux" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_archpkg
  pretty Aur {Text
_aur :: Text
_aur :: VersionSource -> Text
..} =
    Doc ann
"CheckAur" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_aur
  pretty Manual {Text
_manual :: Text
_manual :: VersionSource -> Text
..} =
    Doc ann
"CheckManual" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_manual
  pretty Repology {Text
_repo :: Text
_repology :: Text
_repology :: VersionSource -> Text
_repo :: VersionSource -> Text
..} =
    Doc ann
"CheckRepology"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep
            [ Doc ann
"repology" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_repology,
              Doc ann
"repo" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_repo
            ]
        )
  pretty Webpage {Text
ListOptions
_listOptions :: ListOptions
_regex :: Text
_vurl :: Text
_regex :: VersionSource -> Text
_vurl :: VersionSource -> Text
_listOptions :: VersionSource -> ListOptions
..} =
    Doc ann
"CheckWebpage"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            [ Doc ann
"url" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_vurl,
              Doc ann
"regex" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_regex
            ]
              forall a. Semigroup a => a -> a -> a
<> [Doc ann
"listOptions" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty ListOptions
_listOptions | Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ ListOptions -> Bool
isEmptyListOptions ListOptions
_listOptions]
        )
  pretty HttpHeader {Text
ListOptions
_listOptions :: ListOptions
_regex :: Text
_vurl :: Text
_regex :: VersionSource -> Text
_vurl :: VersionSource -> Text
_listOptions :: VersionSource -> ListOptions
..} =
    Doc ann
"CheckHttpHeader"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            [ Doc ann
"url" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_vurl,
              Doc ann
"regex" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_regex
            ]
              forall a. Semigroup a => a -> a -> a
<> [Doc ann
"listOptions" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty ListOptions
_listOptions | Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ ListOptions -> Bool
isEmptyListOptions ListOptions
_listOptions]
        )
  pretty OpenVsx {Text
_ovExtName :: Text
_ovPublisher :: Text
_ovExtName :: VersionSource -> Text
_ovPublisher :: VersionSource -> Text
..} =
    Doc ann
"CheckOpenVsx"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep
            [ Doc ann
"publisher" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_ovPublisher,
              Doc ann
"extName" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_ovExtName
            ]
        )
  pretty VscodeMarketplace {Text
_vsmExtName :: Text
_vsmPublisher :: Text
_vsmExtName :: VersionSource -> Text
_vsmPublisher :: VersionSource -> Text
..} =
    Doc ann
"CheckVscodeMarketplace"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep
            [ Doc ann
"publisher" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_vsmPublisher,
              Doc ann
"extName" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_vsmExtName
            ]
        )
  pretty Cmd {Text
_vcmd :: Text
_vcmd :: VersionSource -> Text
..} =
    Doc ann
"CheckCmd" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_vcmd
  pretty Container {Text
ListOptions
_listOptions :: ListOptions
_vcontainer :: Text
_vcontainer :: VersionSource -> Text
_listOptions :: VersionSource -> ListOptions
..} =
    Doc ann
"CheckContainer" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_vcontainer

-- | The input of nvchecker
data CheckVersion = CheckVersion VersionSource NvcheckerOptions
  deriving (Int -> CheckVersion -> ShowS
[CheckVersion] -> ShowS
CheckVersion -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [CheckVersion] -> ShowS
$cshowList :: [CheckVersion] -> ShowS
show :: CheckVersion -> FilePath
$cshow :: CheckVersion -> FilePath
showsPrec :: Int -> CheckVersion -> ShowS
$cshowsPrec :: Int -> CheckVersion -> ShowS
Show, Typeable, CheckVersion -> CheckVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckVersion -> CheckVersion -> Bool
$c/= :: CheckVersion -> CheckVersion -> Bool
== :: CheckVersion -> CheckVersion -> Bool
$c== :: CheckVersion -> CheckVersion -> Bool
Eq, Eq CheckVersion
CheckVersion -> CheckVersion -> Bool
CheckVersion -> CheckVersion -> Ordering
CheckVersion -> CheckVersion -> CheckVersion
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CheckVersion -> CheckVersion -> CheckVersion
$cmin :: CheckVersion -> CheckVersion -> CheckVersion
max :: CheckVersion -> CheckVersion -> CheckVersion
$cmax :: CheckVersion -> CheckVersion -> CheckVersion
>= :: CheckVersion -> CheckVersion -> Bool
$c>= :: CheckVersion -> CheckVersion -> Bool
> :: CheckVersion -> CheckVersion -> Bool
$c> :: CheckVersion -> CheckVersion -> Bool
<= :: CheckVersion -> CheckVersion -> Bool
$c<= :: CheckVersion -> CheckVersion -> Bool
< :: CheckVersion -> CheckVersion -> Bool
$c< :: CheckVersion -> CheckVersion -> Bool
compare :: CheckVersion -> CheckVersion -> Ordering
$ccompare :: CheckVersion -> CheckVersion -> Ordering
Ord, forall x. Rep CheckVersion x -> CheckVersion
forall x. CheckVersion -> Rep CheckVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckVersion x -> CheckVersion
$cfrom :: forall x. CheckVersion -> Rep CheckVersion x
Generic, Eq CheckVersion
Int -> CheckVersion -> Int
CheckVersion -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: CheckVersion -> Int
$chash :: CheckVersion -> Int
hashWithSalt :: Int -> CheckVersion -> Int
$chashWithSalt :: Int -> CheckVersion -> Int
Hashable, Get CheckVersion
[CheckVersion] -> Put
CheckVersion -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [CheckVersion] -> Put
$cputList :: [CheckVersion] -> Put
get :: Get CheckVersion
$cget :: Get CheckVersion
put :: CheckVersion -> Put
$cput :: CheckVersion -> Put
Binary, CheckVersion -> ()
forall a. (a -> ()) -> NFData a
rnf :: CheckVersion -> ()
$crnf :: CheckVersion -> ()
NFData)

instance Pretty CheckVersion where
  pretty :: forall ann. CheckVersion -> Doc ann
pretty (CheckVersion VersionSource
v NvcheckerOptions
n) = forall ann. Doc ann -> Doc ann
align (forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$ [forall a ann. Pretty a => a -> Doc ann
pretty VersionSource
v] forall a. Semigroup a => a -> a -> a
<> [forall a ann. Pretty a => a -> Doc ann
pretty NvcheckerOptions
n | Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ NvcheckerOptions -> Bool
isEmptyNvcheckerOptions NvcheckerOptions
n])

-- | The result of nvchecker rule
data NvcheckerResult = NvcheckerResult
  { NvcheckerResult -> Version
nvNow :: Version,
    -- | last result of this nvchecker rule
    -- TODO: consider removing this field
    NvcheckerResult -> Maybe Version
nvOld :: Maybe Version,
    -- | stale means even 'nvNow' comes from json file (last run)
    -- and we actually didn't run nvchecker this time. 'nvOld' will be 'Nothing' in this case.
    NvcheckerResult -> Bool
nvStale :: Bool
  }
  deriving (Int -> NvcheckerResult -> ShowS
[NvcheckerResult] -> ShowS
NvcheckerResult -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [NvcheckerResult] -> ShowS
$cshowList :: [NvcheckerResult] -> ShowS
show :: NvcheckerResult -> FilePath
$cshow :: NvcheckerResult -> FilePath
showsPrec :: Int -> NvcheckerResult -> ShowS
$cshowsPrec :: Int -> NvcheckerResult -> ShowS
Show, Typeable, NvcheckerResult -> NvcheckerResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NvcheckerResult -> NvcheckerResult -> Bool
$c/= :: NvcheckerResult -> NvcheckerResult -> Bool
== :: NvcheckerResult -> NvcheckerResult -> Bool
$c== :: NvcheckerResult -> NvcheckerResult -> Bool
Eq, forall x. Rep NvcheckerResult x -> NvcheckerResult
forall x. NvcheckerResult -> Rep NvcheckerResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NvcheckerResult x -> NvcheckerResult
$cfrom :: forall x. NvcheckerResult -> Rep NvcheckerResult x
Generic, Eq NvcheckerResult
Int -> NvcheckerResult -> Int
NvcheckerResult -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: NvcheckerResult -> Int
$chash :: NvcheckerResult -> Int
hashWithSalt :: Int -> NvcheckerResult -> Int
$chashWithSalt :: Int -> NvcheckerResult -> Int
Hashable, Get NvcheckerResult
[NvcheckerResult] -> Put
NvcheckerResult -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [NvcheckerResult] -> Put
$cputList :: [NvcheckerResult] -> Put
get :: Get NvcheckerResult
$cget :: Get NvcheckerResult
put :: NvcheckerResult -> Put
$cput :: NvcheckerResult -> Put
Binary, NvcheckerResult -> ()
forall a. (a -> ()) -> NFData a
rnf :: NvcheckerResult -> ()
$crnf :: NvcheckerResult -> ()
NFData)

-- | Parsed JSON output from nvchecker
data NvcheckerRaw = NvcheckerSuccess Version | NvcheckerError Text
  deriving (Int -> NvcheckerRaw -> ShowS
[NvcheckerRaw] -> ShowS
NvcheckerRaw -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [NvcheckerRaw] -> ShowS
$cshowList :: [NvcheckerRaw] -> ShowS
show :: NvcheckerRaw -> FilePath
$cshow :: NvcheckerRaw -> FilePath
showsPrec :: Int -> NvcheckerRaw -> ShowS
$cshowsPrec :: Int -> NvcheckerRaw -> ShowS
Show, Typeable, NvcheckerRaw -> NvcheckerRaw -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NvcheckerRaw -> NvcheckerRaw -> Bool
$c/= :: NvcheckerRaw -> NvcheckerRaw -> Bool
== :: NvcheckerRaw -> NvcheckerRaw -> Bool
$c== :: NvcheckerRaw -> NvcheckerRaw -> Bool
Eq, forall x. Rep NvcheckerRaw x -> NvcheckerRaw
forall x. NvcheckerRaw -> Rep NvcheckerRaw x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NvcheckerRaw x -> NvcheckerRaw
$cfrom :: forall x. NvcheckerRaw -> Rep NvcheckerRaw x
Generic)

instance A.FromJSON NvcheckerRaw where
  parseJSON :: Value -> Parser NvcheckerRaw
parseJSON = forall a. FilePath -> (Object -> Parser a) -> Value -> Parser a
A.withObject FilePath
"NvcheckerRaw" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Maybe Version
mVersion <- Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
A..:? Key
"version"
    case Maybe Version
mVersion of
      Just Version
version -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Version -> NvcheckerRaw
NvcheckerSuccess Version
version
      Maybe Version
_ -> Text -> NvcheckerRaw
NvcheckerError forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
A..: Key
"error"

type instance RuleResult CheckVersion = NvcheckerResult

--------------------------------------------------------------------------------

-- | Whether to cache the fetched sha256
--
-- @ForceFetch@ indicates @alwaysRerun@ the fetcher rule
data ForceFetch = ForceFetch | NoForceFetch
  deriving (Int -> ForceFetch -> ShowS
[ForceFetch] -> ShowS
ForceFetch -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ForceFetch] -> ShowS
$cshowList :: [ForceFetch] -> ShowS
show :: ForceFetch -> FilePath
$cshow :: ForceFetch -> FilePath
showsPrec :: Int -> ForceFetch -> ShowS
$cshowsPrec :: Int -> ForceFetch -> ShowS
Show, ForceFetch -> ForceFetch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForceFetch -> ForceFetch -> Bool
$c/= :: ForceFetch -> ForceFetch -> Bool
== :: ForceFetch -> ForceFetch -> Bool
$c== :: ForceFetch -> ForceFetch -> Bool
Eq, Eq ForceFetch
ForceFetch -> ForceFetch -> Bool
ForceFetch -> ForceFetch -> Ordering
ForceFetch -> ForceFetch -> ForceFetch
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForceFetch -> ForceFetch -> ForceFetch
$cmin :: ForceFetch -> ForceFetch -> ForceFetch
max :: ForceFetch -> ForceFetch -> ForceFetch
$cmax :: ForceFetch -> ForceFetch -> ForceFetch
>= :: ForceFetch -> ForceFetch -> Bool
$c>= :: ForceFetch -> ForceFetch -> Bool
> :: ForceFetch -> ForceFetch -> Bool
$c> :: ForceFetch -> ForceFetch -> Bool
<= :: ForceFetch -> ForceFetch -> Bool
$c<= :: ForceFetch -> ForceFetch -> Bool
< :: ForceFetch -> ForceFetch -> Bool
$c< :: ForceFetch -> ForceFetch -> Bool
compare :: ForceFetch -> ForceFetch -> Ordering
$ccompare :: ForceFetch -> ForceFetch -> Ordering
Ord, Eq ForceFetch
Int -> ForceFetch -> Int
ForceFetch -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ForceFetch -> Int
$chash :: ForceFetch -> Int
hashWithSalt :: Int -> ForceFetch -> Int
$chashWithSalt :: Int -> ForceFetch -> Int
Hashable, ForceFetch -> ()
forall a. (a -> ()) -> NFData a
rnf :: ForceFetch -> ()
$crnf :: ForceFetch -> ()
NFData, Get ForceFetch
[ForceFetch] -> Put
ForceFetch -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [ForceFetch] -> Put
$cputList :: [ForceFetch] -> Put
get :: Get ForceFetch
$cget :: Get ForceFetch
put :: ForceFetch -> Put
$cput :: ForceFetch -> Put
Binary, Typeable, forall x. Rep ForceFetch x -> ForceFetch
forall x. ForceFetch -> Rep ForceFetch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForceFetch x -> ForceFetch
$cfrom :: forall x. ForceFetch -> Rep ForceFetch x
Generic)

instance Pretty ForceFetch where
  pretty :: forall ann. ForceFetch -> Doc ann
pretty ForceFetch
ForceFetch = Doc ann
"ForceFetch"
  pretty ForceFetch
NoForceFetch = Doc ann
"NoForceFetch"

instance Default ForceFetch where
  def :: ForceFetch
def = ForceFetch
NoForceFetch

-- | The input of prefetch rule
data RunFetch = RunFetch ForceFetch (NixFetcher Fresh)
  deriving (Int -> RunFetch -> ShowS
[RunFetch] -> ShowS
RunFetch -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [RunFetch] -> ShowS
$cshowList :: [RunFetch] -> ShowS
show :: RunFetch -> FilePath
$cshow :: RunFetch -> FilePath
showsPrec :: Int -> RunFetch -> ShowS
$cshowsPrec :: Int -> RunFetch -> ShowS
Show, RunFetch -> RunFetch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RunFetch -> RunFetch -> Bool
$c/= :: RunFetch -> RunFetch -> Bool
== :: RunFetch -> RunFetch -> Bool
$c== :: RunFetch -> RunFetch -> Bool
Eq, Eq RunFetch
RunFetch -> RunFetch -> Bool
RunFetch -> RunFetch -> Ordering
RunFetch -> RunFetch -> RunFetch
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RunFetch -> RunFetch -> RunFetch
$cmin :: RunFetch -> RunFetch -> RunFetch
max :: RunFetch -> RunFetch -> RunFetch
$cmax :: RunFetch -> RunFetch -> RunFetch
>= :: RunFetch -> RunFetch -> Bool
$c>= :: RunFetch -> RunFetch -> Bool
> :: RunFetch -> RunFetch -> Bool
$c> :: RunFetch -> RunFetch -> Bool
<= :: RunFetch -> RunFetch -> Bool
$c<= :: RunFetch -> RunFetch -> Bool
< :: RunFetch -> RunFetch -> Bool
$c< :: RunFetch -> RunFetch -> Bool
compare :: RunFetch -> RunFetch -> Ordering
$ccompare :: RunFetch -> RunFetch -> Ordering
Ord, Eq RunFetch
Int -> RunFetch -> Int
RunFetch -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: RunFetch -> Int
$chash :: RunFetch -> Int
hashWithSalt :: Int -> RunFetch -> Int
$chashWithSalt :: Int -> RunFetch -> Int
Hashable, RunFetch -> ()
forall a. (a -> ()) -> NFData a
rnf :: RunFetch -> ()
$crnf :: RunFetch -> ()
NFData, Get RunFetch
[RunFetch] -> Put
RunFetch -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [RunFetch] -> Put
$cputList :: [RunFetch] -> Put
get :: Get RunFetch
$cget :: Get RunFetch
put :: RunFetch -> Put
$cput :: RunFetch -> Put
Binary, Typeable, forall x. Rep RunFetch x -> RunFetch
forall x. RunFetch -> Rep RunFetch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RunFetch x -> RunFetch
$cfrom :: forall x. RunFetch -> Rep RunFetch x
Generic)

type instance RuleResult RunFetch = NixFetcher Fetched

-- | If the package is prefetched, then we can obtain the SHA256
data NixFetcher (k :: FetchStatus)
  = FetchGit
      { forall (k :: FetchStatus). NixFetcher k -> Text
_furl :: Text,
        forall (k :: FetchStatus). NixFetcher k -> Version
_rev :: Version,
        forall (k :: FetchStatus). NixFetcher k -> Bool
_deepClone :: Bool,
        forall (k :: FetchStatus). NixFetcher k -> Bool
_fetchSubmodules :: Bool,
        forall (k :: FetchStatus). NixFetcher k -> Bool
_leaveDotGit :: Bool,
        forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_name :: Maybe Text,
        forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_sha256 :: FetchResult Checksum k
      }
  | FetchGitHub
      { forall (k :: FetchStatus). NixFetcher k -> Text
_fowner :: Text,
        forall (k :: FetchStatus). NixFetcher k -> Text
_frepo :: Text,
        _rev :: Version,
        _deepClone :: Bool,
        _fetchSubmodules :: Bool,
        _leaveDotGit :: Bool,
        _name :: Maybe Text,
        _sha256 :: FetchResult Checksum k
      }
  | FetchUrl
      { _furl :: Text,
        _name :: Maybe Text,
        _sha256 :: FetchResult Checksum k
      }
  | FetchTarball
      { _furl :: Text,
        _sha256 :: FetchResult Checksum k
      }
  | FetchDocker
      { forall (k :: FetchStatus). NixFetcher k -> Text
_imageName :: Text,
        forall (k :: FetchStatus). NixFetcher k -> Text
_imageTag :: Text,
        forall (k :: FetchStatus).
NixFetcher k -> FetchResult ContainerDigest k
_imageDigest :: FetchResult ContainerDigest k,
        _sha256 :: FetchResult Checksum k,
        forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_fos :: Maybe Text,
        forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_farch :: Maybe Text,
        forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_finalImageName :: Maybe Text,
        forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_finalImageTag :: Maybe Text,
        forall (k :: FetchStatus). NixFetcher k -> Maybe Bool
_tlsVerify :: Maybe Bool
      }
  deriving (Typeable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (k :: FetchStatus) x. Rep (NixFetcher k) x -> NixFetcher k
forall (k :: FetchStatus) x. NixFetcher k -> Rep (NixFetcher k) x
$cto :: forall (k :: FetchStatus) x. Rep (NixFetcher k) x -> NixFetcher k
$cfrom :: forall (k :: FetchStatus) x. NixFetcher k -> Rep (NixFetcher k) x
Generic)

class (c (FetchResult Checksum k), c (FetchResult ContainerDigest k)) => ForFetchResult c k

instance (c (FetchResult Checksum k), c (FetchResult ContainerDigest k)) => ForFetchResult c k

deriving instance Show `ForFetchResult` k => Show (NixFetcher k)

deriving instance Eq `ForFetchResult` k => Eq (NixFetcher k)

deriving instance Ord `ForFetchResult` k => Ord (NixFetcher k)

deriving instance Hashable `ForFetchResult` k => Hashable (NixFetcher k)

deriving instance Binary `ForFetchResult` k => Binary (NixFetcher k)

deriving instance NFData `ForFetchResult` k => NFData (NixFetcher k)

-- | Fetch status
data FetchStatus = Fresh | Fetched

-- | Prefetched fetchers hold hashes
type family FetchResult a (k :: FetchStatus) where
  FetchResult _ Fresh = ()
  FetchResult a Fetched = a

instance A.ToJSON (NixFetcher Fetched) where
  toJSON :: NixFetcher 'Fetched -> Value
toJSON FetchGit {Bool
Maybe Text
Text
FetchResult Checksum 'Fetched
Version
_sha256 :: FetchResult Checksum 'Fetched
_name :: Maybe Text
_leaveDotGit :: Bool
_fetchSubmodules :: Bool
_deepClone :: Bool
_rev :: Version
_furl :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_leaveDotGit :: forall (k :: FetchStatus). NixFetcher k -> Bool
_fetchSubmodules :: forall (k :: FetchStatus). NixFetcher k -> Bool
_deepClone :: forall (k :: FetchStatus). NixFetcher k -> Bool
_rev :: forall (k :: FetchStatus). NixFetcher k -> Version
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
..} =
    [Pair] -> Value
A.object
      [ Key
"url" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text
_furl,
        Key
"rev" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Version
_rev,
        Key
"deepClone" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Bool
_deepClone,
        Key
"fetchSubmodules" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Bool
_fetchSubmodules,
        Key
"leaveDotGit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Bool
_leaveDotGit,
        Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Text
_name,
        Key
"sha256" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= FetchResult Checksum 'Fetched
_sha256,
        Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text -> Value
A.String Text
"git"
      ]
  toJSON FetchGitHub {Bool
Maybe Text
Text
FetchResult Checksum 'Fetched
Version
_sha256 :: FetchResult Checksum 'Fetched
_name :: Maybe Text
_leaveDotGit :: Bool
_fetchSubmodules :: Bool
_deepClone :: Bool
_rev :: Version
_frepo :: Text
_fowner :: Text
_frepo :: forall (k :: FetchStatus). NixFetcher k -> Text
_fowner :: forall (k :: FetchStatus). NixFetcher k -> Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_leaveDotGit :: forall (k :: FetchStatus). NixFetcher k -> Bool
_fetchSubmodules :: forall (k :: FetchStatus). NixFetcher k -> Bool
_deepClone :: forall (k :: FetchStatus). NixFetcher k -> Bool
_rev :: forall (k :: FetchStatus). NixFetcher k -> Version
..} =
    [Pair] -> Value
A.object
      [ Key
"owner" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text
_fowner,
        Key
"repo" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text
_frepo,
        Key
"rev" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Version
_rev,
        Key
"deepClone" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Bool
_deepClone,
        Key
"fetchSubmodules" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Bool
_fetchSubmodules,
        Key
"leaveDotGit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Bool
_leaveDotGit,
        Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Text
_name,
        Key
"sha256" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= FetchResult Checksum 'Fetched
_sha256,
        Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text -> Value
A.String Text
"github"
      ]
  toJSON FetchUrl {Maybe Text
Text
FetchResult Checksum 'Fetched
_sha256 :: FetchResult Checksum 'Fetched
_name :: Maybe Text
_furl :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
..} =
    [Pair] -> Value
A.object
      [ Key
"url" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text
_furl,
        Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Text
_name,
        Key
"sha256" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= FetchResult Checksum 'Fetched
_sha256,
        Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text -> Value
A.String Text
"url"
      ]
  toJSON FetchTarball {Text
FetchResult Checksum 'Fetched
_sha256 :: FetchResult Checksum 'Fetched
_furl :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
..} =
    [Pair] -> Value
A.object
      [ Key
"url" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text
_furl,
        Key
"sha256" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= FetchResult Checksum 'Fetched
_sha256,
        Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text -> Value
A.String Text
"tarball"
      ]
  toJSON FetchDocker {Maybe Bool
Maybe Text
Text
FetchResult ContainerDigest 'Fetched
FetchResult Checksum 'Fetched
_tlsVerify :: Maybe Bool
_finalImageTag :: Maybe Text
_finalImageName :: Maybe Text
_farch :: Maybe Text
_fos :: Maybe Text
_sha256 :: FetchResult Checksum 'Fetched
_imageDigest :: FetchResult ContainerDigest 'Fetched
_imageTag :: Text
_imageName :: Text
_tlsVerify :: forall (k :: FetchStatus). NixFetcher k -> Maybe Bool
_finalImageTag :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_finalImageName :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_farch :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_fos :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_imageDigest :: forall (k :: FetchStatus).
NixFetcher k -> FetchResult ContainerDigest k
_imageTag :: forall (k :: FetchStatus). NixFetcher k -> Text
_imageName :: forall (k :: FetchStatus). NixFetcher k -> Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
..} =
    [Pair] -> Value
A.object
      [ Key
"imageName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text
_imageName,
        Key
"imageTag" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text
_imageTag,
        Key
"imageDigest" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= FetchResult ContainerDigest 'Fetched
_imageDigest,
        Key
"sha256" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= FetchResult Checksum 'Fetched
_sha256,
        Key
"os" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Text
_fos,
        Key
"arch" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Text
_farch,
        Key
"finalImageName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Text
_finalImageName,
        Key
"finalImageTag" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Text
_finalImageTag,
        Key
"tlsVerify" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Bool
_tlsVerify
      ]

instance Pretty (NixFetcher k) where
  pretty :: forall ann. NixFetcher k -> Doc ann
pretty FetchGit {Bool
Maybe Text
Text
FetchResult Checksum k
Version
_sha256 :: FetchResult Checksum k
_name :: Maybe Text
_leaveDotGit :: Bool
_fetchSubmodules :: Bool
_deepClone :: Bool
_rev :: Version
_furl :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_leaveDotGit :: forall (k :: FetchStatus). NixFetcher k -> Bool
_fetchSubmodules :: forall (k :: FetchStatus). NixFetcher k -> Bool
_deepClone :: forall (k :: FetchStatus). NixFetcher k -> Bool
_rev :: forall (k :: FetchStatus). NixFetcher k -> Version
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
..} =
    Doc ann
"FetchGit"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            [ Doc ann
"url" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_furl,
              Doc ann
"rev" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Version
_rev,
              Doc ann
"deepClone" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Bool
_deepClone,
              Doc ann
"fetchSubmodules" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Bool
_fetchSubmodules,
              Doc ann
"leaveDotGit" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Bool
_leaveDotGit
            ]
              forall a. Semigroup a => a -> a -> a
<> forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"name" Maybe Text
_name
        )
  pretty FetchGitHub {Bool
Maybe Text
Text
FetchResult Checksum k
Version
_sha256 :: FetchResult Checksum k
_name :: Maybe Text
_leaveDotGit :: Bool
_fetchSubmodules :: Bool
_deepClone :: Bool
_rev :: Version
_frepo :: Text
_fowner :: Text
_frepo :: forall (k :: FetchStatus). NixFetcher k -> Text
_fowner :: forall (k :: FetchStatus). NixFetcher k -> Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_leaveDotGit :: forall (k :: FetchStatus). NixFetcher k -> Bool
_fetchSubmodules :: forall (k :: FetchStatus). NixFetcher k -> Bool
_deepClone :: forall (k :: FetchStatus). NixFetcher k -> Bool
_rev :: forall (k :: FetchStatus). NixFetcher k -> Version
..} =
    Doc ann
"FetchGitHub"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            [ Doc ann
"owner" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_fowner,
              Doc ann
"repo" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_frepo,
              Doc ann
"rev" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Version
_rev,
              Doc ann
"deepClone" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Bool
_deepClone,
              Doc ann
"fetchSubmodules" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Bool
_fetchSubmodules,
              Doc ann
"leaveDotGit" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Bool
_leaveDotGit
            ]
              forall a. Semigroup a => a -> a -> a
<> forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"name" Maybe Text
_name
        )
  pretty FetchUrl {Maybe Text
Text
FetchResult Checksum k
_sha256 :: FetchResult Checksum k
_name :: Maybe Text
_furl :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_name :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
..} =
    Doc ann
"FetchUrl"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            [Doc ann
"url" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_furl]
              forall a. Semigroup a => a -> a -> a
<> forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"name" Maybe Text
_name
        )
  pretty FetchTarball {Text
FetchResult Checksum k
_sha256 :: FetchResult Checksum k
_furl :: Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
_furl :: forall (k :: FetchStatus). NixFetcher k -> Text
..} =
    Doc ann
"FetchTarball" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_furl
  pretty FetchDocker {Maybe Bool
Maybe Text
Text
FetchResult ContainerDigest k
FetchResult Checksum k
_tlsVerify :: Maybe Bool
_finalImageTag :: Maybe Text
_finalImageName :: Maybe Text
_farch :: Maybe Text
_fos :: Maybe Text
_sha256 :: FetchResult Checksum k
_imageDigest :: FetchResult ContainerDigest k
_imageTag :: Text
_imageName :: Text
_tlsVerify :: forall (k :: FetchStatus). NixFetcher k -> Maybe Bool
_finalImageTag :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_finalImageName :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_farch :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_fos :: forall (k :: FetchStatus). NixFetcher k -> Maybe Text
_imageDigest :: forall (k :: FetchStatus).
NixFetcher k -> FetchResult ContainerDigest k
_imageTag :: forall (k :: FetchStatus). NixFetcher k -> Text
_imageName :: forall (k :: FetchStatus). NixFetcher k -> Text
_sha256 :: forall (k :: FetchStatus). NixFetcher k -> FetchResult Checksum k
..} =
    Doc ann
"FetchDocker"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep forall a b. (a -> b) -> a -> b
$
            [ Doc ann
"imageName" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_imageName,
              Doc ann
"imageTag" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Maybe Text
_finalImageTag
            ]
              forall a. Semigroup a => a -> a -> a
<> forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"os" Maybe Text
_fos
              forall a. Semigroup a => a -> a -> a
<> forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"arch" Maybe Text
_farch
              forall a. Semigroup a => a -> a -> a
<> forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"finalImageName" Maybe Text
_finalImageName
              forall a. Semigroup a => a -> a -> a
<> forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"finalImageTag" Maybe Text
_finalImageTag
              forall a. Semigroup a => a -> a -> a
<> forall a ann. Pretty a => Doc ann -> Maybe a -> [Doc ann]
ppField Doc ann
"tlsVerify" Maybe Bool
_tlsVerify
        )

--------------------------------------------------------------------------------

-- | Extract file contents from package source
-- e.g. @Cargo.lock@
data ExtractSrcQ = ExtractSrcQ (NixFetcher Fetched) (NE.NonEmpty FilePath)
  deriving (Int -> ExtractSrcQ -> ShowS
[ExtractSrcQ] -> ShowS
ExtractSrcQ -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ExtractSrcQ] -> ShowS
$cshowList :: [ExtractSrcQ] -> ShowS
show :: ExtractSrcQ -> FilePath
$cshow :: ExtractSrcQ -> FilePath
showsPrec :: Int -> ExtractSrcQ -> ShowS
$cshowsPrec :: Int -> ExtractSrcQ -> ShowS
Show, ExtractSrcQ -> ExtractSrcQ -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExtractSrcQ -> ExtractSrcQ -> Bool
$c/= :: ExtractSrcQ -> ExtractSrcQ -> Bool
== :: ExtractSrcQ -> ExtractSrcQ -> Bool
$c== :: ExtractSrcQ -> ExtractSrcQ -> Bool
Eq, Eq ExtractSrcQ
ExtractSrcQ -> ExtractSrcQ -> Bool
ExtractSrcQ -> ExtractSrcQ -> Ordering
ExtractSrcQ -> ExtractSrcQ -> ExtractSrcQ
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExtractSrcQ -> ExtractSrcQ -> ExtractSrcQ
$cmin :: ExtractSrcQ -> ExtractSrcQ -> ExtractSrcQ
max :: ExtractSrcQ -> ExtractSrcQ -> ExtractSrcQ
$cmax :: ExtractSrcQ -> ExtractSrcQ -> ExtractSrcQ
>= :: ExtractSrcQ -> ExtractSrcQ -> Bool
$c>= :: ExtractSrcQ -> ExtractSrcQ -> Bool
> :: ExtractSrcQ -> ExtractSrcQ -> Bool
$c> :: ExtractSrcQ -> ExtractSrcQ -> Bool
<= :: ExtractSrcQ -> ExtractSrcQ -> Bool
$c<= :: ExtractSrcQ -> ExtractSrcQ -> Bool
< :: ExtractSrcQ -> ExtractSrcQ -> Bool
$c< :: ExtractSrcQ -> ExtractSrcQ -> Bool
compare :: ExtractSrcQ -> ExtractSrcQ -> Ordering
$ccompare :: ExtractSrcQ -> ExtractSrcQ -> Ordering
Ord, Eq ExtractSrcQ
Int -> ExtractSrcQ -> Int
ExtractSrcQ -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ExtractSrcQ -> Int
$chash :: ExtractSrcQ -> Int
hashWithSalt :: Int -> ExtractSrcQ -> Int
$chashWithSalt :: Int -> ExtractSrcQ -> Int
Hashable, ExtractSrcQ -> ()
forall a. (a -> ()) -> NFData a
rnf :: ExtractSrcQ -> ()
$crnf :: ExtractSrcQ -> ()
NFData, Get ExtractSrcQ
[ExtractSrcQ] -> Put
ExtractSrcQ -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [ExtractSrcQ] -> Put
$cputList :: [ExtractSrcQ] -> Put
get :: Get ExtractSrcQ
$cget :: Get ExtractSrcQ
put :: ExtractSrcQ -> Put
$cput :: ExtractSrcQ -> Put
Binary, Typeable, forall x. Rep ExtractSrcQ x -> ExtractSrcQ
forall x. ExtractSrcQ -> Rep ExtractSrcQ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExtractSrcQ x -> ExtractSrcQ
$cfrom :: forall x. ExtractSrcQ -> Rep ExtractSrcQ x
Generic)

type instance RuleResult ExtractSrcQ = HashMap FilePath Text

instance Pretty ExtractSrcQ where
  pretty :: forall ann. ExtractSrcQ -> Doc ann
pretty (ExtractSrcQ NixFetcher 'Fetched
f NonEmpty FilePath
n) =
    Doc ann
"ExtractSrc"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep
            [ Doc ann
"fetcher" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty NixFetcher 'Fetched
f,
              Doc ann
"files" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty NonEmpty FilePath
n
            ]
        )

--------------------------------------------------------------------------------

-- | 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@.
data FetchRustGitDepsQ = FetchRustGitDepsQ (NixFetcher Fetched) FilePath
  deriving (Int -> FetchRustGitDepsQ -> ShowS
[FetchRustGitDepsQ] -> ShowS
FetchRustGitDepsQ -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [FetchRustGitDepsQ] -> ShowS
$cshowList :: [FetchRustGitDepsQ] -> ShowS
show :: FetchRustGitDepsQ -> FilePath
$cshow :: FetchRustGitDepsQ -> FilePath
showsPrec :: Int -> FetchRustGitDepsQ -> ShowS
$cshowsPrec :: Int -> FetchRustGitDepsQ -> ShowS
Show, FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
$c/= :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
== :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
$c== :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
Eq, Eq FetchRustGitDepsQ
FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
FetchRustGitDepsQ -> FetchRustGitDepsQ -> Ordering
FetchRustGitDepsQ -> FetchRustGitDepsQ -> FetchRustGitDepsQ
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> FetchRustGitDepsQ
$cmin :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> FetchRustGitDepsQ
max :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> FetchRustGitDepsQ
$cmax :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> FetchRustGitDepsQ
>= :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
$c>= :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
> :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
$c> :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
<= :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
$c<= :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
< :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
$c< :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Bool
compare :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Ordering
$ccompare :: FetchRustGitDepsQ -> FetchRustGitDepsQ -> Ordering
Ord, Eq FetchRustGitDepsQ
Int -> FetchRustGitDepsQ -> Int
FetchRustGitDepsQ -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: FetchRustGitDepsQ -> Int
$chash :: FetchRustGitDepsQ -> Int
hashWithSalt :: Int -> FetchRustGitDepsQ -> Int
$chashWithSalt :: Int -> FetchRustGitDepsQ -> Int
Hashable, FetchRustGitDepsQ -> ()
forall a. (a -> ()) -> NFData a
rnf :: FetchRustGitDepsQ -> ()
$crnf :: FetchRustGitDepsQ -> ()
NFData, Get FetchRustGitDepsQ
[FetchRustGitDepsQ] -> Put
FetchRustGitDepsQ -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [FetchRustGitDepsQ] -> Put
$cputList :: [FetchRustGitDepsQ] -> Put
get :: Get FetchRustGitDepsQ
$cget :: Get FetchRustGitDepsQ
put :: FetchRustGitDepsQ -> Put
$cput :: FetchRustGitDepsQ -> Put
Binary, Typeable, forall x. Rep FetchRustGitDepsQ x -> FetchRustGitDepsQ
forall x. FetchRustGitDepsQ -> Rep FetchRustGitDepsQ x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FetchRustGitDepsQ x -> FetchRustGitDepsQ
$cfrom :: forall x. FetchRustGitDepsQ -> Rep FetchRustGitDepsQ x
Generic)

-- | @outputHashes@, a mapping from nameVer -> output hash
type instance RuleResult FetchRustGitDepsQ = HashMap Text Checksum

instance Pretty FetchRustGitDepsQ where
  pretty :: forall ann. FetchRustGitDepsQ -> Doc ann
pretty (FetchRustGitDepsQ NixFetcher 'Fetched
f FilePath
n) =
    Doc ann
"FetchRustGitDeps"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep
            [ Doc ann
"fetcher" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty NixFetcher 'Fetched
f,
              Doc ann
"cargoLock" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty FilePath
n
            ]
        )

--------------------------------------------------------------------------------

-- | @strftime@ format
--
-- Nothing defaults to @%Y-%m-%d@
newtype DateFormat = DateFormat (Maybe Text)
  deriving newtype (Int -> DateFormat -> ShowS
[DateFormat] -> ShowS
DateFormat -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DateFormat] -> ShowS
$cshowList :: [DateFormat] -> ShowS
show :: DateFormat -> FilePath
$cshow :: DateFormat -> FilePath
showsPrec :: Int -> DateFormat -> ShowS
$cshowsPrec :: Int -> DateFormat -> ShowS
Show, DateFormat -> DateFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateFormat -> DateFormat -> Bool
$c/= :: DateFormat -> DateFormat -> Bool
== :: DateFormat -> DateFormat -> Bool
$c== :: DateFormat -> DateFormat -> Bool
Eq, Eq DateFormat
DateFormat -> DateFormat -> Bool
DateFormat -> DateFormat -> Ordering
DateFormat -> DateFormat -> DateFormat
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DateFormat -> DateFormat -> DateFormat
$cmin :: DateFormat -> DateFormat -> DateFormat
max :: DateFormat -> DateFormat -> DateFormat
$cmax :: DateFormat -> DateFormat -> DateFormat
>= :: DateFormat -> DateFormat -> Bool
$c>= :: DateFormat -> DateFormat -> Bool
> :: DateFormat -> DateFormat -> Bool
$c> :: DateFormat -> DateFormat -> Bool
<= :: DateFormat -> DateFormat -> Bool
$c<= :: DateFormat -> DateFormat -> Bool
< :: DateFormat -> DateFormat -> Bool
$c< :: DateFormat -> DateFormat -> Bool
compare :: DateFormat -> DateFormat -> Ordering
$ccompare :: DateFormat -> DateFormat -> Ordering
Ord, DateFormat
forall a. a -> Default a
def :: DateFormat
$cdef :: DateFormat
Default, forall ann. [DateFormat] -> Doc ann
forall ann. DateFormat -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [DateFormat] -> Doc ann
$cprettyList :: forall ann. [DateFormat] -> Doc ann
pretty :: forall ann. DateFormat -> Doc ann
$cpretty :: forall ann. DateFormat -> Doc ann
Pretty)
  deriving stock (Typeable, forall x. Rep DateFormat x -> DateFormat
forall x. DateFormat -> Rep DateFormat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DateFormat x -> DateFormat
$cfrom :: forall x. DateFormat -> Rep DateFormat x
Generic)
  deriving anyclass (Eq DateFormat
Int -> DateFormat -> Int
DateFormat -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: DateFormat -> Int
$chash :: DateFormat -> Int
hashWithSalt :: Int -> DateFormat -> Int
$chashWithSalt :: Int -> DateFormat -> Int
Hashable, Get DateFormat
[DateFormat] -> Put
DateFormat -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [DateFormat] -> Put
$cputList :: [DateFormat] -> Put
get :: Get DateFormat
$cget :: Get DateFormat
put :: DateFormat -> Put
$cput :: DateFormat -> Put
Binary, DateFormat -> ()
forall a. (a -> ()) -> NFData a
rnf :: DateFormat -> ()
$crnf :: DateFormat -> ()
NFData)

-- | Get the commit date by using shallow clone
--
-- @_gformat@ is in.
-- Note: Requires git >= 2.5
data GetGitCommitDate = GetGitCommitDate {GetGitCommitDate -> Text
_gurl :: Text, GetGitCommitDate -> Text
_grev :: Text, GetGitCommitDate -> DateFormat
_gformat :: DateFormat}
  deriving (Int -> GetGitCommitDate -> ShowS
[GetGitCommitDate] -> ShowS
GetGitCommitDate -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [GetGitCommitDate] -> ShowS
$cshowList :: [GetGitCommitDate] -> ShowS
show :: GetGitCommitDate -> FilePath
$cshow :: GetGitCommitDate -> FilePath
showsPrec :: Int -> GetGitCommitDate -> ShowS
$cshowsPrec :: Int -> GetGitCommitDate -> ShowS
Show, GetGitCommitDate -> GetGitCommitDate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGitCommitDate -> GetGitCommitDate -> Bool
$c/= :: GetGitCommitDate -> GetGitCommitDate -> Bool
== :: GetGitCommitDate -> GetGitCommitDate -> Bool
$c== :: GetGitCommitDate -> GetGitCommitDate -> Bool
Eq, Eq GetGitCommitDate
GetGitCommitDate -> GetGitCommitDate -> Bool
GetGitCommitDate -> GetGitCommitDate -> Ordering
GetGitCommitDate -> GetGitCommitDate -> GetGitCommitDate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GetGitCommitDate -> GetGitCommitDate -> GetGitCommitDate
$cmin :: GetGitCommitDate -> GetGitCommitDate -> GetGitCommitDate
max :: GetGitCommitDate -> GetGitCommitDate -> GetGitCommitDate
$cmax :: GetGitCommitDate -> GetGitCommitDate -> GetGitCommitDate
>= :: GetGitCommitDate -> GetGitCommitDate -> Bool
$c>= :: GetGitCommitDate -> GetGitCommitDate -> Bool
> :: GetGitCommitDate -> GetGitCommitDate -> Bool
$c> :: GetGitCommitDate -> GetGitCommitDate -> Bool
<= :: GetGitCommitDate -> GetGitCommitDate -> Bool
$c<= :: GetGitCommitDate -> GetGitCommitDate -> Bool
< :: GetGitCommitDate -> GetGitCommitDate -> Bool
$c< :: GetGitCommitDate -> GetGitCommitDate -> Bool
compare :: GetGitCommitDate -> GetGitCommitDate -> Ordering
$ccompare :: GetGitCommitDate -> GetGitCommitDate -> Ordering
Ord, Eq GetGitCommitDate
Int -> GetGitCommitDate -> Int
GetGitCommitDate -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: GetGitCommitDate -> Int
$chash :: GetGitCommitDate -> Int
hashWithSalt :: Int -> GetGitCommitDate -> Int
$chashWithSalt :: Int -> GetGitCommitDate -> Int
Hashable, GetGitCommitDate -> ()
forall a. (a -> ()) -> NFData a
rnf :: GetGitCommitDate -> ()
$crnf :: GetGitCommitDate -> ()
NFData, Get GetGitCommitDate
[GetGitCommitDate] -> Put
GetGitCommitDate -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [GetGitCommitDate] -> Put
$cputList :: [GetGitCommitDate] -> Put
get :: Get GetGitCommitDate
$cget :: Get GetGitCommitDate
put :: GetGitCommitDate -> Put
$cput :: GetGitCommitDate -> Put
Binary, Typeable, forall x. Rep GetGitCommitDate x -> GetGitCommitDate
forall x. GetGitCommitDate -> Rep GetGitCommitDate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGitCommitDate x -> GetGitCommitDate
$cfrom :: forall x. GetGitCommitDate -> Rep GetGitCommitDate x
Generic)

type instance RuleResult GetGitCommitDate = Text

instance Pretty GetGitCommitDate where
  pretty :: forall ann. GetGitCommitDate -> Doc ann
pretty GetGitCommitDate {Text
DateFormat
_gformat :: DateFormat
_grev :: Text
_gurl :: Text
_gformat :: GetGitCommitDate -> DateFormat
_grev :: GetGitCommitDate -> Text
_gurl :: GetGitCommitDate -> Text
..} =
    Doc ann
"GetGitCommitDate"
      forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
line
      forall a. Semigroup a => a -> a -> a
<> forall ann. Int -> Doc ann -> Doc ann
indent
        Int
2
        ( forall ann. [Doc ann] -> Doc ann
vsep
            [ Doc ann
"url" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_gurl,
              Doc ann
"rev" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Text
_grev,
              Doc ann
"format" forall a. Semigroup a => a -> a -> a
<> forall ann. Doc ann
colon forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty DateFormat
_gformat
            ]
        )

--------------------------------------------------------------------------------

-- | Package name, used in generating nix expr
type PackageName = Text

-- | How to create package source fetcher given a version
type PackageFetcher = Version -> NixFetcher Fresh

newtype PackageExtractSrc = PackageExtractSrc (NE.NonEmpty FilePath)

newtype PackageCargoLockFiles = PackageCargoLockFiles (NE.NonEmpty FilePath)

newtype PackagePassthru = PackagePassthru (HashMap Text Text)
  deriving newtype (NonEmpty PackagePassthru -> PackagePassthru
PackagePassthru -> PackagePassthru -> PackagePassthru
forall b. Integral b => b -> PackagePassthru -> PackagePassthru
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> PackagePassthru -> PackagePassthru
$cstimes :: forall b. Integral b => b -> PackagePassthru -> PackagePassthru
sconcat :: NonEmpty PackagePassthru -> PackagePassthru
$csconcat :: NonEmpty PackagePassthru -> PackagePassthru
<> :: PackagePassthru -> PackagePassthru -> PackagePassthru
$c<> :: PackagePassthru -> PackagePassthru -> PackagePassthru
Semigroup, Semigroup PackagePassthru
PackagePassthru
[PackagePassthru] -> PackagePassthru
PackagePassthru -> PackagePassthru -> PackagePassthru
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [PackagePassthru] -> PackagePassthru
$cmconcat :: [PackagePassthru] -> PackagePassthru
mappend :: PackagePassthru -> PackagePassthru -> PackagePassthru
$cmappend :: PackagePassthru -> PackagePassthru -> PackagePassthru
mempty :: PackagePassthru
$cmempty :: PackagePassthru
Monoid)

-- | 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.
data UseStaleVersion
  = -- | Specified in configuration file
    PermanentStale
  | -- | Specified by @--filter@ command
    TemporaryStale
  | NoStale
  deriving stock (UseStaleVersion -> UseStaleVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UseStaleVersion -> UseStaleVersion -> Bool
$c/= :: UseStaleVersion -> UseStaleVersion -> Bool
== :: UseStaleVersion -> UseStaleVersion -> Bool
$c== :: UseStaleVersion -> UseStaleVersion -> Bool
Eq, Int -> UseStaleVersion -> ShowS
[UseStaleVersion] -> ShowS
UseStaleVersion -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [UseStaleVersion] -> ShowS
$cshowList :: [UseStaleVersion] -> ShowS
show :: UseStaleVersion -> FilePath
$cshow :: UseStaleVersion -> FilePath
showsPrec :: Int -> UseStaleVersion -> ShowS
$cshowsPrec :: Int -> UseStaleVersion -> ShowS
Show, Eq UseStaleVersion
UseStaleVersion -> UseStaleVersion -> Bool
UseStaleVersion -> UseStaleVersion -> Ordering
UseStaleVersion -> UseStaleVersion -> UseStaleVersion
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UseStaleVersion -> UseStaleVersion -> UseStaleVersion
$cmin :: UseStaleVersion -> UseStaleVersion -> UseStaleVersion
max :: UseStaleVersion -> UseStaleVersion -> UseStaleVersion
$cmax :: UseStaleVersion -> UseStaleVersion -> UseStaleVersion
>= :: UseStaleVersion -> UseStaleVersion -> Bool
$c>= :: UseStaleVersion -> UseStaleVersion -> Bool
> :: UseStaleVersion -> UseStaleVersion -> Bool
$c> :: UseStaleVersion -> UseStaleVersion -> Bool
<= :: UseStaleVersion -> UseStaleVersion -> Bool
$c<= :: UseStaleVersion -> UseStaleVersion -> Bool
< :: UseStaleVersion -> UseStaleVersion -> Bool
$c< :: UseStaleVersion -> UseStaleVersion -> Bool
compare :: UseStaleVersion -> UseStaleVersion -> Ordering
$ccompare :: UseStaleVersion -> UseStaleVersion -> Ordering
Ord, Typeable, forall x. Rep UseStaleVersion x -> UseStaleVersion
forall x. UseStaleVersion -> Rep UseStaleVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UseStaleVersion x -> UseStaleVersion
$cfrom :: forall x. UseStaleVersion -> Rep UseStaleVersion x
Generic)
  deriving anyclass (Eq UseStaleVersion
Int -> UseStaleVersion -> Int
UseStaleVersion -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: UseStaleVersion -> Int
$chash :: UseStaleVersion -> Int
hashWithSalt :: Int -> UseStaleVersion -> Int
$chashWithSalt :: Int -> UseStaleVersion -> Int
Hashable, Get UseStaleVersion
[UseStaleVersion] -> Put
UseStaleVersion -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [UseStaleVersion] -> Put
$cputList :: [UseStaleVersion] -> Put
get :: Get UseStaleVersion
$cget :: Get UseStaleVersion
put :: UseStaleVersion -> Put
$cput :: UseStaleVersion -> Put
Binary, UseStaleVersion -> ()
forall a. (a -> ()) -> NFData a
rnf :: UseStaleVersion -> ()
$crnf :: UseStaleVersion -> ()
NFData)

-- | A package is defined with:
--
-- 1. its name
-- 2. how to track its version
-- 3. how to fetch it as we have the version
-- 4. optional file paths to extract (dump to build dir)
-- 5. optional @Cargo.lock@ path (if it's a rust package)
-- 6. an optional pass through map
-- 7. if the package version was pinned
-- 8. optional git date format (if the version source is git)
-- 9. whether to always fetch a package regardless of the version changing
-- /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./
data Package = Package
  { Package -> Text
_pname :: PackageName,
    Package -> CheckVersion
_pversion :: CheckVersion,
    Package -> PackageFetcher
_pfetcher :: PackageFetcher,
    Package -> Maybe PackageExtractSrc
_pextract :: Maybe PackageExtractSrc,
    Package -> Maybe PackageCargoLockFiles
_pcargo :: Maybe PackageCargoLockFiles,
    Package -> PackagePassthru
_ppassthru :: PackagePassthru,
    Package -> UseStaleVersion
_ppinned :: UseStaleVersion,
    Package -> DateFormat
_pgitdateformat :: DateFormat,
    Package -> ForceFetch
_pforcefetch :: ForceFetch
  }

-- | Package key is the name of a package.
-- We use this type to index packages.
newtype PackageKey = PackageKey PackageName
  deriving newtype (PackageKey -> PackageKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageKey -> PackageKey -> Bool
$c/= :: PackageKey -> PackageKey -> Bool
== :: PackageKey -> PackageKey -> Bool
$c== :: PackageKey -> PackageKey -> Bool
Eq, Int -> PackageKey -> ShowS
[PackageKey] -> ShowS
PackageKey -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PackageKey] -> ShowS
$cshowList :: [PackageKey] -> ShowS
show :: PackageKey -> FilePath
$cshow :: PackageKey -> FilePath
showsPrec :: Int -> PackageKey -> ShowS
$cshowsPrec :: Int -> PackageKey -> ShowS
Show, Eq PackageKey
PackageKey -> PackageKey -> Bool
PackageKey -> PackageKey -> Ordering
PackageKey -> PackageKey -> PackageKey
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PackageKey -> PackageKey -> PackageKey
$cmin :: PackageKey -> PackageKey -> PackageKey
max :: PackageKey -> PackageKey -> PackageKey
$cmax :: PackageKey -> PackageKey -> PackageKey
>= :: PackageKey -> PackageKey -> Bool
$c>= :: PackageKey -> PackageKey -> Bool
> :: PackageKey -> PackageKey -> Bool
$c> :: PackageKey -> PackageKey -> Bool
<= :: PackageKey -> PackageKey -> Bool
$c<= :: PackageKey -> PackageKey -> Bool
< :: PackageKey -> PackageKey -> Bool
$c< :: PackageKey -> PackageKey -> Bool
compare :: PackageKey -> PackageKey -> Ordering
$ccompare :: PackageKey -> PackageKey -> Ordering
Ord, forall ann. [PackageKey] -> Doc ann
forall ann. PackageKey -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
prettyList :: forall ann. [PackageKey] -> Doc ann
$cprettyList :: forall ann. [PackageKey] -> Doc ann
pretty :: forall ann. PackageKey -> Doc ann
$cpretty :: forall ann. PackageKey -> Doc ann
Pretty)
  deriving stock (Typeable, forall x. Rep PackageKey x -> PackageKey
forall x. PackageKey -> Rep PackageKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PackageKey x -> PackageKey
$cfrom :: forall x. PackageKey -> Rep PackageKey x
Generic)
  deriving anyclass (Eq PackageKey
Int -> PackageKey -> Int
PackageKey -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PackageKey -> Int
$chash :: PackageKey -> Int
hashWithSalt :: Int -> PackageKey -> Int
$chashWithSalt :: Int -> PackageKey -> Int
Hashable, Get PackageKey
[PackageKey] -> Put
PackageKey -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [PackageKey] -> Put
$cputList :: [PackageKey] -> Put
get :: Get PackageKey
$cget :: Get PackageKey
put :: PackageKey -> Put
$cput :: PackageKey -> Put
Binary, PackageKey -> ()
forall a. (a -> ()) -> NFData a
rnf :: PackageKey -> ()
$crnf :: PackageKey -> ()
NFData)

--------------------------------------------------------------------------------

-- | The key type of nvfetcher rule. See "NvFetcher.Core"
data Core = Core
  deriving (Core -> Core -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Core -> Core -> Bool
$c/= :: Core -> Core -> Bool
== :: Core -> Core -> Bool
$c== :: Core -> Core -> Bool
Eq, Int -> Core -> ShowS
[Core] -> ShowS
Core -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Core] -> ShowS
$cshowList :: [Core] -> ShowS
show :: Core -> FilePath
$cshow :: Core -> FilePath
showsPrec :: Int -> Core -> ShowS
$cshowsPrec :: Int -> Core -> ShowS
Show, Eq Core
Core -> Core -> Bool
Core -> Core -> Ordering
Core -> Core -> Core
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Core -> Core -> Core
$cmin :: Core -> Core -> Core
max :: Core -> Core -> Core
$cmax :: Core -> Core -> Core
>= :: Core -> Core -> Bool
$c>= :: Core -> Core -> Bool
> :: Core -> Core -> Bool
$c> :: Core -> Core -> Bool
<= :: Core -> Core -> Bool
$c<= :: Core -> Core -> Bool
< :: Core -> Core -> Bool
$c< :: Core -> Core -> Bool
compare :: Core -> Core -> Ordering
$ccompare :: Core -> Core -> Ordering
Ord, Typeable, forall x. Rep Core x -> Core
forall x. Core -> Rep Core x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Core x -> Core
$cfrom :: forall x. Core -> Rep Core x
Generic, Eq Core
Int -> Core -> Int
Core -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Core -> Int
$chash :: Core -> Int
hashWithSalt :: Int -> Core -> Int
$chashWithSalt :: Int -> Core -> Int
Hashable, Get Core
[Core] -> Put
Core -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Core] -> Put
$cputList :: [Core] -> Put
get :: Get Core
$cget :: Get Core
put :: Core -> Put
$cput :: Core -> Put
Binary, Core -> ()
forall a. (a -> ()) -> NFData a
rnf :: Core -> ()
$crnf :: Core -> ()
NFData)

type instance RuleResult Core = PackageResult

-- | Decorate a rule's key with 'PackageKey'
newtype WithPackageKey k = WithPackageKey (k, PackageKey)
  deriving newtype (WithPackageKey k -> WithPackageKey k -> Bool
forall k. Eq k => WithPackageKey k -> WithPackageKey k -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WithPackageKey k -> WithPackageKey k -> Bool
$c/= :: forall k. Eq k => WithPackageKey k -> WithPackageKey k -> Bool
== :: WithPackageKey k -> WithPackageKey k -> Bool
$c== :: forall k. Eq k => WithPackageKey k -> WithPackageKey k -> Bool
Eq, Int -> WithPackageKey k -> Int
WithPackageKey k -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {k}. Hashable k => Eq (WithPackageKey k)
forall k. Hashable k => Int -> WithPackageKey k -> Int
forall k. Hashable k => WithPackageKey k -> Int
hash :: WithPackageKey k -> Int
$chash :: forall k. Hashable k => WithPackageKey k -> Int
hashWithSalt :: Int -> WithPackageKey k -> Int
$chashWithSalt :: forall k. Hashable k => Int -> WithPackageKey k -> Int
Hashable, Get (WithPackageKey k)
[WithPackageKey k] -> Put
WithPackageKey k -> Put
forall k. Binary k => Get (WithPackageKey k)
forall k. Binary k => [WithPackageKey k] -> Put
forall k. Binary k => WithPackageKey k -> Put
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [WithPackageKey k] -> Put
$cputList :: forall k. Binary k => [WithPackageKey k] -> Put
get :: Get (WithPackageKey k)
$cget :: forall k. Binary k => Get (WithPackageKey k)
put :: WithPackageKey k -> Put
$cput :: forall k. Binary k => WithPackageKey k -> Put
Binary, WithPackageKey k -> ()
forall k. NFData k => WithPackageKey k -> ()
forall a. (a -> ()) -> NFData a
rnf :: WithPackageKey k -> ()
$crnf :: forall k. NFData k => WithPackageKey k -> ()
NFData)

instance Show k => Show (WithPackageKey k) where
  show :: WithPackageKey k -> FilePath
show (WithPackageKey (k
k, PackageKey
n)) = forall a. Show a => a -> FilePath
show k
k forall a. Semigroup a => a -> a -> a
<> FilePath
" (" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> FilePath
show PackageKey
n forall a. Semigroup a => a -> a -> a
<> FilePath
")"

type instance RuleResult (WithPackageKey k) = RuleResult k

-- | Result type of 'Core'
data PackageResult = PackageResult
  { PackageResult -> Text
_prname :: PackageName,
    PackageResult -> NvcheckerResult
_prversion :: NvcheckerResult,
    PackageResult -> NixFetcher 'Fetched
_prfetched :: NixFetcher 'Fetched,
    PackageResult -> Maybe (HashMap Text Text)
_prpassthru :: Maybe (HashMap Text Text),
    -- | extracted file name -> file path in build dir
    PackageResult -> Maybe (HashMap FilePath Text)
_prextract :: Maybe (HashMap FilePath NixExpr),
    -- | cargo lock file path in build dir -> (file path in nix, git dependencies)
    PackageResult
-> Maybe (HashMap FilePath (Text, HashMap Text Checksum))
_prcargolock :: Maybe (HashMap FilePath (NixExpr, HashMap Text Checksum)),
    PackageResult -> UseStaleVersion
_prpinned :: UseStaleVersion,
    PackageResult -> Maybe Text
_prgitdate :: Maybe Text
  }
  deriving (Int -> PackageResult -> ShowS
[PackageResult] -> ShowS
PackageResult -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [PackageResult] -> ShowS
$cshowList :: [PackageResult] -> ShowS
show :: PackageResult -> FilePath
$cshow :: PackageResult -> FilePath
showsPrec :: Int -> PackageResult -> ShowS
$cshowsPrec :: Int -> PackageResult -> ShowS
Show, Typeable, forall x. Rep PackageResult x -> PackageResult
forall x. PackageResult -> Rep PackageResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PackageResult x -> PackageResult
$cfrom :: forall x. PackageResult -> Rep PackageResult x
Generic, PackageResult -> ()
forall a. (a -> ()) -> NFData a
rnf :: PackageResult -> ()
$crnf :: PackageResult -> ()
NFData)

instance A.ToJSON PackageResult where
  toJSON :: PackageResult -> Value
toJSON PackageResult {Maybe Text
Maybe (HashMap FilePath (Text, HashMap Text Checksum))
Maybe (HashMap FilePath Text)
Maybe (HashMap Text Text)
Text
UseStaleVersion
NixFetcher 'Fetched
NvcheckerResult
_prgitdate :: Maybe Text
_prpinned :: UseStaleVersion
_prcargolock :: Maybe (HashMap FilePath (Text, HashMap Text Checksum))
_prextract :: Maybe (HashMap FilePath Text)
_prpassthru :: Maybe (HashMap Text Text)
_prfetched :: NixFetcher 'Fetched
_prversion :: NvcheckerResult
_prname :: Text
_prgitdate :: PackageResult -> Maybe Text
_prpinned :: PackageResult -> UseStaleVersion
_prcargolock :: PackageResult
-> Maybe (HashMap FilePath (Text, HashMap Text Checksum))
_prextract :: PackageResult -> Maybe (HashMap FilePath Text)
_prpassthru :: PackageResult -> Maybe (HashMap Text Text)
_prfetched :: PackageResult -> NixFetcher 'Fetched
_prversion :: PackageResult -> NvcheckerResult
_prname :: PackageResult -> Text
..} =
    [Pair] -> Value
A.object
      [ Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Text
_prname,
        Key
"version" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= NvcheckerResult -> Version
nvNow NvcheckerResult
_prversion,
        Key
"src" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= NixFetcher 'Fetched
_prfetched,
        Key
"extract" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe (HashMap FilePath Text)
_prextract,
        Key
"passthru" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe (HashMap Text Text)
_prpassthru,
        Key
"cargoLocks" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe (HashMap FilePath (Text, HashMap Text Checksum))
_prcargolock,
        Key
"pinned" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= case UseStaleVersion
_prpinned of
          UseStaleVersion
PermanentStale -> Bool
True
          UseStaleVersion
_ -> Bool
False,
        Key
"date" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
A..= Maybe Text
_prgitdate
      ]