updated swagger schema

master
Alaudidae Lark 2017-05-06 14:12:09 +05:30
parent 1d44db32f0
commit 00523772ac
5 changed files with 61 additions and 40 deletions

View File

@ -46,11 +46,9 @@ couponServer pool =
return Nothing return Nothing
billCouponServer :: ConnectionPool -> Server BillCouponApi billCouponServer :: ConnectionPool -> Server BillCouponApi
billCouponServer pool = billCouponComputeH billCouponServer _ = billCouponComputeH
where billCouponComputeH bill = liftIO $ billCouponCompute bill where billCouponComputeH bill = liftIO $ billCouponCompute bill
-- return $ Applied 100 billCouponCompute bill = do print bill
billCouponCompute :: BillCoupon -> IO CouponResult
billCouponCompute bill = do putStrLn $ show bill
return $ Applied 100 return $ Applied 100

View File

@ -14,28 +14,35 @@ module Coupon where
import Data.Aeson import Data.Aeson
import Data.Aeson.Types import Data.Aeson.Types
import Data.Swagger
import Data.Text
import Database.Persist.TH import Database.Persist.TH
import GHC.Generics import GHC.Generics
import Prelude import Prelude
data Product = Product { data Product = Product {
productName :: String, productName :: Text,
productPrice:: Int productPrice:: Int
} deriving (Eq, Read, Show, Generic, FromJSON, ToJSON) } deriving (Eq, Read, Show, Generic, FromJSON, ToJSON, ToSchema)
data BillCoupon = BillCoupon { data BillCoupon = BillCoupon {
customer :: String, customer :: Text,
coupon :: String, coupon :: Text,
productList :: [Product] productList :: [Product]
} deriving (Eq, Read, Show, Generic, FromJSON, ToJSON) } deriving (Eq, Read, Show, Generic, FromJSON, ToJSON, ToSchema)
data CouponResult = Applied Int | Rejected String | Partial String data CouponResult = Applied Int | Rejected String | Partial String
deriving (Show, Read, Eq, Generic, FromJSON, ToJSON) deriving (Show, Read, Eq, Generic, FromJSON, ToJSON, ToSchema)
data CouponType = ProductFlat Int | CartFlat Int | CartPercent Int data CouponForProduct = CouponForProduct {
deriving (Show, Read, Eq, Generic) product ::Text,
productDiscount ::Int
} deriving (Show, Read, Eq, Generic, FromJSON, ToJSON, ToSchema)
data CouponType = ProductFlat CouponForProduct | CartFlat Int | CartPercent Int
deriving (Show, Read, Eq, Generic, ToSchema)
couponOption :: Options
couponOption = defaultOptions { sumEncoding = ObjectWithSingleField } couponOption = defaultOptions { sumEncoding = ObjectWithSingleField }
instance FromJSON CouponType where instance FromJSON CouponType where
@ -46,5 +53,11 @@ instance ToJSON CouponType where
derivePersistField "CouponType" derivePersistField "CouponType"
prodListEx = [Product {productName = "Water", productPrice = 15}] -- prodListEx :: [Product]
billCouponExample = BillCoupon { customer = "test@email.com", coupon = "FLAT100", productList = prodListEx} -- prodListEx = [Product {productName = "Water", productPrice = 15}]
-- billCouponExample :: BillCoupon
-- billCouponExample = BillCoupon { customer = "test@email.com",
-- coupon = "FLAT100",
-- productList = prodListEx }

View File

@ -13,26 +13,30 @@
module Models (module Models,module Coupon) where module Models (module Models,module Coupon) where
import Coupon import Coupon
import Data.Aeson
import Data.Text import Data.Text
import Data.Time.Clock import Data.Time.Clock
import Database.Persist.TH import Database.Persist.TH
import GHC.Generics import GHC.Generics
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Customer CustomerCoupon
email Text email Text
code Text
usage Int
UniqueEmail email UniqueEmail email
Primary email Primary email
Foreign Coupon fkcoupon code
deriving Eq Read Show Generic deriving Eq Read Show Generic
-- Product
-- name Text ProductCoupon
-- price Int product Text
-- code Text code Text
-- UniqueName name usage Int
-- Foreign Coupon fkcoupon code UniqueProduct product
-- Primary name Primary product
-- deriving Eq Read Show Generic Foreign Coupon fkcoupon code
deriving Eq Read Show Generic
Coupon json Coupon json
code Text code Text
value CouponType value CouponType

View File

@ -1,7 +1,5 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
@ -12,7 +10,10 @@ import Control.Lens
import Data.Aeson import Data.Aeson
import Data.Aeson.Types (camelTo2) import Data.Aeson.Types (camelTo2)
import qualified Data.ByteString.Lazy.Char8 as BL8 import qualified Data.ByteString.Lazy.Char8 as BL8
import Data.Proxy
import Data.String.Conversions
import Data.Swagger import Data.Swagger
import qualified Data.Text as T
import Servant.Swagger import Servant.Swagger
modifier :: String -> String modifier :: String -> String
@ -21,18 +22,23 @@ modifier = drop 1 . dropWhile (/= '_') . camelTo2 '_'
prefixSchemaOptions :: SchemaOptions prefixSchemaOptions :: SchemaOptions
prefixSchemaOptions = defaultSchemaOptions { fieldLabelModifier = modifier } prefixSchemaOptions = defaultSchemaOptions { fieldLabelModifier = modifier }
instance ToSchema BillCoupon where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions
instance ToSchema CouponType where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions
instance ToSchema Coupon where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions instance ToSchema Coupon where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions
instance ToSchema Product where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions
instance ToSchema Customer where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions
instance ToSchema CouponResult where declareNamedSchema = genericDeclareNamedSchema prefixSchemaOptions
swaggerDoc :: Swagger swaggerDoc :: Swagger
swaggerDoc = toSwagger api swaggerDoc = toSwagger api
& host ?~ "localhost: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"]
genSwaggerDoc :: IO () genSwaggerDoc :: IO ()
genSwaggerDoc = BL8.writeFile "swagger.json" (encode swaggerDoc) genSwaggerDoc = BL8.writeFile "swagger.json" (encode swaggerDoc)
-- billOp :: Traversal' Swagger Operation
-- billOp = subOperations (Proxy :: Proxy BillCouponApi) (Proxy :: Proxy ServerApi)
-- billText :: T.Text
-- billText = cs $ encode billCouponExample
-- billCouponSchema :: BL8.ByteString
-- billCouponSchema = encode $ toSchema (Proxy::Proxy BillCoupon)

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","valid_from","valid_till"],"properties":{"code":{"type":"string"},"value":{"$ref":"#/definitions/CouponType"},"min_price":{"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":["list"],"properties":{"list":{"items":{"type":"string"},"type":"array"}},"minItems":1,"items":[{"type":"string"}],"maxItems":1,"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":{"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"}}}