aboutsummaryrefslogtreecommitdiff
path: root/client/src/Thermoprint/Client.hs
diff options
context:
space:
mode:
Diffstat (limited to 'client/src/Thermoprint/Client.hs')
-rw-r--r--client/src/Thermoprint/Client.hs74
1 files changed, 74 insertions, 0 deletions
diff --git a/client/src/Thermoprint/Client.hs b/client/src/Thermoprint/Client.hs
new file mode 100644
index 0000000..8299821
--- /dev/null
+++ b/client/src/Thermoprint/Client.hs
@@ -0,0 +1,74 @@
1{-# LANGUAGE DataKinds #-}
2{-# LANGUAGE TypeOperators #-}
3{-# LANGUAGE ViewPatterns #-}
4{-# LANGUAGE RecordWildCards #-}
5
6-- | A client library for 'Thermoprint.API'
7module Thermoprint.Client
8 ( Client(..)
9 , mkClient
10 -- = Reexports
11 , ServantError(..)
12 , module Servant.Common.BaseUrl
13 , module Control.Monad.Trans.Either
14 , module Servant.Server.Internal.Enter
15 ) where
16
17import Thermoprint.API
18import Data.Map (Map)
19import Data.Sequence (Seq)
20import Data.Time (UTCTime)
21
22import Servant.Client hiding (HasClient(..))
23import qualified Servant.Client as S
24import Servant.Common.BaseUrl
25import Servant.API
26import Servant.Server.Internal.Enter
27import Control.Monad.Trans.Either
28
29import Control.Category
30import Prelude hiding (id, (.))
31
32-- | All 'ThermoprintAPI'-functions as a record
33--
34-- Use like this:
35--
36-- > import Control.Category
37-- > import Prelude hiding (id, (.))
38-- >
39-- > main :: IO ()
40-- > main = do
41-- > Client{..} <- mkClient id $ Http "localhost" 3000
42-- >
43-- > print =<< runEitherT printers -- Display a list of printers with their status
44data Client m = Client
45 { printers :: EitherT ServantError m (Map PrinterId PrinterStatus)
46 -- ^ List all printers
47 , jobs :: Maybe PrinterId
48 -> Maybe JobId
49 -> Maybe JobId
50 -> Maybe UTCTime
51 -> Maybe UTCTime
52 -> EitherT ServantError m (Seq (JobId, UTCTime, JobStatus))
53 -- ^ @jobs p minId maxId minTime maxTime@ lists a selection of jobs
54 , print :: Maybe PrinterId -> Printout -> EitherT ServantError m JobId
55 -- ^ Send a 'Printout' to be queued
56 , jobContents :: JobId -> EitherT ServantError m Printout
57 , jobStatus :: JobId -> EitherT ServantError m JobStatus
58 , jobDelete :: JobId -> EitherT ServantError m ()
59 }
60
61withArg :: (a -> layoutA :<|> layoutB) -> (a -> layoutA) :<|> (a -> layoutB)
62withArg outer = (\(a :<|> _) -> a) . outer :<|> (\(_ :<|> b) -> b) . outer
63
64mkClient :: (IO :~> m) -- ^ A monad functor ('Nat') used to make the api functions work in any monad which can be constructed from 'IO'
65 -> BaseUrl
66 -> Client m
67-- ^ Generate a 'Client'
68mkClient n url = Client{..}
69 where
70 printers
71 :<|> (jobs :<|> print)
72 :<|> (withArg -> jobContents :<|> (withArg -> jobStatus :<|> jobDelete))
73 :<|> _
74 = enter (hoistNat n) $ client thermoprintAPI url