diff options
| author | Gregor Kleen <pngwjpgh@users.noreply.github.com> | 2016-07-17 19:21:56 +0200 |
|---|---|---|
| committer | Gregor Kleen <pngwjpgh@users.noreply.github.com> | 2016-07-17 19:21:56 +0200 |
| commit | 2b9ceaead3f3cd80e973cccecb9a3eebc51154f7 (patch) | |
| tree | df2378943480647606b6a06f62c0f4b8b2ab406d /client/src | |
| parent | ac4cf4a0a494eafe55364f816569c517684fdf32 (diff) | |
| download | thermoprint-2b9ceaead3f3cd80e973cccecb9a3eebc51154f7.tar thermoprint-2b9ceaead3f3cd80e973cccecb9a3eebc51154f7.tar.gz thermoprint-2b9ceaead3f3cd80e973cccecb9a3eebc51154f7.tar.bz2 thermoprint-2b9ceaead3f3cd80e973cccecb9a3eebc51154f7.tar.xz thermoprint-2b9ceaead3f3cd80e973cccecb9a3eebc51154f7.zip | |
Fixes for GHC 8.0.1
Diffstat (limited to 'client/src')
| -rw-r--r-- | client/src/Thermoprint/Client.hs | 60 |
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' |
| 7 | module Thermoprint.Client | 10 | module 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 | ||
| 19 | import Thermoprint.API | 22 | import Thermoprint.API |
| @@ -24,19 +27,20 @@ import Data.Time (UTCTime) | |||
| 24 | import Servant.Client hiding (HasClient(..)) | 27 | import Servant.Client hiding (HasClient(..)) |
| 25 | import qualified Servant.Client as S | 28 | import qualified Servant.Client as S |
| 26 | import Servant.Common.BaseUrl | 29 | import Servant.Common.BaseUrl |
| 30 | import Network.HTTP.Client (Manager, ManagerSettings, newManager, defaultManagerSettings) | ||
| 27 | import Servant.API | 31 | import Servant.API |
| 28 | import Servant.Server.Internal.Enter | 32 | import Servant.Utils.Enter |
| 29 | import Control.Monad.Trans.Either | 33 | import Control.Monad.Except (ExceptT, runExceptT) |
| 30 | 34 | ||
| 35 | import Control.Monad.Reader (ReaderT, runReaderT, ask) | ||
| 31 | import Control.Monad.Catch (Exception, MonadThrow(..)) | 36 | import Control.Monad.Catch (Exception, MonadThrow(..)) |
| 32 | import Control.Monad.IO.Class (MonadIO(..)) | 37 | import Control.Monad.IO.Class (MonadIO(..)) |
| 38 | import Control.Monad.Trans (lift) | ||
| 33 | 39 | ||
| 34 | import Control.Monad | 40 | import Control.Monad |
| 35 | import Control.Category | 41 | import Control.Category |
| 36 | import Prelude hiding (id, (.)) | 42 | import Prelude hiding (id, (.)) |
| 37 | 43 | ||
| 38 | instance 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 |
| 50 | data Client m = Client | 54 | data 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 |
| 87 | withArgs subAPI = (\(a :<|> _) -> a) . subAPI :<|> (\(_ :<|> b) -> b) . subAPI | 91 | withArgs subAPI = (\(a :<|> _) -> a) . subAPI :<|> (\(_ :<|> b) -> b) . subAPI |
| 88 | 92 | ||
| 89 | mkClient :: (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 | 93 | mkClientS :: 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' |
| 93 | mkClient n url = Client{..} | 99 | mkClientS 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 | ||
| 125 | mkClient :: 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 | ||
| 129 | mkClient n url = mkClientS n defaultManagerSettings url | ||
| 130 | |||
| 102 | mkClient' :: (MonadThrow m, MonadIO m) => BaseUrl -> Client m | 131 | mkClient' :: (MonadThrow m, MonadIO m) => BaseUrl -> Client m |
| 103 | -- ^ @mkClient' = mkClient $ ioNat . throwNat@ | 132 | -- ^ @mkClient' = mkClient $ ioNat . throwNat@ |
| 104 | mkClient' = mkClient $ ioNat . throwNat | 133 | mkClient' = mkClient $ ioNat . throwNat |
| 105 | 134 | ||
| 106 | throwNat :: (Exception e, MonadThrow m) => EitherT e m :~> m | 135 | throwNat :: (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' |
| 108 | throwNat = Nat $ either throwM return <=< runEitherT | 137 | throwNat = Nat $ either throwM return <=< runExceptT |
| 109 | 138 | ||
| 110 | ioNat :: MonadIO m => IO :~> m | 139 | ioNat :: MonadIO m => IO :~> m |
| 111 | -- ^ @ioNat = Nat liftIO@ | 140 | -- ^ @ioNat = Nat liftIO@ |
| 112 | ioNat = Nat liftIO | 141 | ioNat = Nat liftIO |
| 142 | |||
| 143 | readerNat :: a -> ReaderT a m :~> m | ||
| 144 | readerNat a = Nat $ flip runReaderT a | ||
