summaryrefslogtreecommitdiffstats
path: root/RenderTreeView.hs
blob: 21a677118750667a7959809a5af9af7f9a8465d6 (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
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
{-# 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 qualified Data.Tree.Zipper as Z
import qualified TreeZipperUtils as Z
import Blessings
import Data.Char
import Data.Monoid
import Data.Time
import Data.Time.Format.Human
import Data.Tree
import TagUtils (Tag)
import TreeView


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


renderTreeView
    :: UTCTime
    -> Z.TreePos Z.Full TreeView
    -> Z.TreePos Z.Full TreeView
    -> [Blessings String]
renderTreeView now cur =
    renderNode
  where
    isFocus = (Z.label cur==) . Z.label

    renderNode loc =
        renderRootLabel loc :
        maybeRenderSubForest (Z.firstChild loc)

    renderRootLabel loc =
        renderPrefix loc <>
        renderTreeView1 now (isFocus loc) (Z.label loc)

    renderSubForest loc =
        renderNode loc ++
        maybeRenderSubForest (Z.next loc)

    maybeRenderSubForest =
        maybe mempty renderSubForest


renderPrefix :: Z.TreePos Z.Full TreeView -> Blessings String
renderPrefix =
    mconcat . reverse . map prefix . zip [(1 :: Int)..] . Z.path
  where
    prefix (i, (_lhs, x, rhs)) = case x of
        TVSearch _ -> ""
        TVSearchResult _ -> spacePrefix
        TVMessage _ ->
            case i of
                1 ->
                    if null rhs
                        then endPrefix
                        else teePrefix
                _ ->
                    if null rhs
                        then spacePrefix
                        else pipePrefix
        _ ->
            if null $ filter isTVMessage $ map rootLabel rhs
                then spacePrefix
                else pipePrefix


spacePrefix
    , teePrefix
    , pipePrefix
    , endPrefix
    :: Blessings String
spacePrefix = prefixSGR "  "
teePrefix   = prefixSGR "├╴"
pipePrefix  = prefixSGR "│ "
endPrefix   = prefixSGR "└╴"


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

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

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


renderTreeView1 :: UTCTime -> Bool -> TreeView -> Blessings 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 fromSGR =
                if hasFocus then focusSGR else
                    if "unread" `elem` Notmuch.messageTags m
                        then unreadMessageSGR
                        else boringMessageSGR
            from = fromSGR $ renderFrom (M.lookup "from" $ Notmuch.messageHeaders m)
            date = dateSGR $ renderDate now x
            tags = tagsSGR $ renderTags (Notmuch.messageTags m) -- TODO filter common tags
        in 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
            size = Plain $ show $ Notmuch.contentSize (Notmuch.partContent p)
        in c $ "part#" <> i <> " " <> t <> filename <> charset <> " " <> size

    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 -> Blessings 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 -> Blessings String
renderFrom = \case
    Just fromLine -> Plain $ dropAddress $ T.unpack fromLine
    Nothing -> SGR [35,1] "Anonymous"


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


renderTag :: Tag -> Blessings String
renderTag tag = case tag of
    "draft" -> draftTagSGR plain
    "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