{-# LANGUAGE StrictData #-}
-- |
-- Module    : Nix.JenkinsPlugins2Nix.Types
-- Copyright : (c) 2017 Mateusz Kowalczyk
-- License   : BSD3
--
-- Types used through-out jenkinsPlugins2nix
module Nix.JenkinsPlugins2Nix.Types
  ( Config(..)
  , Manifest(..)
  , Plugin(..)
  , PluginDependency(..)
  , PluginResolution(..)
  , RequestedPlugin(..)
  , ResolutionStrategy(..)
  ) where

import qualified Crypto.Hash as Hash
import           Data.Set (Set)
import           Data.Text (Text)

-- | The way in which version of dependencies will be picked.
data ResolutionStrategy =
  -- | Pick the version of the dependency that the package tells us
  -- about in its manifest file. If none, latest version available is
  -- used.
  AsGiven
  -- | Always pick latest version of the dependency we're told about.
  | Latest
  deriving (Int -> ResolutionStrategy -> ShowS
[ResolutionStrategy] -> ShowS
ResolutionStrategy -> String
(Int -> ResolutionStrategy -> ShowS)
-> (ResolutionStrategy -> String)
-> ([ResolutionStrategy] -> ShowS)
-> Show ResolutionStrategy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolutionStrategy] -> ShowS
$cshowList :: [ResolutionStrategy] -> ShowS
show :: ResolutionStrategy -> String
$cshow :: ResolutionStrategy -> String
showsPrec :: Int -> ResolutionStrategy -> ShowS
$cshowsPrec :: Int -> ResolutionStrategy -> ShowS
Show, ResolutionStrategy -> ResolutionStrategy -> Bool
(ResolutionStrategy -> ResolutionStrategy -> Bool)
-> (ResolutionStrategy -> ResolutionStrategy -> Bool)
-> Eq ResolutionStrategy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResolutionStrategy -> ResolutionStrategy -> Bool
$c/= :: ResolutionStrategy -> ResolutionStrategy -> Bool
== :: ResolutionStrategy -> ResolutionStrategy -> Bool
$c== :: ResolutionStrategy -> ResolutionStrategy -> Bool
Eq, Eq ResolutionStrategy
Eq ResolutionStrategy
-> (ResolutionStrategy -> ResolutionStrategy -> Ordering)
-> (ResolutionStrategy -> ResolutionStrategy -> Bool)
-> (ResolutionStrategy -> ResolutionStrategy -> Bool)
-> (ResolutionStrategy -> ResolutionStrategy -> Bool)
-> (ResolutionStrategy -> ResolutionStrategy -> Bool)
-> (ResolutionStrategy -> ResolutionStrategy -> ResolutionStrategy)
-> (ResolutionStrategy -> ResolutionStrategy -> ResolutionStrategy)
-> Ord ResolutionStrategy
ResolutionStrategy -> ResolutionStrategy -> Bool
ResolutionStrategy -> ResolutionStrategy -> Ordering
ResolutionStrategy -> ResolutionStrategy -> ResolutionStrategy
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 :: ResolutionStrategy -> ResolutionStrategy -> ResolutionStrategy
$cmin :: ResolutionStrategy -> ResolutionStrategy -> ResolutionStrategy
max :: ResolutionStrategy -> ResolutionStrategy -> ResolutionStrategy
$cmax :: ResolutionStrategy -> ResolutionStrategy -> ResolutionStrategy
>= :: ResolutionStrategy -> ResolutionStrategy -> Bool
$c>= :: ResolutionStrategy -> ResolutionStrategy -> Bool
> :: ResolutionStrategy -> ResolutionStrategy -> Bool
$c> :: ResolutionStrategy -> ResolutionStrategy -> Bool
<= :: ResolutionStrategy -> ResolutionStrategy -> Bool
$c<= :: ResolutionStrategy -> ResolutionStrategy -> Bool
< :: ResolutionStrategy -> ResolutionStrategy -> Bool
$c< :: ResolutionStrategy -> ResolutionStrategy -> Bool
compare :: ResolutionStrategy -> ResolutionStrategy -> Ordering
$ccompare :: ResolutionStrategy -> ResolutionStrategy -> Ordering
$cp1Ord :: Eq ResolutionStrategy
Ord)

