Skip to content

Commit

Permalink
release v0.4.4
Browse files Browse the repository at this point in the history
  • Loading branch information
soywod committed Jul 27, 2020
1 parent 652e888 commit f4af4f7
Show file tree
Hide file tree
Showing 7 changed files with 343 additions and 297 deletions.
5 changes: 4 additions & 1 deletion CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0

## [Unreleased]

## [0.4.4] - 2020-07-27

### Fixed

- Bad build state for update cmd [#27]
Expand Down Expand Up @@ -174,7 +176,8 @@ First release :tada:

- Linux binaries

[unreleased]: https://github.com/soywod/unfog.cli/compare/v0.4.3...HEAD
[unreleased]: https://github.com/soywod/unfog.cli/compare/v0.4.4...HEAD
[0.4.4]: https://github.com/soywod/unfog.cli/compare/v0.4.3...v0.4.4
[0.4.3]: https://github.com/soywod/unfog.cli/compare/v0.4.2...v0.4.3
[0.4.2]: https://github.com/soywod/unfog.cli/compare/v0.4.1...v0.4.2
[0.4.1]: https://github.com/soywod/unfog.cli/compare/v0.4.0...v0.4.1
Expand Down
2 changes: 1 addition & 1 deletion package.yaml
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
name: unfog
version: 0.4.3
version: 0.4.4
github: "soywod/unfog.cli"
license: BSD3
author: "Clément DOUIN"
Expand Down
4 changes: 2 additions & 2 deletions src/Parsec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,8 @@ data Arg = Arg { _type :: ArgType

emptyArgTree :: Arg
emptyArgTree = Arg { _ids = []
, _type = Cmd
, _cmd = ""
, _type = Qry
, _cmd = "list"
, _desc = ""
, _tags = []
, _due = Nothing
Expand Down
118 changes: 55 additions & 63 deletions src/Query.hs
Original file line number Diff line number Diff line change
@@ -1,21 +1,20 @@
module Query where

import qualified Data.ByteString.Lazy.Char8 as BL
import Control.Exception
import Data.Aeson hiding ( Error )
import Data.Fixed
import Data.List
import Data.Maybe
import Data.Time
import System.Process ( system )
import Text.Read

import Event
import Response
import State
import Store
import Task
import Control.Exception
import Data.Aeson hiding (Error)
import qualified Data.ByteString.Lazy.Char8 as BL
import Data.Fixed
import Data.List
import Data.Maybe
import Data.Time
import Event
import qualified Parsec
import Response
import State
import Store
import System.Process (system)
import Task
import Text.Read

data Query
= List Parsec.Arg
Expand All @@ -31,67 +30,61 @@ data Query
handle :: Parsec.Arg -> IO ()
handle args = do
evts <- readEvents
now <- getCurrentTime
now <- getCurrentTime
let state = applyEvents now evts
let qry = getQuery args
let qry = getQuery args
execute args state qry

getQuery :: Parsec.Arg -> Query
getQuery args = case Parsec._cmd args of
"list" -> List args
"info" -> case Parsec._ids args of
[] -> Error "show" "invalid arguments"
[] -> Error "show" "invalid arguments"
id : _ -> Info args
"worktime" -> Wtime args
"status" -> Status
"upgrade" -> Upgrade
"version" -> Version
"help" -> Help
"status" -> Status
"upgrade" -> Upgrade
"version" -> Version
"help" -> Help

execute :: Parsec.Arg -> State -> Query -> IO ()
execute args state query = do
let rtype = if Parsec._json (Parsec._opts args) then JSON else Text
let more = Parsec._more (Parsec._opts args)
let more = Parsec._more (Parsec._opts args)
case query of
List args -> listTasks args state query rtype

Info args -> do
now <- getCurrentTime
let ctx = _ctx state
let id = head $ Parsec._ids args
let fByTags = filterByTags $ _ctx state
let fByDone = filterByDone $ "done" `elem` ctx
let ctx = _ctx state
let id = head $ Parsec._ids args
let fByTags = filterByTags $ _ctx state
let fByDone = filterByDone $ "done" `elem` ctx
let fByNumber = findById id
let maybeTask = fByNumber . fByTags . fByDone $ _tasks state
case maybeTask of
Nothing -> printErr rtype $ "show: task [" ++ show id ++ "] not found"
Just task -> printTask rtype task { _wtime = getTotalWtime now task }

Nothing -> printErr rtype $ "show: task [" ++ show id ++ "] not found"
Just task -> printTask rtype task {_wtime = getTotalWtime now task}
Wtime args -> do
now <- getCurrentTime
let tags = Parsec._tags args `union` _ctx state
let min = Parsec.parseMinDate now args
let max = Parsec.parseMaxDate now args
let refs = map _ref $ filterByTags tags $ _tasks state
let tags = Parsec._tags args `union` _ctx state
let min = Parsec.parseMinDate now args
let max = Parsec.parseMaxDate now args
let refs = map _ref $ filterByTags tags $ _tasks state
let tasks = filterByRefs refs $ _tasks state
let wtime = getWtimePerDay now min max tasks
let ctx = if null tags then "global" else "for [" ++ unwords tags ++ "]"
printWtime rtype more ("unfog: wtime " ++ ctx) wtime

Status -> do
now <- getCurrentTime
case filter ((> 0) . _active) $ _tasks state of
[] -> printEmptyStatus rtype
[] -> printEmptyStatus rtype
task : _ -> printStatus rtype task

Upgrade ->
system
"curl -sSL https://raw.githubusercontent.com/soywod/unfog.cli/master/bin/install.sh | sh"
"curl -sSL https://raw.githubusercontent.com/soywod/unfog.cli/master/bin/install.sh | sh"
>> return ()

Version -> printVersion rtype "0.4.3"

Help -> do
Version -> printVersion rtype "0.4.4"
Help -> do
putStrLn "Usage: unfog cmd (args)"
putStrLn ""
putStrLn "Create a task:"
Expand Down Expand Up @@ -128,27 +121,26 @@ execute args state query = do
putStrLn ""
putStrLn "Display total worktime by context:"
putStrLn "worktime|wtime (+tags) ([min:time) (]max:time) (--json)"

Error command message -> printErr rtype $ command ++ ": " ++ message

listTasks :: Parsec.Arg -> State -> Query -> ResponseType -> IO ()
listTasks args state query rtype
| Parsec._onlyIds (Parsec._opts args)
= printTasksId rtype . map Task._id . fByTags . fByDone $ allTasks
| Parsec._onlyTags (Parsec._opts args)
= printTasksTags rtype . nub . concatMap Task._tags $ allTasks
| otherwise
= do
now <- getCurrentTime
let ctx = _ctx state
let fByTags = filterByTags ctx
let fByDone = filterByDone $ "done" `elem` ctx
let tasks = mapWithWtime now . fByTags . fByDone $ _tasks state
let ctxStr = if null ctx then "" else " [" ++ unwords ctx ++ "]"
let onlyIds = Parsec._onlyIds (Parsec._opts args)
let onlyTags = Parsec._onlyTags (Parsec._opts args)
printTasks rtype ("unfog: list" ++ ctxStr) tasks
where
allTasks = _tasks state
fByTags = filterByTags . _ctx $ state
fByDone = filterByDone . elem "done" . _ctx $ state
| Parsec._onlyIds (Parsec._opts args) =
printTasksId rtype . map Task._id . fByTags . fByDone $ allTasks
| Parsec._onlyTags (Parsec._opts args) =
printTasksTags rtype . nub . concatMap Task._tags $ allTasks
| otherwise =
do
now <- getCurrentTime
let ctx = _ctx state
let fByTags = filterByTags ctx
let fByDone = filterByDone $ "done" `elem` ctx
let tasks = mapWithWtime now . fByTags . fByDone $ _tasks state
let ctxStr = if null ctx then "" else " [" ++ unwords ctx ++ "]"
let onlyIds = Parsec._onlyIds (Parsec._opts args)
let onlyTags = Parsec._onlyTags (Parsec._opts args)
printTasks rtype ("unfog: list" ++ ctxStr) tasks
where
allTasks = _tasks state
fByTags = filterByTags . _ctx $ state
fByDone = filterByDone . elem "done" . _ctx $ state
4 changes: 2 additions & 2 deletions src/Task.hs
Original file line number Diff line number Diff line change
Expand Up @@ -177,8 +177,8 @@ wtimePerDay (WtimeTask id desc _) (start, stop) = nextWtimes
where
day = show currDay
currDay = utctDay start
endOfDay = read $ show currDay ++ " 23:59:59.999999999" :: UTCTime
nextDay = read $ show (addDays 1 currDay) ++ " 00:00:00" :: UTCTime
endOfDay = read $ show currDay ++ " 23:59:59 UTC" :: UTCTime
nextDay = read $ show (addDays 1 currDay) ++ " 00:00:00 UTC" :: UTCTime
nextWtimes = if stop < endOfDay
then [(day, [WtimeTask id desc $ realToFrac $ diffUTCTime stop start])]
else
Expand Down
Loading

0 comments on commit f4af4f7

Please sign in to comment.