{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module GitLab.SystemHooks.GitLabSystemHooks
( receive,
receiveString,
tryFire,
)
where
import qualified Control.Exception as E
import Control.Monad
import Control.Monad.IO.Class
import qualified Control.Monad.Reader as MR
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Data.Typeable
import GitLab.SystemHooks.Types
import GitLab.Types
import System.IO.Temp
import System.PosixCompat.Files
receive :: [Rule] -> GitLab ()
receive :: [Rule] -> GitLab ()
receive [Rule]
rules = do
Text
eventContent <- IO Text -> GitLabT IO Text
forall a. IO a -> GitLabT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Text
TIO.getContents
Text -> [Rule] -> GitLab ()
receiveString Text
eventContent [Rule]
rules
receiveString :: Text -> [Rule] -> GitLab ()
receiveString :: Text -> [Rule] -> GitLab ()
receiveString Text
eventContent [Rule]
rules = do
Text -> GitLab ()
traceSystemHook Text
eventContent
[Bool]
didFire <- (Rule -> GitLabT IO Bool) -> [Rule] -> GitLabT IO [Bool]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Text -> Rule -> GitLabT IO Bool
fire Text
eventContent) [Rule]
rules
Bool -> GitLab () -> GitLab ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not ([Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or [Bool]
didFire)) (GitLab () -> GitLab ()) -> GitLab () -> GitLab ()
forall a b. (a -> b) -> a -> b
$ do
GitLabServerConfig
cfg <- (GitLabState -> GitLabServerConfig)
-> GitLabT IO GitLabServerConfig
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
MR.asks GitLabState -> GitLabServerConfig
serverCfg
Bool -> GitLab () -> GitLab ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GitLabServerConfig -> Maybe DebugSystemHooks
debugSystemHooks GitLabServerConfig
cfg Maybe DebugSystemHooks -> Maybe DebugSystemHooks -> Bool
forall a. Eq a => a -> a -> Bool
== DebugSystemHooks -> Maybe DebugSystemHooks
forall a. a -> Maybe a
Just DebugSystemHooks
NonParsedJSON) (GitLab () -> GitLab ()) -> GitLab () -> GitLab ()
forall a b. (a -> b) -> a -> b
$ IO () -> GitLab ()
forall a. IO a -> GitLabT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> GitLab ()) -> IO () -> GitLab ()
forall a b. (a -> b) -> a -> b
$ do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Text -> Bool
attemptGitLabEventParse Text
eventContent)) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String
fpath <- String -> String -> IO String
writeSystemTempFile String
"gitlab-system-hook-nonparsed-" (Text -> String
T.unpack Text
eventContent)
IO () -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> FileMode -> IO ()
setFileMode String
fpath FileMode
otherReadMode
Bool -> GitLab () -> GitLab ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GitLabServerConfig -> Maybe DebugSystemHooks
debugSystemHooks GitLabServerConfig
cfg Maybe DebugSystemHooks -> Maybe DebugSystemHooks -> Bool
forall a. Eq a => a -> a -> Bool
== DebugSystemHooks -> Maybe DebugSystemHooks
forall a. a -> Maybe a
Just DebugSystemHooks
UnprocessedEvents) (GitLab () -> GitLab ()) -> GitLab () -> GitLab ()
forall a b. (a -> b) -> a -> b
$ IO () -> GitLab ()
forall a. IO a -> GitLabT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> GitLab ()) -> IO () -> GitLab ()
forall a b. (a -> b) -> a -> b
$ do
String
fpath <- String -> String -> IO String
writeSystemTempFile String
"gitlab-system-hook-unprocessed-" (Text -> String
T.unpack Text
eventContent)
IO () -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> FileMode -> IO ()
setFileMode String
fpath FileMode
otherReadMode
traceSystemHook :: Text -> GitLab ()
traceSystemHook :: Text -> GitLab ()
traceSystemHook Text
eventContent = do
GitLabServerConfig
cfg <- (GitLabState -> GitLabServerConfig)
-> GitLabT IO GitLabServerConfig
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
MR.asks GitLabState -> GitLabServerConfig
serverCfg
IO () -> GitLab ()
forall a. IO a -> GitLabT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> GitLab ()) -> IO () -> GitLab ()
forall a b. (a -> b) -> a -> b
$
IO () -> (ErrorCall -> IO ()) -> IO ()
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
( Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GitLabServerConfig -> Maybe DebugSystemHooks
debugSystemHooks GitLabServerConfig
cfg Maybe DebugSystemHooks -> Maybe DebugSystemHooks -> Bool
forall a. Eq a => a -> a -> Bool
== DebugSystemHooks -> Maybe DebugSystemHooks
forall a. a -> Maybe a
Just DebugSystemHooks
AllJSON) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String
fpath <- String -> String -> IO String
writeSystemTempFile String
"gitlab-system-hook-" (Text -> String
T.unpack Text
eventContent)
IO () -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> FileMode -> IO ()
setFileMode String
fpath FileMode
otherReadMode
)
(\(ErrorCall
_exception :: E.ErrorCall) -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
orElse :: GitLab Bool -> GitLab Bool -> GitLab Bool
orElse :: GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
orElse GitLabT IO Bool
f GitLabT IO Bool
g = do
Bool
x <- GitLabT IO Bool
f
if Bool
x
then Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else GitLabT IO Bool
g
fire :: Text -> Rule -> GitLab Bool
fire :: Text -> Rule -> GitLabT IO Bool
fire Text
contents Rule
rule = do
Bool
result <- Text -> Rule -> GitLabT IO Bool
tryFire Text
contents Rule
rule
case Bool
result of
Bool
True -> do
IO () -> GitLab ()
forall a. IO a -> GitLabT IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (String -> IO ()
putStrLn (String
"fired: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Rule -> String
labelOf Rule
rule))
Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
Bool
False -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
where
labelOf :: Rule -> String
labelOf :: Rule -> String
labelOf (Match String
lbl a -> GitLab ()
_) = String
lbl
labelOf (MatchIf String
lbl a -> GitLabT IO Bool
_ a -> GitLab ()
_) = String
lbl
tryFire :: Text -> Rule -> GitLab Bool
tryFire :: Text -> Rule -> GitLabT IO Bool
tryFire Text
contents (Match String
_ a -> GitLab ()
f) = do
Maybe (ProjectCreate -> GitLabT IO Bool)
-> Maybe (ProjectCreate -> GitLab ())
-> Maybe ProjectCreate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((ProjectCreate -> GitLabT IO Bool)
-> Maybe (ProjectCreate -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\ProjectCreate
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (ProjectCreate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectCreate -> GitLab ()))
(Text -> Maybe ProjectCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectCreate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (ProjectDestroy -> GitLabT IO Bool)
-> Maybe (ProjectDestroy -> GitLab ())
-> Maybe ProjectDestroy
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((ProjectDestroy -> GitLabT IO Bool)
-> Maybe (ProjectDestroy -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\ProjectDestroy
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (ProjectDestroy -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectDestroy -> GitLab ()))
(Text -> Maybe ProjectDestroy
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectDestroy)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (ProjectRename -> GitLabT IO Bool)
-> Maybe (ProjectRename -> GitLab ())
-> Maybe ProjectRename
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((ProjectRename -> GitLabT IO Bool)
-> Maybe (ProjectRename -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\ProjectRename
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (ProjectRename -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectRename -> GitLab ()))
(Text -> Maybe ProjectRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectRename)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (ProjectTransfer -> GitLabT IO Bool)
-> Maybe (ProjectTransfer -> GitLab ())
-> Maybe ProjectTransfer
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((ProjectTransfer -> GitLabT IO Bool)
-> Maybe (ProjectTransfer -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\ProjectTransfer
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (ProjectTransfer -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectTransfer -> GitLab ()))
(Text -> Maybe ProjectTransfer
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectTransfer)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (ProjectUpdate -> GitLabT IO Bool)
-> Maybe (ProjectUpdate -> GitLab ())
-> Maybe ProjectUpdate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((ProjectUpdate -> GitLabT IO Bool)
-> Maybe (ProjectUpdate -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\ProjectUpdate
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (ProjectUpdate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectUpdate -> GitLab ()))
(Text -> Maybe ProjectUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectUpdate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupMemberUpdate -> GitLabT IO Bool)
-> Maybe (GroupMemberUpdate -> GitLab ())
-> Maybe GroupMemberUpdate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((GroupMemberUpdate -> GitLabT IO Bool)
-> Maybe (GroupMemberUpdate -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\GroupMemberUpdate
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (GroupMemberUpdate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupMemberUpdate -> GitLab ()))
(Text -> Maybe GroupMemberUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupMemberUpdate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserAddToTeam -> GitLabT IO Bool)
-> Maybe (UserAddToTeam -> GitLab ())
-> Maybe UserAddToTeam
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((UserAddToTeam -> GitLabT IO Bool)
-> Maybe (UserAddToTeam -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\UserAddToTeam
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (UserAddToTeam -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserAddToTeam -> GitLab ()))
(Text -> Maybe UserAddToTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserAddToTeam)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserUpdateForTeam -> GitLabT IO Bool)
-> Maybe (UserUpdateForTeam -> GitLab ())
-> Maybe UserUpdateForTeam
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((UserUpdateForTeam -> GitLabT IO Bool)
-> Maybe (UserUpdateForTeam -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\UserUpdateForTeam
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (UserUpdateForTeam -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserUpdateForTeam -> GitLab ()))
(Text -> Maybe UserUpdateForTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserUpdateForTeam)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserRemoveFromTeam -> GitLabT IO Bool)
-> Maybe (UserRemoveFromTeam -> GitLab ())
-> Maybe UserRemoveFromTeam
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((UserRemoveFromTeam -> GitLabT IO Bool)
-> Maybe (UserRemoveFromTeam -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\UserRemoveFromTeam
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (UserRemoveFromTeam -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserRemoveFromTeam -> GitLab ()))
(Text -> Maybe UserRemoveFromTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRemoveFromTeam)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserCreate -> GitLabT IO Bool)
-> Maybe (UserCreate -> GitLab ())
-> Maybe UserCreate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((UserCreate -> GitLabT IO Bool)
-> Maybe (UserCreate -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\UserCreate
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (UserCreate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserCreate -> GitLab ()))
(Text -> Maybe UserCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserCreate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserRemove -> GitLabT IO Bool)
-> Maybe (UserRemove -> GitLab ())
-> Maybe UserRemove
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((UserRemove -> GitLabT IO Bool)
-> Maybe (UserRemove -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\UserRemove
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (UserRemove -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserRemove -> GitLab ()))
(Text -> Maybe UserRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRemove)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserFailedLogin -> GitLabT IO Bool)
-> Maybe (UserFailedLogin -> GitLab ())
-> Maybe UserFailedLogin
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((UserFailedLogin -> GitLabT IO Bool)
-> Maybe (UserFailedLogin -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\UserFailedLogin
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (UserFailedLogin -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserFailedLogin -> GitLab ()))
(Text -> Maybe UserFailedLogin
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserFailedLogin)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserRename -> GitLabT IO Bool)
-> Maybe (UserRename -> GitLab ())
-> Maybe UserRename
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((UserRename -> GitLabT IO Bool)
-> Maybe (UserRename -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\UserRename
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (UserRename -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserRename -> GitLab ()))
(Text -> Maybe UserRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRename)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (KeyCreate -> GitLabT IO Bool)
-> Maybe (KeyCreate -> GitLab ())
-> Maybe KeyCreate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((KeyCreate -> GitLabT IO Bool)
-> Maybe (KeyCreate -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\KeyCreate
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (KeyCreate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (KeyCreate -> GitLab ()))
(Text -> Maybe KeyCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe KeyCreate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (KeyRemove -> GitLabT IO Bool)
-> Maybe (KeyRemove -> GitLab ())
-> Maybe KeyRemove
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((KeyRemove -> GitLabT IO Bool)
-> Maybe (KeyRemove -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\KeyRemove
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (KeyRemove -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (KeyRemove -> GitLab ()))
(Text -> Maybe KeyRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe KeyRemove)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupCreate -> GitLabT IO Bool)
-> Maybe (GroupCreate -> GitLab ())
-> Maybe GroupCreate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((GroupCreate -> GitLabT IO Bool)
-> Maybe (GroupCreate -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\GroupCreate
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (GroupCreate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupCreate -> GitLab ()))
(Text -> Maybe GroupCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupCreate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupRemove -> GitLabT IO Bool)
-> Maybe (GroupRemove -> GitLab ())
-> Maybe GroupRemove
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((GroupRemove -> GitLabT IO Bool)
-> Maybe (GroupRemove -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\GroupRemove
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (GroupRemove -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupRemove -> GitLab ()))
(Text -> Maybe GroupRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupRemove)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupRename -> GitLabT IO Bool)
-> Maybe (GroupRename -> GitLab ())
-> Maybe GroupRename
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((GroupRename -> GitLabT IO Bool)
-> Maybe (GroupRename -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\GroupRename
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (GroupRename -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupRename -> GitLab ()))
(Text -> Maybe GroupRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupRename)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (NewGroupMember -> GitLabT IO Bool)
-> Maybe (NewGroupMember -> GitLab ())
-> Maybe NewGroupMember
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((NewGroupMember -> GitLabT IO Bool)
-> Maybe (NewGroupMember -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\NewGroupMember
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (NewGroupMember -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (NewGroupMember -> GitLab ()))
(Text -> Maybe NewGroupMember
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe NewGroupMember)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupMemberRemove -> GitLabT IO Bool)
-> Maybe (GroupMemberRemove -> GitLab ())
-> Maybe GroupMemberRemove
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((GroupMemberRemove -> GitLabT IO Bool)
-> Maybe (GroupMemberRemove -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\GroupMemberRemove
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (GroupMemberRemove -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupMemberRemove -> GitLab ()))
(Text -> Maybe GroupMemberRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupMemberRemove)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (Push -> GitLabT IO Bool)
-> Maybe (Push -> GitLab ()) -> Maybe Push -> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((Push -> GitLabT IO Bool) -> Maybe (Push -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\Push
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (Push -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (Push -> GitLab ()))
(Text -> Maybe Push
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe Push)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (TagPush -> GitLabT IO Bool)
-> Maybe (TagPush -> GitLab ()) -> Maybe TagPush -> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((TagPush -> GitLabT IO Bool) -> Maybe (TagPush -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\TagPush
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (TagPush -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (TagPush -> GitLab ()))
(Text -> Maybe TagPush
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe TagPush)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (RepositoryUpdate -> GitLabT IO Bool)
-> Maybe (RepositoryUpdate -> GitLab ())
-> Maybe RepositoryUpdate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((RepositoryUpdate -> GitLabT IO Bool)
-> Maybe (RepositoryUpdate -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\RepositoryUpdate
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (RepositoryUpdate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (RepositoryUpdate -> GitLab ()))
(Text -> Maybe RepositoryUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe RepositoryUpdate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (MergeRequestEvent -> GitLabT IO Bool)
-> Maybe (MergeRequestEvent -> GitLab ())
-> Maybe MergeRequestEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((MergeRequestEvent -> GitLabT IO Bool)
-> Maybe (MergeRequestEvent -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\MergeRequestEvent
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (MergeRequestEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (MergeRequestEvent -> GitLab ()))
(Text -> Maybe MergeRequestEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe MergeRequestEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (BuildEvent -> GitLabT IO Bool)
-> Maybe (BuildEvent -> GitLab ())
-> Maybe BuildEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((BuildEvent -> GitLabT IO Bool)
-> Maybe (BuildEvent -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\BuildEvent
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (BuildEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (BuildEvent -> GitLab ()))
(Text -> Maybe BuildEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe BuildEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (PipelineEvent -> GitLabT IO Bool)
-> Maybe (PipelineEvent -> GitLab ())
-> Maybe PipelineEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((PipelineEvent -> GitLabT IO Bool)
-> Maybe (PipelineEvent -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\PipelineEvent
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (PipelineEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (PipelineEvent -> GitLab ()))
(Text -> Maybe PipelineEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe PipelineEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (IssueEvent -> GitLabT IO Bool)
-> Maybe (IssueEvent -> GitLab ())
-> Maybe IssueEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((IssueEvent -> GitLabT IO Bool)
-> Maybe (IssueEvent -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\IssueEvent
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (IssueEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (IssueEvent -> GitLab ()))
(Text -> Maybe IssueEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe IssueEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (NoteEvent -> GitLabT IO Bool)
-> Maybe (NoteEvent -> GitLab ())
-> Maybe NoteEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((NoteEvent -> GitLabT IO Bool)
-> Maybe (NoteEvent -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\NoteEvent
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (NoteEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (NoteEvent -> GitLab ()))
(Text -> Maybe NoteEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe NoteEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (WikiPageEvent -> GitLabT IO Bool)
-> Maybe (WikiPageEvent -> GitLab ())
-> Maybe WikiPageEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((WikiPageEvent -> GitLabT IO Bool)
-> Maybe (WikiPageEvent -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\WikiPageEvent
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (WikiPageEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (WikiPageEvent -> GitLab ()))
(Text -> Maybe WikiPageEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe WikiPageEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (WorkItemEvent -> GitLabT IO Bool)
-> Maybe (WorkItemEvent -> GitLab ())
-> Maybe WorkItemEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((WorkItemEvent -> GitLabT IO Bool)
-> Maybe (WorkItemEvent -> GitLabT IO Bool)
forall a. a -> Maybe a
Just (\WorkItemEvent
_ -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True))
((a -> GitLab ()) -> Maybe (WorkItemEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (WorkItemEvent -> GitLab ()))
(Text -> Maybe WorkItemEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe WorkItemEvent)
tryFire Text
contents (MatchIf String
_ a -> GitLabT IO Bool
predF a -> GitLab ()
f) = do
Maybe (ProjectCreate -> GitLabT IO Bool)
-> Maybe (ProjectCreate -> GitLab ())
-> Maybe ProjectCreate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (ProjectCreate -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (ProjectCreate -> GitLab Bool))
((a -> GitLab ()) -> Maybe (ProjectCreate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectCreate -> GitLab ()))
(Text -> Maybe ProjectCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectCreate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (ProjectDestroy -> GitLabT IO Bool)
-> Maybe (ProjectDestroy -> GitLab ())
-> Maybe ProjectDestroy
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (ProjectDestroy -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (ProjectDestroy -> GitLab Bool))
((a -> GitLab ()) -> Maybe (ProjectDestroy -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectDestroy -> GitLab ()))
(Text -> Maybe ProjectDestroy
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectDestroy)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (ProjectRename -> GitLabT IO Bool)
-> Maybe (ProjectRename -> GitLab ())
-> Maybe ProjectRename
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (ProjectRename -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (ProjectRename -> GitLab Bool))
((a -> GitLab ()) -> Maybe (ProjectRename -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectRename -> GitLab ()))
(Text -> Maybe ProjectRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectRename)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (ProjectTransfer -> GitLabT IO Bool)
-> Maybe (ProjectTransfer -> GitLab ())
-> Maybe ProjectTransfer
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool)
-> Maybe (ProjectTransfer -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (ProjectTransfer -> GitLab Bool))
((a -> GitLab ()) -> Maybe (ProjectTransfer -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectTransfer -> GitLab ()))
(Text -> Maybe ProjectTransfer
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectTransfer)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (ProjectUpdate -> GitLabT IO Bool)
-> Maybe (ProjectUpdate -> GitLab ())
-> Maybe ProjectUpdate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (ProjectUpdate -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (ProjectUpdate -> GitLab Bool))
((a -> GitLab ()) -> Maybe (ProjectUpdate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (ProjectUpdate -> GitLab ()))
(Text -> Maybe ProjectUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectUpdate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupMemberUpdate -> GitLabT IO Bool)
-> Maybe (GroupMemberUpdate -> GitLab ())
-> Maybe GroupMemberUpdate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool)
-> Maybe (GroupMemberUpdate -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (GroupMemberUpdate -> GitLab Bool))
((a -> GitLab ()) -> Maybe (GroupMemberUpdate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupMemberUpdate -> GitLab ()))
(Text -> Maybe GroupMemberUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupMemberUpdate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserAddToTeam -> GitLabT IO Bool)
-> Maybe (UserAddToTeam -> GitLab ())
-> Maybe UserAddToTeam
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (UserAddToTeam -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (UserAddToTeam -> GitLab Bool))
((a -> GitLab ()) -> Maybe (UserAddToTeam -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserAddToTeam -> GitLab ()))
(Text -> Maybe UserAddToTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserAddToTeam)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserUpdateForTeam -> GitLabT IO Bool)
-> Maybe (UserUpdateForTeam -> GitLab ())
-> Maybe UserUpdateForTeam
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool)
-> Maybe (UserUpdateForTeam -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (UserUpdateForTeam -> GitLab Bool))
((a -> GitLab ()) -> Maybe (UserUpdateForTeam -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserUpdateForTeam -> GitLab ()))
(Text -> Maybe UserUpdateForTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserUpdateForTeam)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserRemoveFromTeam -> GitLabT IO Bool)
-> Maybe (UserRemoveFromTeam -> GitLab ())
-> Maybe UserRemoveFromTeam
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool)
-> Maybe (UserRemoveFromTeam -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (UserRemoveFromTeam -> GitLab Bool))
((a -> GitLab ()) -> Maybe (UserRemoveFromTeam -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserRemoveFromTeam -> GitLab ()))
(Text -> Maybe UserRemoveFromTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRemoveFromTeam)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserCreate -> GitLabT IO Bool)
-> Maybe (UserCreate -> GitLab ())
-> Maybe UserCreate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (UserCreate -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (UserCreate -> GitLab Bool))
((a -> GitLab ()) -> Maybe (UserCreate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserCreate -> GitLab ()))
(Text -> Maybe UserCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserCreate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserRemove -> GitLabT IO Bool)
-> Maybe (UserRemove -> GitLab ())
-> Maybe UserRemove
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (UserRemove -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (UserRemove -> GitLab Bool))
((a -> GitLab ()) -> Maybe (UserRemove -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserRemove -> GitLab ()))
(Text -> Maybe UserRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRemove)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserFailedLogin -> GitLabT IO Bool)
-> Maybe (UserFailedLogin -> GitLab ())
-> Maybe UserFailedLogin
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool)
-> Maybe (UserFailedLogin -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (UserFailedLogin -> GitLab Bool))
((a -> GitLab ()) -> Maybe (UserFailedLogin -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserFailedLogin -> GitLab ()))
(Text -> Maybe UserFailedLogin
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserFailedLogin)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (UserRename -> GitLabT IO Bool)
-> Maybe (UserRename -> GitLab ())
-> Maybe UserRename
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (UserRename -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (UserRename -> GitLab Bool))
((a -> GitLab ()) -> Maybe (UserRename -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (UserRename -> GitLab ()))
(Text -> Maybe UserRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRename)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (KeyCreate -> GitLabT IO Bool)
-> Maybe (KeyCreate -> GitLab ())
-> Maybe KeyCreate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (KeyCreate -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (KeyCreate -> GitLab Bool))
((a -> GitLab ()) -> Maybe (KeyCreate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (KeyCreate -> GitLab ()))
(Text -> Maybe KeyCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe KeyCreate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (KeyRemove -> GitLabT IO Bool)
-> Maybe (KeyRemove -> GitLab ())
-> Maybe KeyRemove
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (KeyRemove -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (KeyRemove -> GitLab Bool))
((a -> GitLab ()) -> Maybe (KeyRemove -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (KeyRemove -> GitLab ()))
(Text -> Maybe KeyRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe KeyRemove)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupCreate -> GitLabT IO Bool)
-> Maybe (GroupCreate -> GitLab ())
-> Maybe GroupCreate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (GroupCreate -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (GroupCreate -> GitLab Bool))
((a -> GitLab ()) -> Maybe (GroupCreate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupCreate -> GitLab ()))
(Text -> Maybe GroupCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupCreate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupRemove -> GitLabT IO Bool)
-> Maybe (GroupRemove -> GitLab ())
-> Maybe GroupRemove
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (GroupRemove -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (GroupRemove -> GitLab Bool))
((a -> GitLab ()) -> Maybe (GroupRemove -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupRemove -> GitLab ()))
(Text -> Maybe GroupRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupRemove)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupRename -> GitLabT IO Bool)
-> Maybe (GroupRename -> GitLab ())
-> Maybe GroupRename
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (GroupRename -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (GroupRename -> GitLab Bool))
((a -> GitLab ()) -> Maybe (GroupRename -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupRename -> GitLab ()))
(Text -> Maybe GroupRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupRename)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (NewGroupMember -> GitLabT IO Bool)
-> Maybe (NewGroupMember -> GitLab ())
-> Maybe NewGroupMember
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (NewGroupMember -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (NewGroupMember -> GitLab Bool))
((a -> GitLab ()) -> Maybe (NewGroupMember -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (NewGroupMember -> GitLab ()))
(Text -> Maybe NewGroupMember
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe NewGroupMember)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (GroupMemberRemove -> GitLabT IO Bool)
-> Maybe (GroupMemberRemove -> GitLab ())
-> Maybe GroupMemberRemove
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool)
-> Maybe (GroupMemberRemove -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (GroupMemberRemove -> GitLab Bool))
((a -> GitLab ()) -> Maybe (GroupMemberRemove -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (GroupMemberRemove -> GitLab ()))
(Text -> Maybe GroupMemberRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupMemberRemove)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (Push -> GitLabT IO Bool)
-> Maybe (Push -> GitLab ()) -> Maybe Push -> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (Push -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (Push -> GitLab Bool))
((a -> GitLab ()) -> Maybe (Push -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (Push -> GitLab ()))
(Text -> Maybe Push
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe Push)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (TagPush -> GitLabT IO Bool)
-> Maybe (TagPush -> GitLab ()) -> Maybe TagPush -> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (TagPush -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (TagPush -> GitLab Bool))
((a -> GitLab ()) -> Maybe (TagPush -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (TagPush -> GitLab ()))
(Text -> Maybe TagPush
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe TagPush)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (RepositoryUpdate -> GitLabT IO Bool)
-> Maybe (RepositoryUpdate -> GitLab ())
-> Maybe RepositoryUpdate
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool)
-> Maybe (RepositoryUpdate -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (RepositoryUpdate -> GitLab Bool))
((a -> GitLab ()) -> Maybe (RepositoryUpdate -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (RepositoryUpdate -> GitLab ()))
(Text -> Maybe RepositoryUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe RepositoryUpdate)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (MergeRequestEvent -> GitLabT IO Bool)
-> Maybe (MergeRequestEvent -> GitLab ())
-> Maybe MergeRequestEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool)
-> Maybe (MergeRequestEvent -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (MergeRequestEvent -> GitLab Bool))
((a -> GitLab ()) -> Maybe (MergeRequestEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (MergeRequestEvent -> GitLab ()))
(Text -> Maybe MergeRequestEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe MergeRequestEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (BuildEvent -> GitLabT IO Bool)
-> Maybe (BuildEvent -> GitLab ())
-> Maybe BuildEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (BuildEvent -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (BuildEvent -> GitLab Bool))
((a -> GitLab ()) -> Maybe (BuildEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (BuildEvent -> GitLab ()))
(Text -> Maybe BuildEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe BuildEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (PipelineEvent -> GitLabT IO Bool)
-> Maybe (PipelineEvent -> GitLab ())
-> Maybe PipelineEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (PipelineEvent -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (PipelineEvent -> GitLab Bool))
((a -> GitLab ()) -> Maybe (PipelineEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (PipelineEvent -> GitLab ()))
(Text -> Maybe PipelineEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe PipelineEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (IssueEvent -> GitLabT IO Bool)
-> Maybe (IssueEvent -> GitLab ())
-> Maybe IssueEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (IssueEvent -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (IssueEvent -> GitLab Bool))
((a -> GitLab ()) -> Maybe (IssueEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (IssueEvent -> GitLab ()))
(Text -> Maybe IssueEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe IssueEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (NoteEvent -> GitLabT IO Bool)
-> Maybe (NoteEvent -> GitLab ())
-> Maybe NoteEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (NoteEvent -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (NoteEvent -> GitLab Bool))
((a -> GitLab ()) -> Maybe (NoteEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (NoteEvent -> GitLab ()))
(Text -> Maybe NoteEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe NoteEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (WikiPageEvent -> GitLabT IO Bool)
-> Maybe (WikiPageEvent -> GitLab ())
-> Maybe WikiPageEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (WikiPageEvent -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (WikiPageEvent -> GitLab Bool))
((a -> GitLab ()) -> Maybe (WikiPageEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (WikiPageEvent -> GitLab ()))
(Text -> Maybe WikiPageEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe WikiPageEvent)
GitLabT IO Bool -> GitLabT IO Bool -> GitLabT IO Bool
`orElse` Maybe (WorkItemEvent -> GitLabT IO Bool)
-> Maybe (WorkItemEvent -> GitLab ())
-> Maybe WorkItemEvent
-> GitLabT IO Bool
forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf'
((a -> GitLabT IO Bool) -> Maybe (WorkItemEvent -> GitLabT IO Bool)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLabT IO Bool
predF :: Maybe (WorkItemEvent -> GitLab Bool))
((a -> GitLab ()) -> Maybe (WorkItemEvent -> GitLab ())
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a -> GitLab ()
f :: Maybe (WorkItemEvent -> GitLab ()))
(Text -> Maybe WorkItemEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe WorkItemEvent)
fireIf' :: (Typeable a, Show a) => Maybe (a -> GitLab Bool) -> Maybe (a -> GitLab ()) -> Maybe a -> GitLab Bool
fireIf' :: forall a.
(Typeable a, Show a) =>
Maybe (a -> GitLabT IO Bool)
-> Maybe (a -> GitLab ()) -> Maybe a -> GitLabT IO Bool
fireIf' Maybe (a -> GitLabT IO Bool)
castPred Maybe (a -> GitLab ())
castF Maybe a
parsed = do
case Maybe (a -> GitLabT IO Bool)
castPred of
Maybe (a -> GitLabT IO Bool)
Nothing -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Just a -> GitLabT IO Bool
pred' ->
case Maybe (a -> GitLab ())
castF of
Maybe (a -> GitLab ())
Nothing -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Just a -> GitLab ()
f' ->
case Maybe a
parsed of
Maybe a
Nothing -> Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
Just a
parsed' -> do
Bool
testPred <- a -> GitLabT IO Bool
pred' a
parsed'
if Bool
testPred
then do
a -> GitLab ()
f' a
parsed'
Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else Bool -> GitLabT IO Bool
forall a. a -> GitLabT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
attemptGitLabEventParse :: T.Text -> Bool
attemptGitLabEventParse :: Text -> Bool
attemptGitLabEventParse Text
contents =
case Text -> Maybe ProjectCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectCreate of
Just ProjectCreate
_ -> Bool
True
Maybe ProjectCreate
Nothing ->
case Text -> Maybe ProjectDestroy
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectDestroy of
Just ProjectDestroy
_ -> Bool
True
Maybe ProjectDestroy
Nothing ->
case Text -> Maybe ProjectRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectRename of
Just ProjectRename
_ -> Bool
True
Maybe ProjectRename
Nothing ->
case Text -> Maybe ProjectTransfer
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectTransfer of
Just ProjectTransfer
_ -> Bool
True
Maybe ProjectTransfer
Nothing ->
case Text -> Maybe ProjectUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe ProjectUpdate of
Just ProjectUpdate
_ -> Bool
True
Maybe ProjectUpdate
Nothing ->
case Text -> Maybe GroupMemberUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupMemberUpdate of
Just GroupMemberUpdate
_ -> Bool
True
Maybe GroupMemberUpdate
Nothing ->
case Text -> Maybe UserAddToTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserAddToTeam of
Just UserAddToTeam
_ -> Bool
True
Maybe UserAddToTeam
Nothing ->
case Text -> Maybe UserUpdateForTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserUpdateForTeam of
Just UserUpdateForTeam
_ -> Bool
True
Maybe UserUpdateForTeam
Nothing ->
case Text -> Maybe UserRemoveFromTeam
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRemoveFromTeam of
Just UserRemoveFromTeam
_ -> Bool
True
Maybe UserRemoveFromTeam
Nothing ->
case Text -> Maybe UserCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserCreate of
Just UserCreate
_ -> Bool
True
Maybe UserCreate
Nothing ->
case Text -> Maybe UserRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRemove of
Just UserRemove
_ -> Bool
True
Maybe UserRemove
Nothing ->
case Text -> Maybe UserFailedLogin
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserFailedLogin of
Just UserFailedLogin
_ -> Bool
True
Maybe UserFailedLogin
Nothing ->
case Text -> Maybe UserRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe UserRename of
Just UserRename
_ -> Bool
True
Maybe UserRename
Nothing ->
case Text -> Maybe KeyCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe KeyCreate of
Just KeyCreate
_ -> Bool
True
Maybe KeyCreate
Nothing ->
case Text -> Maybe KeyRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe KeyRemove of
Just KeyRemove
_ -> Bool
True
Maybe KeyRemove
Nothing ->
case Text -> Maybe GroupCreate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupCreate of
Just GroupCreate
_ -> Bool
True
Maybe GroupCreate
Nothing ->
case Text -> Maybe GroupRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupRemove of
Just GroupRemove
_ -> Bool
True
Maybe GroupRemove
Nothing ->
case Text -> Maybe GroupRename
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupRename of
Just GroupRename
_ -> Bool
True
Maybe GroupRename
Nothing ->
case Text -> Maybe NewGroupMember
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe NewGroupMember of
Just NewGroupMember
_ -> Bool
True
Maybe NewGroupMember
Nothing ->
case Text -> Maybe GroupMemberRemove
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe GroupMemberRemove of
Just GroupMemberRemove
_ -> Bool
True
Maybe GroupMemberRemove
Nothing ->
case Text -> Maybe Push
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe Push of
Just Push
_ -> Bool
True
Maybe Push
Nothing ->
case Text -> Maybe TagPush
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe TagPush of
Just TagPush
_ -> Bool
True
Maybe TagPush
Nothing ->
case Text -> Maybe RepositoryUpdate
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe RepositoryUpdate of
Just RepositoryUpdate
_ -> Bool
True
Maybe RepositoryUpdate
Nothing ->
case Text -> Maybe MergeRequestEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe MergeRequestEvent of
Just MergeRequestEvent
_ -> Bool
True
Maybe MergeRequestEvent
Nothing ->
case Text -> Maybe BuildEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe BuildEvent of
Just BuildEvent
_ -> Bool
True
Maybe BuildEvent
Nothing ->
case Text -> Maybe PipelineEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe PipelineEvent of
Just PipelineEvent
_ -> Bool
True
Maybe PipelineEvent
Nothing ->
case Text -> Maybe IssueEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe IssueEvent of
Just IssueEvent
_ -> Bool
True
Maybe IssueEvent
Nothing ->
case Text -> Maybe NoteEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe NoteEvent of
Just NoteEvent
_ -> Bool
True
Maybe NoteEvent
Nothing ->
case Text -> Maybe WikiPageEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe WikiPageEvent of
Just WikiPageEvent
_ -> Bool
True
Maybe WikiPageEvent
Nothing ->
case Text -> Maybe WorkItemEvent
forall a. FromJSON a => Text -> Maybe a
parseEvent Text
contents :: Maybe WorkItemEvent of
Just WorkItemEvent
_ -> Bool
True
Maybe WorkItemEvent
Nothing -> Bool
False