swagger now includes UI
This commit is contained in:
parent
7aea50af90
commit
2ddf3d907b
3 changed files with 59 additions and 47 deletions
101
app/Main.hs
101
app/Main.hs
|
@ -5,6 +5,7 @@
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Prelude as P
|
import Prelude as P
|
||||||
|
@ -12,6 +13,8 @@ import Prelude as P
|
||||||
import Servant
|
import Servant
|
||||||
import Servant.Server.Experimental.Auth
|
import Servant.Server.Experimental.Auth
|
||||||
import qualified Servant.OpenApi as OA
|
import qualified Servant.OpenApi as OA
|
||||||
|
import Servant.Swagger.UI
|
||||||
|
import Servant.Swagger.UI.Core
|
||||||
import Servant.RawM
|
import Servant.RawM
|
||||||
|
|
||||||
import Data.Set as S (empty)
|
import Data.Set as S (empty)
|
||||||
|
@ -24,6 +27,7 @@ import Data.IP
|
||||||
import qualified Data.OpenApi as OA hiding (Server)
|
import qualified Data.OpenApi as OA hiding (Server)
|
||||||
import Data.Typeable
|
import Data.Typeable
|
||||||
import Data.Data (Typeable)
|
import Data.Data (Typeable)
|
||||||
|
import Data.Tagged
|
||||||
|
|
||||||
import Database.PostgreSQL.Simple
|
import Database.PostgreSQL.Simple
|
||||||
import Database.PostgreSQL.Simple.Migration
|
import Database.PostgreSQL.Simple.Migration
|
||||||
|
@ -60,6 +64,7 @@ import Janitor
|
||||||
-- import Middleware
|
-- import Middleware
|
||||||
|
|
||||||
import Paths_mateamt (version)
|
import Paths_mateamt (version)
|
||||||
|
import Control.Monad.Except (runExceptT)
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
|
@ -162,59 +167,65 @@ main = do
|
||||||
|
|
||||||
app :: ReadState -> Application
|
app :: ReadState -> Application
|
||||||
-- app conn = serveWithContext userApi genAuthServerContext (users conn)
|
-- app conn = serveWithContext userApi genAuthServerContext (users conn)
|
||||||
app initState =
|
app initState =
|
||||||
serveWithContext combinedAPI (genAuthServerContext (rsConnection initState)) $
|
serveWithContext combinedAPI (genAuthServerContext (rsConnection initState)) server
|
||||||
hoistServerWithContext
|
where
|
||||||
combinedAPI
|
server :: Server CombinedAPI
|
||||||
authProxy
|
server = appToServer initState mateAPI thisApi :<|>
|
||||||
(`runReaderT` initState)
|
swaggerSchemaUIServer mateSwagger
|
||||||
( mateSwagger :<|>
|
|
||||||
( authGet :<|>
|
|
||||||
authSend :<|>
|
|
||||||
authLogout :<|>
|
|
||||||
|
|
||||||
authManageList :<|>
|
appToServer initState myApi =
|
||||||
authManageNewAuth :<|>
|
hoistServerWithContext
|
||||||
authManageDeleteAuth :<|>
|
myApi
|
||||||
|
authProxy
|
||||||
|
(`runReaderT` initState)
|
||||||
|
|
||||||
userNew :<|>
|
thisApi :: ServerT MateAPI MateHandler
|
||||||
userGet :<|>
|
thisApi =
|
||||||
userUpdate :<|>
|
authGet :<|>
|
||||||
userList :<|>
|
authSend :<|>
|
||||||
userRecharge :<|>
|
authLogout :<|>
|
||||||
userTransfer :<|>
|
|
||||||
|
|
||||||
productNew :<|>
|
authManageList :<|>
|
||||||
productOverview :<|>
|
authManageNewAuth :<|>
|
||||||
productStockRefill :<|>
|
authManageDeleteAuth :<|>
|
||||||
productStockUpdate :<|>
|
|
||||||
productList :<|>
|
|
||||||
productShortList :<|>
|
|
||||||
|
|
||||||
buy :<|>
|
userNew :<|>
|
||||||
|
userGet :<|>
|
||||||
|
userUpdate :<|>
|
||||||
|
userList :<|>
|
||||||
|
userRecharge :<|>
|
||||||
|
userTransfer :<|>
|
||||||
|
|
||||||
journalShow :<|>
|
productNew :<|>
|
||||||
journalCheck :<|>
|
productOverview :<|>
|
||||||
|
productStockRefill :<|>
|
||||||
|
productStockUpdate :<|>
|
||||||
|
productList :<|>
|
||||||
|
productShortList :<|>
|
||||||
|
|
||||||
avatarGet :<|>
|
buy :<|>
|
||||||
avatarInsert :<|>
|
|
||||||
avatarUpdate :<|>
|
|
||||||
avatarList :<|>
|
|
||||||
|
|
||||||
roleList :<|>
|
journalShow :<|>
|
||||||
roleNew :<|>
|
journalCheck :<|>
|
||||||
roleUpdate :<|>
|
|
||||||
roleDelete :<|>
|
|
||||||
roleAssociationList :<|>
|
|
||||||
roleAssociationSubmit :<|>
|
|
||||||
roleAssociationDelete :<|>
|
|
||||||
|
|
||||||
metaGet
|
avatarGet :<|>
|
||||||
)
|
avatarInsert :<|>
|
||||||
)
|
avatarUpdate :<|>
|
||||||
|
avatarList :<|>
|
||||||
|
|
||||||
mateSwagger :: ReaderT ReadState Handler OA.OpenApi
|
roleList :<|>
|
||||||
mateSwagger = return $ OA.toOpenApi mateAPI
|
roleNew :<|>
|
||||||
|
roleUpdate :<|>
|
||||||
|
roleDelete :<|>
|
||||||
|
roleAssociationList :<|>
|
||||||
|
roleAssociationSubmit :<|>
|
||||||
|
roleAssociationDelete :<|>
|
||||||
|
|
||||||
|
metaGet
|
||||||
|
|
||||||
|
mateSwagger :: OA.OpenApi
|
||||||
|
mateSwagger = OA.toOpenApi mateAPI
|
||||||
& OA.info.OA.title .~ "Mateamt API"
|
& OA.info.OA.title .~ "Mateamt API"
|
||||||
& OA.info.OA.version .~ "1.0"
|
& OA.info.OA.version .~ "1.0"
|
||||||
& OA.info.OA.description ?~ "AN API to buy Mate and other products from your local Hackerspace or event."
|
& OA.info.OA.description ?~ "AN API to buy Mate and other products from your local Hackerspace or event."
|
||||||
|
@ -229,7 +240,7 @@ swaggerAPI = Proxy
|
||||||
combinedAPI :: Proxy CombinedAPI
|
combinedAPI :: Proxy CombinedAPI
|
||||||
combinedAPI = Proxy
|
combinedAPI = Proxy
|
||||||
|
|
||||||
type CombinedAPI = SwaggerAPI :<|> MateAPI
|
type CombinedAPI = MateAPI :<|> SwaggerSchemaUI "swagger-ui" "swagger.json"
|
||||||
|
|
||||||
authProxy :: Proxy '[ AuthHandler Request (Maybe (Int, AuthMethod)) ]
|
authProxy :: Proxy '[ AuthHandler Request (Maybe (Int, AuthMethod)) ]
|
||||||
authProxy = Proxy
|
authProxy = Proxy
|
||||||
|
|
|
@ -149,6 +149,8 @@ executable mateamt
|
||||||
, servant-server
|
, servant-server
|
||||||
, servant-rawm
|
, servant-rawm
|
||||||
, servant-openapi3
|
, servant-openapi3
|
||||||
|
, servant-swagger-ui
|
||||||
|
, servant-swagger-ui-core
|
||||||
, warp
|
, warp
|
||||||
, wai
|
, wai
|
||||||
, wai-logger
|
, wai-logger
|
||||||
|
@ -158,6 +160,7 @@ executable mateamt
|
||||||
, case-insensitive
|
, case-insensitive
|
||||||
, iproute
|
, iproute
|
||||||
, clock
|
, clock
|
||||||
|
, tagged
|
||||||
|
|
||||||
hs-source-dirs: app
|
hs-source-dirs: app
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
|
|
|
@ -16,8 +16,6 @@ import Data.Proxy
|
||||||
import Servant.RawM
|
import Servant.RawM
|
||||||
import Servant.RawM.Server ()
|
import Servant.RawM.Server ()
|
||||||
|
|
||||||
import Network.Wai (Application)
|
|
||||||
|
|
||||||
-- internal imports
|
-- internal imports
|
||||||
|
|
||||||
import Types
|
import Types
|
||||||
|
|
Loading…
Reference in a new issue