{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module System.Taffybar.Widget.FreedesktopNotifications
( Notification(..)
, NotificationConfig(..)
, defaultNotificationConfig
, notifyAreaNew
) where
import Control.Concurrent
import Control.Concurrent.STM
import Control.Monad ( forever, void )
import Control.Monad.IO.Class
import DBus
import DBus.Client
import Data.Foldable
import Data.Int ( Int32 )
import Data.Map ( Map )
import Data.Monoid
import Data.Sequence ( Seq, (|>), viewl, ViewL(..) )
import qualified Data.Sequence as S
import Data.Text ( Text )
import qualified Data.Text as T
import Data.Word ( Word32 )
import Graphics.UI.Gtk hiding ( Variant )
data Notification = Notification
{ noteAppName :: Text
, noteReplaceId :: Word32
, noteSummary :: Text
, noteBody :: Text
, noteExpireTimeout :: Maybe Int32
, noteId :: Word32
} deriving (Show, Eq)
data NotifyState = NotifyState
{ noteWidget :: Label
, noteContainer :: Widget
, noteConfig :: NotificationConfig
, noteQueue :: TVar (Seq Notification)
, noteIdSource :: TVar Word32
, noteChan :: Chan ()
}
initialNoteState :: Widget -> Label -> NotificationConfig -> IO NotifyState
initialNoteState wrapper l cfg = do
m <- newTVarIO 1
q <- newTVarIO S.empty
ch <- newChan
return NotifyState { noteQueue = q
, noteIdSource = m
, noteWidget = l
, noteContainer = wrapper
, noteConfig = cfg
, noteChan = ch
}
notePurge :: NotifyState -> Word32 -> IO ()
notePurge s nId = atomically . modifyTVar' (noteQueue s) $
S.filter ((nId /=) . noteId)
noteNext :: NotifyState -> IO ()
noteNext s = atomically $ modifyTVar' (noteQueue s) aux
where
aux queue = case viewl queue of
EmptyL -> S.empty
_ :< ns -> ns
noteFreshId :: NotifyState -> IO Word32
noteFreshId NotifyState { noteIdSource } = atomically $ do
nId <- readTVar noteIdSource
writeTVar noteIdSource (succ nId)
return nId
notify :: NotifyState
-> Text
-> Word32
-> Text
-> Text
-> Text
-> [Text]
-> Map Text Variant
-> Int32
-> IO Word32
notify s appName replaceId _ summary body _ _ timeout = do
realId <- if replaceId == 0 then noteFreshId s else return replaceId
let escapeText = T.pack . escapeMarkup . T.unpack
configTimeout = notificationMaxTimeout (noteConfig s)
realTimeout = if timeout <= 0
then configTimeout
else case configTimeout of
Nothing -> Just timeout
Just maxTimeout -> Just (min maxTimeout timeout)
n = Notification { noteAppName = appName
, noteReplaceId = replaceId
, noteSummary = escapeText summary
, noteBody = escapeText body
, noteExpireTimeout = realTimeout
, noteId = realId
}
atomically $ do
queue <- readTVar $ noteQueue s
writeTVar (noteQueue s) $ case S.findIndexL (\n_ -> noteId n == noteId n_) queue of
Nothing -> queue |> n
Just index -> S.update index n queue
startTimeoutThread s n
wakeupDisplayThread s
return realId
closeNotification :: NotifyState -> Word32 -> IO ()
closeNotification s nId = do
notePurge s nId
wakeupDisplayThread s
notificationDaemon :: (AutoMethod f1, AutoMethod f2)
=> f1 -> f2 -> IO ()
notificationDaemon onNote onCloseNote = do
client <- connectSession
_ <- requestName client "org.freedesktop.Notifications" [nameAllowReplacement, nameReplaceExisting]
export client "/org/freedesktop/Notifications" interface
where
getServerInformation :: IO (Text, Text, Text, Text)
getServerInformation = return ("haskell-notification-daemon",
"nochair.net",
"0.0.1",
"1.1")
getCapabilities :: IO [Text]
getCapabilities = return ["body", "body-markup"]
interface = defaultInterface
{ interfaceName = "org.freedesktop.Notifications"
, interfaceMethods =
[ autoMethod "GetServerInformation" getServerInformation
, autoMethod "GetCapabilities" getCapabilities
, autoMethod "CloseNotification" onCloseNote
, autoMethod "Notify" onNote
]
}
wakeupDisplayThread :: NotifyState -> IO ()
wakeupDisplayThread s = writeChan (noteChan s) ()
displayThread :: NotifyState -> IO ()
displayThread s = forever $ do
() <- readChan (noteChan s)
ns <- readTVarIO (noteQueue s)
postGUIAsync $
if S.length ns == 0
then widgetHide (noteContainer s)
else do
labelSetMarkup (noteWidget s) $ formatMessage (noteConfig s) (toList ns)
widgetShowAll (noteContainer s)
where
formatMessage NotificationConfig {..} ns =
take notificationMaxLength $ notificationFormatter ns
startTimeoutThread :: NotifyState -> Notification -> IO ()
startTimeoutThread s Notification {..} = case noteExpireTimeout of
Nothing -> return ()
Just timeout -> void $ forkIO $ do
threadDelay (fromIntegral timeout * 10^(6 :: Int))
notePurge s noteId
wakeupDisplayThread s
data NotificationConfig = NotificationConfig
{ notificationMaxTimeout :: Maybe Int32
, notificationMaxLength :: Int
, notificationFormatter :: [Notification] -> String
}
defaultFormatter :: [Notification] -> String
defaultFormatter ns =
let count = length ns
n = head ns
prefix = if count == 1
then ""
else "(" <> show count <> ") "
msg = T.unpack $ if T.null (noteBody n)
then noteSummary n
else noteSummary n <> ": " <> noteBody n
in "<span fgcolor='yellow'>" <> prefix <> "</span>" <> msg
defaultNotificationConfig :: NotificationConfig
defaultNotificationConfig =
NotificationConfig { notificationMaxTimeout = Nothing
, notificationMaxLength = 100
, notificationFormatter = defaultFormatter
}
notifyAreaNew :: MonadIO m => NotificationConfig -> m Widget
notifyAreaNew cfg = liftIO $ do
frame <- frameNew
box <- hBoxNew False 3
textArea <- labelNew (Nothing :: Maybe String)
button <- eventBoxNew
sep <- vSeparatorNew
bLabel <- labelNew (Nothing :: Maybe String)
widgetSetName bLabel ("NotificationCloseButton" :: String)
labelSetMarkup bLabel ("×" :: String)
labelSetMaxWidthChars textArea (notificationMaxLength cfg)
labelSetEllipsize textArea EllipsizeEnd
containerAdd button bLabel
boxPackStart box textArea PackGrow 0
boxPackStart box sep PackNatural 0
boxPackStart box button PackNatural 0
containerAdd frame box
widgetHide frame
s <- initialNoteState (toWidget frame) textArea cfg
_ <- on button buttonReleaseEvent (userCancel s)
realizableWrapper <- hBoxNew False 0
boxPackStart realizableWrapper frame PackNatural 0
widgetShow realizableWrapper
void $ on realizableWrapper realize $ do
void $ forkIO (displayThread s)
notificationDaemon (notify s) (closeNotification s)
return (toWidget realizableWrapper)
where
userCancel s = liftIO $ do
noteNext s
wakeupDisplayThread s
return True