Skip to content

Commit

Permalink
reorganised code
Browse files Browse the repository at this point in the history
  • Loading branch information
smallhadroncollider committed Nov 19, 2017
1 parent 47ca5b7 commit 5dbda01
Show file tree
Hide file tree
Showing 11 changed files with 68 additions and 55 deletions.
6 changes: 3 additions & 3 deletions app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
module Main where

import Draw (render)
import State (initial, setTasks)
import TaskellJSON (exists, readJSON)
import UI.Render (render)
import Flow.State (initial, setTasks)
import Persistence.Taskell (exists, readJSON)

import Data.Bool

Expand Down
2 changes: 1 addition & 1 deletion src/Task.hs → src/Data/Taskell/Task.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
{-# LANGUAGE DeriveGeneric #-}

module Task where
module Data.Taskell.Task where

import GHC.Generics
import Data.Aeson
Expand Down
6 changes: 3 additions & 3 deletions src/Actions.hs → src/Flow/Actions.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
module Actions (event) where
module Flow.Actions (event) where

import State
import Graphics.Vty.Input.Events
import Keyboard
import Flow.State
import Flow.Keyboard

event :: Event -> State -> State
event e | isChar 'q' e = quit
Expand Down
2 changes: 1 addition & 1 deletion src/Keyboard.hs → src/Flow/Keyboard.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Keyboard (
module Flow.Keyboard (
isChar,
isUp,
isDown
Expand Down
4 changes: 2 additions & 2 deletions src/State.hs → src/Flow/State.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module State where
module Flow.State where

import Task (Tasks, completed, empty)
import Data.Taskell.Task (Tasks, completed, empty)
import Data.Sequence (mapWithIndex)

data State = State {
Expand Down
6 changes: 3 additions & 3 deletions src/TaskellJSON.hs → src/Persistence/Taskell.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
module TaskellJSON where
module Persistence.Taskell where

import System.Directory
import Data.Aeson
import Data.Aeson.Encode.Pretty
import qualified Data.ByteString.Lazy as BS

import CLI (promptYN)
import Task (Tasks, empty)
import UI.CLI (promptYN)
import Data.Taskell.Task (Tasks, empty)

path :: FilePath
path = "taskell.json"
Expand Down
2 changes: 1 addition & 1 deletion src/CLI.hs → src/UI/CLI.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module CLI where
module UI.CLI where

import System.IO (stdout, hFlush)

Expand Down
12 changes: 12 additions & 0 deletions src/UI/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
module UI.Main where

import Graphics.Vty

attrTitle :: Attr
attrTitle = defAttr `withForeColor` green

marginBottom :: Image -> Image
marginBottom = pad 0 0 0 1

-- creates the title element
title = marginBottom $ string attrTitle "[Taskell]"
42 changes: 8 additions & 34 deletions src/Draw.hs → src/UI/Render.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Draw (
module UI.Render (
render
) where

Expand All @@ -7,38 +7,12 @@ import Data.Sequence (mapWithIndex, filter)
import Data.Foldable (toList)
import Graphics.Vty

import State
import Actions
import Task (Task, Tasks, description, completed, filterCompleted)
import TaskellJSON (writeJSON)

-- styles
attrTask :: Attr
attrTask = defAttr `withForeColor` magenta

attrDone :: Attr
attrDone = defAttr `withStyle` dim

attrCurrent :: Attr
attrCurrent = defAttr `withForeColor` blue

attrTitle :: Attr
attrTitle = defAttr `withForeColor` green

marginBottom :: Image -> Image
marginBottom = pad 0 0 0 1

-- style a task
bullet :: Int -> Int -> Task -> Image
bullet cur i t = string style' ("" ++ s ++ tick)
where
s = description t
tick = if completed t then "" else ""
style = if completed t then attrDone else attrTask
style' = if cur == i then attrCurrent else style

-- creates the title element
title = marginBottom $ string attrTitle "[Taskell]"
import Flow.State
import Flow.Actions
import Data.Taskell.Task (Task, Tasks, description, completed, filterCompleted)
import Persistence.Taskell (writeJSON)
import UI.Task (present)
import UI.Main (title)

-- filter out completed if option set
getTasks :: State -> Tasks
Expand All @@ -49,7 +23,7 @@ getTasks s = if showCompleted s then ts else filterCompleted ts
pic :: State -> Picture
pic state = picForImage $ title <-> imgs
where
bullet' = bullet $ current state
bullet' = present $ current state
imgs = vertCat $ toList $ mapWithIndex bullet' $ getTasks state

-- the draw loop
Expand Down
23 changes: 23 additions & 0 deletions src/UI/Task.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
module UI.Task where

import Graphics.Vty
import Data.Taskell.Task

-- styles
attrTask :: Attr
attrTask = defAttr `withForeColor` magenta

attrDone :: Attr
attrDone = defAttr `withStyle` dim

attrCurrent :: Attr
attrCurrent = defAttr `withForeColor` blue

-- style a task
present :: Int -> Int -> Task -> Image
present cur i t = string style' ("" ++ s ++ tick)
where
s = description t
tick = if completed t then "" else ""
style = if completed t then attrDone else attrTask
style' = if cur == i then attrCurrent else style
18 changes: 11 additions & 7 deletions taskell.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -15,13 +15,17 @@ cabal-version: >=1.10

library
hs-source-dirs: src
exposed-modules: Draw
, Actions
, Keyboard
, Task
, State
, CLI
, TaskellJSON
, src/UI
, src/Data
exposed-modules: Data.Taskell.Task
, Flow.Actions
, Flow.Keyboard
, Flow.State
, Persistence.Taskell
, UI.CLI
, UI.Main
, UI.Render
, UI.Task
build-depends: base >= 4.7 && < 5
, vty
, bytestring
Expand Down

0 comments on commit 5dbda01

Please sign in to comment.