From 7d2ff634815e3cb243674eec02d462f1c74a99b3 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Mon, 11 Jan 2016 05:22:20 +0000 Subject: thermoprint-3 --- provider/posts/thermoprint-3.lhs | 92 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 92 insertions(+) create mode 100644 provider/posts/thermoprint-3.lhs diff --git a/provider/posts/thermoprint-3.lhs b/provider/posts/thermoprint-3.lhs new file mode 100644 index 0000000..82d5056 --- /dev/null +++ b/provider/posts/thermoprint-3.lhs @@ -0,0 +1,92 @@ +--- +title: Thoughts on a network protocol for a toolset for interacting with character-oriented printers +published: 2016-01-11 +tags: Thermoprint +--- + +This post is an annotated version of the file `spec/src/Thermoprint/API.hs` as of commit [3ad700c](git://git.yggdrasil.li/thermoprint#3ad700c). + +> {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} +> {-# LANGUAGE TypeOperators, DataKinds #-} +> {-# LANGUAGE OverloadedStrings #-} +> +> module Thermoprint.API +> ( PrinterStatus(..) +> , JobStatus(..) +> , ThermoprintAPI +> , thermoprintAPI +> , module Thermoprint.Identifiers +> , module Thermoprint.Printout +> ) where +> +> import Thermoprint.Printout + +See [a previous post](https://dirty-haskell.org/posts/thermoprint-2.html). + +> import Thermoprint.Identifiers + +`Thermoprint.Identifiers` provides some newtypes of `Integer` to add some typesafety to dealing with objects identified by autoincremented numbers + +> import Servant.API +> import Servant.Docs +> import Data.Aeson + +We will define our API to be compatible with [servant](https://hackage.haskell.org/package/servant) + +> import Data.Set (Set) +> import Data.Sequence (Seq) + +Higher performance versions of lists for our various applications + +> import GHC.Generics (Generic) +> +> import Data.Proxy (Proxy(..)) +> +> import Control.Exception (Exception) +> import Data.Typeable (Typeable) +> +> data PrinterStatus = Busy JobId +> | Available +> deriving (Generic, Show, FromJSON, ToJSON) +> +> data JobStatus = Queued +> | Printing +> | Done +> | Failed PrintingError +> deriving (Generic, Show, FromJSON, ToJSON) +> +> data PrintingError = UnknownError +> deriving (Typeable, Generic, Show, FromJSON, ToJSON, Exception) + +We expect the definiton of `PrintingError` to grow considerably while implementing a server for this API + +We support the following actions through our API: + +> type ThermoprintAPI = "printers" :> Get '[JSON] (Set PrinterId) -- List the identifiers of all available printers (/printers) +> :<|> "printer" :> Capture "printerId" PrinterId :> ( +> ReqBody '[JSON] Printout :> Post '[JSON] JobId -- Add a new job to the bottom of the queue by sending its content (/printer:printerId) +> :<|> "status" :> Get '[JSON] PrinterStatus -- Query the current status of a printer (/printer:printerId/status) +> ) +> :<|> "jobs" :> ( +> 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=*) +> ) +> :<|> "job" :> Capture "jobId" JobId :> ( +> Get '[JSON] Printout -- Getting the contents of a job currently known to the server (/job:jobId) +> :<|> "status" :> Get '[JSON] JobStatus -- Getting the status of a job (/job:jobId/status) +> :<|> "printer" :> Get '[JSON] PrinterId -- Finding the printer a job was queued for (/job:jobId/printer) +> :<|> Delete '[] () -- Aborting a job (which we expect to make it unknown to the server) (/job:jobId) +> ) +> :<|> "drafts" :> ( +> Get '[JSON] (Set DraftId) -- Getting a list of the ids of all drafts known to the server (/drafts) +> :<|> ReqBody '[JSON] Printout :> Post '[JSON] DraftId -- Making a draft known to the server by submitting its contents (/drafts) +> ) +> :<|> "draft" :> Capture "draftId" DraftId :> ( +> ReqBody '[JSON] Printout :> Put '[] () -- Updating a draft by replacing its contents (/draft:draftId) +> :<|> Get '[JSON] Printout -- Getting the contents of a draft (/draft:draftId) +> :<|> Delete '[] () -- Deleting a draft (/draft:draftId) +> ) +> +> thermoprintAPI :: Proxy ThermoprintAPI +> thermoprintAPI = Proxy + +servant needs an object of type `Proxy ThermoprintAPI` in various places -- cgit v1.2.3