summaryrefslogtreecommitdiffstats
path: root/RenderTreeView.hs
blob: b08ff14f8710a96616da97630e90dc28096abc6d (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
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}

module RenderTreeView (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.Char
import Data.Monoid
import Data.Time
import Data.Time.Format.Human
import Data.Tree
import TagUtils (Tag)
import Trammel
import TreeView


-- TODO make configurable
humanTimeLocale :: HumanTimeLocale
humanTimeLocale = defaultHumanTimeLocale
    { justNow       = "now"
    , secondsAgo    = (++ "s ago")
    , oneMinuteAgo  = "1m ago"
    , minutesAgo    = (++ "m ago")
    , oneHourAgo    = "1h ago"
    , aboutHoursAgo = (++ "h ago")
    , at            = \_ -> ("" ++)
    , daysAgo       = (++ "d ago")
    , weekAgo       = (++ "w ago")
    , weeksAgo      = (++ "w ago")
    , onYear        = ("" ++)
    , dayOfWeekFmt  = "%a %H:%M"
    , thisYearFmt   = "%b %e"
    , prevYearFmt   = "%b %e, %Y"
    }


renderTreeView :: UTCTime -> TreeView -> Tree TreeView -> [Trammel String]
renderTreeView now cur _loc@(Node label children) =
    [ renderTreeView1 now hasFocus label ] ++
    concatMap (map ("  "<>) . renderTreeView now cur) children
  where
    hasFocus = cur == label


-- TODO locale-style: headerKey = \s -> SGR [..] (s <> ": ")

searchSGR
    , focusSGR
    , quoteSGR
    , boringSGR
    , dateSGR
    , tagsSGR
    , unreadMessageSGR
    , unreadSearchSGR
    , killedTagSGR
    , starTagSGR
    :: Trammel String -> Trammel String
searchSGR = SGR [38,5,162]
focusSGR = SGR [38,5,160]
quoteSGR = SGR [38,5,242]
boringSGR = SGR [38,5,240]
dateSGR = SGR [38,5,071]
tagsSGR = SGR [38,5,036]
killedTagSGR = SGR [38,5,088]
starTagSGR = SGR [38,5,226]

unreadMessageSGR = SGR [38,5,117]
unreadSearchSGR = SGR [38,5,250]


renderTreeView1 :: UTCTime -> Bool -> TreeView -> Trammel String
renderTreeView1 now hasFocus x = case x of

    TVSearch s ->
        let c = if hasFocus then focusSGR else searchSGR
        in c $ Plain s

    TVSearchResult sr ->
        let c = if hasFocus then focusSGR else
                    if "unread" `elem` Notmuch.searchTags sr
                        then unreadSearchSGR
                        else boringSGR
            date = dateSGR $ renderDate now x
            tags = tagsSGR $ renderTags (Notmuch.searchTags sr)
            subj = Plain $ T.unpack $ Notmuch.searchSubject sr
        in c $ subj <> " " <> date <> " " <> tags

    TVMessage m ->
        let c = if hasFocus then focusSGR else
                    if "unread" `elem` Notmuch.messageTags m
                        then unreadMessageSGR
                        else boringSGR
            from = renderFrom (M.lookup "from" $ Notmuch.messageHeaders m)
            date = dateSGR $ renderDate now x
            tags = tagsSGR $ renderTags (Notmuch.messageTags m) -- TODO filter common tags
        in c $ from <> " " <> date <> " " <> tags

    TVMessageHeaderField m fieldName ->
        let c = if hasFocus then focusSGR else boringSGR
            k = Plain $ T.unpack $ CI.original fieldName
            v = maybe "nothing"
                      (Plain . T.unpack)
                      (M.lookup fieldName $ Notmuch.messageHeaders m)
        in c $ k <> ": " <> v

    TVMessagePart _ p ->
        let c = if hasFocus then focusSGR else boringSGR
            i = Plain $ show $ Notmuch.partID p
            t = Plain $ T.unpack $ CI.original $ Notmuch.partContentType p
            filename = maybe "" (Plain . (" "<>) . show) $ Notmuch.partContentFilename p
            charset = maybe "" (Plain . (" "<>) . show) $ Notmuch.partContentCharset p
        in c $ "part#" <> i <> " " <> t <> filename <> charset

    TVMessageQuoteLine _ _ _ s ->
        if hasFocus
            then focusSGR $ Plain s
            else quoteSGR $ Plain s

    TVMessageLine _ _ _ s ->
        if hasFocus
            then focusSGR $ Plain s
            else Plain s



renderDate :: UTCTime -> TreeView -> Trammel String
renderDate now = \case
    TVSearchResult sr -> f humanTimeLocale (Notmuch.searchTime sr)
    TVMessage m -> f humanTimeLocale (Notmuch.messageTime m)
    _ -> SGR [35,1] "timeless"
  where
    f timeLocale time =
        Plain $ humanReadableTimeI18N' timeLocale now time


renderFrom :: Maybe T.Text -> Trammel String
renderFrom = \case
    Just fromLine -> Plain $ dropAddress $ T.unpack fromLine
    Nothing -> SGR [35,1] "Anonymous"


renderTags :: [Tag] -> Trammel String
renderTags =
    -- TODO sort somewhere else
    mconcat . L.intersperse " " . map renderTag . L.sort


renderTag :: Tag -> Trammel String
renderTag tag = case tag of
    "killed" -> killedTagSGR plain
    "star" -> starTagSGR plain
    _ -> plain
  where
    plain = Plain $ T.unpack tag


dropAddress :: String -> String
dropAddress xs =
    case L.findIndices (=='<') xs of
        [] -> xs
        is -> L.dropWhileEnd isSpace $ take (last is) xs