ebook-manager/backend/src/Server.hs

44 lines
1.4 KiB
Haskell
Raw Normal View History

2018-08-02 22:11:11 +03:00
{-# Language DataKinds #-}
{-# Language TypeFamilies #-}
{-# Language TypeOperators #-}
{-# Language NoImplicitPrelude #-}
{-# Language MultiParamTypeClasses #-}
{-# Language OverloadedStrings #-}
{-# Language TemplateHaskell #-}
{-# Language QuasiQuotes #-}
{-# Language RecordWildCards #-}
{-# Language DeriveGeneric #-}
{-# Language FlexibleInstances #-}
2018-08-04 23:43:26 +03:00
{-# Language TypeApplications #-}
2018-10-17 23:51:30 +03:00
{-# Language ScopedTypeVariables #-}
2018-08-02 22:11:11 +03:00
module Server where
import qualified API as API
2018-08-04 23:53:40 +03:00
import Server.Auth (authCheck)
2018-08-02 22:11:11 +03:00
import Servant
2018-08-02 22:32:23 +03:00
import Types
import ClassyPrelude hiding (Handler)
import Control.Monad.Logger
import Control.Monad.Except
2018-08-05 23:13:49 +03:00
import Servant.Auth.Server as SAS
2018-08-04 23:43:26 +03:00
import Control.Lens
import Data.Generics.Product
2018-10-17 23:51:30 +03:00
import Server.Auth (SafeUser)
2018-08-02 22:11:11 +03:00
type API = API.API :<|> "static" :> Raw
2018-10-17 23:51:30 +03:00
type Ctx = '[BasicAuthData -> IO (AuthResult SafeUser), CookieSettings, JWTSettings]
2018-08-02 22:11:11 +03:00
2018-08-02 22:32:23 +03:00
server :: App -> Application
2018-10-17 23:51:30 +03:00
server app = serveWithContext api cfg (hoistServerWithContext (Proxy @ API.API) (Proxy @ Ctx) server' API.handler :<|> serveDirectoryFileServer "static")
2018-08-02 22:11:11 +03:00
where
2018-08-04 23:43:26 +03:00
myKey = view (field @"jwk") app
jwtCfg = defaultJWTSettings myKey
2018-08-04 23:53:40 +03:00
authCfg = authCheck app
2018-08-05 23:13:49 +03:00
cookieSettings = SAS.defaultCookieSettings{cookieIsSecure=SAS.NotSecure}
cfg = jwtCfg :. cookieSettings :. authCfg :. EmptyContext
2018-10-17 23:51:30 +03:00
server' :: AppM a -> Servant.Handler a
server' = Handler . ExceptT . try . (`runReaderT` app) . (runFileLoggingT "logs/server.log")
2018-08-02 22:11:11 +03:00
api :: Proxy API
api = Proxy