-- | Program configuration
data Config = Config
  { -- | Dependency resolution strategy
    Config -> ResolutionStrategy
resolution_strategy :: !ResolutionStrategy
    -- | User-required plugins.
  , Config -> [RequestedPlugin]
requested_plugins :: ![RequestedPlugin]
  } deriving (Int -> Config -> ShowS
[Config] -> ShowS
Config -> String
(Int -> Config -> ShowS)
-> (Config -> String) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Config] -> ShowS
$cshowList :: [Config] -> ShowS
show :: Config -> String
$cshow :: Config -> String
showsPrec :: Int -> Config -> ShowS
$cshowsPrec :: Int -> Config -> ShowS
Show, Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c== :: Config -> Config -> Bool
Eq, Eq Config
Eq Config
-> (Config -> Config -> Ordering)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Bool)
-> (Config -> Config -> Config)
-> (Config -> Config -> Config)
-> Ord Config
Config -> Config -> Bool
Config -> Config -> Ordering
Config -> Config -> Config
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 :: Config -> Config -> Config
$cmin :: Config -> Config -> Config
max :: Config -> Config -> Config
$cmax :: Config -> Config -> Config
>= :: Config -> Config -> Bool
$c>= :: Config -> Config -> Bool
> :: Config -> Config -> Bool
$c> :: Config -> Config -> Bool
<= :: Config -> Config -> Bool
$c<= :: Config -> Config -> Bool
< :: Config -> Config -> Bool
$c< :: Config -> Config -> Bool
compare :: Config -> Config -> Ordering
$ccompare :: Config -> Config -> Ordering
$cp1Ord :: Eq Config
Ord)

-- | Plugin that user requested on the command line.
data RequestedPlugin = RequestedPlugin
  { -- | Name of the plugin.
    RequestedPlugin -> Text
requested_name :: !Text
    -- | Possibly a specified version. If version not present, latest
    -- version is downloaded then pinned.
  , RequestedPlugin -> Maybe Text
requested_version :: !(Maybe Text)
  } deriving (Int -> RequestedPlugin -> ShowS
[RequestedPlugin] -> ShowS
RequestedPlugin -> String
(Int -> RequestedPlugin -> ShowS)
-> (RequestedPlugin -> String)
-> ([RequestedPlugin] -> ShowS)
-> Show RequestedPlugin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestedPlugin] -> ShowS
$cshowList :: [RequestedPlugin] -> ShowS
show :: RequestedPlugin -> String
$cshow :: RequestedPlugin -> String
showsPrec :: Int -> RequestedPlugin -> ShowS
$cshowsPrec :: Int -> RequestedPlugin -> ShowS
Show, RequestedPlugin -> RequestedPlugin -> Bool
(RequestedPlugin -> RequestedPlugin -> Bool)
-> (RequestedPlugin -> RequestedPlugin -> Bool)
-> Eq RequestedPlugin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestedPlugin -> RequestedPlugin -> Bool
$c/= :: RequestedPlugin -> RequestedPlugin -> Bool
== :: RequestedPlugin -> RequestedPlugin -> Bool
$c== :: RequestedPlugin -> RequestedPlugin -> Bool
Eq, Eq RequestedPlugin
Eq RequestedPlugin
-> (RequestedPlugin -> RequestedPlugin -> Ordering)
-> (RequestedPlugin -> RequestedPlugin -> Bool)
-> (RequestedPlugin -> RequestedPlugin -> Bool)
-> (RequestedPlugin -> RequestedPlugin -> Bool)
-> (RequestedPlugin -> RequestedPlugin -> Bool)
-> (RequestedPlugin -> RequestedPlugin -> RequestedPlugin)
-> (RequestedPlugin -> RequestedPlugin -> RequestedPlugin)
-> Ord RequestedPlugin
RequestedPlugin -> RequestedPlugin -> Bool
RequestedPlugin -> RequestedPlugin -> Ordering
RequestedPlugin -> RequestedPlugin -> RequestedPlugin
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 :: RequestedPlugin -> RequestedPlugin -> RequestedPlugin
$cmin :: RequestedPlugin -> RequestedPlugin -> RequestedPlugin
max :: RequestedPlugin -> RequestedPlugin -> RequestedPlugin
$cmax :: RequestedPlugin -> RequestedPlugin -> RequestedPlugin
>= :: RequestedPlugin -> RequestedPlugin -> Bool
$c>= :: RequestedPlugin -> RequestedPlugin -> Bool
> :: RequestedPlugin -> RequestedPlugin -> Bool
$c> :: RequestedPlugin -> RequestedPlugin -> Bool
<= :: RequestedPlugin -> RequestedPlugin -> Bool
$c<= :: RequestedPlugin -> RequestedPlugin -> Bool
< :: RequestedPlugin -> RequestedPlugin -> Bool
$c< :: RequestedPlugin -> RequestedPlugin -> Bool
compare :: RequestedPlugin -> RequestedPlugin -> Ordering
$ccompare :: RequestedPlugin -> RequestedPlugin -> Ordering
$cp1Ord :: Eq RequestedPlugin
Ord)

