aboutsummaryrefslogtreecommitdiff
path: root/src/Model/Mail.hs
blob: dd166ab6edb8eb0ed319a38eeb66e38344b3e354 (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
{-# LANGUAGE OverloadedStrings #-}

module Model.Mail
  ( mailSubject
  , mailBody
  ) where

import Data.Text (Text)
import qualified Data.Text as T
import Data.Maybe (fromMaybe)

import Model.Date
import Model.Event

data Time =
  Today
  | NextWeek
  deriving (Eq, Show)

mailSubject :: [Event] -> [Event] -> Text
mailSubject eventsToday eventsNextWeek =
  T.concat
    [ "Hey, "
    , if not . null $ eventsToday
        then mailSubjectSentence Today eventsToday
        else ""
    , if not . null $ eventsNextWeek
        then
          T.concat
            [ if not . null $ eventsToday then " and " else ""
            , mailSubjectSentence NextWeek eventsNextWeek
            ]
        else
          ""
    , "!"
    ]

mailSubjectSentence :: Time -> [Event] -> Text
mailSubjectSentence time events =
  let count = length events
  in  T.concat
        [ case time of
            Today -> if count > 1 then "there are" else "there is"
            NextWeek -> "there will be"
        , " "
        , T.pack . show $ count
        , " event"
        , if count > 1 then "s" else ""
        , " "
        , if time == Today then "today" else "next week"
        ]

mailBody :: Date -> SuccessiveDates -> [Event] -> [Event] -> Text
mailBody currentDate nextWeek eventsToday eventsNextWeek =
  T.concat
    [ if not . null $ eventsToday
        then mailBodySentence Today currentDate nextWeek eventsToday
        else ""
    , if not . null $ eventsNextWeek
        then
          T.concat
            [ if not . null $ eventsToday then " " else ""
            , mailBodySentence NextWeek currentDate nextWeek eventsNextWeek
            ]
        else ""
    ]

mailBodySentence :: Time -> Date -> SuccessiveDates -> [Event] -> Text
mailBodySentence time currentDate nextWeek events =
  T.concat $ map (mailBodyPart time currentDate nextWeek) (attachLines events)

attachLines :: [Event] -> [(Line, Event)]
attachLines events =
  let count = length events
      lineKind 1 = if count == 1 then SingleLine else FirstLine
      lineKind line = if line == count then LastLine else MiddleLine
      mapFst f (x, y) = (f x, y)
  in  map (mapFst lineKind) . zip [1..] $ events

data Line =
  SingleLine
  | FirstLine
  | MiddleLine
  | LastLine
  deriving (Eq, Show)

mailBodyPart :: Time -> Date -> SuccessiveDates -> (Line, Event) -> Text
mailBodyPart time currDate nextWeek (line, event) =
  let nextWeekDay = dayAndMonthInRange nextWeek (date event)
  in  T.concat
        [ case line of
            x | x `elem` [SingleLine, FirstLine] ->
              if time == Today then "Today, " else "Next week, "
            MiddleLine ->
              ", "
            LastLine ->
              " and "
            _ ->
              ""
        , name event
        , if time == Today then " is " else " will be "
        , T.pack . show $
            if time == Today
              then age currDate event
              else fromMaybe 0 $ (\d -> year d - year (date event)) <$> nextWeekDay
        , " years old"
        , if time == NextWeek
            then
              fromMaybe "" $ (\d -> T.concat [" on " , getWeekDay d]) <$> nextWeekDay
            else
              ""
        , if line == SingleLine || line == LastLine then "." else ""
        ]