module XNobar.Impl.Scroller where import Control.Arrow ((&&&)) import Data.Function ((&)) import Data.List (genericLength) import Data.List.Extra (groupOn) import Data.Semigroup (Max(Max)) import Data.Tuple.Extra (first, second, third3) import Flow ((.>)) import XNobar.Internal.Notification (Notification(..), urgency, Id) import XNobar.Internal.Positive32 (toWord32) type Offset = Int scroll :: (Show n) => Maybe (Id, Offset, [(Id, n)]) -> Maybe (Id, Offset, [(Id, n)]) scroll Nothing = Nothing scroll (Just (i, o, notifs)) = let notifs' = cycle notifs & dropWhile (theId .> (/= i)) (i', n') = head notifs' (i'', n'') = notifs' !! 1 in Just (if o < genericLength (show n') - 1 then (i', o + 1, notifs) else (i'', 0, notifs)) theId = fst enableClick p ((Max i, u), s) = attachAction ("echo " ++ show i ++ " > " ++ p) 1 ((if u == 2 then red else id) s) where red = wrap "" "" attachAction a b = wrap ("") "" wrap a c b = a ++ b ++ c -- TODO: probably Offset should be a class merge :: [(Id, n)] -> Maybe (Id, Offset, [(Id, n)]) -> Maybe (Id, Offset, [(Id, n)]) merge news Nothing = Just (theId $ head news, 0, news) merge news (Just olds) = Just $ third3 (`combine` news) olds remove :: Num offset => Id -> Maybe (Id, offset, [(Id, n)]) -> Maybe (Id, offset, [(Id, n)]) remove _ Nothing = error "This should not be possible!" remove _ (Just (_, _, [])) = error "This should not be possible!" remove i (Just (i', _, [_])) = if i /= i' then error "This should not be possible!" else Nothing remove i (Just (i', o, ns)) = let l = length ns (b, a) = second tail $ break ((== i) . theId) $ cycle ns ns' = take (l - 1) $ b ++ a newCurr = head $ if null a then b else a in Just (if i == i' then (theId newCurr, 0, ns') else (i', o, ns')) combine :: [(Id, n)] -> [(Id, n)] -> [(Id, n)] combine olds news = let olds' = olds `suchThat` (theId .> (not . (`elem` (theId <$> news)))) in olds' <> news where suchThat = flip filter onlyIf b a = if b then a else id monospace = (`withFont` 4) where withFont t n = wrap ("") "" t showNotifs :: Int -> [Char] -> (Id, Int, [(Id, Notification)]) -> [Char] showNotifs len pipe (curId, curOffset, oldNotifs') = oldNotifs' & cycle & dropWhile (theId .> (/= curId)) & concatMap (((theId &&& getNotif .> urgency) &&& getNotif .> show) .> spreadChars) & drop curOffset & take len & groupOn theId & concatMap (joinChars .> toWord32' .> enableClick pipe .> niceLineBreak) & ("\x1f4ec " ++) & monospace where getNotif = snd toWord32' = first (first toWord32) spreadChars = sequence joinChars l = (theId (head l), map getNotif l) niceLineBreak = map (\c -> if c `elem` ['\r', '\n'] then '⏎' else c) instance Show Notification where show n = (if urgency n /= 2 then " \x1f4dc " else " \x26a0\xfe0f ") ++ summary n ++ maybeBody ++ " " where maybeBody = if not $ null $ body n then " | " ++ body n else ""