-- | Plugin resolution. Determines optional plugins.
data PluginResolution = Mandatory | Optional
  deriving (Int -> PluginResolution -> ShowS
[PluginResolution] -> ShowS
PluginResolution -> String
(Int -> PluginResolution -> ShowS)
-> (PluginResolution -> String)
-> ([PluginResolution] -> ShowS)
-> Show PluginResolution
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PluginResolution] -> ShowS
$cshowList :: [PluginResolution] -> ShowS
show :: PluginResolution -> String
$cshow :: PluginResolution -> String
showsPrec :: Int -> PluginResolution -> ShowS
$cshowsPrec :: Int -> PluginResolution -> ShowS
Show, PluginResolution -> PluginResolution -> Bool
(PluginResolution -> PluginResolution -> Bool)
-> (PluginResolution -> PluginResolution -> Bool)
-> Eq PluginResolution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PluginResolution -> PluginResolution -> Bool
$c/= :: PluginResolution -> PluginResolution -> Bool
== :: PluginResolution -> PluginResolution -> Bool
$c== :: PluginResolution -> PluginResolution -> Bool
Eq, Eq PluginResolution
Eq PluginResolution
-> (PluginResolution -> PluginResolution -> Ordering)
-> (PluginResolution -> PluginResolution -> Bool)
-> (PluginResolution -> PluginResolution -> Bool)
-> (PluginResolution -> PluginResolution -> Bool)
-> (PluginResolution -> PluginResolution -> Bool)
-> (PluginResolution -> PluginResolution -> PluginResolution)
-> (PluginResolution -> PluginResolution -> PluginResolution)
-> Ord PluginResolution
PluginResolution -> PluginResolution -> Bool
PluginResolution -> PluginResolution -> Ordering
PluginResolution -> PluginResolution -> PluginResolution
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 :: PluginResolution -> PluginResolution -> PluginResolution
$cmin :: PluginResolution -> PluginResolution -> PluginResolution
max :: PluginResolution -> PluginResolution -> PluginResolution
$cmax :: PluginResolution -> PluginResolution -> PluginResolution
>= :: PluginResolution -> PluginResolution -> Bool
$c>= :: PluginResolution -> PluginResolution -> Bool
> :: PluginResolution -> PluginResolution -> Bool
$c> :: PluginResolution -> PluginResolution -> Bool
<= :: PluginResolution -> PluginResolution -> Bool
$c<= :: PluginResolution -> PluginResolution -> Bool
< :: PluginResolution -> PluginResolution -> Bool
$c< :: PluginResolution -> PluginResolution -> Bool
compare :: PluginResolution -> PluginResolution -> Ordering
$ccompare :: PluginResolution -> PluginResolution -> Ordering
$cp1Ord :: Eq PluginResolution
Ord)

