module XNobar.Internal.Notification ( CapId, uncap, Id, makeId, Notification(..), urgency, NotificationsById, append, parseNotif, notifyInSig, notifyOutSig ) where import DBus (Variant, fromVariant, Type(..)) import Data.Int (Int32) import Data.Map.Strict hiding (filter) import Data.Maybe (fromJust, fromMaybe) import Data.Semigroup (Max) import Data.Word (Word8, Word32) import Flow ((.>)) import Prelude hiding (String, lookup) import qualified Prelude as P (String) import XNobar.Internal.Positive32 type String = P.String -- in case I want to change type type Id = Positive32 makeId = positive32 newtype CapId = CapId { uncap :: Max Id } deriving (Eq, Ord, Bounded, Semigroup, Monoid) instance Enum CapId where toEnum = error "Not meant to be used" fromEnum = error "Not meant to be used" pred = error "Not meant to be used" succ c@(CapId i) | i == maxBound = c | otherwise = CapId $ succ i notifyInSig = [ TypeString, TypeWord32, TypeString, TypeString, TypeString, TypeArray TypeString, TypeDictionary TypeString TypeString, TypeInt32 ] notifyOutSig = [TypeWord32] data Notification = Notification { appName :: !String, appIcon :: !String, summary :: !String, body :: !String, actions :: ![String], hints :: !(Map String Variant), expireTout :: !Int32 } urgency :: Notification -> Word8 urgency n = let u = lookup "urgency" (hints n) in case u of Nothing -> 0 (Just x) -> fromMaybe 0 (fromVariant x) parseNotif :: [Variant] -> (Word32, Notification) parseNotif [name, rid, icon, summary, body, actions, hints, expire] = (fromJust $ fromVariant rid, Notification (fromJust $ fromVariant name) (fromJust $ fromVariant icon) (fromJust $ fromVariant summary) (fromJust $ fromVariant body) (fromJust $ fromVariant actions) (fromJust $ fromVariant hints) (fromJust $ fromVariant expire)) parseNotif _ = error "WTF, something went wrong with DBus?" type NotificationsById = [(Id, Notification)] append :: Eq i => [(i, n)] -> (i, n) -> [(i, n)] ns `append` n = let ns' = filter (theId .> (/= theId n)) ns in ns' <> [n] where theId = fst