aboutsummaryrefslogtreecommitdiff
path: root/tprint/src/Main.hs
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2015-10-17 02:26:25 +0200
committerGregor Kleen <gkleen@yggdrasil.li>2015-10-17 02:26:25 +0200
commit005dc408dc09c3b479398ebe3e92efa2cd54846e (patch)
tree23dcfe7a545885c9aa145f1ccae6d33206a87820 /tprint/src/Main.hs
parent2dcbb4482de2c352b76372b389fda20c63075295 (diff)
downloadthermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.tar
thermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.tar.gz
thermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.tar.bz2
thermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.tar.xz
thermoprint-005dc408dc09c3b479398ebe3e92efa2cd54846e.zip
Working prototype
Diffstat (limited to 'tprint/src/Main.hs')
-rw-r--r--tprint/src/Main.hs77
1 files changed, 77 insertions, 0 deletions
diff --git a/tprint/src/Main.hs b/tprint/src/Main.hs
new file mode 100644
index 0000000..565295b
--- /dev/null
+++ b/tprint/src/Main.hs
@@ -0,0 +1,77 @@
1{-# LANGUAGE RecordWildCards #-}
2
3import Thermoprint
4import Thermoprint.Api
5
6import qualified BBCode (parse)
7
8import Options.Applicative
9
10import Data.Either
11import Control.Monad
12import Control.Monad.Trans.Either
13
14import System.IO
15import System.Exit
16
17import Data.Proxy
18import Servant.Client
19
20thermoprintApi :: Proxy ThermoprintApi
21thermoprintApi = Proxy
22
23data Options = Options
24 { baseUrl :: BaseUrl
25 , printerId :: Integer
26 , dryRun :: Bool
27 }
28
29options :: Parser Options
30options = Options
31 <$> option baseUrlReader (
32 long "url"
33 <> short 'u'
34 <> metavar "URL"
35 <> help "The base url of the api"
36 <> value (BaseUrl Http "localhost" 8080)
37 <> showDefaultWith showBaseUrl
38 )
39 <*> option auto (
40 long "printer"
41 <> short 'p'
42 <> metavar "INT"
43 <> help "The number of the printer to use"
44 <> value 0
45 <> showDefault
46 )
47 <*> flag False True (
48 long "dry-run"
49 <> short 'd'
50 <> help "Instead of sending data to printer output the parsed stream to stderr"
51 <> showDefault
52 )
53 where
54 baseUrlReader = str >>= either readerError return . parseBaseUrl
55
56main :: IO ()
57main = execParser opts >>= main'
58 where
59 opts = info (helper <*> options) (
60 fullDesc
61 <> header "tprint - A cli tool for interfacing with the REST api as provided by thermoprint-servant"
62 )
63
64 main' Options{..} = do
65 let
66 print :: Integer -> Block String -> EitherT ServantError IO ()
67 print = client thermoprintApi baseUrl
68 input <- BBCode.parse `liftM` getContents
69 input' <- either (\err -> hPutStrLn stderr ("Parse error: " ++ err) >> exitFailure) return input
70 case dryRun of
71 False -> do
72 res <- runEitherT $ print printerId input'
73 case res of
74 Left err -> hPutStrLn stderr $ show err
75 Right _ -> exitSuccess
76 True -> do
77 hPutStrLn stderr $ show input'