{- This file is part of funbot. - - Written in 2015 by fr33domlover . - - ♡ Copying is an act of love. Please copy, reuse and share. - - The author(s) have dedicated all copyright and related and neighboring - rights to this software to the public domain worldwide. This software is - distributed without any warranty. - - You should have received a copy of the CC0 Public Domain Dedication along - with this software. If not, see - . -} module FunBot.Types ( Filter (..) , BranchFilter , PushAnnSpec (..) , NewsItemFields (..) , NewsAnnSpec (..) , BotEnv (..) , Settings (..) , SettingsOption , SettingsTree , Memo (..) , BotState (..) , Branch (..) , Commit (..) , Push (..) , Tag (..) , MR (..) , FeedItem (..) , ExtEvent (..) , BotSession , ExtEventSource , ExtEventHandler ) where import qualified Data.HashMap.Lazy as M import qualified Data.HashSet as S import Data.Settings.Types (Section (..), Option (..)) import Data.Time.Clock (UTCTime) import Network.IRC.Fun.Bot.Types (Session, EventSource, EventHandler) -- | Generic item filter data Filter a = Accept [a] | Reject [a] -- | Chooser for repo branches whose commits should be announced to IRC type BranchFilter = Filter String -- | Configuration for announcing a git repo's commits to a specific channel data PushAnnSpec = PushAnnSpec { -- | IRC channel into which to announce pAnnChannel :: String -- Branch filter to choose which branches to announce , pAnnBranches :: BranchFilter -- Whether to report all commits in a push ('True') or shorten long -- pushes to avoid channel spam ('False'). , pAnnAllCommits :: Bool } -- | Pick news item fields to display data NewsItemFields = NewsItemFields { dispFeedTitle :: Bool , dispAuthor :: Bool , dispUrl :: Bool } -- | Configuration for announcing news items data NewsAnnSpec = NewsAnnSpec { -- | IRC channels into which to announce nAnnChannels :: [String] -- | Filter for picking news item fields to display or hide , nAnnFields :: NewsItemFields } -- | Read-only custom bot environment data BotEnv = BotEnv { -- | Port on which the web hook event source will run webHookSourcePort :: Int -- | Maps a Git repo name+owner to annoucement details , gitAnnChans :: M.HashMap (String, String) [PushAnnSpec] -- | An 'IO' action which schedules saving settings to disk. There is a -- wrapper in the 'Session' monad which uses this with the settings -- stored in bot state, so you probably don't need this field directly. , saveSettings :: Settings -> IO () -- | An 'IO' action which schedules saving memos to disk. There is a -- wrapper in the 'Session' monad which uses this with the memos -- stored in bot state, so you probably don't need this field directly. , saveMemos :: M.HashMap String [Memo] -> IO () -- | Filename for logging feed listener errors , feedErrorLogFile :: FilePath } -- | User-modifiable bot behavior settings data Settings = Settings { -- | Maps a feed label to its URL and announcement details watchedFeeds :: M.HashMap String (String, NewsAnnSpec) } -- | Alias for the settings option type type SettingsOption = Option BotSession -- | Alias for the settings section type type SettingsTree = Section BotSession -- | A message left to an offline user, for them to read later. data Memo = Memo { memoTime :: String , memoSender :: String , memoRecvIn :: Maybe String , memoSendIn :: Maybe String , memoContent :: String --, memoRead :: Bool } -- | Read-write custom bot state data BotState = BotState { -- | User-modifiable bot behavior settings settings :: Settings -- | Settings tree and access definition for UI , stree :: SettingsTree -- | Memos waiting for users to connect. , memos :: M.HashMap String [Memo] } data Branch = Branch { branchName :: String , branchRepo :: String , branchRepoOwner :: String } deriving Show data Commit = Commit { commitAuthor :: String , commitTitle :: String , commitUrl :: String } deriving Show data Push = Push { pushBranch :: Branch , pushCommits :: [Commit] } deriving Show data Tag = Tag { tagAuthor :: String , tagRef :: String , tagRepo :: String , tagRepoOwner :: String } deriving Show data MR = MR { mrAuthor :: String , mrId :: Int , mrRepo :: String , mrRepoOwner :: String , mrTitle :: String , mrUrl :: String , mrAction :: String } deriving Show data FeedItem = FeedItem { itemFeedLabel :: String , itemFeedTitle :: Maybe String , itemTitle :: String , itemAuthor :: Maybe String , itemUrl :: Maybe String } deriving Show -- | An event coming from one of the extra event sources. data ExtEvent = GitPush Push | GitTag Tag | MergeRequest MR | NewsItem FeedItem deriving Show -- | Shortcut alias for bot session monad type BotSession = Session BotEnv BotState -- | Shortcut alias for event source function type type ExtEventSource = EventSource BotEnv BotState ExtEvent -- | Shortcut alias for event handler function type type ExtEventHandler = EventHandler BotEnv BotState ExtEvent