Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Boundary a
- data Options = Options {
- doPR :: Bool
- batchUpdate :: Bool
- githubUser :: Name Owner
- githubToken :: Text
- makeCVEReport :: Bool
- runNixpkgsReview :: Bool
- calculateOutpaths :: Bool
- type ProductID = Text
- type URL = Text
- data UpdateEnv = UpdateEnv {
- packageName :: Text
- oldVersion :: Version
- newVersion :: Version
- sourceURL :: Maybe URL
- options :: Options
- type Version = Text
- data VersionMatcher
- branchName :: UpdateEnv -> Text
- branchPrefix :: Text
- getGithubToken :: IO Text
- getGithubUser :: IO (Name Owner)
- logDir :: IO FilePath
- nixBuildOptions :: [String]
- nixCommonOptions :: [String]
- overwriteErrorT :: MonadIO m => Text -> ExceptT Text m a -> ExceptT Text m a
- parseUpdates :: Text -> [Either Text (Text, Version, Version, Maybe URL)]
- prTitle :: UpdateEnv -> Text -> Text
- runLog :: Member (Embed IO) r => (Text -> IO ()) -> Sem (Output Text ': r) a -> Sem r a
- srcOrMain :: MonadIO m => (Text -> ExceptT Text m a) -> Text -> ExceptT Text m a
- stripQuotes :: Text -> Maybe Text
- tRead :: Read a => Text -> a
- whenBatch :: Applicative f => UpdateEnv -> f () -> f ()
Documentation
The Ord instance is used to sort lists of matchers in order to compare them as a set, it is not useful for comparing bounds since the ordering of bounds depends on whether it is a start or end bound.
Instances
Eq a => Eq (Boundary a) Source # | |
Ord a => Ord (Boundary a) Source # | |
Read a => Read (Boundary a) Source # | |
Show a => Show (Boundary a) Source # | |
Options | |
|
UpdateEnv | |
|
data VersionMatcher Source #
The Ord instance is used to sort lists of matchers in order to compare them as a set, it is not useful for comparing versions.
Instances
Eq VersionMatcher Source # | |
Defined in Utils (==) :: VersionMatcher -> VersionMatcher -> Bool # (/=) :: VersionMatcher -> VersionMatcher -> Bool # | |
Ord VersionMatcher Source # | |
Defined in Utils compare :: VersionMatcher -> VersionMatcher -> Ordering # (<) :: VersionMatcher -> VersionMatcher -> Bool # (<=) :: VersionMatcher -> VersionMatcher -> Bool # (>) :: VersionMatcher -> VersionMatcher -> Bool # (>=) :: VersionMatcher -> VersionMatcher -> Bool # max :: VersionMatcher -> VersionMatcher -> VersionMatcher # min :: VersionMatcher -> VersionMatcher -> VersionMatcher # | |
Read VersionMatcher Source # | |
Defined in Utils readsPrec :: Int -> ReadS VersionMatcher # readList :: ReadS [VersionMatcher] # | |
Show VersionMatcher Source # | |
Defined in Utils showsPrec :: Int -> VersionMatcher -> ShowS # show :: VersionMatcher -> String # showList :: [VersionMatcher] -> ShowS # | |
FromField VersionMatcher Source # | |
Defined in Utils | |
ToField VersionMatcher Source # | |
Defined in Utils toField :: VersionMatcher -> SQLData # |
branchName :: UpdateEnv -> Text Source #
branchPrefix :: Text Source #
getGithubToken :: IO Text Source #
nixBuildOptions :: [String] Source #
nixCommonOptions :: [String] Source #
whenBatch :: Applicative f => UpdateEnv -> f () -> f () Source #