-- | A dependency on another plugin.
data PluginDependency = PluginDependency
  { -- | Is the dependency optional?
    PluginDependency -> PluginResolution
plugin_dependency_resolution :: !PluginResolution
    -- | Name of the dependency.
  , PluginDependency -> Text
plugin_dependency_name :: !Text
    -- | Version of the dependency.
  , PluginDependency -> Text
plugin_dependency_version :: !Text
  } deriving (Int -> PluginDependency -> ShowS
[PluginDependency] -> ShowS
PluginDependency -> String
(Int -> PluginDependency -> ShowS)
-> (PluginDependency -> String)
-> ([PluginDependency] -> ShowS)
-> Show PluginDependency
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PluginDependency] -> ShowS
$cshowList :: [PluginDependency] -> ShowS
show :: PluginDependency -> String
$cshow :: PluginDependency -> String
showsPrec :: Int -> PluginDependency -> ShowS
$cshowsPrec :: Int -> PluginDependency -> ShowS
Show, PluginDependency -> PluginDependency -> Bool
(PluginDependency -> PluginDependency -> Bool)
-> (PluginDependency -> PluginDependency -> Bool)
-> Eq PluginDependency
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PluginDependency -> PluginDependency -> Bool
$c/= :: PluginDependency -> PluginDependency -> Bool
== :: PluginDependency -> PluginDependency -> Bool
$c== :: PluginDependency -> PluginDependency -> Bool
Eq, Eq PluginDependency
Eq PluginDependency
-> (PluginDependency -> PluginDependency -> Ordering)
-> (PluginDependency -> PluginDependency -> Bool)
-> (PluginDependency -> PluginDependency -> Bool)
-> (PluginDependency -> PluginDependency -> Bool)
-> (PluginDependency -> PluginDependency -> Bool)
-> (PluginDependency -> PluginDependency -> PluginDependency)
-> (PluginDependency -> PluginDependency -> PluginDependency)
-> Ord PluginDependency
PluginDependency -> PluginDependency -> Bool
PluginDependency -> PluginDependency -> Ordering
PluginDependency -> PluginDependency -> PluginDependency
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 :: PluginDependency -> PluginDependency -> PluginDependency
$cmin :: PluginDependency -> PluginDependency -> PluginDependency
max :: PluginDependency -> PluginDependency -> PluginDependency
$cmax :: PluginDependency -> PluginDependency -> PluginDependency
>= :: PluginDependency -> PluginDependency -> Bool
$c>= :: PluginDependency -> PluginDependency -> Bool
> :: PluginDependency -> PluginDependency -> Bool
$c> :: PluginDependency -> PluginDependency -> Bool
<= :: PluginDependency -> PluginDependency -> Bool
$c<= :: PluginDependency -> PluginDependency -> Bool
< :: PluginDependency -> PluginDependency -> Bool
$c< :: PluginDependency -> PluginDependency -> Bool
compare :: PluginDependency -> PluginDependency -> Ordering
$ccompare :: PluginDependency -> PluginDependency -> Ordering
$cp1Ord :: Eq PluginDependency
Ord)

-- | All the information we need about the plugin to generate a nix
-- expression.
data Plugin = Plugin
  { -- | Download location of the plugin.
    Plugin -> Text
download_url :: !Text
    -- | Checksum.
  , Plugin -> Digest SHA256
sha256 :: !(Hash.Digest Hash.SHA256)
    -- | Manifest information of the plugin.
  , Plugin -> Manifest
manifest :: !Manifest
  } deriving (Int -> Plugin -> ShowS
[Plugin] -> ShowS
Plugin -> String
(Int -> Plugin -> ShowS)
-> (Plugin -> String) -> ([Plugin] -> ShowS) -> Show Plugin
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Plugin] -> ShowS
$cshowList :: [Plugin] -> ShowS
show :: Plugin -> String
$cshow :: Plugin -> String
showsPrec :: Int -> Plugin -> ShowS
$cshowsPrec :: Int -> Plugin -> ShowS
Show, Plugin -> Plugin -> Bool
(Plugin -> Plugin -> Bool)
-> (Plugin -> Plugin -> Bool) -> Eq Plugin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Plugin -> Plugin -> Bool
$c/= :: Plugin -> Plugin -> Bool
== :: Plugin -> Plugin -> Bool
$c== :: Plugin -> Plugin -> Bool
Eq, Eq Plugin
Eq Plugin
-> (Plugin -> Plugin -> Ordering)
-> (Plugin -> Plugin -> Bool)
-> (Plugin -> Plugin -> Bool)
-> (Plugin -> Plugin -> Bool)
-> (Plugin -> Plugin -> Bool)
-> (Plugin -> Plugin -> Plugin)
-> (Plugin -> Plugin -> Plugin)
-> Ord Plugin
Plugin -> Plugin -> Bool
Plugin -> Plugin -> Ordering
Plugin -> Plugin -> Plugin
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 :: Plugin -> Plugin -> Plugin
$cmin :: Plugin -> Plugin -> Plugin
max :: Plugin -> Plugin -> Plugin
$cmax :: Plugin -> Plugin -> Plugin
>= :: Plugin -> Plugin -> Bool
$c>= :: Plugin -> Plugin -> Bool
> :: Plugin -> Plugin -> Bool
$c> :: Plugin -> Plugin -> Bool
<= :: Plugin -> Plugin -> Bool
$c<= :: Plugin -> Plugin -> Bool
< :: Plugin -> Plugin -> Bool
$c< :: Plugin -> Plugin -> Bool
compare :: Plugin -> Plugin -> Ordering
$ccompare :: Plugin -> Plugin -> Ordering
$cp1Ord :: Eq Plugin
Ord)

