aboutsummaryrefslogtreecommitdiffhomepage
path: root/src/Utility/Emacs.hs
blob: 2b197eb7e401b07780ad76932b766af8088ed510 (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
{-# LANGUAGE DataKinds     #-}
{-# LANGUAGE TypeOperators #-}

module Utility.Emacs ( getEmacsOutput
                     , parseEmacsOutput) where

import           Control.Applicative ((<$>))
import           Control.Monad       (foldM, when)
import qualified Control.SremConfig  as SremConfig
import           Data.Maybe.Read
import           Data.Modular
import           System.Directory    (getHomeDirectory)
import           System.FilePath     ((</>))
import           System.Process      (readProcess)
import           Text.Regex.Posix    ((=~))
import           Types.Reminder

parseEmacsOutput :: String -> [Reminder]
parseEmacsOutput = foldr step [] . drop 2 . lines
  where
    step line rems = maybe rems (++ rems) $ parseLine line

parseLine              :: String -> Maybe [Reminder]
parseLine line         = do
    when (not lineMatch) $ fail ""
    let hStr:mStr:s:[] = drop 1 . concat $ lineMatchStrings
    h <- readMaybe hStr
    m <- readMaybe mStr
    staggeredReminders =<< makeReminder h m s
  where
    apptRegexp         = " ([0-9]{1,2}):([0-9][0-9])[-]{0,1}[0-9:]{0,5}[.]* (.*)$"
    snipRegexp         = "[ ]{2,}:.*:*$"

    lineMatch        = line =~ apptRegexp :: Bool
    lineMatchStrings = line =~ apptRegexp :: [[String]]

staggeredReminders   :: Reminder -> Maybe [Reminder]
staggeredReminders r = sequence $ foldr step [] SremConfig.intervals
  where
    step minsBefore rems =
        makeReminder' (h minsBefore) (m minsBefore) (getReminderText r) : rems
    h m = if   m > getReminderMinute r
          then getReminderHour r - 1
          else getReminderHour r
    m m = unMod $ (toMod (getReminderMinute r) :: Int/60) - (toMod m :: Int/60)

getEmacsOutput :: IO String
getEmacsOutput = do
    args <- makeEmacsArgs <$> getHomeDirectory
    readProcess "emacs" args ""

makeEmacsArgs      :: String -> [String]
makeEmacsArgs home = [ "-batch"
                     , "-l", home </> ".emacs.d" </> "init.el"
                     , "-eval", "(setq org-agenda-sticky nil)"
                     , "-eval", "(org-batch-agenda \"D\")" ]