Fix post-merge build
This commit is contained in:
parent
1146d15f52
commit
9e71d083e5
6 changed files with 17 additions and 15 deletions
|
@ -28,7 +28,7 @@ import Control.Arrow (left)
|
|||
import Control.Concurrent (forkIO, killThread, ThreadId)
|
||||
import Control.Exception (bracket)
|
||||
import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)
|
||||
import Data.Aeson hiding ((.:))
|
||||
import Data.Aeson
|
||||
import Data.Char (chr, isPrint)
|
||||
import Data.Foldable (forM_)
|
||||
import Data.Monoid hiding (getLast)
|
||||
|
@ -178,7 +178,7 @@ authHandler =
|
|||
serverConfig :: Config '[ ConfigEntry "basic-tag" (BasicAuthCheck ())
|
||||
, ConfigEntry "auth-tag" (AuthHandler Request ())
|
||||
]
|
||||
serverConfig = basicAuthHandler .: authHandler .: EmptyConfig
|
||||
serverConfig = basicAuthHandler .:. authHandler .:. EmptyConfig
|
||||
|
||||
authServer :: Application
|
||||
authServer = serve authAPI serverConfig (const (return alice) :<|> const (return alice))
|
||||
|
|
|
@ -7,7 +7,7 @@
|
|||
{-# LANGUAGE TypeOperators #-}
|
||||
|
||||
import Control.Monad.Trans.Except (ExceptT, throwE)
|
||||
import Data.Aeson hiding ((.:))
|
||||
import Data.Aeson
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.Monoid ((<>))
|
||||
import Data.Text (Text)
|
||||
|
@ -70,7 +70,7 @@ type instance AuthReturnType (AuthProtect "cookie-auth") = User
|
|||
-- "cookie-auth"-tagged request handler defined above, so that the 'HasServer' instance
|
||||
-- of 'AuthProtect' can extract the handler and run it on the request.
|
||||
serverConfig :: Config (ConfigEntry "cookie-auth" (AuthHandler Request User) ': '[])
|
||||
serverConfig = authHandler .: EmptyConfig
|
||||
serverConfig = authHandler .:. EmptyConfig
|
||||
|
||||
-- | Our API, where we provide all the author-supplied handlers for each end point.
|
||||
-- note that 'prvdata' is a function that takes 'User' as an argument. We dont' worry
|
||||
|
|
|
@ -14,7 +14,7 @@ import Network.Wai.Handler.Warp (run)
|
|||
import Servant.API ((:<|>) ((:<|>)), (:>), BasicAuth,
|
||||
Get, JSON)
|
||||
import Servant.Server (BasicAuthResult (Authorized, Unauthorized), Config (EmptyConfig),
|
||||
ConfigEntry, Server, serve, (.:), BasicAuthCheck(BasicAuthCheck))
|
||||
ConfigEntry, Server, serve, (.:.), BasicAuthCheck(BasicAuthCheck))
|
||||
|
||||
-- | let's define some types that our API returns.
|
||||
|
||||
|
@ -66,7 +66,7 @@ authCheck =
|
|||
-- tagged with "foo-tag" This config is then supplied to 'server' and threaded
|
||||
-- to the BasicAuth HasServer handlers.
|
||||
serverConfig :: Config (ConfigEntry "foo-tag" (BasicAuthCheck User) ': '[])
|
||||
serverConfig = authCheck .: EmptyConfig
|
||||
serverConfig = authCheck .:. EmptyConfig
|
||||
|
||||
-- | an implementation of our server. Here is where we pass all the handlers to our endpoints.
|
||||
-- In particular, for the BasicAuth protected handler, we need to supply a function
|
||||
|
|
|
@ -23,9 +23,10 @@ module Servant.Server.Internal
|
|||
#if !MIN_VERSION_base(4,8,0)
|
||||
import Control.Applicative ((<$>))
|
||||
#endif
|
||||
import Control.Monad.Trans.Except (ExceptT)
|
||||
import Control.Monad.Trans.Except (ExceptT, runExceptT)
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import qualified Data.ByteString.Char8 as BC8
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe (fromMaybe, mapMaybe)
|
||||
import Data.String (fromString)
|
||||
|
@ -48,7 +49,7 @@ import Web.HttpApiData.Internal (parseHeaderMaybe,
|
|||
parseQueryParamMaybe,
|
||||
parseUrlPieceMaybe)
|
||||
|
||||
import Servant.API ((:<|>) (..), (:>), Capture,
|
||||
import Servant.API ((:<|>) (..), (:>), AuthProtect, BasicAuth, Capture,
|
||||
Verb, ReflectMethod(reflectMethod),
|
||||
IsSecure(..), Header,
|
||||
QueryFlag, QueryParam, QueryParams,
|
||||
|
|
|
@ -19,7 +19,7 @@
|
|||
|
||||
module Servant.Server.Internal.Config where
|
||||
|
||||
import Control.DeepSeq (NFData(rnf))
|
||||
import Control.DeepSeq (NFData)
|
||||
import GHC.Generics (Generic)
|
||||
import Data.Typeable (Typeable)
|
||||
|
||||
|
|
|
@ -33,13 +33,14 @@ import Network.HTTP.Types (Status (..), hAccept, hContentType,
|
|||
parseQuery)
|
||||
import Network.Wai (Application, Request, pathInfo,
|
||||
queryString, rawQueryString,
|
||||
responseBuilder, responseLBS)
|
||||
responseBuilder, responseLBS,
|
||||
requestHeaders)
|
||||
import Network.Wai.Internal (Response (ResponseBuilder))
|
||||
import Network.Wai.Test (defaultRequest, request,
|
||||
runSession, simpleBody,
|
||||
simpleHeaders, simpleStatus)
|
||||
import Servant.API ((:<|>) (..), (:>), Capture, Delete,
|
||||
Get, Header (..),
|
||||
import Servant.API ((:<|>) (..), (:>), AuthProtect, BasicAuth,
|
||||
Capture, Delete, Get, Header (..),
|
||||
Headers, HttpVersion,
|
||||
IsSecure (..), JSON,
|
||||
NoContent (..), Patch, PlainText,
|
||||
|
@ -50,10 +51,11 @@ import Servant.API ((:<|>) (..), (:>), Capture, Delete,
|
|||
import Servant.Server ((.:.), AuthHandler, AuthReturnType,
|
||||
BasicAuthCheck (BasicAuthCheck),
|
||||
BasicAuthResult (Authorized, Unauthorized),
|
||||
Config (EmptyConfig), ServantErr (..),
|
||||
Server, err404, serve)
|
||||
Config (EmptyConfig), ConfigEntry, ServantErr (..),
|
||||
mkAuthHandler, Server, err401, err404, serve)
|
||||
import Test.Hspec (Spec, context, describe, it,
|
||||
shouldBe, shouldContain)
|
||||
import qualified Test.Hspec.Wai as THW
|
||||
import Test.Hspec.Wai (get, liftIO, matchHeaders,
|
||||
matchStatus, request,
|
||||
shouldRespondWith, with, (<:>))
|
||||
|
@ -600,4 +602,3 @@ jerry = Animal "Mouse" 4
|
|||
tweety :: Animal
|
||||
tweety = Animal "Bird" 2
|
||||
-- }}}
|
||||
>>>>>>> shahn/config
|
||||
|
|
Loading…
Reference in a new issue