diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2017-07-24 19:57:16 +0200 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2017-07-24 19:57:16 +0200 |
commit | ef16292b588d312601af350254bae73c5278dc8a (patch) | |
tree | 256b9bebca03f3d024f9450b0376f6dd77f57518 /tprint/src | |
parent | 94a216ad062646a509b824f23915e95271efb243 (diff) | |
download | thermoprint-ef16292b588d312601af350254bae73c5278dc8a.tar thermoprint-ef16292b588d312601af350254bae73c5278dc8a.tar.gz thermoprint-ef16292b588d312601af350254bae73c5278dc8a.tar.bz2 thermoprint-ef16292b588d312601af350254bae73c5278dc8a.tar.xz thermoprint-ef16292b588d312601af350254bae73c5278dc8a.zip |
draft edit
Diffstat (limited to 'tprint/src')
-rw-r--r-- | tprint/src/Main.hs | 27 | ||||
-rw-r--r-- | tprint/src/Options.hs | 8 |
2 files changed, 34 insertions, 1 deletions
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 @@ | |||
1 | {-# LANGUAGE RecordWildCards #-} | 1 | {-# LANGUAGE RecordWildCards #-} |
2 | {-# LANGUAGE ViewPatterns #-} | 2 | {-# LANGUAGE ViewPatterns #-} |
3 | {-# LANGUAGE TupleSections #-} | ||
3 | 4 | ||
4 | import Data.Map (Map) | 5 | import Data.Map (Map) |
5 | import qualified Data.Map as Map | 6 | import qualified Data.Map as Map |
@@ -8,7 +9,9 @@ import qualified Data.Sequence as Seq | |||
8 | import Data.Text (Text) | 9 | import Data.Text (Text) |
9 | import qualified Data.Text as T | 10 | import qualified Data.Text as T |
10 | import qualified Data.Text.IO as T | 11 | import qualified Data.Text.IO as T |
12 | import qualified Data.Text.Encoding as T | ||
11 | import qualified Data.ByteString.Lazy.Char8 as Lazy (ByteString) | 13 | import qualified Data.ByteString.Lazy.Char8 as Lazy (ByteString) |
14 | import qualified Data.ByteString.Lazy as LBS | ||
12 | import qualified Data.ByteString.Lazy.Char8 as LCBS | 15 | import qualified Data.ByteString.Lazy.Char8 as LCBS |
13 | import Data.Time | 16 | import Data.Time |
14 | 17 | ||
@@ -26,7 +29,9 @@ import Control.Concurrent (threadDelay) | |||
26 | 29 | ||
27 | import Text.Show.Pretty (dumpStr) | 30 | import Text.Show.Pretty (dumpStr) |
28 | import Data.Aeson.Encode.Pretty (encodePretty) | 31 | import Data.Aeson.Encode.Pretty (encodePretty) |
29 | import Data.Aeson (eitherDecode') | 32 | import Data.Aeson (eitherDecode', eitherDecodeStrict') |
33 | |||
34 | import Text.Editor (runUserEditorDWIM, jsonTemplate, plainTemplate) | ||
30 | 35 | ||
31 | import System.IO | 36 | import System.IO |
32 | 37 | ||
@@ -135,6 +140,26 @@ tprint TPrint{ operation = DraftCreate{..}, ..} Client{..} out = withPrintout in | |||
135 | tprint TPrint{ operation = DraftReplace{..}, ..} Client{..} _ = withPrintout input $ \p -> do | 140 | tprint TPrint{ operation = DraftReplace{..}, ..} Client{..} _ = withPrintout input $ \p -> do |
136 | unless dryRun $ draftReplace draftId draftTitle p | 141 | unless dryRun $ draftReplace draftId draftTitle p |
137 | 142 | ||
143 | tprint TPrint{ operation = DraftEdit{..}, ..} Client{..} _ = do | ||
144 | d@(fromMaybe T.empty -> dTitle, dContent) <- draft draftId | ||
145 | let | ||
146 | content | ||
147 | | (JSON, _) <- output = return . LBS.toStrict $ encodePretty d | ||
148 | | otherwise = do | ||
149 | c <- either throwM return (cobbcode dContent) | ||
150 | return . T.encodeUtf8 $ dTitle <> T.pack "\n" <> c | ||
151 | tmpl | ||
152 | | (JSON, _) <- output = jsonTemplate | ||
153 | | otherwise = plainTemplate | ||
154 | parse | ||
155 | | (JSON, _) <- output = either (throwM . userError) return . eitherDecodeStrict' | ||
156 | | otherwise = (\(t:(T.unlines -> c)) -> (massage t, ) <$> either throwM return (bbcode c)) . T.lines . T.decodeUtf8 | ||
157 | massage (T.strip -> t) | ||
158 | | T.null t = Nothing | ||
159 | | otherwise = Just t | ||
160 | (dTitle', dContent') <- parse =<< runUserEditorDWIM tmpl =<< content | ||
161 | unless dryRun $ draftReplace draftId dTitle' dContent' | ||
162 | |||
138 | tprint TPrint{ operation = DraftDelete{..}, ..} Client{..} _ = unless dryRun $ draftDelete draftId | 163 | tprint TPrint{ operation = DraftDelete{..}, ..} Client{..} _ = unless dryRun $ draftDelete draftId |
139 | 164 | ||
140 | tprint TPrint{ operation = DraftPrint{..}, ..} client@Client{..} out = do | 165 | 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 | |||
41 | } | 41 | } |
42 | deriving (Show, Generic, PrettyVal) | 42 | deriving (Show, Generic, PrettyVal) |
43 | 43 | ||
44 | data Interactive = Interactive | ||
45 | deriving (Show, Generic, PrettyVal) | ||
46 | |||
44 | data Operation | 47 | data Operation |
45 | = Printers | 48 | = Printers |
46 | | Jobs | 49 | | Jobs |
@@ -66,6 +69,7 @@ data Operation | |||
66 | , draftTitle :: Maybe DraftTitle | 69 | , draftTitle :: Maybe DraftTitle |
67 | , input :: Input | 70 | , input :: Input |
68 | } | 71 | } |
72 | | DraftEdit { draftId :: DraftId } | ||
69 | | Draft { draftId :: DraftId } | 73 | | Draft { draftId :: DraftId } |
70 | | DraftDelete { draftId :: DraftId } | 74 | | DraftDelete { draftId :: DraftId } |
71 | | DraftPrint | 75 | | DraftPrint |
@@ -125,6 +129,9 @@ cmdDraftCreate = info cmdDraftCreate' $ progDesc "Create a new draft" | |||
125 | cmdDraftReplace = info cmdDraftReplace' $ progDesc "Update the contents and title of a draft" | 129 | cmdDraftReplace = info cmdDraftReplace' $ progDesc "Update the contents and title of a draft" |
126 | where cmdDraftReplace' = DraftReplace <$> aDraft <*> optional pTitle <*> pInput | 130 | where cmdDraftReplace' = DraftReplace <$> aDraft <*> optional pTitle <*> pInput |
127 | 131 | ||
132 | cmdDraftEdit = info cmdDraftEdit' $ progDesc "Edit an existing draft" | ||
133 | where cmdDraftEdit' = DraftEdit <$> aDraft | ||
134 | |||
128 | cmdDraft = info cmdDraft' $ progDesc "Retrieve a drafts contents" | 135 | cmdDraft = info cmdDraft' $ progDesc "Retrieve a drafts contents" |
129 | where cmdDraft' = Draft <$> aDraft | 136 | where cmdDraft' = Draft <$> aDraft |
130 | 137 | ||
@@ -146,6 +153,7 @@ pOperation = hsubparser $ mconcat [ command "printers" cmdPrinters | |||
146 | ) (progDesc "Interact with jobs") | 153 | ) (progDesc "Interact with jobs") |
147 | , command "draft" $ info ( hsubparser $ mconcat [ command "create" cmdDraftCreate | 154 | , command "draft" $ info ( hsubparser $ mconcat [ command "create" cmdDraftCreate |
148 | , command "replace" cmdDraftReplace | 155 | , command "replace" cmdDraftReplace |
156 | , command "edit" cmdDraftEdit | ||
149 | , command "content" cmdDraft | 157 | , command "content" cmdDraft |
150 | , command "delete" cmdDraftDelete | 158 | , command "delete" cmdDraftDelete |
151 | , command "print" cmdDraftPrint | 159 | , command "print" cmdDraftPrint |