aboutsummaryrefslogtreecommitdiff
path: root/spec/src/Thermoprint/API.hs
blob: 627f9b14108405ab6e41dbe6574f7022fbb94216 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
{-# LANGUAGE TypeOperators, DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}

-- | A specification of an API for interacting with a set of printers
module Thermoprint.API
       ( PrinterStatus(..)
       , JobStatus(..)
       , PrintingError(..)
       , ThermoprintAPI
       , thermoprintAPI
       , module Thermoprint.Identifiers
       , module Thermoprint.Printout
       ) where

import Thermoprint.Printout
import Thermoprint.Identifiers

import Servant.API
import Data.Aeson

import Data.Set (Set)
import Data.Sequence (Seq)

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)

type ThermoprintAPI = "printers" :> Get '[JSON] (Set PrinterId)
                      :<|> "printer" :> Capture "printerId" PrinterId :> (
                        ReqBody '[JSON] Printout :> Post '[JSON] JobId
                        :<|> "status" :> Get '[JSON] PrinterStatus
                      )
                      :<|> "jobs" :> (
                        QueryParam "printer" PrinterId :> QueryParam "min" JobId :> QueryParam "max" JobId :> Get '[JSON] (Seq JobId)
                      )
                      :<|> "job" :> Capture "jobId" JobId :> (
                        Get '[JSON] Printout
                        :<|> "status" :> Get '[JSON] JobStatus
                        :<|> "printer" :> Get '[JSON] PrinterId
                        :<|> Delete '[] ()
                      )
                      :<|> "drafts" :> (
                        Get '[JSON] (Set DraftId)
                        :<|> ReqBody '[JSON] Printout :> Post '[JSON] DraftId
                      )
                      :<|> "draft" :> Capture "draftId" DraftId :> (
                        ReqBody '[JSON] Printout :> Put '[] ()
                        :<|> Get '[JSON] Printout
                        :<|> Delete '[] ()
                      )

thermoprintAPI :: Proxy ThermoprintAPI
-- ^ Servant occasionally needs an object of this type 
thermoprintAPI = Proxy