get rid of some more proxies, client-side capture support, client and server side request body support
This commit is contained in:
parent
8c8bc15ea9
commit
35c9078fcb
1 changed files with 81 additions and 21 deletions
102
src/Servant.hs
102
src/Servant.hs
|
@ -3,95 +3,155 @@
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
module Servant where
|
module Servant where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
import Control.Concurrent (forkIO, killThread)
|
||||||
|
import Control.Monad
|
||||||
|
import Control.Monad.IO.Class
|
||||||
|
import Control.Monad.Trans.Either
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
|
import Data.ByteString.Lazy (ByteString)
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import Data.Text
|
import Data.Text
|
||||||
import GHC.Generics
|
import GHC.Generics
|
||||||
import GHC.TypeLits
|
import GHC.TypeLits
|
||||||
|
import Network.HTTP.Types
|
||||||
|
import Network.URI
|
||||||
import Network.Wai
|
import Network.Wai
|
||||||
import Network.Wai.Handler.Warp
|
import Network.Wai.Handler.Warp
|
||||||
import Soenke
|
import Soenke
|
||||||
|
|
||||||
|
import qualified Network.HTTP.Client as Http.Client
|
||||||
|
|
||||||
-- * Captures
|
-- * Captures
|
||||||
data Capture sym a
|
data Capture sym a
|
||||||
|
|
||||||
class FromText a where
|
class FromText a where
|
||||||
capture :: Text -> Maybe a
|
capture :: Text -> Maybe a
|
||||||
|
|
||||||
|
class ToText a where
|
||||||
|
toText :: a -> Text
|
||||||
|
|
||||||
instance FromText Text where
|
instance FromText Text where
|
||||||
capture = Just
|
capture = Just
|
||||||
|
|
||||||
|
instance ToText Text where
|
||||||
|
toText = id
|
||||||
|
|
||||||
captured :: FromText a => proxy (Capture sym a) -> Text -> Maybe a
|
captured :: FromText a => proxy (Capture sym a) -> Text -> Maybe a
|
||||||
captured _ = capture
|
captured _ = capture
|
||||||
|
|
||||||
instance (KnownSymbol capture, FromText a, HasServer sublayout)
|
instance (KnownSymbol capture, FromText a, HasServer sublayout)
|
||||||
=> HasServer (Capture capture a :> sublayout) where
|
=> HasServer (Capture capture a :> sublayout) where
|
||||||
|
|
||||||
-- this means that what follows the capture
|
|
||||||
-- must necessarily be a function that expects
|
|
||||||
-- the captured value. :-(
|
|
||||||
type Server (Capture capture a :> sublayout) =
|
type Server (Capture capture a :> sublayout) =
|
||||||
Capture capture a :> (a -> Server sublayout)
|
a -> Server sublayout
|
||||||
|
|
||||||
route Proxy (capture :> subserver) request = case pathInfo request of
|
route Proxy subserver request = case pathInfo request of
|
||||||
(first : rest)
|
(first : rest)
|
||||||
-> case captured capture first of
|
-> case captured captureProxy first of
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
Just v -> route (Proxy :: Proxy sublayout) (subserver v) request{
|
Just v -> route (Proxy :: Proxy sublayout) (subserver v) request{
|
||||||
pathInfo = rest
|
pathInfo = rest
|
||||||
}
|
}
|
||||||
_ -> return Nothing
|
_ -> return Nothing
|
||||||
|
|
||||||
|
where captureProxy = Proxy :: Proxy (Capture capture a)
|
||||||
|
|
||||||
|
instance (KnownSymbol capture, ToText a, HasClient sublayout)
|
||||||
|
=> HasClient (Capture capture a :> sublayout) where
|
||||||
|
|
||||||
|
type Client (Capture capture a :> sublayout) =
|
||||||
|
a -> Client sublayout
|
||||||
|
|
||||||
|
clientWithRoute Proxy path val =
|
||||||
|
clientWithRoute (Proxy :: Proxy sublayout)
|
||||||
|
(path ++ "/" ++ unpack (toText val))
|
||||||
|
|
||||||
-- * Request Body support
|
-- * Request Body support
|
||||||
data RQBody a
|
data RQBody a
|
||||||
|
|
||||||
instance (FromJSON a, HasServer sublayout)
|
instance (FromJSON a, HasServer sublayout)
|
||||||
=> HasServer (RQBody a :> sublayout) where
|
=> HasServer (RQBody a :> sublayout) where
|
||||||
|
|
||||||
-- same caveat as for the Captures...
|
|
||||||
type Server (RQBody a :> sublayout) =
|
type Server (RQBody a :> sublayout) =
|
||||||
RQBody a :> (a -> Server sublayout)
|
a -> Server sublayout
|
||||||
|
|
||||||
route Proxy (rqbody :> subserver) request = do
|
route Proxy subserver request = do
|
||||||
mrqbody <- decode' <$> lazyRequestBody request
|
mrqbody <- decode' <$> lazyRequestBody request
|
||||||
case mrqbody of
|
case mrqbody of
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
Just v -> route (Proxy :: Proxy sublayout) (subserver v) request
|
Just v -> route (Proxy :: Proxy sublayout) (subserver v) request
|
||||||
|
|
||||||
|
instance (ToJSON a, FromJSON b)
|
||||||
|
=> HasClient (RQBody a :> Post b) where
|
||||||
|
|
||||||
|
type Client (RQBody a :> Post b) =
|
||||||
|
a -> URI -> EitherT String IO b
|
||||||
|
|
||||||
|
clientWithRoute Proxy path body uri = do
|
||||||
|
partialRequest <- liftIO . Http.Client.parseUrl $
|
||||||
|
show ( nullURI { uriPath = path }
|
||||||
|
`relativeTo` uri
|
||||||
|
)
|
||||||
|
|
||||||
|
let request = partialRequest
|
||||||
|
{ Http.Client.method = methodPost
|
||||||
|
, Http.Client.requestBody = Http.Client.RequestBodyLBS (encode body)
|
||||||
|
}
|
||||||
|
|
||||||
|
innerResponse <- liftIO . __withGlobalManager $ \ manager ->
|
||||||
|
Http.Client.httpLbs request manager
|
||||||
|
|
||||||
|
when (Http.Client.responseStatus innerResponse /= status201) $
|
||||||
|
left ("HTTP POST request failed with status: " ++ show (Http.Client.responseStatus innerResponse))
|
||||||
|
|
||||||
|
maybe (left "HTTP POST request returned invalid json") return $
|
||||||
|
decode' (Http.Client.responseBody innerResponse)
|
||||||
|
|
||||||
-- * Example
|
-- * Example
|
||||||
|
|
||||||
type TestApi = "hello" :> Capture "name" Text :> Get Greet
|
type TestApi = "hello" :> Capture "name" Text :> Get Greet
|
||||||
|
:<|> "greet" :> RQBody Greet :> Post Greet
|
||||||
|
|
||||||
testApi :: Proxy TestApi
|
testApi :: Proxy TestApi
|
||||||
testApi = Proxy
|
testApi = Proxy
|
||||||
|
|
||||||
data Greet = Greet { msg :: Text }
|
data Greet = Greet { msg :: Text }
|
||||||
deriving Generic
|
deriving (Generic, Show)
|
||||||
|
|
||||||
|
instance FromJSON Greet
|
||||||
instance ToJSON Greet
|
instance ToJSON Greet
|
||||||
|
|
||||||
server :: Server TestApi
|
server :: Server TestApi
|
||||||
server =
|
server = hello :<|> greet
|
||||||
Proxy -- :: Proxy "hello"
|
|
||||||
:> Proxy -- :: Proxy (Capture "name" Text)
|
|
||||||
:> (return . func)
|
|
||||||
|
|
||||||
where func name = Greet ("Hello, " <> name)
|
where hello = return . Greet . ("Hello, " <>)
|
||||||
|
greet = return
|
||||||
|
|
||||||
|
getGreet :: Text -> URI -> EitherT String IO Greet
|
||||||
|
postGreet :: Greet -> URI -> EitherT String IO Greet
|
||||||
|
|
||||||
|
getGreet :<|> postGreet
|
||||||
|
= client testApi
|
||||||
|
|
||||||
test :: Application
|
test :: Application
|
||||||
test = serve testApi server
|
test = serve testApi server
|
||||||
|
|
||||||
runTest :: Port -> IO ()
|
runTestServer :: Port -> IO ()
|
||||||
runTest port = run port test
|
runTestServer port = run port test
|
||||||
|
|
||||||
-- load in ghci, call 'runTest 8000'
|
runTest :: IO ()
|
||||||
-- visit http://localhost:8000/hello/world
|
runTest = do
|
||||||
-- visit http://localhost:8000/hello/soenke
|
tid <- forkIO $ runTestServer 8001
|
||||||
-- visit http://localhost:8000/hello/alp
|
let Just uri = parseURI "http://localhost:8001/"
|
||||||
|
print =<< runEitherT (getGreet "alp" uri)
|
||||||
|
let g = Greet "yo"
|
||||||
|
print =<< runEitherT (postGreet g uri)
|
||||||
|
killThread tid
|
||||||
|
|
Loading…
Reference in a new issue