{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
module GitHub.Data.Options (
stateOpen,
stateClosed,
stateAll,
sortAscending,
sortDescending,
sortByCreated,
sortByUpdated,
PullRequestMod,
prModToQueryString,
optionsBase,
optionsNoBase,
optionsHead,
optionsNoHead,
sortByPopularity,
sortByLongRunning,
IssueMod,
issueModToQueryString,
sortByComments,
optionsLabels,
optionsSince,
optionsSinceAll,
optionsAssignedIssues,
optionsCreatedIssues,
optionsMentionedIssues,
optionsSubscribedIssues,
optionsAllIssues,
IssueRepoMod,
issueRepoModToQueryString,
optionsCreator,
optionsMentioned,
optionsIrrelevantMilestone,
optionsAnyMilestone,
optionsNoMilestone,
optionsMilestone,
optionsIrrelevantAssignee,
optionsAnyAssignee,
optionsNoAssignee,
optionsAssignee,
ArtifactMod,
artifactModToQueryString,
optionsArtifactName,
CacheMod,
cacheModToQueryString,
optionsRef,
optionsNoRef,
optionsKey,
optionsNoKey,
optionsDirectionAsc,
optionsDirectionDesc,
sortByCreatedAt,
sortByLastAccessedAt,
sortBySizeInBytes,
WorkflowRunMod,
workflowRunModToQueryString,
optionsWorkflowRunActor,
optionsWorkflowRunBranch,
optionsWorkflowRunEvent,
optionsWorkflowRunStatus,
optionsWorkflowRunCreated,
optionsWorkflowRunHeadSha,
IssueState (..),
IssueStateReason (..),
MergeableState (..),
HasState,
HasDirection,
HasCreatedUpdated,
HasComments,
HasLabels,
HasSince,
) where
import GitHub.Data.Definitions
import GitHub.Data.Id (Id, untagId)
import GitHub.Data.Milestone (Milestone)
import GitHub.Data.Name (Name, untagName)
import GitHub.Internal.Prelude
import Prelude ()
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
data IssueState
= StateOpen
| StateClosed
deriving
(IssueState -> IssueState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IssueState -> IssueState -> Bool
$c/= :: IssueState -> IssueState -> Bool
== :: IssueState -> IssueState -> Bool
$c== :: IssueState -> IssueState -> Bool
Eq, Eq IssueState
IssueState -> IssueState -> Bool
IssueState -> IssueState -> Ordering
IssueState -> IssueState -> IssueState
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 :: IssueState -> IssueState -> IssueState
$cmin :: IssueState -> IssueState -> IssueState
max :: IssueState -> IssueState -> IssueState
$cmax :: IssueState -> IssueState -> IssueState
>= :: IssueState -> IssueState -> Bool
$c>= :: IssueState -> IssueState -> Bool
> :: IssueState -> IssueState -> Bool
$c> :: IssueState -> IssueState -> Bool
<= :: IssueState -> IssueState -> Bool
$c<= :: IssueState -> IssueState -> Bool
< :: IssueState -> IssueState -> Bool
$c< :: IssueState -> IssueState -> Bool
compare :: IssueState -> IssueState -> Ordering
$ccompare :: IssueState -> IssueState -> Ordering
Ord, Int -> IssueState -> ShowS
[IssueState] -> ShowS
IssueState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IssueState] -> ShowS
$cshowList :: [IssueState] -> ShowS
show :: IssueState -> String
$cshow :: IssueState -> String
showsPrec :: Int -> IssueState -> ShowS
$cshowsPrec :: Int -> IssueState -> ShowS
Show, Int -> IssueState
IssueState -> Int
IssueState -> [IssueState]
IssueState -> IssueState
IssueState -> IssueState -> [IssueState]
IssueState -> IssueState -> IssueState -> [IssueState]
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 :: IssueState -> IssueState -> IssueState -> [IssueState]
$cenumFromThenTo :: IssueState -> IssueState -> IssueState -> [IssueState]
enumFromTo :: IssueState -> IssueState -> [IssueState]
$cenumFromTo :: IssueState -> IssueState -> [IssueState]
enumFromThen :: IssueState -> IssueState -> [IssueState]
$cenumFromThen :: IssueState -> IssueState -> [IssueState]
enumFrom :: IssueState -> [IssueState]
$cenumFrom :: IssueState -> [IssueState]
fromEnum :: IssueState -> Int
$cfromEnum :: IssueState -> Int
toEnum :: Int -> IssueState
$ctoEnum :: Int -> IssueState
pred :: IssueState -> IssueState
$cpred :: IssueState -> IssueState
succ :: IssueState -> IssueState
$csucc :: IssueState -> IssueState
Enum, IssueState
forall a. a -> a -> Bounded a
maxBound :: IssueState
$cmaxBound :: IssueState
minBound :: IssueState
$cminBound :: IssueState
Bounded, forall x. Rep IssueState x -> IssueState
forall x. IssueState -> Rep IssueState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IssueState x -> IssueState
$cfrom :: forall x. IssueState -> Rep IssueState x
Generic, Typeable, Typeable IssueState
IssueState -> DataType
IssueState -> Constr
(forall b. Data b => b -> b) -> IssueState -> IssueState
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IssueState -> u
forall u. (forall d. Data d => d -> u) -> IssueState -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueState -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueState -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueState -> m IssueState
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueState -> m IssueState
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueState
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueState -> c IssueState
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueState)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IssueState)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueState -> m IssueState
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueState -> m IssueState
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueState -> m IssueState
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueState -> m IssueState
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueState -> m IssueState
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueState -> m IssueState
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IssueState -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IssueState -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> IssueState -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IssueState -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueState -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueState -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueState -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueState -> r
gmapT :: (forall b. Data b => b -> b) -> IssueState -> IssueState
$cgmapT :: (forall b. Data b => b -> b) -> IssueState -> IssueState
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IssueState)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IssueState)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueState)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueState)
dataTypeOf :: IssueState -> DataType
$cdataTypeOf :: IssueState -> DataType
toConstr :: IssueState -> Constr
$ctoConstr :: IssueState -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueState
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueState
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueState -> c IssueState
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueState -> c IssueState
Data)
instance ToJSON IssueState where
toJSON :: IssueState -> Value
toJSON IssueState
StateOpen = Text -> Value
String Text
"open"
toJSON IssueState
StateClosed = Text -> Value
String Text
"closed"
instance FromJSON IssueState where
parseJSON :: Value -> Parser IssueState
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"IssueState" forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Text
T.toLower Text
t of
Text
"open" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure IssueState
StateOpen
Text
"closed" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure IssueState
StateClosed
Text
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Unknown IssueState: " forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
t
instance NFData IssueState where rnf :: IssueState -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary IssueState
data IssueStateReason
= StateReasonCompleted
| StateReasonNotPlanned
| StateReasonReopened
deriving
(IssueStateReason -> IssueStateReason -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IssueStateReason -> IssueStateReason -> Bool
$c/= :: IssueStateReason -> IssueStateReason -> Bool
== :: IssueStateReason -> IssueStateReason -> Bool
$c== :: IssueStateReason -> IssueStateReason -> Bool
Eq, Eq IssueStateReason
IssueStateReason -> IssueStateReason -> Bool
IssueStateReason -> IssueStateReason -> Ordering
IssueStateReason -> IssueStateReason -> IssueStateReason
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 :: IssueStateReason -> IssueStateReason -> IssueStateReason
$cmin :: IssueStateReason -> IssueStateReason -> IssueStateReason
max :: IssueStateReason -> IssueStateReason -> IssueStateReason
$cmax :: IssueStateReason -> IssueStateReason -> IssueStateReason
>= :: IssueStateReason -> IssueStateReason -> Bool
$c>= :: IssueStateReason -> IssueStateReason -> Bool
> :: IssueStateReason -> IssueStateReason -> Bool
$c> :: IssueStateReason -> IssueStateReason -> Bool
<= :: IssueStateReason -> IssueStateReason -> Bool
$c<= :: IssueStateReason -> IssueStateReason -> Bool
< :: IssueStateReason -> IssueStateReason -> Bool
$c< :: IssueStateReason -> IssueStateReason -> Bool
compare :: IssueStateReason -> IssueStateReason -> Ordering
$ccompare :: IssueStateReason -> IssueStateReason -> Ordering
Ord, Int -> IssueStateReason -> ShowS
[IssueStateReason] -> ShowS
IssueStateReason -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IssueStateReason] -> ShowS
$cshowList :: [IssueStateReason] -> ShowS
show :: IssueStateReason -> String
$cshow :: IssueStateReason -> String
showsPrec :: Int -> IssueStateReason -> ShowS
$cshowsPrec :: Int -> IssueStateReason -> ShowS
Show, Int -> IssueStateReason
IssueStateReason -> Int
IssueStateReason -> [IssueStateReason]
IssueStateReason -> IssueStateReason
IssueStateReason -> IssueStateReason -> [IssueStateReason]
IssueStateReason
-> IssueStateReason -> IssueStateReason -> [IssueStateReason]
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 :: IssueStateReason
-> IssueStateReason -> IssueStateReason -> [IssueStateReason]
$cenumFromThenTo :: IssueStateReason
-> IssueStateReason -> IssueStateReason -> [IssueStateReason]
enumFromTo :: IssueStateReason -> IssueStateReason -> [IssueStateReason]
$cenumFromTo :: IssueStateReason -> IssueStateReason -> [IssueStateReason]
enumFromThen :: IssueStateReason -> IssueStateReason -> [IssueStateReason]
$cenumFromThen :: IssueStateReason -> IssueStateReason -> [IssueStateReason]
enumFrom :: IssueStateReason -> [IssueStateReason]
$cenumFrom :: IssueStateReason -> [IssueStateReason]
fromEnum :: IssueStateReason -> Int
$cfromEnum :: IssueStateReason -> Int
toEnum :: Int -> IssueStateReason
$ctoEnum :: Int -> IssueStateReason
pred :: IssueStateReason -> IssueStateReason
$cpred :: IssueStateReason -> IssueStateReason
succ :: IssueStateReason -> IssueStateReason
$csucc :: IssueStateReason -> IssueStateReason
Enum, IssueStateReason
forall a. a -> a -> Bounded a
maxBound :: IssueStateReason
$cmaxBound :: IssueStateReason
minBound :: IssueStateReason
$cminBound :: IssueStateReason
Bounded, forall x. Rep IssueStateReason x -> IssueStateReason
forall x. IssueStateReason -> Rep IssueStateReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IssueStateReason x -> IssueStateReason
$cfrom :: forall x. IssueStateReason -> Rep IssueStateReason x
Generic, Typeable, Typeable IssueStateReason
IssueStateReason -> DataType
IssueStateReason -> Constr
(forall b. Data b => b -> b)
-> IssueStateReason -> IssueStateReason
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> IssueStateReason -> u
forall u. (forall d. Data d => d -> u) -> IssueStateReason -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueStateReason -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueStateReason -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IssueStateReason -> m IssueStateReason
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueStateReason -> m IssueStateReason
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueStateReason
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueStateReason -> c IssueStateReason
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueStateReason)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueStateReason)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueStateReason -> m IssueStateReason
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueStateReason -> m IssueStateReason
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueStateReason -> m IssueStateReason
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueStateReason -> m IssueStateReason
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IssueStateReason -> m IssueStateReason
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IssueStateReason -> m IssueStateReason
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IssueStateReason -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IssueStateReason -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> IssueStateReason -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IssueStateReason -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueStateReason -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueStateReason -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueStateReason -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueStateReason -> r
gmapT :: (forall b. Data b => b -> b)
-> IssueStateReason -> IssueStateReason
$cgmapT :: (forall b. Data b => b -> b)
-> IssueStateReason -> IssueStateReason
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueStateReason)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueStateReason)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueStateReason)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueStateReason)
dataTypeOf :: IssueStateReason -> DataType
$cdataTypeOf :: IssueStateReason -> DataType
toConstr :: IssueStateReason -> Constr
$ctoConstr :: IssueStateReason -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueStateReason
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueStateReason
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueStateReason -> c IssueStateReason
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueStateReason -> c IssueStateReason
Data)
instance ToJSON IssueStateReason where
toJSON :: IssueStateReason -> Value
toJSON = Text -> Value
String forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
IssueStateReason
StateReasonCompleted -> Text
"completed"
IssueStateReason
StateReasonNotPlanned -> Text
"not_planned"
IssueStateReason
StateReasonReopened -> Text
"reopened"
instance FromJSON IssueStateReason where
parseJSON :: Value -> Parser IssueStateReason
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"IssueStateReason" forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Text
T.toLower Text
t of
Text
"completed" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure IssueStateReason
StateReasonCompleted
Text
"not_planned" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure IssueStateReason
StateReasonNotPlanned
Text
"reopened" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure IssueStateReason
StateReasonReopened
Text
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Unknown IssueStateReason: " forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
t
instance NFData IssueStateReason where rnf :: IssueStateReason -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary IssueStateReason
data MergeableState
= StateUnknown
| StateClean
| StateDirty
| StateUnstable
| StateBlocked
| StateBehind
| StateDraft
deriving
(MergeableState -> MergeableState -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MergeableState -> MergeableState -> Bool
$c/= :: MergeableState -> MergeableState -> Bool
== :: MergeableState -> MergeableState -> Bool
$c== :: MergeableState -> MergeableState -> Bool
Eq, Eq MergeableState
MergeableState -> MergeableState -> Bool
MergeableState -> MergeableState -> Ordering
MergeableState -> MergeableState -> MergeableState
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 :: MergeableState -> MergeableState -> MergeableState
$cmin :: MergeableState -> MergeableState -> MergeableState
max :: MergeableState -> MergeableState -> MergeableState
$cmax :: MergeableState -> MergeableState -> MergeableState
>= :: MergeableState -> MergeableState -> Bool
$c>= :: MergeableState -> MergeableState -> Bool
> :: MergeableState -> MergeableState -> Bool
$c> :: MergeableState -> MergeableState -> Bool
<= :: MergeableState -> MergeableState -> Bool
$c<= :: MergeableState -> MergeableState -> Bool
< :: MergeableState -> MergeableState -> Bool
$c< :: MergeableState -> MergeableState -> Bool
compare :: MergeableState -> MergeableState -> Ordering
$ccompare :: MergeableState -> MergeableState -> Ordering
Ord, Int -> MergeableState -> ShowS
[MergeableState] -> ShowS
MergeableState -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MergeableState] -> ShowS
$cshowList :: [MergeableState] -> ShowS
show :: MergeableState -> String
$cshow :: MergeableState -> String
showsPrec :: Int -> MergeableState -> ShowS
$cshowsPrec :: Int -> MergeableState -> ShowS
Show, Int -> MergeableState
MergeableState -> Int
MergeableState -> [MergeableState]
MergeableState -> MergeableState
MergeableState -> MergeableState -> [MergeableState]
MergeableState
-> MergeableState -> MergeableState -> [MergeableState]
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 :: MergeableState
-> MergeableState -> MergeableState -> [MergeableState]
$cenumFromThenTo :: MergeableState
-> MergeableState -> MergeableState -> [MergeableState]
enumFromTo :: MergeableState -> MergeableState -> [MergeableState]
$cenumFromTo :: MergeableState -> MergeableState -> [MergeableState]
enumFromThen :: MergeableState -> MergeableState -> [MergeableState]
$cenumFromThen :: MergeableState -> MergeableState -> [MergeableState]
enumFrom :: MergeableState -> [MergeableState]
$cenumFrom :: MergeableState -> [MergeableState]
fromEnum :: MergeableState -> Int
$cfromEnum :: MergeableState -> Int
toEnum :: Int -> MergeableState
$ctoEnum :: Int -> MergeableState
pred :: MergeableState -> MergeableState
$cpred :: MergeableState -> MergeableState
succ :: MergeableState -> MergeableState
$csucc :: MergeableState -> MergeableState
Enum, MergeableState
forall a. a -> a -> Bounded a
maxBound :: MergeableState
$cmaxBound :: MergeableState
minBound :: MergeableState
$cminBound :: MergeableState
Bounded, forall x. Rep MergeableState x -> MergeableState
forall x. MergeableState -> Rep MergeableState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MergeableState x -> MergeableState
$cfrom :: forall x. MergeableState -> Rep MergeableState x
Generic, Typeable, Typeable MergeableState
MergeableState -> DataType
MergeableState -> Constr
(forall b. Data b => b -> b) -> MergeableState -> MergeableState
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> MergeableState -> u
forall u. (forall d. Data d => d -> u) -> MergeableState -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MergeableState -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MergeableState -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MergeableState -> m MergeableState
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MergeableState -> m MergeableState
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MergeableState
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MergeableState -> c MergeableState
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MergeableState)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MergeableState)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MergeableState -> m MergeableState
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MergeableState -> m MergeableState
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MergeableState -> m MergeableState
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MergeableState -> m MergeableState
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MergeableState -> m MergeableState
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MergeableState -> m MergeableState
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MergeableState -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> MergeableState -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> MergeableState -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MergeableState -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MergeableState -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MergeableState -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MergeableState -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MergeableState -> r
gmapT :: (forall b. Data b => b -> b) -> MergeableState -> MergeableState
$cgmapT :: (forall b. Data b => b -> b) -> MergeableState -> MergeableState
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MergeableState)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MergeableState)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MergeableState)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MergeableState)
dataTypeOf :: MergeableState -> DataType
$cdataTypeOf :: MergeableState -> DataType
toConstr :: MergeableState -> Constr
$ctoConstr :: MergeableState -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MergeableState
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MergeableState
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MergeableState -> c MergeableState
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MergeableState -> c MergeableState
Data)
instance ToJSON MergeableState where
toJSON :: MergeableState -> Value
toJSON MergeableState
StateUnknown = Text -> Value
String Text
"unknown"
toJSON MergeableState
StateClean = Text -> Value
String Text
"clean"
toJSON MergeableState
StateDirty = Text -> Value
String Text
"dirty"
toJSON MergeableState
StateUnstable = Text -> Value
String Text
"unstable"
toJSON MergeableState
StateBlocked = Text -> Value
String Text
"blocked"
toJSON MergeableState
StateBehind = Text -> Value
String Text
"behind"
toJSON MergeableState
StateDraft = Text -> Value
String Text
"draft"
instance FromJSON MergeableState where
parseJSON :: Value -> Parser MergeableState
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"MergeableState" forall a b. (a -> b) -> a -> b
$ \Text
t -> case Text -> Text
T.toLower Text
t of
Text
"unknown" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MergeableState
StateUnknown
Text
"clean" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MergeableState
StateClean
Text
"dirty" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MergeableState
StateDirty
Text
"unstable" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MergeableState
StateUnstable
Text
"blocked" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MergeableState
StateBlocked
Text
"behind" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MergeableState
StateBehind
Text
"draft" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MergeableState
StateDraft
Text
_ -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Unknown MergeableState: " forall a. Semigroup a => a -> a -> a
<> Text -> String
T.unpack Text
t
instance NFData MergeableState where rnf :: MergeableState -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary MergeableState
data SortDirection
= SortAscending
| SortDescending
deriving
(SortDirection -> SortDirection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortDirection -> SortDirection -> Bool
$c/= :: SortDirection -> SortDirection -> Bool
== :: SortDirection -> SortDirection -> Bool
$c== :: SortDirection -> SortDirection -> Bool
Eq, Eq SortDirection
SortDirection -> SortDirection -> Bool
SortDirection -> SortDirection -> Ordering
SortDirection -> SortDirection -> SortDirection
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 :: SortDirection -> SortDirection -> SortDirection
$cmin :: SortDirection -> SortDirection -> SortDirection
max :: SortDirection -> SortDirection -> SortDirection
$cmax :: SortDirection -> SortDirection -> SortDirection
>= :: SortDirection -> SortDirection -> Bool
$c>= :: SortDirection -> SortDirection -> Bool
> :: SortDirection -> SortDirection -> Bool
$c> :: SortDirection -> SortDirection -> Bool
<= :: SortDirection -> SortDirection -> Bool
$c<= :: SortDirection -> SortDirection -> Bool
< :: SortDirection -> SortDirection -> Bool
$c< :: SortDirection -> SortDirection -> Bool
compare :: SortDirection -> SortDirection -> Ordering
$ccompare :: SortDirection -> SortDirection -> Ordering
Ord, Int -> SortDirection -> ShowS
[SortDirection] -> ShowS
SortDirection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortDirection] -> ShowS
$cshowList :: [SortDirection] -> ShowS
show :: SortDirection -> String
$cshow :: SortDirection -> String
showsPrec :: Int -> SortDirection -> ShowS
$cshowsPrec :: Int -> SortDirection -> ShowS
Show, Int -> SortDirection
SortDirection -> Int
SortDirection -> [SortDirection]
SortDirection -> SortDirection
SortDirection -> SortDirection -> [SortDirection]
SortDirection -> SortDirection -> SortDirection -> [SortDirection]
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 :: SortDirection -> SortDirection -> SortDirection -> [SortDirection]
$cenumFromThenTo :: SortDirection -> SortDirection -> SortDirection -> [SortDirection]
enumFromTo :: SortDirection -> SortDirection -> [SortDirection]
$cenumFromTo :: SortDirection -> SortDirection -> [SortDirection]
enumFromThen :: SortDirection -> SortDirection -> [SortDirection]
$cenumFromThen :: SortDirection -> SortDirection -> [SortDirection]
enumFrom :: SortDirection -> [SortDirection]
$cenumFrom :: SortDirection -> [SortDirection]
fromEnum :: SortDirection -> Int
$cfromEnum :: SortDirection -> Int
toEnum :: Int -> SortDirection
$ctoEnum :: Int -> SortDirection
pred :: SortDirection -> SortDirection
$cpred :: SortDirection -> SortDirection
succ :: SortDirection -> SortDirection
$csucc :: SortDirection -> SortDirection
Enum, SortDirection
forall a. a -> a -> Bounded a
maxBound :: SortDirection
$cmaxBound :: SortDirection
minBound :: SortDirection
$cminBound :: SortDirection
Bounded, forall x. Rep SortDirection x -> SortDirection
forall x. SortDirection -> Rep SortDirection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SortDirection x -> SortDirection
$cfrom :: forall x. SortDirection -> Rep SortDirection x
Generic, Typeable, Typeable SortDirection
SortDirection -> DataType
SortDirection -> Constr
(forall b. Data b => b -> b) -> SortDirection -> SortDirection
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SortDirection -> u
forall u. (forall d. Data d => d -> u) -> SortDirection -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortDirection -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortDirection -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortDirection -> m SortDirection
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortDirection -> m SortDirection
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortDirection
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortDirection -> c SortDirection
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortDirection)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SortDirection)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortDirection -> m SortDirection
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortDirection -> m SortDirection
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortDirection -> m SortDirection
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortDirection -> m SortDirection
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortDirection -> m SortDirection
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortDirection -> m SortDirection
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SortDirection -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SortDirection -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SortDirection -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SortDirection -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortDirection -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortDirection -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortDirection -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortDirection -> r
gmapT :: (forall b. Data b => b -> b) -> SortDirection -> SortDirection
$cgmapT :: (forall b. Data b => b -> b) -> SortDirection -> SortDirection
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SortDirection)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SortDirection)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortDirection)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortDirection)
dataTypeOf :: SortDirection -> DataType
$cdataTypeOf :: SortDirection -> DataType
toConstr :: SortDirection -> Constr
$ctoConstr :: SortDirection -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortDirection
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortDirection
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortDirection -> c SortDirection
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortDirection -> c SortDirection
Data)
instance NFData SortDirection where rnf :: SortDirection -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary SortDirection
data SortPR
= SortPRCreated
| SortPRUpdated
| SortPRPopularity
| SortPRLongRunning
deriving
(SortPR -> SortPR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortPR -> SortPR -> Bool
$c/= :: SortPR -> SortPR -> Bool
== :: SortPR -> SortPR -> Bool
$c== :: SortPR -> SortPR -> Bool
Eq, Eq SortPR
SortPR -> SortPR -> Bool
SortPR -> SortPR -> Ordering
SortPR -> SortPR -> SortPR
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 :: SortPR -> SortPR -> SortPR
$cmin :: SortPR -> SortPR -> SortPR
max :: SortPR -> SortPR -> SortPR
$cmax :: SortPR -> SortPR -> SortPR
>= :: SortPR -> SortPR -> Bool
$c>= :: SortPR -> SortPR -> Bool
> :: SortPR -> SortPR -> Bool
$c> :: SortPR -> SortPR -> Bool
<= :: SortPR -> SortPR -> Bool
$c<= :: SortPR -> SortPR -> Bool
< :: SortPR -> SortPR -> Bool
$c< :: SortPR -> SortPR -> Bool
compare :: SortPR -> SortPR -> Ordering
$ccompare :: SortPR -> SortPR -> Ordering
Ord, Int -> SortPR -> ShowS
[SortPR] -> ShowS
SortPR -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortPR] -> ShowS
$cshowList :: [SortPR] -> ShowS
show :: SortPR -> String
$cshow :: SortPR -> String
showsPrec :: Int -> SortPR -> ShowS
$cshowsPrec :: Int -> SortPR -> ShowS
Show, Int -> SortPR
SortPR -> Int
SortPR -> [SortPR]
SortPR -> SortPR
SortPR -> SortPR -> [SortPR]
SortPR -> SortPR -> SortPR -> [SortPR]
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 :: SortPR -> SortPR -> SortPR -> [SortPR]
$cenumFromThenTo :: SortPR -> SortPR -> SortPR -> [SortPR]
enumFromTo :: SortPR -> SortPR -> [SortPR]
$cenumFromTo :: SortPR -> SortPR -> [SortPR]
enumFromThen :: SortPR -> SortPR -> [SortPR]
$cenumFromThen :: SortPR -> SortPR -> [SortPR]
enumFrom :: SortPR -> [SortPR]
$cenumFrom :: SortPR -> [SortPR]
fromEnum :: SortPR -> Int
$cfromEnum :: SortPR -> Int
toEnum :: Int -> SortPR
$ctoEnum :: Int -> SortPR
pred :: SortPR -> SortPR
$cpred :: SortPR -> SortPR
succ :: SortPR -> SortPR
$csucc :: SortPR -> SortPR
Enum, SortPR
forall a. a -> a -> Bounded a
maxBound :: SortPR
$cmaxBound :: SortPR
minBound :: SortPR
$cminBound :: SortPR
Bounded, forall x. Rep SortPR x -> SortPR
forall x. SortPR -> Rep SortPR x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SortPR x -> SortPR
$cfrom :: forall x. SortPR -> Rep SortPR x
Generic, Typeable, Typeable SortPR
SortPR -> DataType
SortPR -> Constr
(forall b. Data b => b -> b) -> SortPR -> SortPR
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SortPR -> u
forall u. (forall d. Data d => d -> u) -> SortPR -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortPR -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortPR -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortPR -> m SortPR
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortPR -> m SortPR
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortPR
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortPR -> c SortPR
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortPR)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortPR)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortPR -> m SortPR
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortPR -> m SortPR
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortPR -> m SortPR
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortPR -> m SortPR
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortPR -> m SortPR
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortPR -> m SortPR
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SortPR -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SortPR -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SortPR -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SortPR -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortPR -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortPR -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortPR -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortPR -> r
gmapT :: (forall b. Data b => b -> b) -> SortPR -> SortPR
$cgmapT :: (forall b. Data b => b -> b) -> SortPR -> SortPR
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortPR)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortPR)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortPR)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortPR)
dataTypeOf :: SortPR -> DataType
$cdataTypeOf :: SortPR -> DataType
toConstr :: SortPR -> Constr
$ctoConstr :: SortPR -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortPR
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortPR
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortPR -> c SortPR
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortPR -> c SortPR
Data)
instance NFData SortPR where rnf :: SortPR -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary SortPR
data IssueFilter
= IssueFilterAssigned
| IssueFilterCreated
| IssueFilterMentioned
| IssueFilterSubscribed
| IssueFilterAll
deriving
(IssueFilter -> IssueFilter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IssueFilter -> IssueFilter -> Bool
$c/= :: IssueFilter -> IssueFilter -> Bool
== :: IssueFilter -> IssueFilter -> Bool
$c== :: IssueFilter -> IssueFilter -> Bool
Eq, Eq IssueFilter
IssueFilter -> IssueFilter -> Bool
IssueFilter -> IssueFilter -> Ordering
IssueFilter -> IssueFilter -> IssueFilter
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 :: IssueFilter -> IssueFilter -> IssueFilter
$cmin :: IssueFilter -> IssueFilter -> IssueFilter
max :: IssueFilter -> IssueFilter -> IssueFilter
$cmax :: IssueFilter -> IssueFilter -> IssueFilter
>= :: IssueFilter -> IssueFilter -> Bool
$c>= :: IssueFilter -> IssueFilter -> Bool
> :: IssueFilter -> IssueFilter -> Bool
$c> :: IssueFilter -> IssueFilter -> Bool
<= :: IssueFilter -> IssueFilter -> Bool
$c<= :: IssueFilter -> IssueFilter -> Bool
< :: IssueFilter -> IssueFilter -> Bool
$c< :: IssueFilter -> IssueFilter -> Bool
compare :: IssueFilter -> IssueFilter -> Ordering
$ccompare :: IssueFilter -> IssueFilter -> Ordering
Ord, Int -> IssueFilter -> ShowS
[IssueFilter] -> ShowS
IssueFilter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IssueFilter] -> ShowS
$cshowList :: [IssueFilter] -> ShowS
show :: IssueFilter -> String
$cshow :: IssueFilter -> String
showsPrec :: Int -> IssueFilter -> ShowS
$cshowsPrec :: Int -> IssueFilter -> ShowS
Show, Int -> IssueFilter
IssueFilter -> Int
IssueFilter -> [IssueFilter]
IssueFilter -> IssueFilter
IssueFilter -> IssueFilter -> [IssueFilter]
IssueFilter -> IssueFilter -> IssueFilter -> [IssueFilter]
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 :: IssueFilter -> IssueFilter -> IssueFilter -> [IssueFilter]
$cenumFromThenTo :: IssueFilter -> IssueFilter -> IssueFilter -> [IssueFilter]
enumFromTo :: IssueFilter -> IssueFilter -> [IssueFilter]
$cenumFromTo :: IssueFilter -> IssueFilter -> [IssueFilter]
enumFromThen :: IssueFilter -> IssueFilter -> [IssueFilter]
$cenumFromThen :: IssueFilter -> IssueFilter -> [IssueFilter]
enumFrom :: IssueFilter -> [IssueFilter]
$cenumFrom :: IssueFilter -> [IssueFilter]
fromEnum :: IssueFilter -> Int
$cfromEnum :: IssueFilter -> Int
toEnum :: Int -> IssueFilter
$ctoEnum :: Int -> IssueFilter
pred :: IssueFilter -> IssueFilter
$cpred :: IssueFilter -> IssueFilter
succ :: IssueFilter -> IssueFilter
$csucc :: IssueFilter -> IssueFilter
Enum, IssueFilter
forall a. a -> a -> Bounded a
maxBound :: IssueFilter
$cmaxBound :: IssueFilter
minBound :: IssueFilter
$cminBound :: IssueFilter
Bounded, forall x. Rep IssueFilter x -> IssueFilter
forall x. IssueFilter -> Rep IssueFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IssueFilter x -> IssueFilter
$cfrom :: forall x. IssueFilter -> Rep IssueFilter x
Generic, Typeable, Typeable IssueFilter
IssueFilter -> DataType
IssueFilter -> Constr
(forall b. Data b => b -> b) -> IssueFilter -> IssueFilter
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IssueFilter -> u
forall u. (forall d. Data d => d -> u) -> IssueFilter -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueFilter -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueFilter -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueFilter -> m IssueFilter
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueFilter -> m IssueFilter
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueFilter
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueFilter -> c IssueFilter
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueFilter)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueFilter)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueFilter -> m IssueFilter
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueFilter -> m IssueFilter
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueFilter -> m IssueFilter
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueFilter -> m IssueFilter
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueFilter -> m IssueFilter
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueFilter -> m IssueFilter
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IssueFilter -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IssueFilter -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> IssueFilter -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IssueFilter -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueFilter -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueFilter -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueFilter -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueFilter -> r
gmapT :: (forall b. Data b => b -> b) -> IssueFilter -> IssueFilter
$cgmapT :: (forall b. Data b => b -> b) -> IssueFilter -> IssueFilter
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueFilter)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueFilter)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueFilter)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueFilter)
dataTypeOf :: IssueFilter -> DataType
$cdataTypeOf :: IssueFilter -> DataType
toConstr :: IssueFilter -> Constr
$ctoConstr :: IssueFilter -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueFilter
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueFilter
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueFilter -> c IssueFilter
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueFilter -> c IssueFilter
Data)
instance NFData IssueFilter where rnf :: IssueFilter -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary IssueFilter
data SortIssue
= SortIssueCreated
| SortIssueUpdated
|
deriving
(SortIssue -> SortIssue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortIssue -> SortIssue -> Bool
$c/= :: SortIssue -> SortIssue -> Bool
== :: SortIssue -> SortIssue -> Bool
$c== :: SortIssue -> SortIssue -> Bool
Eq, Eq SortIssue
SortIssue -> SortIssue -> Bool
SortIssue -> SortIssue -> Ordering
SortIssue -> SortIssue -> SortIssue
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 :: SortIssue -> SortIssue -> SortIssue
$cmin :: SortIssue -> SortIssue -> SortIssue
max :: SortIssue -> SortIssue -> SortIssue
$cmax :: SortIssue -> SortIssue -> SortIssue
>= :: SortIssue -> SortIssue -> Bool
$c>= :: SortIssue -> SortIssue -> Bool
> :: SortIssue -> SortIssue -> Bool
$c> :: SortIssue -> SortIssue -> Bool
<= :: SortIssue -> SortIssue -> Bool
$c<= :: SortIssue -> SortIssue -> Bool
< :: SortIssue -> SortIssue -> Bool
$c< :: SortIssue -> SortIssue -> Bool
compare :: SortIssue -> SortIssue -> Ordering
$ccompare :: SortIssue -> SortIssue -> Ordering
Ord, Int -> SortIssue -> ShowS
[SortIssue] -> ShowS
SortIssue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortIssue] -> ShowS
$cshowList :: [SortIssue] -> ShowS
show :: SortIssue -> String
$cshow :: SortIssue -> String
showsPrec :: Int -> SortIssue -> ShowS
$cshowsPrec :: Int -> SortIssue -> ShowS
Show, Int -> SortIssue
SortIssue -> Int
SortIssue -> [SortIssue]
SortIssue -> SortIssue
SortIssue -> SortIssue -> [SortIssue]
SortIssue -> SortIssue -> SortIssue -> [SortIssue]
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 :: SortIssue -> SortIssue -> SortIssue -> [SortIssue]
$cenumFromThenTo :: SortIssue -> SortIssue -> SortIssue -> [SortIssue]
enumFromTo :: SortIssue -> SortIssue -> [SortIssue]
$cenumFromTo :: SortIssue -> SortIssue -> [SortIssue]
enumFromThen :: SortIssue -> SortIssue -> [SortIssue]
$cenumFromThen :: SortIssue -> SortIssue -> [SortIssue]
enumFrom :: SortIssue -> [SortIssue]
$cenumFrom :: SortIssue -> [SortIssue]
fromEnum :: SortIssue -> Int
$cfromEnum :: SortIssue -> Int
toEnum :: Int -> SortIssue
$ctoEnum :: Int -> SortIssue
pred :: SortIssue -> SortIssue
$cpred :: SortIssue -> SortIssue
succ :: SortIssue -> SortIssue
$csucc :: SortIssue -> SortIssue
Enum, SortIssue
forall a. a -> a -> Bounded a
maxBound :: SortIssue
$cmaxBound :: SortIssue
minBound :: SortIssue
$cminBound :: SortIssue
Bounded, forall x. Rep SortIssue x -> SortIssue
forall x. SortIssue -> Rep SortIssue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SortIssue x -> SortIssue
$cfrom :: forall x. SortIssue -> Rep SortIssue x
Generic, Typeable, Typeable SortIssue
SortIssue -> DataType
SortIssue -> Constr
(forall b. Data b => b -> b) -> SortIssue -> SortIssue
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SortIssue -> u
forall u. (forall d. Data d => d -> u) -> SortIssue -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortIssue -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortIssue -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortIssue -> m SortIssue
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortIssue -> m SortIssue
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortIssue
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortIssue -> c SortIssue
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortIssue)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortIssue)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortIssue -> m SortIssue
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortIssue -> m SortIssue
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortIssue -> m SortIssue
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortIssue -> m SortIssue
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortIssue -> m SortIssue
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortIssue -> m SortIssue
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SortIssue -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SortIssue -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SortIssue -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SortIssue -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortIssue -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortIssue -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortIssue -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortIssue -> r
gmapT :: (forall b. Data b => b -> b) -> SortIssue -> SortIssue
$cgmapT :: (forall b. Data b => b -> b) -> SortIssue -> SortIssue
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortIssue)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortIssue)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortIssue)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortIssue)
dataTypeOf :: SortIssue -> DataType
$cdataTypeOf :: SortIssue -> DataType
toConstr :: SortIssue -> Constr
$ctoConstr :: SortIssue -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortIssue
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortIssue
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortIssue -> c SortIssue
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortIssue -> c SortIssue
Data)
instance NFData SortIssue where rnf :: SortIssue -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary SortIssue
data FilterBy a
= FilterAny
| FilterNone
| FilterBy a
| FilterNotSpecified
deriving
(FilterBy a -> FilterBy a -> Bool
forall a. Eq a => FilterBy a -> FilterBy a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilterBy a -> FilterBy a -> Bool
$c/= :: forall a. Eq a => FilterBy a -> FilterBy a -> Bool
== :: FilterBy a -> FilterBy a -> Bool
$c== :: forall a. Eq a => FilterBy a -> FilterBy a -> Bool
Eq, FilterBy a -> FilterBy a -> Ordering
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
forall {a}. Ord a => Eq (FilterBy a)
forall a. Ord a => FilterBy a -> FilterBy a -> Bool
forall a. Ord a => FilterBy a -> FilterBy a -> Ordering
forall a. Ord a => FilterBy a -> FilterBy a -> FilterBy a
min :: FilterBy a -> FilterBy a -> FilterBy a
$cmin :: forall a. Ord a => FilterBy a -> FilterBy a -> FilterBy a
max :: FilterBy a -> FilterBy a -> FilterBy a
$cmax :: forall a. Ord a => FilterBy a -> FilterBy a -> FilterBy a
>= :: FilterBy a -> FilterBy a -> Bool
$c>= :: forall a. Ord a => FilterBy a -> FilterBy a -> Bool
> :: FilterBy a -> FilterBy a -> Bool
$c> :: forall a. Ord a => FilterBy a -> FilterBy a -> Bool
<= :: FilterBy a -> FilterBy a -> Bool
$c<= :: forall a. Ord a => FilterBy a -> FilterBy a -> Bool
< :: FilterBy a -> FilterBy a -> Bool
$c< :: forall a. Ord a => FilterBy a -> FilterBy a -> Bool
compare :: FilterBy a -> FilterBy a -> Ordering
$ccompare :: forall a. Ord a => FilterBy a -> FilterBy a -> Ordering
Ord, Int -> FilterBy a -> ShowS
forall a. Show a => Int -> FilterBy a -> ShowS
forall a. Show a => [FilterBy a] -> ShowS
forall a. Show a => FilterBy a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilterBy a] -> ShowS
$cshowList :: forall a. Show a => [FilterBy a] -> ShowS
show :: FilterBy a -> String
$cshow :: forall a. Show a => FilterBy a -> String
showsPrec :: Int -> FilterBy a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> FilterBy a -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (FilterBy a) x -> FilterBy a
forall a x. FilterBy a -> Rep (FilterBy a) x
$cto :: forall a x. Rep (FilterBy a) x -> FilterBy a
$cfrom :: forall a x. FilterBy a -> Rep (FilterBy a) x
Generic, Typeable, FilterBy a -> DataType
FilterBy a -> Constr
forall {a}. Data a => Typeable (FilterBy a)
forall a. Data a => FilterBy a -> DataType
forall a. Data a => FilterBy a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> FilterBy a -> FilterBy a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> FilterBy a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> FilterBy a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FilterBy a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FilterBy a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> FilterBy a -> m (FilterBy a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> FilterBy a -> m (FilterBy a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FilterBy a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FilterBy a -> c (FilterBy a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (FilterBy a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (FilterBy a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FilterBy a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FilterBy a -> c (FilterBy a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (FilterBy a))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilterBy a -> m (FilterBy a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> FilterBy a -> m (FilterBy a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FilterBy a -> m (FilterBy a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> FilterBy a -> m (FilterBy a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FilterBy a -> m (FilterBy a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> FilterBy a -> m (FilterBy a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FilterBy a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> FilterBy a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> FilterBy a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> FilterBy a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FilterBy a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FilterBy a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FilterBy a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FilterBy a -> r
gmapT :: (forall b. Data b => b -> b) -> FilterBy a -> FilterBy a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> FilterBy a -> FilterBy a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (FilterBy a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (FilterBy a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (FilterBy a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (FilterBy a))
dataTypeOf :: FilterBy a -> DataType
$cdataTypeOf :: forall a. Data a => FilterBy a -> DataType
toConstr :: FilterBy a -> Constr
$ctoConstr :: forall a. Data a => FilterBy a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FilterBy a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (FilterBy a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FilterBy a -> c (FilterBy a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FilterBy a -> c (FilterBy a)
Data)
data SortCache
= SortCacheCreatedAt
| SortCacheLastAccessedAt
| SortCacheSizeInBytes
deriving
(SortCache -> SortCache -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortCache -> SortCache -> Bool
$c/= :: SortCache -> SortCache -> Bool
== :: SortCache -> SortCache -> Bool
$c== :: SortCache -> SortCache -> Bool
Eq, Eq SortCache
SortCache -> SortCache -> Bool
SortCache -> SortCache -> Ordering
SortCache -> SortCache -> SortCache
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 :: SortCache -> SortCache -> SortCache
$cmin :: SortCache -> SortCache -> SortCache
max :: SortCache -> SortCache -> SortCache
$cmax :: SortCache -> SortCache -> SortCache
>= :: SortCache -> SortCache -> Bool
$c>= :: SortCache -> SortCache -> Bool
> :: SortCache -> SortCache -> Bool
$c> :: SortCache -> SortCache -> Bool
<= :: SortCache -> SortCache -> Bool
$c<= :: SortCache -> SortCache -> Bool
< :: SortCache -> SortCache -> Bool
$c< :: SortCache -> SortCache -> Bool
compare :: SortCache -> SortCache -> Ordering
$ccompare :: SortCache -> SortCache -> Ordering
Ord, Int -> SortCache -> ShowS
[SortCache] -> ShowS
SortCache -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortCache] -> ShowS
$cshowList :: [SortCache] -> ShowS
show :: SortCache -> String
$cshow :: SortCache -> String
showsPrec :: Int -> SortCache -> ShowS
$cshowsPrec :: Int -> SortCache -> ShowS
Show, Int -> SortCache
SortCache -> Int
SortCache -> [SortCache]
SortCache -> SortCache
SortCache -> SortCache -> [SortCache]
SortCache -> SortCache -> SortCache -> [SortCache]
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 :: SortCache -> SortCache -> SortCache -> [SortCache]
$cenumFromThenTo :: SortCache -> SortCache -> SortCache -> [SortCache]
enumFromTo :: SortCache -> SortCache -> [SortCache]
$cenumFromTo :: SortCache -> SortCache -> [SortCache]
enumFromThen :: SortCache -> SortCache -> [SortCache]
$cenumFromThen :: SortCache -> SortCache -> [SortCache]
enumFrom :: SortCache -> [SortCache]
$cenumFrom :: SortCache -> [SortCache]
fromEnum :: SortCache -> Int
$cfromEnum :: SortCache -> Int
toEnum :: Int -> SortCache
$ctoEnum :: Int -> SortCache
pred :: SortCache -> SortCache
$cpred :: SortCache -> SortCache
succ :: SortCache -> SortCache
$csucc :: SortCache -> SortCache
Enum, SortCache
forall a. a -> a -> Bounded a
maxBound :: SortCache
$cmaxBound :: SortCache
minBound :: SortCache
$cminBound :: SortCache
Bounded, forall x. Rep SortCache x -> SortCache
forall x. SortCache -> Rep SortCache x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SortCache x -> SortCache
$cfrom :: forall x. SortCache -> Rep SortCache x
Generic, Typeable, Typeable SortCache
SortCache -> DataType
SortCache -> Constr
(forall b. Data b => b -> b) -> SortCache -> SortCache
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> SortCache -> u
forall u. (forall d. Data d => d -> u) -> SortCache -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortCache -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortCache -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortCache -> m SortCache
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortCache -> m SortCache
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortCache
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortCache -> c SortCache
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortCache)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortCache)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortCache -> m SortCache
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortCache -> m SortCache
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortCache -> m SortCache
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SortCache -> m SortCache
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortCache -> m SortCache
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SortCache -> m SortCache
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SortCache -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SortCache -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> SortCache -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SortCache -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortCache -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SortCache -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortCache -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SortCache -> r
gmapT :: (forall b. Data b => b -> b) -> SortCache -> SortCache
$cgmapT :: (forall b. Data b => b -> b) -> SortCache -> SortCache
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortCache)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortCache)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortCache)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SortCache)
dataTypeOf :: SortCache -> DataType
$cdataTypeOf :: SortCache -> DataType
toConstr :: SortCache -> Constr
$ctoConstr :: SortCache -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortCache
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SortCache
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortCache -> c SortCache
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SortCache -> c SortCache
Data)
instance NFData SortCache where rnf :: SortCache -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Binary SortCache
class HasState mod where
state :: Maybe IssueState -> mod
stateOpen :: HasState mod => mod
stateOpen :: forall mod. HasState mod => mod
stateOpen = forall mod. HasState mod => Maybe IssueState -> mod
state (forall a. a -> Maybe a
Just IssueState
StateOpen)
stateClosed :: HasState mod => mod
stateClosed :: forall mod. HasState mod => mod
stateClosed = forall mod. HasState mod => Maybe IssueState -> mod
state (forall a. a -> Maybe a
Just IssueState
StateClosed)
stateAll :: HasState mod => mod
stateAll :: forall mod. HasState mod => mod
stateAll = forall mod. HasState mod => Maybe IssueState -> mod
state forall a. Maybe a
Nothing
instance HasState PullRequestMod where
state :: Maybe IssueState -> PullRequestMod
state Maybe IssueState
s = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsState :: Maybe IssueState
pullRequestOptionsState = Maybe IssueState
s }
instance HasState IssueMod where
state :: Maybe IssueState -> IssueMod
state Maybe IssueState
s = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsState :: Maybe IssueState
issueOptionsState = Maybe IssueState
s }
instance HasState IssueRepoMod where
state :: Maybe IssueState -> IssueRepoMod
state Maybe IssueState
s = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsState :: Maybe IssueState
issueRepoOptionsState = Maybe IssueState
s }
class HasDirection mod where
sortDir :: SortDirection -> mod
sortAscending :: HasDirection mod => mod
sortAscending :: forall mod. HasDirection mod => mod
sortAscending = forall mod. HasDirection mod => SortDirection -> mod
sortDir SortDirection
SortAscending
sortDescending :: HasDirection mod => mod
sortDescending :: forall mod. HasDirection mod => mod
sortDescending = forall mod. HasDirection mod => SortDirection -> mod
sortDir SortDirection
SortDescending
instance HasDirection PullRequestMod where
sortDir :: SortDirection -> PullRequestMod
sortDir SortDirection
x = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsDirection :: SortDirection
pullRequestOptionsDirection = SortDirection
x }
instance HasDirection IssueMod where
sortDir :: SortDirection -> IssueMod
sortDir SortDirection
x = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsDirection :: SortDirection
issueOptionsDirection = SortDirection
x }
instance HasDirection IssueRepoMod where
sortDir :: SortDirection -> IssueRepoMod
sortDir SortDirection
x = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsDirection :: SortDirection
issueRepoOptionsDirection = SortDirection
x }
class HasCreatedUpdated mod where
sortByCreated :: mod
sortByUpdated :: mod
instance HasCreatedUpdated PullRequestMod where
sortByCreated :: PullRequestMod
sortByCreated = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsSort :: SortPR
pullRequestOptionsSort = SortPR
SortPRCreated }
sortByUpdated :: PullRequestMod
sortByUpdated = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsSort :: SortPR
pullRequestOptionsSort = SortPR
SortPRUpdated }
instance HasCreatedUpdated IssueMod where
sortByCreated :: IssueMod
sortByCreated = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsSort :: SortIssue
issueOptionsSort = SortIssue
SortIssueCreated }
sortByUpdated :: IssueMod
sortByUpdated = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsSort :: SortIssue
issueOptionsSort = SortIssue
SortIssueUpdated }
instance HasCreatedUpdated IssueRepoMod where
sortByCreated :: IssueRepoMod
sortByCreated = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsSort :: SortIssue
issueRepoOptionsSort = SortIssue
SortIssueCreated }
sortByUpdated :: IssueRepoMod
sortByUpdated = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsSort :: SortIssue
issueRepoOptionsSort = SortIssue
SortIssueUpdated }
data PullRequestOptions = PullRequestOptions
{ PullRequestOptions -> Maybe IssueState
pullRequestOptionsState :: !(Maybe IssueState)
, PullRequestOptions -> Maybe Text
pullRequestOptionsHead :: !(Maybe Text)
, PullRequestOptions -> Maybe Text
pullRequestOptionsBase :: !(Maybe Text)
, PullRequestOptions -> SortPR
pullRequestOptionsSort :: !SortPR
, PullRequestOptions -> SortDirection
pullRequestOptionsDirection :: !SortDirection
}
deriving
(PullRequestOptions -> PullRequestOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PullRequestOptions -> PullRequestOptions -> Bool
$c/= :: PullRequestOptions -> PullRequestOptions -> Bool
== :: PullRequestOptions -> PullRequestOptions -> Bool
$c== :: PullRequestOptions -> PullRequestOptions -> Bool
Eq, Eq PullRequestOptions
PullRequestOptions -> PullRequestOptions -> Bool
PullRequestOptions -> PullRequestOptions -> Ordering
PullRequestOptions -> PullRequestOptions -> PullRequestOptions
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 :: PullRequestOptions -> PullRequestOptions -> PullRequestOptions
$cmin :: PullRequestOptions -> PullRequestOptions -> PullRequestOptions
max :: PullRequestOptions -> PullRequestOptions -> PullRequestOptions
$cmax :: PullRequestOptions -> PullRequestOptions -> PullRequestOptions
>= :: PullRequestOptions -> PullRequestOptions -> Bool
$c>= :: PullRequestOptions -> PullRequestOptions -> Bool
> :: PullRequestOptions -> PullRequestOptions -> Bool
$c> :: PullRequestOptions -> PullRequestOptions -> Bool
<= :: PullRequestOptions -> PullRequestOptions -> Bool
$c<= :: PullRequestOptions -> PullRequestOptions -> Bool
< :: PullRequestOptions -> PullRequestOptions -> Bool
$c< :: PullRequestOptions -> PullRequestOptions -> Bool
compare :: PullRequestOptions -> PullRequestOptions -> Ordering
$ccompare :: PullRequestOptions -> PullRequestOptions -> Ordering
Ord, Int -> PullRequestOptions -> ShowS
[PullRequestOptions] -> ShowS
PullRequestOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PullRequestOptions] -> ShowS
$cshowList :: [PullRequestOptions] -> ShowS
show :: PullRequestOptions -> String
$cshow :: PullRequestOptions -> String
showsPrec :: Int -> PullRequestOptions -> ShowS
$cshowsPrec :: Int -> PullRequestOptions -> ShowS
Show, forall x. Rep PullRequestOptions x -> PullRequestOptions
forall x. PullRequestOptions -> Rep PullRequestOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PullRequestOptions x -> PullRequestOptions
$cfrom :: forall x. PullRequestOptions -> Rep PullRequestOptions x
Generic, Typeable, Typeable PullRequestOptions
PullRequestOptions -> DataType
PullRequestOptions -> Constr
(forall b. Data b => b -> b)
-> PullRequestOptions -> PullRequestOptions
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> PullRequestOptions -> u
forall u. (forall d. Data d => d -> u) -> PullRequestOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PullRequestOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PullRequestOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PullRequestOptions -> m PullRequestOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullRequestOptions -> m PullRequestOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PullRequestOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PullRequestOptions
-> c PullRequestOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PullRequestOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PullRequestOptions)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullRequestOptions -> m PullRequestOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullRequestOptions -> m PullRequestOptions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullRequestOptions -> m PullRequestOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PullRequestOptions -> m PullRequestOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PullRequestOptions -> m PullRequestOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PullRequestOptions -> m PullRequestOptions
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PullRequestOptions -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PullRequestOptions -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PullRequestOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PullRequestOptions -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PullRequestOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PullRequestOptions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PullRequestOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PullRequestOptions -> r
gmapT :: (forall b. Data b => b -> b)
-> PullRequestOptions -> PullRequestOptions
$cgmapT :: (forall b. Data b => b -> b)
-> PullRequestOptions -> PullRequestOptions
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PullRequestOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PullRequestOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PullRequestOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PullRequestOptions)
dataTypeOf :: PullRequestOptions -> DataType
$cdataTypeOf :: PullRequestOptions -> DataType
toConstr :: PullRequestOptions -> Constr
$ctoConstr :: PullRequestOptions -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PullRequestOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PullRequestOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PullRequestOptions
-> c PullRequestOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PullRequestOptions
-> c PullRequestOptions
Data)
defaultPullRequestOptions :: PullRequestOptions
defaultPullRequestOptions :: PullRequestOptions
defaultPullRequestOptions = PullRequestOptions
{ pullRequestOptionsState :: Maybe IssueState
pullRequestOptionsState = forall a. a -> Maybe a
Just IssueState
StateOpen
, pullRequestOptionsHead :: Maybe Text
pullRequestOptionsHead = forall a. Maybe a
Nothing
, pullRequestOptionsBase :: Maybe Text
pullRequestOptionsBase = forall a. Maybe a
Nothing
, pullRequestOptionsSort :: SortPR
pullRequestOptionsSort = SortPR
SortPRCreated
, pullRequestOptionsDirection :: SortDirection
pullRequestOptionsDirection = SortDirection
SortDescending
}
newtype PullRequestMod = PRMod (PullRequestOptions -> PullRequestOptions)
instance Semigroup PullRequestMod where
PRMod PullRequestOptions -> PullRequestOptions
f <> :: PullRequestMod -> PullRequestMod -> PullRequestMod
<> PRMod PullRequestOptions -> PullRequestOptions
g = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod (PullRequestOptions -> PullRequestOptions
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. PullRequestOptions -> PullRequestOptions
f)
instance Monoid PullRequestMod where
mempty :: PullRequestMod
mempty = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a. a -> a
id
mappend :: PullRequestMod -> PullRequestMod -> PullRequestMod
mappend = forall a. Semigroup a => a -> a -> a
(<>)
toPullRequestOptions :: PullRequestMod -> PullRequestOptions
toPullRequestOptions :: PullRequestMod -> PullRequestOptions
toPullRequestOptions (PRMod PullRequestOptions -> PullRequestOptions
f) = PullRequestOptions -> PullRequestOptions
f PullRequestOptions
defaultPullRequestOptions
prModToQueryString :: PullRequestMod -> QueryString
prModToQueryString :: PullRequestMod -> QueryString
prModToQueryString = PullRequestOptions -> QueryString
pullRequestOptionsToQueryString forall b c a. (b -> c) -> (a -> b) -> a -> c
. PullRequestMod -> PullRequestOptions
toPullRequestOptions
pullRequestOptionsToQueryString :: PullRequestOptions -> QueryString
pullRequestOptionsToQueryString :: PullRequestOptions -> QueryString
pullRequestOptionsToQueryString (PullRequestOptions Maybe IssueState
st Maybe Text
head_ Maybe Text
base SortPR
sort SortDirection
dir) =
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"state" ByteString
state'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"sort" ByteString
sort'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"direction" ByteString
direction'
] forall a. [a] -> [a] -> [a]
++ forall a. [Maybe a] -> [a]
catMaybes
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"head" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
head'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"base" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
base'
]
where
mk :: a -> a -> (a, Maybe a)
mk a
k a
v = (a
k, forall a. a -> Maybe a
Just a
v)
state' :: ByteString
state' = case Maybe IssueState
st of
Maybe IssueState
Nothing -> ByteString
"all"
Just IssueState
StateOpen -> ByteString
"open"
Just IssueState
StateClosed -> ByteString
"closed"
sort' :: ByteString
sort' = case SortPR
sort of
SortPR
SortPRCreated -> ByteString
"created"
SortPR
SortPRUpdated -> ByteString
"updated"
SortPR
SortPRPopularity -> ByteString
"popularity"
SortPR
SortPRLongRunning -> ByteString
"long-running"
direction' :: ByteString
direction' = case SortDirection
dir of
SortDirection
SortDescending -> ByteString
"desc"
SortDirection
SortAscending -> ByteString
"asc"
head' :: Maybe ByteString
head' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
head_
base' :: Maybe ByteString
base' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
base
optionsBase :: Text -> PullRequestMod
optionsBase :: Text -> PullRequestMod
optionsBase Text
x = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsBase :: Maybe Text
pullRequestOptionsBase = forall a. a -> Maybe a
Just Text
x }
optionsNoBase :: PullRequestMod
optionsNoBase :: PullRequestMod
optionsNoBase = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsBase :: Maybe Text
pullRequestOptionsBase = forall a. Maybe a
Nothing }
optionsHead :: Text -> PullRequestMod
optionsHead :: Text -> PullRequestMod
optionsHead Text
x = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsHead :: Maybe Text
pullRequestOptionsHead = forall a. a -> Maybe a
Just Text
x }
optionsNoHead :: PullRequestMod
optionsNoHead :: PullRequestMod
optionsNoHead = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsHead :: Maybe Text
pullRequestOptionsHead = forall a. Maybe a
Nothing }
sortByPopularity :: PullRequestMod
sortByPopularity :: PullRequestMod
sortByPopularity = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsSort :: SortPR
pullRequestOptionsSort = SortPR
SortPRPopularity }
sortByLongRunning :: PullRequestMod
sortByLongRunning :: PullRequestMod
sortByLongRunning = (PullRequestOptions -> PullRequestOptions) -> PullRequestMod
PRMod forall a b. (a -> b) -> a -> b
$ \PullRequestOptions
opts ->
PullRequestOptions
opts { pullRequestOptionsSort :: SortPR
pullRequestOptionsSort = SortPR
SortPRLongRunning }
data IssueOptions = IssueOptions
{ IssueOptions -> IssueFilter
issueOptionsFilter :: !IssueFilter
, IssueOptions -> Maybe IssueState
issueOptionsState :: !(Maybe IssueState)
, IssueOptions -> [Name IssueLabel]
issueOptionsLabels :: ![Name IssueLabel]
, IssueOptions -> SortIssue
issueOptionsSort :: !SortIssue
, IssueOptions -> SortDirection
issueOptionsDirection :: !SortDirection
, IssueOptions -> Maybe UTCTime
issueOptionsSince :: !(Maybe UTCTime)
}
deriving
(IssueOptions -> IssueOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IssueOptions -> IssueOptions -> Bool
$c/= :: IssueOptions -> IssueOptions -> Bool
== :: IssueOptions -> IssueOptions -> Bool
$c== :: IssueOptions -> IssueOptions -> Bool
Eq, Eq IssueOptions
IssueOptions -> IssueOptions -> Bool
IssueOptions -> IssueOptions -> Ordering
IssueOptions -> IssueOptions -> IssueOptions
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 :: IssueOptions -> IssueOptions -> IssueOptions
$cmin :: IssueOptions -> IssueOptions -> IssueOptions
max :: IssueOptions -> IssueOptions -> IssueOptions
$cmax :: IssueOptions -> IssueOptions -> IssueOptions
>= :: IssueOptions -> IssueOptions -> Bool
$c>= :: IssueOptions -> IssueOptions -> Bool
> :: IssueOptions -> IssueOptions -> Bool
$c> :: IssueOptions -> IssueOptions -> Bool
<= :: IssueOptions -> IssueOptions -> Bool
$c<= :: IssueOptions -> IssueOptions -> Bool
< :: IssueOptions -> IssueOptions -> Bool
$c< :: IssueOptions -> IssueOptions -> Bool
compare :: IssueOptions -> IssueOptions -> Ordering
$ccompare :: IssueOptions -> IssueOptions -> Ordering
Ord, Int -> IssueOptions -> ShowS
[IssueOptions] -> ShowS
IssueOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IssueOptions] -> ShowS
$cshowList :: [IssueOptions] -> ShowS
show :: IssueOptions -> String
$cshow :: IssueOptions -> String
showsPrec :: Int -> IssueOptions -> ShowS
$cshowsPrec :: Int -> IssueOptions -> ShowS
Show, forall x. Rep IssueOptions x -> IssueOptions
forall x. IssueOptions -> Rep IssueOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IssueOptions x -> IssueOptions
$cfrom :: forall x. IssueOptions -> Rep IssueOptions x
Generic, Typeable, Typeable IssueOptions
IssueOptions -> DataType
IssueOptions -> Constr
(forall b. Data b => b -> b) -> IssueOptions -> IssueOptions
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> IssueOptions -> u
forall u. (forall d. Data d => d -> u) -> IssueOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueOptions -> m IssueOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueOptions -> m IssueOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueOptions -> c IssueOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueOptions)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueOptions -> m IssueOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueOptions -> m IssueOptions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueOptions -> m IssueOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> IssueOptions -> m IssueOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueOptions -> m IssueOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> IssueOptions -> m IssueOptions
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IssueOptions -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> IssueOptions -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> IssueOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IssueOptions -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueOptions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueOptions -> r
gmapT :: (forall b. Data b => b -> b) -> IssueOptions -> IssueOptions
$cgmapT :: (forall b. Data b => b -> b) -> IssueOptions -> IssueOptions
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueOptions)
dataTypeOf :: IssueOptions -> DataType
$cdataTypeOf :: IssueOptions -> DataType
toConstr :: IssueOptions -> Constr
$ctoConstr :: IssueOptions -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueOptions -> c IssueOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueOptions -> c IssueOptions
Data)
defaultIssueOptions :: IssueOptions
defaultIssueOptions :: IssueOptions
defaultIssueOptions = IssueOptions
{ issueOptionsFilter :: IssueFilter
issueOptionsFilter = IssueFilter
IssueFilterAssigned
, issueOptionsState :: Maybe IssueState
issueOptionsState = forall a. a -> Maybe a
Just IssueState
StateOpen
, issueOptionsLabels :: [Name IssueLabel]
issueOptionsLabels = []
, issueOptionsSort :: SortIssue
issueOptionsSort = SortIssue
SortIssueCreated
, issueOptionsDirection :: SortDirection
issueOptionsDirection = SortDirection
SortDescending
, issueOptionsSince :: Maybe UTCTime
issueOptionsSince = forall a. Maybe a
Nothing
}
newtype IssueMod = IssueMod (IssueOptions -> IssueOptions)
instance Semigroup IssueMod where
IssueMod IssueOptions -> IssueOptions
f <> :: IssueMod -> IssueMod -> IssueMod
<> IssueMod IssueOptions -> IssueOptions
g = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod (IssueOptions -> IssueOptions
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. IssueOptions -> IssueOptions
f)
instance Monoid IssueMod where
mempty :: IssueMod
mempty = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a. a -> a
id
mappend :: IssueMod -> IssueMod -> IssueMod
mappend = forall a. Semigroup a => a -> a -> a
(<>)
toIssueOptions :: IssueMod -> IssueOptions
toIssueOptions :: IssueMod -> IssueOptions
toIssueOptions (IssueMod IssueOptions -> IssueOptions
f) = IssueOptions -> IssueOptions
f IssueOptions
defaultIssueOptions
issueModToQueryString :: IssueMod -> QueryString
issueModToQueryString :: IssueMod -> QueryString
issueModToQueryString = IssueOptions -> QueryString
issueOptionsToQueryString forall b c a. (b -> c) -> (a -> b) -> a -> c
. IssueMod -> IssueOptions
toIssueOptions
issueOptionsToQueryString :: IssueOptions -> QueryString
issueOptionsToQueryString :: IssueOptions -> QueryString
issueOptionsToQueryString (IssueOptions IssueFilter
filt Maybe IssueState
st [Name IssueLabel]
labels SortIssue
sort SortDirection
dir Maybe UTCTime
since) =
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"state" ByteString
state'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"sort" ByteString
sort'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"direction" ByteString
direction'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"filter" ByteString
filt'
] forall a. [a] -> [a] -> [a]
++ forall a. [Maybe a] -> [a]
catMaybes
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"labels" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
labels'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"since" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
since'
]
where
mk :: a -> a -> (a, Maybe a)
mk a
k a
v = (a
k, forall a. a -> Maybe a
Just a
v)
filt' :: ByteString
filt' = case IssueFilter
filt of
IssueFilter
IssueFilterAssigned -> ByteString
"assigned"
IssueFilter
IssueFilterCreated -> ByteString
"created"
IssueFilter
IssueFilterMentioned -> ByteString
"mentioned"
IssueFilter
IssueFilterSubscribed -> ByteString
"subscribed"
IssueFilter
IssueFilterAll -> ByteString
"all"
state' :: ByteString
state' = case Maybe IssueState
st of
Maybe IssueState
Nothing -> ByteString
"all"
Just IssueState
StateOpen -> ByteString
"open"
Just IssueState
StateClosed -> ByteString
"closed"
sort' :: ByteString
sort' = case SortIssue
sort of
SortIssue
SortIssueCreated -> ByteString
"created"
SortIssue
SortIssueUpdated -> ByteString
"updated"
SortIssue
SortIssueComments -> ByteString
"comments"
direction' :: ByteString
direction' = case SortDirection
dir of
SortDirection
SortDescending -> ByteString
"desc"
SortDirection
SortAscending -> ByteString
"asc"
since' :: Maybe ByteString
since' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> ByteString
TE.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show) Maybe UTCTime
since
labels' :: Maybe ByteString
labels' = Text -> ByteString
TE.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
"," forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall entity. Name entity -> Text
untagName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Foldable f => f a -> Maybe (f a)
nullToNothing [Name IssueLabel]
labels
nullToNothing :: Foldable f => f a -> Maybe (f a)
nullToNothing :: forall (f :: * -> *) a. Foldable f => f a -> Maybe (f a)
nullToNothing f a
xs
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null f a
xs = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just f a
xs
class mod where
:: mod
instance HasComments IssueMod where
sortByComments :: IssueMod
sortByComments = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsSort :: SortIssue
issueOptionsSort = SortIssue
SortIssueComments }
instance HasComments IssueRepoMod where
sortByComments :: IssueRepoMod
sortByComments = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsSort :: SortIssue
issueRepoOptionsSort = SortIssue
SortIssueComments }
class HasLabels mod where
optionsLabels :: Foldable f => f (Name IssueLabel) -> mod
instance HasLabels IssueMod where
optionsLabels :: forall (f :: * -> *). Foldable f => f (Name IssueLabel) -> IssueMod
optionsLabels f (Name IssueLabel)
lbls = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsLabels :: [Name IssueLabel]
issueOptionsLabels = forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (Name IssueLabel)
lbls }
instance HasLabels IssueRepoMod where
optionsLabels :: forall (f :: * -> *).
Foldable f =>
f (Name IssueLabel) -> IssueRepoMod
optionsLabels f (Name IssueLabel)
lbls = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsLabels :: [Name IssueLabel]
issueRepoOptionsLabels = forall (t :: * -> *) a. Foldable t => t a -> [a]
toList f (Name IssueLabel)
lbls }
class HasSince mod where
optionsSince :: UTCTime -> mod
optionsSinceAll :: mod
instance HasSince IssueMod where
optionsSince :: UTCTime -> IssueMod
optionsSince UTCTime
since = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsSince :: Maybe UTCTime
issueOptionsSince = forall a. a -> Maybe a
Just UTCTime
since }
optionsSinceAll :: IssueMod
optionsSinceAll = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsSince :: Maybe UTCTime
issueOptionsSince = forall a. Maybe a
Nothing }
instance HasSince IssueRepoMod where
optionsSince :: UTCTime -> IssueRepoMod
optionsSince UTCTime
since = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsSince :: Maybe UTCTime
issueRepoOptionsSince = forall a. a -> Maybe a
Just UTCTime
since }
optionsSinceAll :: IssueRepoMod
optionsSinceAll = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsSince :: Maybe UTCTime
issueRepoOptionsSince = forall a. Maybe a
Nothing }
optionsAssignedIssues, optionsCreatedIssues, optionsMentionedIssues,
optionsSubscribedIssues, optionsAllIssues :: IssueMod
optionsAssignedIssues :: IssueMod
optionsAssignedIssues = IssueFilter -> IssueMod
issueFilter IssueFilter
IssueFilterAssigned
optionsCreatedIssues :: IssueMod
optionsCreatedIssues = IssueFilter -> IssueMod
issueFilter IssueFilter
IssueFilterCreated
optionsMentionedIssues :: IssueMod
optionsMentionedIssues = IssueFilter -> IssueMod
issueFilter IssueFilter
IssueFilterMentioned
optionsSubscribedIssues :: IssueMod
optionsSubscribedIssues = IssueFilter -> IssueMod
issueFilter IssueFilter
IssueFilterSubscribed
optionsAllIssues :: IssueMod
optionsAllIssues = IssueFilter -> IssueMod
issueFilter IssueFilter
IssueFilterAll
issueFilter :: IssueFilter -> IssueMod
issueFilter :: IssueFilter -> IssueMod
issueFilter IssueFilter
f = (IssueOptions -> IssueOptions) -> IssueMod
IssueMod forall a b. (a -> b) -> a -> b
$ \IssueOptions
opts ->
IssueOptions
opts { issueOptionsFilter :: IssueFilter
issueOptionsFilter = IssueFilter
f }
data IssueRepoOptions = IssueRepoOptions
{ IssueRepoOptions -> FilterBy (Id Milestone)
issueRepoOptionsMilestone :: !(FilterBy (Id Milestone))
, IssueRepoOptions -> Maybe IssueState
issueRepoOptionsState :: !(Maybe IssueState)
, IssueRepoOptions -> FilterBy (Name User)
issueRepoOptionsAssignee :: !(FilterBy (Name User))
, IssueRepoOptions -> Maybe (Name User)
issueRepoOptionsCreator :: !(Maybe (Name User))
, IssueRepoOptions -> Maybe (Name User)
issueRepoOptionsMentioned :: !(Maybe (Name User))
, IssueRepoOptions -> [Name IssueLabel]
issueRepoOptionsLabels :: ![Name IssueLabel]
, IssueRepoOptions -> SortIssue
issueRepoOptionsSort :: !SortIssue
, IssueRepoOptions -> SortDirection
issueRepoOptionsDirection :: !SortDirection
, IssueRepoOptions -> Maybe UTCTime
issueRepoOptionsSince :: !(Maybe UTCTime)
}
deriving
(IssueRepoOptions -> IssueRepoOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IssueRepoOptions -> IssueRepoOptions -> Bool
$c/= :: IssueRepoOptions -> IssueRepoOptions -> Bool
== :: IssueRepoOptions -> IssueRepoOptions -> Bool
$c== :: IssueRepoOptions -> IssueRepoOptions -> Bool
Eq, Eq IssueRepoOptions
IssueRepoOptions -> IssueRepoOptions -> Bool
IssueRepoOptions -> IssueRepoOptions -> Ordering
IssueRepoOptions -> IssueRepoOptions -> IssueRepoOptions
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 :: IssueRepoOptions -> IssueRepoOptions -> IssueRepoOptions
$cmin :: IssueRepoOptions -> IssueRepoOptions -> IssueRepoOptions
max :: IssueRepoOptions -> IssueRepoOptions -> IssueRepoOptions
$cmax :: IssueRepoOptions -> IssueRepoOptions -> IssueRepoOptions
>= :: IssueRepoOptions -> IssueRepoOptions -> Bool
$c>= :: IssueRepoOptions -> IssueRepoOptions -> Bool
> :: IssueRepoOptions -> IssueRepoOptions -> Bool
$c> :: IssueRepoOptions -> IssueRepoOptions -> Bool
<= :: IssueRepoOptions -> IssueRepoOptions -> Bool
$c<= :: IssueRepoOptions -> IssueRepoOptions -> Bool
< :: IssueRepoOptions -> IssueRepoOptions -> Bool
$c< :: IssueRepoOptions -> IssueRepoOptions -> Bool
compare :: IssueRepoOptions -> IssueRepoOptions -> Ordering
$ccompare :: IssueRepoOptions -> IssueRepoOptions -> Ordering
Ord, Int -> IssueRepoOptions -> ShowS
[IssueRepoOptions] -> ShowS
IssueRepoOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IssueRepoOptions] -> ShowS
$cshowList :: [IssueRepoOptions] -> ShowS
show :: IssueRepoOptions -> String
$cshow :: IssueRepoOptions -> String
showsPrec :: Int -> IssueRepoOptions -> ShowS
$cshowsPrec :: Int -> IssueRepoOptions -> ShowS
Show, forall x. Rep IssueRepoOptions x -> IssueRepoOptions
forall x. IssueRepoOptions -> Rep IssueRepoOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IssueRepoOptions x -> IssueRepoOptions
$cfrom :: forall x. IssueRepoOptions -> Rep IssueRepoOptions x
Generic, Typeable, Typeable IssueRepoOptions
IssueRepoOptions -> DataType
IssueRepoOptions -> Constr
(forall b. Data b => b -> b)
-> IssueRepoOptions -> IssueRepoOptions
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> IssueRepoOptions -> u
forall u. (forall d. Data d => d -> u) -> IssueRepoOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueRepoOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueRepoOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IssueRepoOptions -> m IssueRepoOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueRepoOptions -> m IssueRepoOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueRepoOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueRepoOptions -> c IssueRepoOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueRepoOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueRepoOptions)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueRepoOptions -> m IssueRepoOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueRepoOptions -> m IssueRepoOptions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueRepoOptions -> m IssueRepoOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> IssueRepoOptions -> m IssueRepoOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IssueRepoOptions -> m IssueRepoOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> IssueRepoOptions -> m IssueRepoOptions
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IssueRepoOptions -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> IssueRepoOptions -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> IssueRepoOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> IssueRepoOptions -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueRepoOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> IssueRepoOptions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueRepoOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> IssueRepoOptions -> r
gmapT :: (forall b. Data b => b -> b)
-> IssueRepoOptions -> IssueRepoOptions
$cgmapT :: (forall b. Data b => b -> b)
-> IssueRepoOptions -> IssueRepoOptions
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueRepoOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c IssueRepoOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueRepoOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c IssueRepoOptions)
dataTypeOf :: IssueRepoOptions -> DataType
$cdataTypeOf :: IssueRepoOptions -> DataType
toConstr :: IssueRepoOptions -> Constr
$ctoConstr :: IssueRepoOptions -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueRepoOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c IssueRepoOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueRepoOptions -> c IssueRepoOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IssueRepoOptions -> c IssueRepoOptions
Data)
defaultIssueRepoOptions :: IssueRepoOptions
defaultIssueRepoOptions :: IssueRepoOptions
defaultIssueRepoOptions = IssueRepoOptions
{ issueRepoOptionsMilestone :: FilterBy (Id Milestone)
issueRepoOptionsMilestone = forall a. FilterBy a
FilterNotSpecified
, issueRepoOptionsState :: Maybe IssueState
issueRepoOptionsState = (forall a. a -> Maybe a
Just IssueState
StateOpen)
, issueRepoOptionsAssignee :: FilterBy (Name User)
issueRepoOptionsAssignee = forall a. FilterBy a
FilterNotSpecified
, issueRepoOptionsCreator :: Maybe (Name User)
issueRepoOptionsCreator = forall a. Maybe a
Nothing
, issueRepoOptionsMentioned :: Maybe (Name User)
issueRepoOptionsMentioned = forall a. Maybe a
Nothing
, issueRepoOptionsLabels :: [Name IssueLabel]
issueRepoOptionsLabels = []
, issueRepoOptionsSort :: SortIssue
issueRepoOptionsSort = SortIssue
SortIssueCreated
, issueRepoOptionsDirection :: SortDirection
issueRepoOptionsDirection = SortDirection
SortDescending
, issueRepoOptionsSince :: Maybe UTCTime
issueRepoOptionsSince = forall a. Maybe a
Nothing
}
newtype IssueRepoMod = IssueRepoMod (IssueRepoOptions -> IssueRepoOptions)
instance Semigroup IssueRepoMod where
IssueRepoMod IssueRepoOptions -> IssueRepoOptions
f <> :: IssueRepoMod -> IssueRepoMod -> IssueRepoMod
<> IssueRepoMod IssueRepoOptions -> IssueRepoOptions
g = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod (IssueRepoOptions -> IssueRepoOptions
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. IssueRepoOptions -> IssueRepoOptions
f)
instance Monoid IssueRepoMod where
mempty :: IssueRepoMod
mempty = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a. a -> a
id
mappend :: IssueRepoMod -> IssueRepoMod -> IssueRepoMod
mappend = forall a. Semigroup a => a -> a -> a
(<>)
toIssueRepoOptions :: IssueRepoMod -> IssueRepoOptions
toIssueRepoOptions :: IssueRepoMod -> IssueRepoOptions
toIssueRepoOptions (IssueRepoMod IssueRepoOptions -> IssueRepoOptions
f) = IssueRepoOptions -> IssueRepoOptions
f IssueRepoOptions
defaultIssueRepoOptions
issueRepoModToQueryString :: IssueRepoMod -> QueryString
issueRepoModToQueryString :: IssueRepoMod -> QueryString
issueRepoModToQueryString = IssueRepoOptions -> QueryString
issueRepoOptionsToQueryString forall b c a. (b -> c) -> (a -> b) -> a -> c
. IssueRepoMod -> IssueRepoOptions
toIssueRepoOptions
issueRepoOptionsToQueryString :: IssueRepoOptions -> QueryString
issueRepoOptionsToQueryString :: IssueRepoOptions -> QueryString
issueRepoOptionsToQueryString IssueRepoOptions {[Name IssueLabel]
Maybe UTCTime
Maybe (Name User)
Maybe IssueState
FilterBy (Name User)
FilterBy (Id Milestone)
SortIssue
SortDirection
issueRepoOptionsSince :: Maybe UTCTime
issueRepoOptionsDirection :: SortDirection
issueRepoOptionsSort :: SortIssue
issueRepoOptionsLabels :: [Name IssueLabel]
issueRepoOptionsMentioned :: Maybe (Name User)
issueRepoOptionsCreator :: Maybe (Name User)
issueRepoOptionsAssignee :: FilterBy (Name User)
issueRepoOptionsState :: Maybe IssueState
issueRepoOptionsMilestone :: FilterBy (Id Milestone)
issueRepoOptionsMentioned :: IssueRepoOptions -> Maybe (Name User)
issueRepoOptionsCreator :: IssueRepoOptions -> Maybe (Name User)
issueRepoOptionsAssignee :: IssueRepoOptions -> FilterBy (Name User)
issueRepoOptionsMilestone :: IssueRepoOptions -> FilterBy (Id Milestone)
issueRepoOptionsSince :: IssueRepoOptions -> Maybe UTCTime
issueRepoOptionsLabels :: IssueRepoOptions -> [Name IssueLabel]
issueRepoOptionsSort :: IssueRepoOptions -> SortIssue
issueRepoOptionsDirection :: IssueRepoOptions -> SortDirection
issueRepoOptionsState :: IssueRepoOptions -> Maybe IssueState
..} =
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"state" ByteString
state'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"sort" ByteString
sort'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"direction" ByteString
direction'
] forall a. [a] -> [a] -> [a]
++ forall a. [Maybe a] -> [a]
catMaybes
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"milestone" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
milestone'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"assignee" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
assignee'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"labels" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
labels'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"since" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
since'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"creator" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
creator'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"mentioned" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
mentioned'
]
where
mk :: a -> a -> (a, Maybe a)
mk a
k a
v = (a
k, forall a. a -> Maybe a
Just a
v)
filt :: (t -> Text) -> FilterBy t -> Maybe ByteString
filt t -> Text
f FilterBy t
x = case FilterBy t
x of
FilterBy t
FilterAny -> forall a. a -> Maybe a
Just ByteString
"*"
FilterBy t
FilterNone -> forall a. a -> Maybe a
Just ByteString
"none"
FilterBy t
x' -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> ByteString
TE.encodeUtf8 forall a b. (a -> b) -> a -> b
$ t -> Text
f t
x'
FilterBy t
FilterNotSpecified -> forall a. Maybe a
Nothing
milestone' :: Maybe ByteString
milestone' = forall {t}. (t -> Text) -> FilterBy t -> Maybe ByteString
filt (String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall entity. Id entity -> Int
untagId) FilterBy (Id Milestone)
issueRepoOptionsMilestone
assignee' :: Maybe ByteString
assignee' = forall {t}. (t -> Text) -> FilterBy t -> Maybe ByteString
filt forall entity. Name entity -> Text
untagName FilterBy (Name User)
issueRepoOptionsAssignee
state' :: ByteString
state' = case Maybe IssueState
issueRepoOptionsState of
Maybe IssueState
Nothing -> ByteString
"all"
Just IssueState
StateOpen -> ByteString
"open"
Just IssueState
StateClosed -> ByteString
"closed"
sort' :: ByteString
sort' = case SortIssue
issueRepoOptionsSort of
SortIssue
SortIssueCreated -> ByteString
"created"
SortIssue
SortIssueUpdated -> ByteString
"updated"
SortIssue
SortIssueComments -> ByteString
"comments"
direction' :: ByteString
direction' = case SortDirection
issueRepoOptionsDirection of
SortDirection
SortDescending -> ByteString
"desc"
SortDirection
SortAscending -> ByteString
"asc"
since' :: Maybe ByteString
since' = Text -> ByteString
TE.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe UTCTime
issueRepoOptionsSince
labels' :: Maybe ByteString
labels' = Text -> ByteString
TE.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
"," forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall entity. Name entity -> Text
untagName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Foldable f => f a -> Maybe (f a)
nullToNothing [Name IssueLabel]
issueRepoOptionsLabels
creator' :: Maybe ByteString
creator' = Text -> ByteString
TE.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall entity. Name entity -> Text
untagName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Name User)
issueRepoOptionsCreator
mentioned' :: Maybe ByteString
mentioned' = Text -> ByteString
TE.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall entity. Name entity -> Text
untagName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Name User)
issueRepoOptionsMentioned
optionsCreator :: Name User -> IssueRepoMod
optionsCreator :: Name User -> IssueRepoMod
optionsCreator Name User
u = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsCreator :: Maybe (Name User)
issueRepoOptionsCreator = forall a. a -> Maybe a
Just Name User
u }
optionsMentioned :: Name User -> IssueRepoMod
optionsMentioned :: Name User -> IssueRepoMod
optionsMentioned Name User
u = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsMentioned :: Maybe (Name User)
issueRepoOptionsMentioned = forall a. a -> Maybe a
Just Name User
u }
optionsIrrelevantMilestone :: IssueRepoMod
optionsIrrelevantMilestone :: IssueRepoMod
optionsIrrelevantMilestone = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsMilestone :: FilterBy (Id Milestone)
issueRepoOptionsMilestone = forall a. FilterBy a
FilterNotSpecified }
optionsAnyMilestone :: IssueRepoMod
optionsAnyMilestone :: IssueRepoMod
optionsAnyMilestone = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsMilestone :: FilterBy (Id Milestone)
issueRepoOptionsMilestone = forall a. FilterBy a
FilterAny }
optionsNoMilestone :: IssueRepoMod
optionsNoMilestone :: IssueRepoMod
optionsNoMilestone = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsMilestone :: FilterBy (Id Milestone)
issueRepoOptionsMilestone = forall a. FilterBy a
FilterNone }
optionsMilestone :: Id Milestone -> IssueRepoMod
optionsMilestone :: Id Milestone -> IssueRepoMod
optionsMilestone Id Milestone
m = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsMilestone :: FilterBy (Id Milestone)
issueRepoOptionsMilestone = forall a. a -> FilterBy a
FilterBy Id Milestone
m }
optionsIrrelevantAssignee :: IssueRepoMod
optionsIrrelevantAssignee :: IssueRepoMod
optionsIrrelevantAssignee = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsAssignee :: FilterBy (Name User)
issueRepoOptionsAssignee = forall a. FilterBy a
FilterNotSpecified }
optionsAnyAssignee :: IssueRepoMod
optionsAnyAssignee :: IssueRepoMod
optionsAnyAssignee = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsAssignee :: FilterBy (Name User)
issueRepoOptionsAssignee = forall a. FilterBy a
FilterAny }
optionsNoAssignee :: IssueRepoMod
optionsNoAssignee :: IssueRepoMod
optionsNoAssignee = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsAssignee :: FilterBy (Name User)
issueRepoOptionsAssignee = forall a. FilterBy a
FilterNone }
optionsAssignee :: Name User -> IssueRepoMod
optionsAssignee :: Name User -> IssueRepoMod
optionsAssignee Name User
u = (IssueRepoOptions -> IssueRepoOptions) -> IssueRepoMod
IssueRepoMod forall a b. (a -> b) -> a -> b
$ \IssueRepoOptions
opts ->
IssueRepoOptions
opts { issueRepoOptionsAssignee :: FilterBy (Name User)
issueRepoOptionsAssignee = forall a. a -> FilterBy a
FilterBy Name User
u }
data ArtifactOptions = ArtifactOptions
{ ArtifactOptions -> Maybe Text
artifactOptionsName :: !(Maybe Text)
}
deriving
(ArtifactOptions -> ArtifactOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArtifactOptions -> ArtifactOptions -> Bool
$c/= :: ArtifactOptions -> ArtifactOptions -> Bool
== :: ArtifactOptions -> ArtifactOptions -> Bool
$c== :: ArtifactOptions -> ArtifactOptions -> Bool
Eq, Eq ArtifactOptions
ArtifactOptions -> ArtifactOptions -> Bool
ArtifactOptions -> ArtifactOptions -> Ordering
ArtifactOptions -> ArtifactOptions -> ArtifactOptions
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 :: ArtifactOptions -> ArtifactOptions -> ArtifactOptions
$cmin :: ArtifactOptions -> ArtifactOptions -> ArtifactOptions
max :: ArtifactOptions -> ArtifactOptions -> ArtifactOptions
$cmax :: ArtifactOptions -> ArtifactOptions -> ArtifactOptions
>= :: ArtifactOptions -> ArtifactOptions -> Bool
$c>= :: ArtifactOptions -> ArtifactOptions -> Bool
> :: ArtifactOptions -> ArtifactOptions -> Bool
$c> :: ArtifactOptions -> ArtifactOptions -> Bool
<= :: ArtifactOptions -> ArtifactOptions -> Bool
$c<= :: ArtifactOptions -> ArtifactOptions -> Bool
< :: ArtifactOptions -> ArtifactOptions -> Bool
$c< :: ArtifactOptions -> ArtifactOptions -> Bool
compare :: ArtifactOptions -> ArtifactOptions -> Ordering
$ccompare :: ArtifactOptions -> ArtifactOptions -> Ordering
Ord, Int -> ArtifactOptions -> ShowS
[ArtifactOptions] -> ShowS
ArtifactOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ArtifactOptions] -> ShowS
$cshowList :: [ArtifactOptions] -> ShowS
show :: ArtifactOptions -> String
$cshow :: ArtifactOptions -> String
showsPrec :: Int -> ArtifactOptions -> ShowS
$cshowsPrec :: Int -> ArtifactOptions -> ShowS
Show, forall x. Rep ArtifactOptions x -> ArtifactOptions
forall x. ArtifactOptions -> Rep ArtifactOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ArtifactOptions x -> ArtifactOptions
$cfrom :: forall x. ArtifactOptions -> Rep ArtifactOptions x
Generic, Typeable, Typeable ArtifactOptions
ArtifactOptions -> DataType
ArtifactOptions -> Constr
(forall b. Data b => b -> b) -> ArtifactOptions -> ArtifactOptions
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ArtifactOptions -> u
forall u. (forall d. Data d => d -> u) -> ArtifactOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArtifactOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArtifactOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ArtifactOptions -> m ArtifactOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ArtifactOptions -> m ArtifactOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArtifactOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArtifactOptions -> c ArtifactOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArtifactOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ArtifactOptions)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ArtifactOptions -> m ArtifactOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ArtifactOptions -> m ArtifactOptions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ArtifactOptions -> m ArtifactOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ArtifactOptions -> m ArtifactOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ArtifactOptions -> m ArtifactOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ArtifactOptions -> m ArtifactOptions
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ArtifactOptions -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ArtifactOptions -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ArtifactOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ArtifactOptions -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArtifactOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ArtifactOptions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArtifactOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ArtifactOptions -> r
gmapT :: (forall b. Data b => b -> b) -> ArtifactOptions -> ArtifactOptions
$cgmapT :: (forall b. Data b => b -> b) -> ArtifactOptions -> ArtifactOptions
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ArtifactOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ArtifactOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArtifactOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ArtifactOptions)
dataTypeOf :: ArtifactOptions -> DataType
$cdataTypeOf :: ArtifactOptions -> DataType
toConstr :: ArtifactOptions -> Constr
$ctoConstr :: ArtifactOptions -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArtifactOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ArtifactOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArtifactOptions -> c ArtifactOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ArtifactOptions -> c ArtifactOptions
Data)
defaultArtifactOptions :: ArtifactOptions
defaultArtifactOptions :: ArtifactOptions
defaultArtifactOptions = ArtifactOptions
{ artifactOptionsName :: Maybe Text
artifactOptionsName = forall a. Maybe a
Nothing
}
newtype ArtifactMod = ArtifactMod (ArtifactOptions -> ArtifactOptions)
instance Semigroup ArtifactMod where
ArtifactMod ArtifactOptions -> ArtifactOptions
f <> :: ArtifactMod -> ArtifactMod -> ArtifactMod
<> ArtifactMod ArtifactOptions -> ArtifactOptions
g = (ArtifactOptions -> ArtifactOptions) -> ArtifactMod
ArtifactMod (ArtifactOptions -> ArtifactOptions
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtifactOptions -> ArtifactOptions
f)
instance Monoid ArtifactMod where
mempty :: ArtifactMod
mempty = (ArtifactOptions -> ArtifactOptions) -> ArtifactMod
ArtifactMod forall a. a -> a
id
mappend :: ArtifactMod -> ArtifactMod -> ArtifactMod
mappend = forall a. Semigroup a => a -> a -> a
(<>)
optionsArtifactName :: Text -> ArtifactMod
optionsArtifactName :: Text -> ArtifactMod
optionsArtifactName Text
n = (ArtifactOptions -> ArtifactOptions) -> ArtifactMod
ArtifactMod forall a b. (a -> b) -> a -> b
$ \ArtifactOptions
opts ->
ArtifactOptions
opts { artifactOptionsName :: Maybe Text
artifactOptionsName = forall a. a -> Maybe a
Just Text
n }
toArtifactOptions :: ArtifactMod -> ArtifactOptions
toArtifactOptions :: ArtifactMod -> ArtifactOptions
toArtifactOptions (ArtifactMod ArtifactOptions -> ArtifactOptions
f) = ArtifactOptions -> ArtifactOptions
f ArtifactOptions
defaultArtifactOptions
artifactModToQueryString :: ArtifactMod -> QueryString
artifactModToQueryString :: ArtifactMod -> QueryString
artifactModToQueryString = ArtifactOptions -> QueryString
artifactOptionsToQueryString forall b c a. (b -> c) -> (a -> b) -> a -> c
. ArtifactMod -> ArtifactOptions
toArtifactOptions
artifactOptionsToQueryString :: ArtifactOptions -> QueryString
artifactOptionsToQueryString :: ArtifactOptions -> QueryString
artifactOptionsToQueryString (ArtifactOptions Maybe Text
name) =
forall a. [Maybe a] -> [a]
catMaybes
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"name" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
name'
]
where
mk :: a -> a -> (a, Maybe a)
mk a
k a
v = (a
k, forall a. a -> Maybe a
Just a
v)
name' :: Maybe ByteString
name' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
name
data CacheOptions = CacheOptions
{ CacheOptions -> Maybe Text
cacheOptionsRef :: !(Maybe Text)
, CacheOptions -> Maybe Text
cacheOptionsKey :: !(Maybe Text)
, CacheOptions -> Maybe SortCache
cacheOptionsSort :: !(Maybe SortCache)
, CacheOptions -> Maybe SortDirection
cacheOptionsDirection :: !(Maybe SortDirection)
}
deriving
(CacheOptions -> CacheOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CacheOptions -> CacheOptions -> Bool
$c/= :: CacheOptions -> CacheOptions -> Bool
== :: CacheOptions -> CacheOptions -> Bool
$c== :: CacheOptions -> CacheOptions -> Bool
Eq, Eq CacheOptions
CacheOptions -> CacheOptions -> Bool
CacheOptions -> CacheOptions -> Ordering
CacheOptions -> CacheOptions -> CacheOptions
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 :: CacheOptions -> CacheOptions -> CacheOptions
$cmin :: CacheOptions -> CacheOptions -> CacheOptions
max :: CacheOptions -> CacheOptions -> CacheOptions
$cmax :: CacheOptions -> CacheOptions -> CacheOptions
>= :: CacheOptions -> CacheOptions -> Bool
$c>= :: CacheOptions -> CacheOptions -> Bool
> :: CacheOptions -> CacheOptions -> Bool
$c> :: CacheOptions -> CacheOptions -> Bool
<= :: CacheOptions -> CacheOptions -> Bool
$c<= :: CacheOptions -> CacheOptions -> Bool
< :: CacheOptions -> CacheOptions -> Bool
$c< :: CacheOptions -> CacheOptions -> Bool
compare :: CacheOptions -> CacheOptions -> Ordering
$ccompare :: CacheOptions -> CacheOptions -> Ordering
Ord, Int -> CacheOptions -> ShowS
[CacheOptions] -> ShowS
CacheOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CacheOptions] -> ShowS
$cshowList :: [CacheOptions] -> ShowS
show :: CacheOptions -> String
$cshow :: CacheOptions -> String
showsPrec :: Int -> CacheOptions -> ShowS
$cshowsPrec :: Int -> CacheOptions -> ShowS
Show, forall x. Rep CacheOptions x -> CacheOptions
forall x. CacheOptions -> Rep CacheOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CacheOptions x -> CacheOptions
$cfrom :: forall x. CacheOptions -> Rep CacheOptions x
Generic, Typeable, Typeable CacheOptions
CacheOptions -> DataType
CacheOptions -> Constr
(forall b. Data b => b -> b) -> CacheOptions -> CacheOptions
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> CacheOptions -> u
forall u. (forall d. Data d => d -> u) -> CacheOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CacheOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CacheOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CacheOptions -> m CacheOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CacheOptions -> m CacheOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CacheOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CacheOptions -> c CacheOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CacheOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CacheOptions)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CacheOptions -> m CacheOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CacheOptions -> m CacheOptions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CacheOptions -> m CacheOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> CacheOptions -> m CacheOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CacheOptions -> m CacheOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> CacheOptions -> m CacheOptions
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CacheOptions -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> CacheOptions -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> CacheOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> CacheOptions -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CacheOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CacheOptions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CacheOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CacheOptions -> r
gmapT :: (forall b. Data b => b -> b) -> CacheOptions -> CacheOptions
$cgmapT :: (forall b. Data b => b -> b) -> CacheOptions -> CacheOptions
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CacheOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c CacheOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CacheOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c CacheOptions)
dataTypeOf :: CacheOptions -> DataType
$cdataTypeOf :: CacheOptions -> DataType
toConstr :: CacheOptions -> Constr
$ctoConstr :: CacheOptions -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CacheOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CacheOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CacheOptions -> c CacheOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CacheOptions -> c CacheOptions
Data)
defaultCacheOptions :: CacheOptions
defaultCacheOptions :: CacheOptions
defaultCacheOptions = CacheOptions
{ cacheOptionsRef :: Maybe Text
cacheOptionsRef = forall a. Maybe a
Nothing
, cacheOptionsKey :: Maybe Text
cacheOptionsKey = forall a. Maybe a
Nothing
, cacheOptionsSort :: Maybe SortCache
cacheOptionsSort = forall a. Maybe a
Nothing
, cacheOptionsDirection :: Maybe SortDirection
cacheOptionsDirection = forall a. Maybe a
Nothing
}
newtype CacheMod = CacheMod (CacheOptions -> CacheOptions)
instance Semigroup CacheMod where
CacheMod CacheOptions -> CacheOptions
f <> :: CacheMod -> CacheMod -> CacheMod
<> CacheMod CacheOptions -> CacheOptions
g = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod (CacheOptions -> CacheOptions
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. CacheOptions -> CacheOptions
f)
instance Monoid CacheMod where
mempty :: CacheMod
mempty = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a. a -> a
id
mappend :: CacheMod -> CacheMod -> CacheMod
mappend = forall a. Semigroup a => a -> a -> a
(<>)
toCacheOptions :: CacheMod -> CacheOptions
toCacheOptions :: CacheMod -> CacheOptions
toCacheOptions (CacheMod CacheOptions -> CacheOptions
f) = CacheOptions -> CacheOptions
f CacheOptions
defaultCacheOptions
cacheModToQueryString :: CacheMod -> QueryString
cacheModToQueryString :: CacheMod -> QueryString
cacheModToQueryString = CacheOptions -> QueryString
cacheOptionsToQueryString forall b c a. (b -> c) -> (a -> b) -> a -> c
. CacheMod -> CacheOptions
toCacheOptions
cacheOptionsToQueryString :: CacheOptions -> QueryString
cacheOptionsToQueryString :: CacheOptions -> QueryString
cacheOptionsToQueryString (CacheOptions Maybe Text
ref Maybe Text
key Maybe SortCache
sort Maybe SortDirection
dir) =
forall a. [Maybe a] -> [a]
catMaybes
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"ref" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
ref'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"key" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
key'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"sort" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
sort'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"directions" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
direction'
]
where
mk :: a -> a -> (a, Maybe a)
mk a
k a
v = (a
k, forall a. a -> Maybe a
Just a
v)
sort' :: Maybe ByteString
sort' = Maybe SortCache
sort forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
SortCache
SortCacheCreatedAt -> ByteString
"created_at"
SortCache
SortCacheLastAccessedAt -> ByteString
"last_accessed_at"
SortCache
SortCacheSizeInBytes -> ByteString
"size_in_bytes"
direction' :: Maybe ByteString
direction' = Maybe SortDirection
dir forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
SortDirection
SortDescending -> ByteString
"desc"
SortDirection
SortAscending -> ByteString
"asc"
ref' :: Maybe ByteString
ref' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
ref
key' :: Maybe ByteString
key' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
key
optionsRef :: Text -> CacheMod
optionsRef :: Text -> CacheMod
optionsRef Text
x = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsRef :: Maybe Text
cacheOptionsRef = forall a. a -> Maybe a
Just Text
x }
optionsNoRef :: CacheMod
optionsNoRef :: CacheMod
optionsNoRef = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsRef :: Maybe Text
cacheOptionsRef = forall a. Maybe a
Nothing }
optionsKey :: Text -> CacheMod
optionsKey :: Text -> CacheMod
optionsKey Text
x = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsKey :: Maybe Text
cacheOptionsKey = forall a. a -> Maybe a
Just Text
x }
optionsNoKey :: CacheMod
optionsNoKey :: CacheMod
optionsNoKey = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsKey :: Maybe Text
cacheOptionsKey = forall a. Maybe a
Nothing }
optionsDirectionAsc :: CacheMod
optionsDirectionAsc :: CacheMod
optionsDirectionAsc = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsDirection :: Maybe SortDirection
cacheOptionsDirection = forall a. a -> Maybe a
Just SortDirection
SortAscending }
optionsDirectionDesc :: CacheMod
optionsDirectionDesc :: CacheMod
optionsDirectionDesc = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsDirection :: Maybe SortDirection
cacheOptionsDirection = forall a. a -> Maybe a
Just SortDirection
SortDescending }
sortByCreatedAt :: CacheMod
sortByCreatedAt :: CacheMod
sortByCreatedAt = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsSort :: Maybe SortCache
cacheOptionsSort = forall a. a -> Maybe a
Just SortCache
SortCacheCreatedAt }
sortByLastAccessedAt :: CacheMod
sortByLastAccessedAt :: CacheMod
sortByLastAccessedAt = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsSort :: Maybe SortCache
cacheOptionsSort = forall a. a -> Maybe a
Just SortCache
SortCacheLastAccessedAt }
sortBySizeInBytes :: CacheMod
sortBySizeInBytes :: CacheMod
sortBySizeInBytes = (CacheOptions -> CacheOptions) -> CacheMod
CacheMod forall a b. (a -> b) -> a -> b
$ \CacheOptions
opts ->
CacheOptions
opts { cacheOptionsSort :: Maybe SortCache
cacheOptionsSort = forall a. a -> Maybe a
Just SortCache
SortCacheSizeInBytes }
data WorkflowRunOptions = WorkflowRunOptions
{ WorkflowRunOptions -> Maybe Text
workflowRunOptionsActor :: !(Maybe Text)
, WorkflowRunOptions -> Maybe Text
workflowRunOptionsBranch :: !(Maybe Text)
, WorkflowRunOptions -> Maybe Text
workflowRunOptionsEvent :: !(Maybe Text)
, WorkflowRunOptions -> Maybe Text
workflowRunOptionsStatus :: !(Maybe Text)
, WorkflowRunOptions -> Maybe Text
workflowRunOptionsCreated :: !(Maybe Text)
, WorkflowRunOptions -> Maybe Text
workflowRunOptionsHeadSha :: !(Maybe Text)
}
deriving
(WorkflowRunOptions -> WorkflowRunOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
$c/= :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
== :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
$c== :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
Eq, Eq WorkflowRunOptions
WorkflowRunOptions -> WorkflowRunOptions -> Bool
WorkflowRunOptions -> WorkflowRunOptions -> Ordering
WorkflowRunOptions -> WorkflowRunOptions -> WorkflowRunOptions
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 :: WorkflowRunOptions -> WorkflowRunOptions -> WorkflowRunOptions
$cmin :: WorkflowRunOptions -> WorkflowRunOptions -> WorkflowRunOptions
max :: WorkflowRunOptions -> WorkflowRunOptions -> WorkflowRunOptions
$cmax :: WorkflowRunOptions -> WorkflowRunOptions -> WorkflowRunOptions
>= :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
$c>= :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
> :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
$c> :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
<= :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
$c<= :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
< :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
$c< :: WorkflowRunOptions -> WorkflowRunOptions -> Bool
compare :: WorkflowRunOptions -> WorkflowRunOptions -> Ordering
$ccompare :: WorkflowRunOptions -> WorkflowRunOptions -> Ordering
Ord, Int -> WorkflowRunOptions -> ShowS
[WorkflowRunOptions] -> ShowS
WorkflowRunOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WorkflowRunOptions] -> ShowS
$cshowList :: [WorkflowRunOptions] -> ShowS
show :: WorkflowRunOptions -> String
$cshow :: WorkflowRunOptions -> String
showsPrec :: Int -> WorkflowRunOptions -> ShowS
$cshowsPrec :: Int -> WorkflowRunOptions -> ShowS
Show, forall x. Rep WorkflowRunOptions x -> WorkflowRunOptions
forall x. WorkflowRunOptions -> Rep WorkflowRunOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WorkflowRunOptions x -> WorkflowRunOptions
$cfrom :: forall x. WorkflowRunOptions -> Rep WorkflowRunOptions x
Generic, Typeable, Typeable WorkflowRunOptions
WorkflowRunOptions -> DataType
WorkflowRunOptions -> Constr
(forall b. Data b => b -> b)
-> WorkflowRunOptions -> WorkflowRunOptions
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> WorkflowRunOptions -> u
forall u. (forall d. Data d => d -> u) -> WorkflowRunOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WorkflowRunOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WorkflowRunOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> WorkflowRunOptions -> m WorkflowRunOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WorkflowRunOptions -> m WorkflowRunOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WorkflowRunOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> WorkflowRunOptions
-> c WorkflowRunOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WorkflowRunOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WorkflowRunOptions)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WorkflowRunOptions -> m WorkflowRunOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WorkflowRunOptions -> m WorkflowRunOptions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WorkflowRunOptions -> m WorkflowRunOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> WorkflowRunOptions -> m WorkflowRunOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> WorkflowRunOptions -> m WorkflowRunOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> WorkflowRunOptions -> m WorkflowRunOptions
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> WorkflowRunOptions -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> WorkflowRunOptions -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> WorkflowRunOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> WorkflowRunOptions -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WorkflowRunOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WorkflowRunOptions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WorkflowRunOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WorkflowRunOptions -> r
gmapT :: (forall b. Data b => b -> b)
-> WorkflowRunOptions -> WorkflowRunOptions
$cgmapT :: (forall b. Data b => b -> b)
-> WorkflowRunOptions -> WorkflowRunOptions
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WorkflowRunOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c WorkflowRunOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WorkflowRunOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WorkflowRunOptions)
dataTypeOf :: WorkflowRunOptions -> DataType
$cdataTypeOf :: WorkflowRunOptions -> DataType
toConstr :: WorkflowRunOptions -> Constr
$ctoConstr :: WorkflowRunOptions -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WorkflowRunOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WorkflowRunOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> WorkflowRunOptions
-> c WorkflowRunOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> WorkflowRunOptions
-> c WorkflowRunOptions
Data)
defaultWorkflowRunOptions :: WorkflowRunOptions
defaultWorkflowRunOptions :: WorkflowRunOptions
defaultWorkflowRunOptions = WorkflowRunOptions
{ workflowRunOptionsActor :: Maybe Text
workflowRunOptionsActor = forall a. Maybe a
Nothing
, workflowRunOptionsBranch :: Maybe Text
workflowRunOptionsBranch = forall a. Maybe a
Nothing
, workflowRunOptionsEvent :: Maybe Text
workflowRunOptionsEvent = forall a. Maybe a
Nothing
, workflowRunOptionsStatus :: Maybe Text
workflowRunOptionsStatus = forall a. Maybe a
Nothing
, workflowRunOptionsCreated :: Maybe Text
workflowRunOptionsCreated = forall a. Maybe a
Nothing
, workflowRunOptionsHeadSha :: Maybe Text
workflowRunOptionsHeadSha = forall a. Maybe a
Nothing
}
newtype WorkflowRunMod = WorkflowRunMod (WorkflowRunOptions -> WorkflowRunOptions)
instance Semigroup WorkflowRunMod where
WorkflowRunMod WorkflowRunOptions -> WorkflowRunOptions
f <> :: WorkflowRunMod -> WorkflowRunMod -> WorkflowRunMod
<> WorkflowRunMod WorkflowRunOptions -> WorkflowRunOptions
g = (WorkflowRunOptions -> WorkflowRunOptions) -> WorkflowRunMod
WorkflowRunMod (WorkflowRunOptions -> WorkflowRunOptions
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkflowRunOptions -> WorkflowRunOptions
f)
instance Monoid WorkflowRunMod where
mempty :: WorkflowRunMod
mempty = (WorkflowRunOptions -> WorkflowRunOptions) -> WorkflowRunMod
WorkflowRunMod forall a. a -> a
id
mappend :: WorkflowRunMod -> WorkflowRunMod -> WorkflowRunMod
mappend = forall a. Semigroup a => a -> a -> a
(<>)
toWorkflowRunOptions :: WorkflowRunMod -> WorkflowRunOptions
toWorkflowRunOptions :: WorkflowRunMod -> WorkflowRunOptions
toWorkflowRunOptions (WorkflowRunMod WorkflowRunOptions -> WorkflowRunOptions
f) = WorkflowRunOptions -> WorkflowRunOptions
f WorkflowRunOptions
defaultWorkflowRunOptions
workflowRunModToQueryString :: WorkflowRunMod -> QueryString
workflowRunModToQueryString :: WorkflowRunMod -> QueryString
workflowRunModToQueryString = WorkflowRunOptions -> QueryString
workflowRunOptionsToQueryString forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkflowRunMod -> WorkflowRunOptions
toWorkflowRunOptions
workflowRunOptionsToQueryString :: WorkflowRunOptions -> QueryString
workflowRunOptionsToQueryString :: WorkflowRunOptions -> QueryString
workflowRunOptionsToQueryString (WorkflowRunOptions Maybe Text
actor Maybe Text
branch Maybe Text
event Maybe Text
status Maybe Text
created Maybe Text
headSha) =
forall a. [Maybe a] -> [a]
catMaybes
[ forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"actor" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
actor'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"branch" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
branch'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"event" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
event'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"status" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
status'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"created" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
created'
, forall {a} {a}. a -> a -> (a, Maybe a)
mk ByteString
"head_sha" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
headSha'
]
where
mk :: a -> a -> (a, Maybe a)
mk a
k a
v = (a
k, forall a. a -> Maybe a
Just a
v)
actor' :: Maybe ByteString
actor' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
actor
branch' :: Maybe ByteString
branch' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
branch
event' :: Maybe ByteString
event' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
event
status' :: Maybe ByteString
status' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
status
created' :: Maybe ByteString
created' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
created
headSha' :: Maybe ByteString
headSha' = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
TE.encodeUtf8 Maybe Text
headSha
optionsWorkflowRunActor :: Text -> WorkflowRunMod
optionsWorkflowRunActor :: Text -> WorkflowRunMod
optionsWorkflowRunActor Text
x = (WorkflowRunOptions -> WorkflowRunOptions) -> WorkflowRunMod
WorkflowRunMod forall a b. (a -> b) -> a -> b
$ \WorkflowRunOptions
opts ->
WorkflowRunOptions
opts { workflowRunOptionsActor :: Maybe Text
workflowRunOptionsActor = forall a. a -> Maybe a
Just Text
x }
optionsWorkflowRunBranch :: Text -> WorkflowRunMod
optionsWorkflowRunBranch :: Text -> WorkflowRunMod
optionsWorkflowRunBranch Text
x = (WorkflowRunOptions -> WorkflowRunOptions) -> WorkflowRunMod
WorkflowRunMod forall a b. (a -> b) -> a -> b
$ \WorkflowRunOptions
opts ->
WorkflowRunOptions
opts { workflowRunOptionsBranch :: Maybe Text
workflowRunOptionsBranch = forall a. a -> Maybe a
Just Text
x }
optionsWorkflowRunEvent :: Text -> WorkflowRunMod
optionsWorkflowRunEvent :: Text -> WorkflowRunMod
optionsWorkflowRunEvent Text
x = (WorkflowRunOptions -> WorkflowRunOptions) -> WorkflowRunMod
WorkflowRunMod forall a b. (a -> b) -> a -> b
$ \WorkflowRunOptions
opts ->
WorkflowRunOptions
opts { workflowRunOptionsEvent :: Maybe Text
workflowRunOptionsEvent = forall a. a -> Maybe a
Just Text
x }
optionsWorkflowRunStatus :: Text -> WorkflowRunMod
optionsWorkflowRunStatus :: Text -> WorkflowRunMod
optionsWorkflowRunStatus Text
x = (WorkflowRunOptions -> WorkflowRunOptions) -> WorkflowRunMod
WorkflowRunMod forall a b. (a -> b) -> a -> b
$ \WorkflowRunOptions
opts ->
WorkflowRunOptions
opts { workflowRunOptionsStatus :: Maybe Text
workflowRunOptionsStatus = forall a. a -> Maybe a
Just Text
x }
optionsWorkflowRunCreated :: Text -> WorkflowRunMod
optionsWorkflowRunCreated :: Text -> WorkflowRunMod
optionsWorkflowRunCreated Text
x = (WorkflowRunOptions -> WorkflowRunOptions) -> WorkflowRunMod
WorkflowRunMod forall a b. (a -> b) -> a -> b
$ \WorkflowRunOptions
opts ->
WorkflowRunOptions
opts { workflowRunOptionsCreated :: Maybe Text
workflowRunOptionsCreated = forall a. a -> Maybe a
Just Text
x }
optionsWorkflowRunHeadSha :: Text -> WorkflowRunMod
optionsWorkflowRunHeadSha :: Text -> WorkflowRunMod
optionsWorkflowRunHeadSha Text
x = (WorkflowRunOptions -> WorkflowRunOptions) -> WorkflowRunMod
WorkflowRunMod forall a b. (a -> b) -> a -> b
$ \WorkflowRunOptions
opts ->
WorkflowRunOptions
opts { workflowRunOptionsHeadSha :: Maybe Text
workflowRunOptionsHeadSha = forall a. a -> Maybe a
Just Text
x }