summaryrefslogtreecommitdiff
path: root/provider/posts/thermoprint/3.lhs
diff options
context:
space:
mode:
Diffstat (limited to 'provider/posts/thermoprint/3.lhs')
-rw-r--r--provider/posts/thermoprint/3.lhs92
1 files changed, 92 insertions, 0 deletions
diff --git a/provider/posts/thermoprint/3.lhs b/provider/posts/thermoprint/3.lhs
new file mode 100644
index 0000000..5e7eee9
--- /dev/null
+++ b/provider/posts/thermoprint/3.lhs
@@ -0,0 +1,92 @@
1---
2title: Thoughts on a network protocol for a toolset for interacting with character-oriented printers
3published: 2016-01-11
4tags: Thermoprint
5---
6
7This post is an annotated version of the file [spec/src/Thermoprint/API.hs](https://git.yggdrasil.li/thermoprint/tree/spec/src/Thermoprint/API.hs?h=rewrite&id=3ad700c) as of commit `3ad700c`.
8
9> {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
10> {-# LANGUAGE TypeOperators, DataKinds #-}
11> {-# LANGUAGE OverloadedStrings #-}
12>
13> module Thermoprint.API
14> ( PrinterStatus(..)
15> , JobStatus(..)
16> , ThermoprintAPI
17> , thermoprintAPI
18> , module Thermoprint.Identifiers
19> , module Thermoprint.Printout
20> ) where
21>
22> import Thermoprint.Printout
23
24See [a previous post](https://dirty-haskell.org/posts/thermoprint-2.html).
25
26> import Thermoprint.Identifiers
27
28`Thermoprint.Identifiers` provides some newtypes of `Integer` to add some typesafety to dealing with objects identified by autoincremented numbers
29
30> import Servant.API
31> import Servant.Docs
32> import Data.Aeson
33
34We will define our API to be compatible with [servant](https://hackage.haskell.org/package/servant)
35
36> import Data.Set (Set)
37> import Data.Sequence (Seq)
38
39Higher performance versions of lists for our various applications
40
41> import GHC.Generics (Generic)
42>
43> import Data.Proxy (Proxy(..))
44>
45> import Control.Exception (Exception)
46> import Data.Typeable (Typeable)
47>
48> data PrinterStatus = Busy JobId
49> | Available
50> deriving (Generic, Show, FromJSON, ToJSON)
51>
52> data JobStatus = Queued
53> | Printing
54> | Done
55> | Failed PrintingError
56> deriving (Generic, Show, FromJSON, ToJSON)
57>
58> data PrintingError = UnknownError
59> deriving (Typeable, Generic, Show, FromJSON, ToJSON, Exception)
60
61We expect the definiton of `PrintingError` to grow considerably while implementing a server for this API
62
63We support the following actions through our API:
64
65> type ThermoprintAPI = "printers" :> Get '[JSON] (Set PrinterId) -- List the identifiers of all available printers (/printers)
66> :<|> "printer" :> Capture "printerId" PrinterId :> (
67> ReqBody '[JSON] Printout :> Post '[JSON] JobId -- Add a new job to the bottom of the queue by sending its content (/printer:printerId)
68> :<|> "status" :> Get '[JSON] PrinterStatus -- Query the current status of a printer (/printer:printerId/status)
69> )
70> :<|> "jobs" :> (
71> QueryParam "printer" PrinterId :> QueryParam "min" JobId :> QueryParam "max" JobId :> Get '[JSON] (Seq JobId) -- List all jobs allowing for selection by printerId and pagination (/jobs?printer=*&min=*&max=*)
72> )
73> :<|> "job" :> Capture "jobId" JobId :> (
74> Get '[JSON] Printout -- Get the contents of a job currently known to the server (/job:jobId)
75> :<|> "status" :> Get '[JSON] JobStatus -- Get the status of a job (/job:jobId/status)
76> :<|> "printer" :> Get '[JSON] PrinterId -- Find the printer a job was queued for (/job:jobId/printer)
77> :<|> Delete '[] () -- Abort a job (which we expect to make it unknown to the server) (/job:jobId)
78> )
79> :<|> "drafts" :> (
80> Get '[JSON] (Set DraftId) -- List the identifiers of all drafts known to the server (/drafts)
81> :<|> ReqBody '[JSON] Printout :> Post '[JSON] DraftId -- Make a draft known to the server by submitting its contents (/drafts)
82> )
83> :<|> "draft" :> Capture "draftId" DraftId :> (
84> ReqBody '[JSON] Printout :> Put '[] () -- Update a draft by replacing its contents (/draft:draftId)
85> :<|> Get '[JSON] Printout -- Get the contents of a draft (/draft:draftId)
86> :<|> Delete '[] () -- Delete a draft (/draft:draftId)
87> )
88>
89> thermoprintAPI :: Proxy ThermoprintAPI
90> thermoprintAPI = Proxy
91
92servant needs an object of type `Proxy ThermoprintAPI` in various places