{- |Description: Combinator for Servant to allow Handlers access to
  the raw path from the WAI request.
-}
module Servant.API.PathInfo where

import Data.Text (Text)
import Network.HTTP.Types (decodePathSegments)
import Network.Wai
import Servant
import Servant.Server.Internal.Delayed (passToServer)

{- |
  @PathInfo@ provides handlers access to the path segments from the
  request, without the domain name or query parameters. We re-generate
  this from the rawPathInfo via
  @Network.HTTP.Types.decodePathSegments@ because Servant removes all
  fields from the @pathInfo@ field of a request as part of routing the
  request to the appropriate handler.

  Example:

@
import Data.ByteString (ByteString)
import Control.Monad.IO.Class (liftIO)
import Servant
import ServantExtras.RawPathInfo

type MyAPI = "merlin" :> "my-path-info-endpoint"
           :> PathInfo
           :> Get '[JSON] NoContent

myServer :: Server MyAPI
myServer = pathInfoEndpointHandler
 where
   pathInfoEndpointHandler :: [Text] -> Handler NoContent
   pathInfoEndpointHandler pInfo = do
     case (elem "merlin" pInfo) of
      False -> do
        liftIO $ print "This example has a bug!"
        throwError err400 { errBody = "Patches accepted!" }
      True -> do
        liftIO $ print "Hopefully this demonstrates how path info works."
        pure NoContent
@
-}
data PathInfo

instance HasServer api ctx => HasServer (PathInfo :> api) ctx where
  type ServerT (PathInfo :> api) m = [Text] -> ServerT api m

  hoistServerWithContext :: forall (m :: * -> *) (n :: * -> *).
Proxy (PathInfo :> api)
-> Proxy ctx
-> (forall x. m x -> n x)
-> ServerT (PathInfo :> api) m
-> ServerT (PathInfo :> api) n
hoistServerWithContext Proxy (PathInfo :> api)
_ Proxy ctx
ctx forall x. m x -> n x
nt ServerT (PathInfo :> api) m
server =
    forall {k} (api :: k) (context :: [*]) (m :: * -> *) (n :: * -> *).
HasServer api context =>
Proxy api
-> Proxy context
-> (forall x. m x -> n x)
-> ServerT api m
-> ServerT api n
hoistServerWithContext (forall {k} (t :: k). Proxy t
Proxy @api) Proxy ctx
ctx forall x. m x -> n x
nt forall b c a. (b -> c) -> (a -> b) -> a -> c
. ServerT (PathInfo :> api) m
server
  route :: forall env.
Proxy (PathInfo :> api)
-> Context ctx
-> Delayed env (Server (PathInfo :> api))
-> Router env
route Proxy (PathInfo :> api)
_ Context ctx
ctx Delayed env (Server (PathInfo :> api))
server =
    forall {k} (api :: k) (context :: [*]) env.
HasServer api context =>
Proxy api
-> Context context -> Delayed env (Server api) -> Router env
route (forall {k} (t :: k). Proxy t
Proxy @api) Context ctx
ctx forall a b. (a -> b) -> a -> b
$
      Delayed env (Server (PathInfo :> api))
server forall env a b.
Delayed env (a -> b) -> (Request -> a) -> Delayed env b
`passToServer` \Request
req ->
        ByteString -> [Text]
decodePathSegments forall a b. (a -> b) -> a -> b
$ Request -> ByteString
rawPathInfo Request
req