{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module System.Taffybar.Widget.FreedesktopNotifications
  ( Notification(..)
  , NotificationConfig(..)
  , defaultNotificationConfig
  , notifyAreaNew
  ) where
import           BroadcastChan
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           GI.GLib (markupEscapeText)
import           GI.Gtk
import qualified GI.Pango as Pango
import           System.Taffybar.Util
import Prelude
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 :: BroadcastChan In () 
  }
initialNoteState :: Widget -> Label -> NotificationConfig -> IO NotifyState
initialNoteState wrapper l cfg = do
  m <- newTVarIO 1
  q <- newTVarIO S.empty
  ch <- newBroadcastChan
  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 configTimeout = notificationMaxTimeout (noteConfig s)
      realTimeout = if timeout <= 0 
                    then configTimeout
                    else case configTimeout of
                           Nothing -> Just timeout
                           Just maxTimeout -> Just (min maxTimeout timeout)
  escapedSummary <- markupEscapeText summary (-1)
  escapedBody <- markupEscapeText body (-1)
  let n = Notification { noteAppName = appName
                       , noteReplaceId = replaceId
                       , noteSummary = escapedSummary
                       , noteBody = escapedBody
                       , 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 = void $ writeBChan (noteChan s) ()
displayThread :: NotifyState -> IO ()
displayThread s = do
  chan <- newBChanListener (noteChan s)
  forever $ do
    _ <- readBChan chan
    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 =
      T.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^(3 :: Int))
    notePurge s noteId
    wakeupDisplayThread s
data NotificationConfig = NotificationConfig
  { notificationMaxTimeout :: Maybe Int32 
  , notificationMaxLength :: Int 
  , notificationFormatter :: [Notification] -> T.Text 
  }
defaultFormatter :: [Notification] -> T.Text
defaultFormatter ns =
  let count = length ns
      n = head ns
      prefix = if count == 1
               then ""
               else "(" <> T.pack (show count) <> ") "
      msg =  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 Nothing
  box <- boxNew OrientationHorizontal 3
  textArea <- labelNew (Nothing :: Maybe Text)
  button <- eventBoxNew
  sep <- separatorNew OrientationHorizontal
  bLabel <- labelNew (Nothing :: Maybe Text)
  widgetSetName bLabel "NotificationCloseButton"
  labelSetMarkup bLabel "×"
  labelSetMaxWidthChars textArea (fromIntegral $ notificationMaxLength cfg)
  labelSetEllipsize textArea Pango.EllipsizeModeEnd
  containerAdd button bLabel
  boxPackStart box textArea True True 0
  boxPackStart box sep False False 0
  boxPackStart box button False False 0
  containerAdd frame box
  widgetHide frame
  w <- toWidget frame
  s <- initialNoteState w textArea cfg
  _ <- onWidgetButtonReleaseEvent button (userCancel s)
  realizableWrapper <- boxNew OrientationHorizontal 0
  boxPackStart realizableWrapper frame False False 0
  widgetShow realizableWrapper
  
  
  
  
  void $ onWidgetRealize realizableWrapper $ do
    void $ forkIO (displayThread s)
    notificationDaemon (notify s) (closeNotification s)
  
  toWidget realizableWrapper
  where
    
    userCancel s _ = do
      noteNext s
      wakeupDisplayThread s
      return True