-- | Plugin meta-data.
data Manifest = Manifest
  { -- | @Manifest-Version@.
    Manifest -> Text
manifest_version :: !Text
    -- | @Archiver-Version@.
  , Manifest -> Maybe Text
archiver_version :: !(Maybe Text)
    -- | @Created-By@.
  , Manifest -> Maybe Text
created_by :: !(Maybe Text)
    -- | @Built-By@.
  , Manifest -> Maybe Text
built_by :: !(Maybe Text)
    -- | @Build-Jdk@.
  , Manifest -> Maybe Text
build_jdk :: !(Maybe Text)
    -- | @Extension-Name@.
  , Manifest -> Maybe Text
extension_name :: !(Maybe Text)
    -- | @Specification-Title@.
  , Manifest -> Maybe Text
specification_title :: !(Maybe Text)
    -- | @Implementation-Title@.
  , Manifest -> Maybe Text
implementation_title :: !(Maybe Text)
    -- | @Implementation-Version@.
  , Manifest -> Maybe Text
implementation_version :: !(Maybe Text)
    -- | @Group-Id@.
  , Manifest -> Maybe Text
group_id :: !(Maybe Text)
    -- | @Short-Name@.
  , Manifest -> Text
short_name :: !Text
    -- | @Long-Name@.
  , Manifest -> Text
long_name :: !Text
    -- | @Url@.
  , Manifest -> Maybe Text
url :: !(Maybe Text)
    -- | @Plugin-Version@.
  , Manifest -> Text
plugin_version :: !Text
    -- | @Hudson-Version@.
  , Manifest -> Maybe Text
hudson_version :: !(Maybe Text)
    -- | @Jenkins-Version@.
  , Manifest -> Maybe Text
jenkins_version :: !(Maybe Text)
    -- | @Plugin-Dependencies@.
  , Manifest -> Set PluginDependency
plugin_dependencies :: !(Set PluginDependency)
    -- | @Plugin-Developers@.
  , Manifest -> Set Text
plugin_developers :: !(Set Text)
  } deriving (Int -> Manifest -> ShowS
[Manifest] -> ShowS
Manifest -> String
(Int -> Manifest -> ShowS)
-> (Manifest -> String) -> ([Manifest] -> ShowS) -> Show Manifest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Manifest] -> ShowS
$cshowList :: [Manifest] -> ShowS
show :: Manifest -> String
$cshow :: Manifest -> String
showsPrec :: Int -> Manifest -> ShowS
$cshowsPrec :: Int -> Manifest -> ShowS
Show, Manifest -> Manifest -> Bool
(Manifest -> Manifest -> Bool)
-> (Manifest -> Manifest -> Bool) -> Eq Manifest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Manifest -> Manifest -> Bool
$c/= :: Manifest -> Manifest -> Bool
== :: Manifest -> Manifest -> Bool
$c== :: Manifest -> Manifest -> Bool
Eq, Eq Manifest
Eq Manifest
-> (Manifest -> Manifest -> Ordering)
-> (Manifest -> Manifest -> Bool)
-> (Manifest -> Manifest -> Bool)
-> (Manifest -> Manifest -> Bool)
-> (Manifest -> Manifest -> Bool)
-> (Manifest -> Manifest -> Manifest)
-> (Manifest -> Manifest -> Manifest)
-> Ord Manifest
Manifest -> Manifest -> Bool
Manifest -> Manifest -> Ordering
Manifest -> Manifest -> Manifest
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 :: Manifest -> Manifest -> Manifest
$cmin :: Manifest -> Manifest -> Manifest
max :: Manifest -> Manifest -> Manifest
$cmax :: Manifest -> Manifest -> Manifest
>= :: Manifest -> Manifest -> Bool
$c>= :: Manifest -> Manifest -> Bool
> :: Manifest -> Manifest -> Bool
$c> :: Manifest -> Manifest -> Bool
<= :: Manifest -> Manifest -> Bool
$c<= :: Manifest -> Manifest -> Bool
< :: Manifest -> Manifest -> Bool
$c< :: Manifest -> Manifest -> Bool
compare :: Manifest -> Manifest -> Ordering
$ccompare :: Manifest -> Manifest -> Ordering
$cp1Ord :: Eq Manifest
Ord)