8

I have a servant app and have looked through the following issues for my problem I am getting a 400 for preflight request with the OPTIONS verb:

https://github.com/haskell-servant/servant/issues/154

https://github.com/haskell-servant/servant-swagger/issues/45

https://github.com/haskell-servant/servant/issues/278

And the package created for it https://hackage.haskell.org/package/servant-options

I havent been able to solve the preflight request issue when issuing the following request:

curl -X OPTIONS \
  http://localhost:8081/todos \
  -H 'authorization: JWT xxx' \
  -H 'cache-control: no-cache' \
  -H 'postman-token: 744dff43-a6ad-337d-8b67-5a6f70af8864'

I am still getting:

Access-Control-Request-Method header is missing in CORS preflight request

Despite using the following middleware as suggested:

{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE FlexibleContexts      #-}

module Adapter.Servant.Main (main) where

import ClassyPrelude hiding (Handler)
import           Domain.Types.AppEnv
import           Network.Wai.Handler.Warp
import           Network.Wai
import           Network.Wai.Middleware.RequestLogger
-- import qualified Adapter.Servant.TodoAPI as TodoAPI
import qualified Adapter.Servant.TODO.API as TodoAPI
import qualified Adapter.Servant.Swagger as Swagger
import qualified Adapter.Servant.Auth as Auth
import           Network.Wai.Middleware.Cors
import           Servant
import           Servant.Server
import           Network.Wai.Middleware.Servant.Options
import           Network.Wai.Middleware.AddHeaders

allowCsrf :: Middleware
allowCsrf = addHeaders [("Access-Control-Allow-Headers", "x-csrf-token,authorization")]

middleware :: Application -> Application
middleware =  logStdoutDev . allowCsrf . corsMiddleware
--middleware = logStdoutDev . myCors

corsMiddleware :: Application -> Application
corsMiddleware = cors (const $ Just appCorsResourcePolicy)

myCors :: Middleware
myCors = cors (const $ Just policy)
    where
      policy = simpleCorsResourcePolicy
        { corsRequestHeaders = ["Content-Type"]
        , corsMethods = "PUT" : simpleMethods }

appCorsResourcePolicy :: CorsResourcePolicy
appCorsResourcePolicy =
    simpleCorsResourcePolicy
        { corsMethods = ["OPTIONS", "GET", "PUT", "POST"]
        , corsRequestHeaders = ["Authorization", "Content-Type"]
        }
{-
main :: AppEnv -> IO ()
main env = do
  Swagger.writeSwaggerJSON
  run 8081 $ middleware (TodoAPI.todoApp env)
-}
type AppAPI = TodoAPI.TodoAPI :<|> "docs" :> Raw

appApi :: Proxy AppAPI
appApi = Proxy

main :: AppEnv -> IO ()
main env = do
  Swagger.writeSwaggerJSON
  run 8081 $ corsMiddleware $ logStdoutDev $ (appServer env)
  -- run 8081 $ middleware (TodoAPI.todoApp env)
  -- run 8081 $ middleware $ (appServer env)


appServer :: AppEnv -> Application
appServer env = serveWithContext appApi (Auth.genAuthServerContext env) ((TodoAPI.todoServer env) :<|> Swagger.docServer)

The servant-options package also doesn't work with my API as I get the following error:

    • No instance for (servant-foreign-0.15:Servant.Foreign.Internal.GenerateList
                         NoContent
                         (servant-foreign-0.15:Servant.Foreign.Internal.Foreign
                            NoContent
                            (AuthProtect "JWT"
                             :> (ReqBody '[JSON] Domain.Types.TODO.NewTodo
                                 :> Post '[JSON] Int64))))
        arising from a use of ‘provideOptions’
    • In the expression: provideOptions appApi
      In the expression:
        provideOptions appApi
          $ serveWithContext
              appApi
              (Auth.genAuthServerContext env)
              ((TodoAPI.todoServer env) :<|> Swagger.docServer)
      In an equation for ‘appServer’:
          appServer env
            = provideOptions appApi
                $ serveWithContext
                    appApi
                    (Auth.genAuthServerContext env)
                    ((TodoAPI.todoServer env) :<|> Swagger.docServer)
   |

I am sure this has been solved but the examples shown in the threads don't work and the package provided doesn't appear to work if you serve with context

emg184
  • 850
  • 8
  • 19

1 Answers1

5

The issue was never with servant. After further inspection this issue occured because of how postman handles OPTIONS HTTP verb. The Access-Control-Request-Method is never actually sent unless you enable postman interceptor. This was a naive issue on my end, but leaving it up here in case others run across this.

emg184
  • 850
  • 8
  • 19