Skip to content

Commit

Permalink
Include notes when exporting tasks as ndjson
Browse files Browse the repository at this point in the history
  • Loading branch information
ad-si committed Nov 18, 2024
1 parent 3de5f8e commit 2bd11a1
Show file tree
Hide file tree
Showing 4 changed files with 291 additions and 211 deletions.
60 changes: 44 additions & 16 deletions tasklite-core/source/ImportExport.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}

{-# HLINT ignore "Use maybe" #-}
Expand Down Expand Up @@ -75,8 +76,9 @@ import Data.Yaml (
YamlMark (YamlMark),
)
import Data.Yaml qualified as Yaml
import Database.SQLite.Simple as Sql (Connection, query_)
import FullTask (FullTask)
import Database.SQLite.Simple (Connection, Only (Only), query, query_)
import Database.SQLite.Simple.QQ (sql)
import FullTask (FullTask (..))
import Hooks (HookResult (message, task), executeHooks, formatHookResult)
import ImportTask (
ImportTask (..),
Expand Down Expand Up @@ -387,14 +389,39 @@ dumpCsv conf = do
pure $ pretty $ TL.decodeUtf8 $ Csv.encodeDefaultOrderedByName rows


getNdjsonLines :: Connection -> IO [Doc AnsiStyle]
getNdjsonLines conn = do
-- TODO: Fix after tasks_view is updated to include notes
tasksWithoutNotes :: [FullTask] <- query_ conn "SELECT * FROM tasks_view"
tasks <-
tasksWithoutNotes
& P.mapM
( \task -> do
notes <-
query
conn
[sql|
SELECT ulid, note
FROM task_to_note
WHERE task_ulid == ?
|]
(Only task.ulid)

pure $
task
{ FullTask.notes =
if P.null notes then Nothing else Just notes
}
)

pure $ tasks <&> (Aeson.encode >>> TL.decodeUtf8 >>> pretty)


dumpNdjson :: Config -> IO (Doc AnsiStyle)
dumpNdjson conf = do
-- TODO: Use Task instead of FullTask to fix broken notes export
execWithConn conf $ \connection -> do
tasks :: [FullTask] <- query_ connection "SELECT * FROM tasks_view"
pure $
vsep $
fmap (pretty . TL.decodeUtf8 . Aeson.encode) tasks
execWithConn conf $ \conn -> do
lines <- getNdjsonLines conn
pure $ vsep lines


dumpJson :: Config -> IO (Doc AnsiStyle)
Expand Down Expand Up @@ -612,8 +639,8 @@ editTask conf conn idSubstr = do
let importTaskDraft =
emptyImportTask
{ ImportTask.task = taskToEdit
, tags = []
, notes = []
, ImportTask.tags = []
, ImportTask.notes = []
}
args <- P.getArgs
preModifyResults <-
Expand All @@ -638,12 +665,13 @@ editTask conf conn idSubstr = do
case hookResult.task of
Nothing -> pure (importTaskDraft, Empty)
Just importTask -> do
fullImportTask <- setMissingFields
importTask
{ ImportTask.task = importTask.task
{ Task.ulid = taskToEdit.ulid }
}
pure ( fullImportTask, formatHookResult hookResult )
fullImportTask <-
setMissingFields
importTask
{ ImportTask.task =
importTask.task{Task.ulid = taskToEdit.ulid}
}
pure (fullImportTask, formatHookResult hookResult)
_ -> do
pure
( importTaskDraft
Expand Down
2 changes: 1 addition & 1 deletion tasklite-core/tasklite-core.cabal
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
cabal-version: 2.2

-- This file has been generated from package.yaml by hpack version 0.36.0.
-- This file has been generated from package.yaml by hpack version 0.37.0.
--
-- see: https://github.com/sol/hpack

Expand Down
Loading

0 comments on commit 2bd11a1

Please sign in to comment.