summaryrefslogtreecommitdiff
path: root/Assistant/Types
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2013-04-04 01:48:26 -0400
committerGravatar Joey Hess <joey@kitenet.net>2013-04-04 01:48:26 -0400
commit0d021ce388369f3f683f9c9c8d13b5c983b12ca3 (patch)
treedab67313491f4680ef0454f6396f6007d750511a /Assistant/Types
parent8fb369aa5667f95d46b24f26b06636559155402b (diff)
refactor alert button creation code
Diffstat (limited to 'Assistant/Types')
-rw-r--r--Assistant/Types/Alert.hs74
-rw-r--r--Assistant/Types/DaemonStatus.hs2
2 files changed, 75 insertions, 1 deletions
diff --git a/Assistant/Types/Alert.hs b/Assistant/Types/Alert.hs
new file mode 100644
index 000000000..34bbc1b08
--- /dev/null
+++ b/Assistant/Types/Alert.hs
@@ -0,0 +1,74 @@
+{- git-annex assistant alert types
+ -
+ - Copyright 2013 Joey Hess <joey@kitenet.net>
+ -
+ - Licensed under the GNU GPL version 3 or higher.
+ -}
+
+module Assistant.Types.Alert where
+
+import Utility.Tense
+
+import Data.Text (Text)
+import qualified Data.Map as M
+
+{- Different classes of alerts are displayed differently. -}
+data AlertClass = Success | Message | Activity | Warning | Error
+ deriving (Eq, Ord)
+
+data AlertPriority = Filler | Low | Medium | High | Pinned
+ deriving (Eq, Ord)
+
+{- An alert can have an name, which is used to combine it with other similar
+ - alerts. -}
+data AlertName
+ = FileAlert TenseChunk
+ | SanityCheckFixAlert
+ | WarningAlert String
+ | PairAlert String
+ | XMPPNeededAlert
+ | RemoteRemovalAlert String
+ | CloudRepoNeededAlert
+ | SyncAlert
+ deriving (Eq)
+
+{- The first alert is the new alert, the second is an old alert.
+ - Should return a modified version of the old alert. -}
+type AlertCombiner = Alert -> Alert -> Maybe Alert
+
+data Alert = Alert
+ { alertClass :: AlertClass
+ , alertHeader :: Maybe TenseText
+ , alertMessageRender :: [TenseChunk] -> TenseText
+ , alertData :: [TenseChunk]
+ , alertBlockDisplay :: Bool
+ , alertClosable :: Bool
+ , alertPriority :: AlertPriority
+ , alertIcon :: Maybe AlertIcon
+ , alertCombiner :: Maybe AlertCombiner
+ , alertName :: Maybe AlertName
+ , alertButton :: Maybe AlertButton
+ }
+
+data AlertIcon = ActivityIcon | SuccessIcon | ErrorIcon | InfoIcon | TheCloud
+
+type AlertMap = M.Map AlertId Alert
+
+{- Higher AlertId indicates a more recent alert. -}
+newtype AlertId = AlertId Integer
+ deriving (Read, Show, Eq, Ord)
+
+firstAlertId :: AlertId
+firstAlertId = AlertId 0
+
+nextAlertId :: AlertId -> AlertId
+nextAlertId (AlertId i) = AlertId $ succ i
+
+{- When clicked, a button always redirects to a URL
+ - It may also run an IO action in the background, which is useful
+ - to make the button close or otherwise change the alert. -}
+data AlertButton = AlertButton
+ { buttonLabel :: Text
+ , buttonUrl :: Text
+ , buttonAction :: Maybe (AlertId -> IO ())
+ }
diff --git a/Assistant/Types/DaemonStatus.hs b/Assistant/Types/DaemonStatus.hs
index 99baf1572..17e535b6d 100644
--- a/Assistant/Types/DaemonStatus.hs
+++ b/Assistant/Types/DaemonStatus.hs
@@ -10,12 +10,12 @@
module Assistant.Types.DaemonStatus where
import Common.Annex
-import Assistant.Alert
import Assistant.Pairing
import Utility.NotificationBroadcaster
import Logs.Transfer
import Assistant.Types.ThreadName
import Assistant.Types.NetMessager
+import Assistant.Types.Alert
import Control.Concurrent.STM
import Control.Concurrent.Async