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.hs60
1 files changed, 46 insertions, 14 deletions
diff --git a/client/src/Thermoprint/Client.hs b/client/src/Thermoprint/Client.hs
index 7072ad0..448a912 100644
--- a/client/src/Thermoprint/Client.hs
+++ b/client/src/Thermoprint/Client.hs
@@ -1,7 +1,10 @@
1{-# LANGUAGE DataKinds #-} 1{-# LANGUAGE DataKinds #-}
2{-# LANGUAGE TypeOperators #-} 2{-# LANGUAGE TypeOperators #-}
3{-# LANGUAGE TypeFamilies #-}
3{-# LANGUAGE ViewPatterns #-} 4{-# LANGUAGE ViewPatterns #-}
4{-# LANGUAGE RecordWildCards #-} 5{-# LANGUAGE RecordWildCards #-}
6{-# LANGUAGE FlexibleContexts #-}
7{-# LANGUAGE FlexibleInstances #-}
5 8
6-- | A client library for 'Thermoprint.API' 9-- | A client library for 'Thermoprint.API'
7module Thermoprint.Client 10module Thermoprint.Client
@@ -12,8 +15,8 @@ module Thermoprint.Client
12 , ServantError(..) 15 , ServantError(..)
13 , module Thermoprint.API 16 , module Thermoprint.API
14 , module Servant.Common.BaseUrl 17 , module Servant.Common.BaseUrl
15 , module Control.Monad.Trans.Either 18 , module Control.Monad.Except
16 , module Servant.Server.Internal.Enter 19 , module Servant.Utils.Enter
17 ) where 20 ) where
18 21
19import Thermoprint.API 22import Thermoprint.API
@@ -24,19 +27,20 @@ import Data.Time (UTCTime)
24import Servant.Client hiding (HasClient(..)) 27import Servant.Client hiding (HasClient(..))
25import qualified Servant.Client as S 28import qualified Servant.Client as S
26import Servant.Common.BaseUrl 29import Servant.Common.BaseUrl
30import Network.HTTP.Client (Manager, ManagerSettings, newManager, defaultManagerSettings)
27import Servant.API 31import Servant.API
28import Servant.Server.Internal.Enter 32import Servant.Utils.Enter
29import Control.Monad.Trans.Either 33import Control.Monad.Except (ExceptT, runExceptT)
30 34
35import Control.Monad.Reader (ReaderT, runReaderT, ask)
31import Control.Monad.Catch (Exception, MonadThrow(..)) 36import Control.Monad.Catch (Exception, MonadThrow(..))
32import Control.Monad.IO.Class (MonadIO(..)) 37import Control.Monad.IO.Class (MonadIO(..))
38import Control.Monad.Trans (lift)
33 39
34import Control.Monad 40import Control.Monad
35import Control.Category 41import Control.Category
36import Prelude hiding (id, (.)) 42import Prelude hiding (id, (.))
37 43
38instance Exception ServantError
39
40-- | All 'ThermoprintAPI'-functions as a record 44-- | All 'ThermoprintAPI'-functions as a record
41-- 45--
42-- Use like this: 46-- Use like this:
@@ -46,7 +50,7 @@ instance Exception ServantError
46-- > main :: IO () 50-- > main :: IO ()
47-- > -- ^ Display a list of printers with their status 51-- > -- ^ Display a list of printers with their status
48-- > main = print =<< printers 52-- > main = print =<< printers
49-- > where Client{..} = mkClient' $ Http "localhost" 3000 53-- > where Client{..} = mkClient' defaultManagerSettings $ Http "localhost" 3000
50data Client m = Client 54data Client m = Client
51 { printers :: m (Map PrinterId PrinterStatus) 55 { printers :: m (Map PrinterId PrinterStatus)
52 -- ^ List all printers 56 -- ^ List all printers
@@ -86,27 +90,55 @@ withArgs :: (x -> a :<|> b) -> ((x -> a) :<|> (x -> b))
86-- ^ Undo factoring of APIs 90-- ^ Undo factoring of APIs
87withArgs subAPI = (\(a :<|> _) -> a) . subAPI :<|> (\(_ :<|> b) -> b) . subAPI 91withArgs subAPI = (\(a :<|> _) -> a) . subAPI :<|> (\(_ :<|> b) -> b) . subAPI
88 92
89mkClient :: (EitherT ServantError IO :~> m) -- ^ A monad functor ('Nat') used to make the api functions work in any monad which can do 'IO' and handle errors 93mkClientS :: Monad m
90 -> BaseUrl 94 => (ClientM :~> m) -- ^ A monad functor ('Nat') used to make the api functions work in any monad which can do 'IO' and handle errors
91 -> Client m 95 -> ManagerSettings
96 -> BaseUrl
97 -> Client m
92-- ^ Generate a 'Client' 98-- ^ Generate a 'Client'
93mkClient n url = Client{..} 99mkClientS n mgrS url = Client
100 { printers = clientF n printers
101 , jobs = \a b c -> clientF n $ jobs a b c
102 , jobCreate = \a b -> clientF n $ jobCreate a b
103 , job = \a -> clientF n $ job a
104 , jobStatus = \a -> clientF n $ jobStatus a
105 , jobDelete = \a -> clientF n $ jobDelete a
106 , drafts = clientF n drafts
107 , draftCreate = \a b -> clientF n $ draftCreate a b
108 , draftReplace = \a b c -> clientF n $ draftReplace a b c
109 , draft = \a -> clientF n $ draft a
110 , draftDelete = \a -> clientF n $ draftDelete a
111 , draftPrint = \a b -> clientF n $ draftPrint a b
112 }
94 where 113 where
114 clientF :: Monad m => (ClientM :~> m) -> (Manager -> BaseUrl -> m a) -> m a
115 clientF n f = do
116 mgr <- unNat n $ (liftIO $ newManager mgrS :: ClientM Manager)
117 f mgr url
95 printers 118 printers
96 :<|> (jobs :<|> jobCreate) 119 :<|> (jobs :<|> jobCreate)
97 :<|> (withArgs -> job :<|> (withArgs -> jobStatus :<|> jobDelete)) 120 :<|> (withArgs -> job :<|> (withArgs -> jobStatus :<|> jobDelete))
98 :<|> (drafts :<|> draftCreate) 121 :<|> (drafts :<|> draftCreate)
99 :<|> (withArgs -> draftReplace :<|> (withArgs -> draft :<|> (withArgs -> draftDelete :<|> draftPrint))) 122 :<|> (withArgs -> draftReplace :<|> (withArgs -> draft :<|> (withArgs -> draftDelete :<|> draftPrint)))
100 = enter n $ client thermoprintAPI url 123 = enter n $ client thermoprintAPI
101 124
125mkClient :: Monad m
126 => (ClientM :~> m) -- ^ A monad functor ('Nat') used to make the api functions work in any monad which can do 'IO' and handle errors
127 -> BaseUrl
128 -> Client m
129mkClient n url = mkClientS n defaultManagerSettings url
130
102mkClient' :: (MonadThrow m, MonadIO m) => BaseUrl -> Client m 131mkClient' :: (MonadThrow m, MonadIO m) => BaseUrl -> Client m
103-- ^ @mkClient' = mkClient $ ioNat . throwNat@ 132-- ^ @mkClient' = mkClient $ ioNat . throwNat@
104mkClient' = mkClient $ ioNat . throwNat 133mkClient' = mkClient $ ioNat . throwNat
105 134
106throwNat :: (Exception e, MonadThrow m) => EitherT e m :~> m 135throwNat :: (Exception e, MonadThrow m) => ExceptT e m :~> m
107-- ^ Squash a layer of 'EitherT' into the underlying monad supporting 'throwM' 136-- ^ Squash a layer of 'EitherT' into the underlying monad supporting 'throwM'
108throwNat = Nat $ either throwM return <=< runEitherT 137throwNat = Nat $ either throwM return <=< runExceptT
109 138
110ioNat :: MonadIO m => IO :~> m 139ioNat :: MonadIO m => IO :~> m
111-- ^ @ioNat = Nat liftIO@ 140-- ^ @ioNat = Nat liftIO@
112ioNat = Nat liftIO 141ioNat = Nat liftIO
142
143readerNat :: a -> ReaderT a m :~> m
144readerNat a = Nat $ flip runReaderT a