integrated a swagger json api endpoint

master
Alaudidae Lark 2017-05-06 15:25:27 +05:30
parent 00523772ac
commit 5f19bd02ac
5 changed files with 23 additions and 14 deletions

View File

@ -2,10 +2,7 @@ module Main where
import App import App
import SwaggerGen
main :: IO () main :: IO ()
main = do genSwaggerDoc main = run "host=localhost port=5432 user=msfuser dbname=coupon password="
run "host=localhost port=5432 user=msfuser dbname=coupon password="
-- run "testSql.db" -- run "testSql.db"

View File

@ -6,9 +6,11 @@
module Api (module Api,module Models) where module Api (module Api,module Models) where
import Data.Proxy import Data.Proxy
import Data.Swagger
import Data.Text import Data.Text
import Models import Models
import Servant.API import Servant.API
import SwaggerGen
type CouponApi = type CouponApi =
"coupon" :> "add" :> ReqBody '[JSON] Coupon :> Post '[JSON] (Maybe Coupon) "coupon" :> "add" :> ReqBody '[JSON] Coupon :> Post '[JSON] (Maybe Coupon)
@ -18,7 +20,12 @@ type CouponApi =
type BillCouponApi = type BillCouponApi =
"billcoupon" :> ReqBody '[JSON] BillCoupon :> Post '[JSON] CouponResult "billcoupon" :> ReqBody '[JSON] BillCoupon :> Post '[JSON] CouponResult
type ServerApi = CouponApi :<|> BillCouponApi type SwaggerApi = "swagger.json" :> Get '[JSON] Swagger
type ServerApi = CouponApi :<|> BillCouponApi :<|> SwaggerApi
couponApi :: Proxy (CouponApi :<|> BillCouponApi)
couponApi = Proxy
api :: Proxy ServerApi api :: Proxy ServerApi
api = Proxy api = Proxy

View File

@ -17,6 +17,7 @@ import Network.Wai
import Network.Wai.Handler.Warp as Warp import Network.Wai.Handler.Warp as Warp
import Network.Wai.Middleware.Cors import Network.Wai.Middleware.Cors
import Servant import Servant
import SwaggerGen
-- import Network.Wai.Middleware.RequestLogger (logStdoutDev) -- import Network.Wai.Middleware.RequestLogger (logStdoutDev)
couponServer :: ConnectionPool -> Server CouponApi couponServer :: ConnectionPool -> Server CouponApi
@ -51,9 +52,11 @@ billCouponServer _ = billCouponComputeH
billCouponCompute bill = do print bill billCouponCompute bill = do print bill
return $ Applied 100 return $ Applied 100
swaggerServer :: Server SwaggerApi
swaggerServer = liftIO $ return $ swaggerDoc couponApi
server :: ConnectionPool -> Server ServerApi server :: ConnectionPool -> Server ServerApi
server pool = couponServer pool :<|> billCouponServer pool server pool = couponServer pool :<|> billCouponServer pool :<|> swaggerServer
app :: ConnectionPool -> Application app :: ConnectionPool -> Application
@ -74,5 +77,4 @@ mkApp sqliteFile = do
return $ app pool return $ app pool
run :: String -> IO () run :: String -> IO ()
run dbConnStr = run dbConnStr = Warp.run 3000 =<< mkPgApp dbConnStr
Warp.run 3000 =<< mkPgApp dbConnStr

View File

@ -5,7 +5,6 @@
module SwaggerGen where module SwaggerGen where
import Api
import Control.Lens import Control.Lens
import Data.Aeson import Data.Aeson
import Data.Aeson.Types (camelTo2) import Data.Aeson.Types (camelTo2)
@ -14,6 +13,8 @@ import Data.Proxy
import Data.String.Conversions import Data.String.Conversions
import Data.Swagger import Data.Swagger
import qualified Data.Text as T import qualified Data.Text as T
import Models
import Servant.API
import Servant.Swagger import Servant.Swagger
modifier :: String -> String modifier :: String -> String
@ -24,15 +25,17 @@ prefixSchemaOptions = defaultSchemaOptions { fieldLabelModifier = modifier }
instance ToSchema Coupon where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions instance ToSchema Coupon where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions
swaggerDoc :: Swagger
swaggerDoc = toSwagger api -- swaggerDoc :: Swagger
swaggerDoc :: HasSwagger api => Proxy api -> Swagger
swaggerDoc api = toSwagger api
& host ?~ Host {_hostName = "localhost",_hostPort = Just 3000} & host ?~ Host {_hostName = "localhost",_hostPort = Just 3000}
& info.title .~ "Coupon Api" & info.title .~ "Coupon Api"
& info.version .~ "v1" & info.version .~ "v1"
-- & applyTagsFor billOp ["billcoupon" & description ?~ "Text"] -- & applyTagsFor billOp ["billcoupon" & description ?~ "Text"]
genSwaggerDoc :: IO () -- genSwaggerDoc :: IO ()
genSwaggerDoc = BL8.writeFile "swagger.json" (encode swaggerDoc) -- genSwaggerDoc = BL8.writeFile "swagger.json" (encode swaggerDoc)
-- billOp :: Traversal' Swagger Operation -- billOp :: Traversal' Swagger Operation
-- billOp = subOperations (Proxy :: Proxy BillCouponApi) (Proxy :: Proxy ServerApi) -- billOp = subOperations (Proxy :: Proxy BillCouponApi) (Proxy :: Proxy ServerApi)

View File

