From ef16292b588d312601af350254bae73c5278dc8a Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Mon, 24 Jul 2017 19:57:16 +0200 Subject: draft edit --- tprint/src/Main.hs | 27 ++++++++++++++++++++++++++- tprint/src/Options.hs | 8 ++++++++ 2 files changed, 34 insertions(+), 1 deletion(-) (limited to 'tprint/src') diff --git a/tprint/src/Main.hs b/tprint/src/Main.hs index bc5ee2f..f6008ac 100644 --- a/tprint/src/Main.hs +++ b/tprint/src/Main.hs @@ -1,5 +1,6 @@ {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE TupleSections #-} import Data.Map (Map) import qualified Data.Map as Map @@ -8,7 +9,9 @@ import qualified Data.Sequence as Seq import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.IO as T +import qualified Data.Text.Encoding as T import qualified Data.ByteString.Lazy.Char8 as Lazy (ByteString) +import qualified Data.ByteString.Lazy as LBS import qualified Data.ByteString.Lazy.Char8 as LCBS import Data.Time @@ -26,7 +29,9 @@ import Control.Concurrent (threadDelay) import Text.Show.Pretty (dumpStr) import Data.Aeson.Encode.Pretty (encodePretty) -import Data.Aeson (eitherDecode') +import Data.Aeson (eitherDecode', eitherDecodeStrict') + +import Text.Editor (runUserEditorDWIM, jsonTemplate, plainTemplate) import System.IO @@ -135,6 +140,26 @@ tprint TPrint{ operation = DraftCreate{..}, ..} Client{..} out = withPrintout in tprint TPrint{ operation = DraftReplace{..}, ..} Client{..} _ = withPrintout input $ \p -> do unless dryRun $ draftReplace draftId draftTitle p +tprint TPrint{ operation = DraftEdit{..}, ..} Client{..} _ = do + d@(fromMaybe T.empty -> dTitle, dContent) <- draft draftId + let + content + | (JSON, _) <- output = return . LBS.toStrict $ encodePretty d + | otherwise = do + c <- either throwM return (cobbcode dContent) + return . T.encodeUtf8 $ dTitle <> T.pack "\n" <> c + tmpl + | (JSON, _) <- output = jsonTemplate + | otherwise = plainTemplate + parse + | (JSON, _) <- output = either (throwM . userError) return . eitherDecodeStrict' + | otherwise = (\(t:(T.unlines -> c)) -> (massage t, ) <$> either throwM return (bbcode c)) . T.lines . T.decodeUtf8 + massage (T.strip -> t) + | T.null t = Nothing + | otherwise = Just t + (dTitle', dContent') <- parse =<< runUserEditorDWIM tmpl =<< content + unless dryRun $ draftReplace draftId dTitle' dContent' + tprint TPrint{ operation = DraftDelete{..}, ..} Client{..} _ = unless dryRun $ draftDelete draftId tprint TPrint{ operation = DraftPrint{..}, ..} client@Client{..} out = do diff --git a/tprint/src/Options.hs b/tprint/src/Options.hs index 703c23b..f4c7ebd 100644 --- a/tprint/src/Options.hs +++ b/tprint/src/Options.hs @@ -41,6 +41,9 @@ data TPrint = TPrint } deriving (Show, Generic, PrettyVal) +data Interactive = Interactive + deriving (Show, Generic, PrettyVal) + data Operation = Printers | Jobs @@ -66,6 +69,7 @@ data Operation , draftTitle :: Maybe DraftTitle , input :: Input } + | DraftEdit { draftId :: DraftId } | Draft { draftId :: DraftId } | DraftDelete { draftId :: DraftId } | DraftPrint @@ -125,6 +129,9 @@ cmdDraftCreate = info cmdDraftCreate' $ progDesc "Create a new draft" cmdDraftReplace = info cmdDraftReplace' $ progDesc "Update the contents and title of a draft" where cmdDraftReplace' = DraftReplace <$> aDraft <*> optional pTitle <*> pInput +cmdDraftEdit = info cmdDraftEdit' $ progDesc "Edit an existing draft" + where cmdDraftEdit' = DraftEdit <$> aDraft + cmdDraft = info cmdDraft' $ progDesc "Retrieve a drafts contents" where cmdDraft' = Draft <$> aDraft @@ -146,6 +153,7 @@ pOperation = hsubparser $ mconcat [ command "printers" cmdPrinters ) (progDesc "Interact with jobs") , command "draft" $ info ( hsubparser $ mconcat [ command "create" cmdDraftCreate , command "replace" cmdDraftReplace + , command "edit" cmdDraftEdit , command "content" cmdDraft , command "delete" cmdDraftDelete , command "print" cmdDraftPrint -- cgit v1.2.3