summaryrefslogtreecommitdiffstats
path: root/TreeViewRaw.hs
blob: db4a899f1ac260765f19fbec47cbd3d8a3f86eb1 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}

module TreeViewRaw (renderTreeView) where

import qualified Notmuch.Message as Notmuch
import qualified Notmuch.SearchResult as Notmuch
import qualified Data.CaseInsensitive as CI
import qualified Data.List as L
import qualified Data.Map as M
import qualified Data.Text as T
import Data.Monoid
import Data.Tree
import Trammel
import TreeView
import Utils (padl)


renderTreeView :: TreeView -> Tree TreeView -> [Trammel String]
renderTreeView cur _loc@(Node label children) =
    [ colorize $ renderTreeView1 hasFocus label ] ++
    concatMap (map ("  "<>) . renderTreeView cur) children
  where
    hasFocus = cur == label
    colorize s =
        if hasFocus
            then SGR [31] s
            else s


renderTreeView1 :: Bool -> TreeView -> Trammel String
renderTreeView1 hasFocus = \case

    TVSearch s ->
        Plain s

    TVSearchResult sr ->
        let c = case (hasFocus, "unread" `elem` Notmuch.searchTags sr) of
                    (False, False) -> SGR [38,5,240]
                    (False,  True) -> SGR [38,5,250]
                    (True,  False) -> SGR [38,5,088]
                    (True,   True) -> SGR [38,5,160]
        in c $
        Plain (
            (padl 11 ' ' $ T.unpack $ Notmuch.searchDateRel sr)
            ++ " (" ++ (show $ Notmuch.searchMatched sr) ++ ")  "
            ++ (T.unpack $ Notmuch.searchSubject sr)
            ++ " "
            )
        <>
        mconcat (L.intersperse " " (map (SGR [38,5,036] . Plain . T.unpack) $ Notmuch.searchTags sr))

    TVMessage m ->
        let c = case (hasFocus, "unread" `elem` Notmuch.messageTags m) of
                    (False, False) -> SGR [38,5,240]
                    (False,  True) -> SGR [38,5,250]
                    (True,  False) -> SGR [38,5,088]
                    (True,   True) -> SGR [38,5,160]
        in c $
        Plain (
            (Notmuch.unMessageID $ Notmuch.messageId m)
            ++ " "
            ++ T.unpack (T.intercalate (T.pack ",") $ Notmuch.messageTags m)
            )

    TVMessageHeaderField m fieldName -> Plain $
        let k = T.unpack $ CI.original fieldName
            v = maybe "nothing"
                      T.unpack
                      (M.lookup fieldName $ Notmuch.messageHeaders m)
        in k ++ ": " ++ v

    TVMessagePart _ p -> Plain $
        "part#"
        ++ (show $ Notmuch.partID p)
        ++ " "
        ++ (T.unpack $ CI.original $ Notmuch.partContentType p)

    TVMessageLine _ _ _ s ->
        Plain s