@ -1 +1 @@
{"swagger":"2.0","info":{"version":"v1","title":"Coupon Api"},"host":"localhost:3000","paths":{"/coupon/add":{"post":{"consumes":["application/json"],"produces":["application/json"],"parameters":[{"required":true,"schema":{"$ref":"#/definitions/Coupon"},"in":"body","name":"body"}],"responses":{"400":{"description":"Invalid `body`"},"200":{"schema":{"$ref":"#/definitions/Coupon"},"description":""}}}},"/coupon/get/{name}":{"get":{"produces":["application/json"],"parameters":[{"required":true,"in":"path","name":"name","type":"string"}],"responses":{"404":{"description":"`name` not found"},"200":{"schema":{"$ref":"#/definitions/Coupon"},"description":""}}}},"/coupon/del/{name}":{"get":{"produces":["application/json"],"parameters":[{"required":true,"in":"path","name":"name","type":"string"}],"responses":{"404":{"description":"`name` not found"},"200":{"schema":{"$ref":"#/definitions/Coupon"},"description":""}}}},"/billcoupon":{"post":{"consumes":["application/json"],"produces":["application/json"],"parameters":[{"required":true,"schema":{"$ref":"#/definitions/BillCoupon"},"in":"body","name":"body"}],"responses":{"400":{"description":"Invalid `body`"},"200":{"schema":{"$ref":"#/definitions/CouponResult"},"description":""}}}}},"definitions":{"Coupon":{"required":["code","value","min_price","customer_limit","usage_limit","valid_from","valid_till"],"properties":{"code":{"type":"string"},"value":{"$ref":"#/definitions/CouponType"},"min_price":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"customer_limit":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"usage_limit":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"valid_from":{"$ref":"#/definitions/UTCTime"},"valid_till":{"$ref":"#/definitions/UTCTime"}},"type":"object"},"CouponType":{"properties":{"ProductFlat":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"CartFlat":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"CartPercent":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"}},"maxProperties":1,"minProperties":1,"type":"object"},"UTCTime":{"example":"2016-07-22T00:00:00Z","format":"yyyy-mm-ddThh:MM:ssZ","type":"string"},"CouponResult":{"properties":{"Applied":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"Rejected":{"type":"string"},"Partial":{"type":"string"}},"maxProperties":1,"minProperties":1,"type":"object"},"BillCoupon":{"required":["customer","coupon","productList"],"properties":{"customer":{"type":"string"},"coupon":{"type":"string"},"productList":{"items":{"$ref":"#/definitions/Product"},"type":"array"}},"type":"object"},"Product":{"required":["productName","productPrice"],"properties":{"productName":{"type":"string"},"productPrice":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"}},"type":"object"}}} {"swagger":"2.0","info":{"version":"v1","title":"Coupon Api"},"host":"localhost:3000","paths":{"/coupon/add":{"post":{"consumes":["application/json"],"produces":["application/json"],"parameters":[{"required":true,"schema":{"$ref":"#/definitions/Coupon"},"in":"body","name":"body"}],"responses":{"400":{"description":"Invalid `body`"},"200":{"schema":{"$ref":"#/definitions/Coupon"},"description":""}}}},"/coupon/get/{name}":{"get":{"produces":["application/json"],"parameters":[{"required":true,"in":"path","name":"name","type":"string"}],"responses":{"404":{"description":"`name` not found"},"200":{"schema":{"$ref":"#/definitions/Coupon"},"description":""}}}},"/coupon/del/{name}":{"get":{"produces":["application/json"],"parameters":[{"required":true,"in":"path","name":"name","type":"string"}],"responses":{"404":{"description":"`name` not found"},"200":{"schema":{"$ref":"#/definitions/Coupon"},"description":""}}}},"/billcoupon":{"post":{"consumes":["application/json"],"produces":["application/json"],"parameters":[{"required":true,"schema":{"$ref":"#/definitions/BillCoupon"},"in":"body","name":"body"}],"responses":{"400":{"description":"Invalid `body`"},"200":{"schema":{"$ref":"#/definitions/CouponResult"},"description":""}}}}},"definitions":{"Coupon":{"required":["code","value","min_price","customer_limit","usage_limit","valid_from","valid_till"],"properties":{"code":{"type":"string"},"value":{"$ref":"#/definitions/CouponType"},"min_price":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"customer_limit":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"usage_limit":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"valid_from":{"$ref":"#/definitions/UTCTime"},"valid_till":{"$ref":"#/definitions/UTCTime"}},"type":"object"},"CouponType":{"properties":{"ProductFlat":{"$ref":"#/definitions/CouponForProduct"},"CartFlat":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"CartPercent":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"}},"maxProperties":1,"minProperties":1,"type":"object"},"CouponForProduct":{"required":["product","productDiscount"],"properties":{"product":{"type":"string"},"productDiscount":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"}},"type":"object"},"UTCTime":{"example":"2016-07-22T00:00:00Z","format":"yyyy-mm-ddThh:MM:ssZ","type":"string"},"CouponResult":{"properties":{"Applied":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"},"Rejected":{"type":"string"},"Partial":{"type":"string"}},"maxProperties":1,"minProperties":1,"type":"object"},"BillCoupon":{"required":["customer","coupon","productList"],"properties":{"customer":{"type":"string"},"coupon":{"type":"string"},"productList":{"items":{"$ref":"#/definitions/Product"},"type":"array"}},"type":"object"},"Product":{"required":["productName","productPrice"],"properties":{"productName":{"type":"string"},"productPrice":{"maximum":9223372036854775807,"minimum":-9223372036854775808,"type":"integer"}},"type":"object"}}}