Skip to content
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 4 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,10 @@ Haskell library and terminal GUI tool for time tracking.

cabal run t4

## Run t4 TUI (t5)

cabal run t5

## Run tests

cabal test --test-show-details=direct
Expand Down
4 changes: 2 additions & 2 deletions lib/T4/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -63,8 +63,8 @@ getDay :: Clock -> Day
getDay = localDay . getLocalTime . time

summary :: Clock -> String
summary (Out t) = "out (" ++ sltString t ++ ")"
summary (In t mc ts) = "in (" ++ sltString t ++ ")" ++ catStr ++ tagsStr
summary (Out t) = "OUT (" ++ sltString t ++ ")"
summary (In t mc ts) = "IN (" ++ sltString t ++ ")" ++ catStr ++ tagsStr
where catStr = maybe "" ((" [" ++) . (++ "]")) mc
tagsStr = concatMap (" #" ++) ts

Expand Down
86 changes: 86 additions & 0 deletions t4-tui/TUI.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,86 @@
module Main where

import T4.Data
import T4.Storage
import Util
import Data.Time
import Brick
import Brick.BChan
import Brick.Widgets.Border
import Graphics.Vty
import Lens.Micro.Platform
import Control.Monad
import Control.Monad.IO.Class
import Control.Concurrent
import System.Process

data Tick = Tick
deriving Show

data T4State = T4State
{ _dir :: FilePath
, _clocks :: [Clock]
, _now :: SimpleLocalTime
, _durConf :: DurationConfig
} deriving Show
makeLenses ''T4State

main :: IO ()
main = do

-- Prepare initial state
dd <- getStorageDirectory
curr <- getCurrentSLT
let initState = T4State dd [] curr manDurationConfig

-- Prepare ticking thread
tickChan <- newBChan 42
tickThreadID <- forkIO $ forever $ do writeBChan tickChan Tick
threadDelay $ 1000 * 1000 -- 1 sec.
-- Go
void $ customMainWithDefaultVty (Just tickChan) t4App initState

-- Cleanup
callCommand "clear"
killThread tickThreadID

t4App :: App T4State Tick ()
t4App = App
{ appDraw = drawT4
, appChooseCursor = neverShowCursor
, appHandleEvent = handleEvent
, appStartEvent = initT4
, appAttrMap = const $ attrMap defAttr []
}

initT4 :: EventM () T4State ()
initT4 = do
loadedClocks <- liftIO . loadDataFromDir =<< use dir
clocks .= loadedClocks

drawT4 :: T4State -> [Widget ()]
drawT4 state = [ui]
where ui = hBox [ box (lastClock (state^.clocks^?_last))
, fill ' '
, box (duration (state^.durConf) durPair)
]
durPair = do c1 <- state^.clocks^?_last
guard $ isIn c1
let t1 = getLocalTime $ time c1
t2 = getLocalTime $ state^.now
return $ diffLocalTime t2 t1
box = border . padLeftRight 2

lastClock :: Maybe Clock -> Widget ()
lastClock = str . maybe "no data" summary

duration :: DurationConfig -> Maybe NominalDiffTime -> Widget ()
duration dc = str . maybe "Not clocked in" (showDiffTime dc)

handleEvent :: BrickEvent () Tick -> EventM () T4State ()
handleEvent (AppEvent Tick) = do
c <- liftIO getCurrentSLT
now .= c
return ()
handleEvent (VtyEvent (EvKey KEsc [])) = halt
handleEvent e = liftIO $ print e
12 changes: 11 additions & 1 deletion terminal-time-tracking-tool.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,6 @@ common basics
, yaml
, regex-tdfa
, text
, brick

library
import: basics
Expand All @@ -51,6 +50,17 @@ executable t4
hs-source-dirs: t4-commands
main-is: Commands.hs

executable t5
import: basics
ghc-options: -threaded
build-depends: terminal-time-tracking-tool
, vty
, brick
, microlens-platform
, process
hs-source-dirs: t4-tui
main-is: TUI.hs

test-suite t4-test
import: basics
ghc-options: -Wno-orphans
Expand Down
6 changes: 3 additions & 3 deletions test/T4/DataSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -82,11 +82,11 @@ spec = do

context "Summary: stringification for humans" $ do
it "Simple clock in" $
summary cIn `shouldBe` "in (2017-11-23 17:42:37) [foo] #bar #baz"
summary cIn `shouldBe` "IN (2017-11-23 17:42:37) [foo] #bar #baz"
it "Clock in without category" $
summary cInNoCat `shouldBe` "in (2017-11-23 17:42:37) #bar #baz"
summary cInNoCat `shouldBe` "IN (2017-11-23 17:42:37) #bar #baz"
it "Clock out" $
summary cOut `shouldBe` "out (2017-11-23 17:42:37)"
summary cOut `shouldBe` "OUT (2017-11-23 17:42:37)"

context "YAML clock data" $ do
it "Reading simple clock-in data" $
Expand Down