{-# LANGUAGE DuplicateRecordFields #-}

{- | HTTP basic authentication support.

 Middlewares defined in this module add basic authentication support
 to handlers. In most cases, you just need to use `BasicAuth` trait
 and `basicAuth` middleware. The table below describes when to use
 other traits and middlewares.

 +----------+-------------+-------------------------+----------------------+
 | Type     | Auth Scheme | Trait                   | Middleware           |
 +----------+-------------+-------------------------+----------------------+
 | Required | Basic       | 'BasicAuth'             | 'basicAuth'          |
 +----------+-------------+-------------------------+----------------------+
 | Optional | Basic       | 'BasicAuth'' 'Optional' | 'optionalBasicAuth'  |
 +----------+-------------+-------------------------+----------------------+
 | Required | Any scheme  | 'BasicAuth'' 'Required' | 'basicAuth''         |
 +----------+-------------+-------------------------+----------------------+
 | Optional | Any scheme  | 'BasicAuth'' 'Optional' | 'optionalBasicAuth'' |
 +----------+-------------+-------------------------+----------------------+

 For example, given this handler:

 @
 myHandler :: ('Handler' h IO, 'HasTrait' ('BasicAuth' IO () 'Credentials') req) => 'RequestHandler' h req
 myHandler = ....
 @

 and the following definitions:

 @
 authConfig :: 'BasicAuth' IO () 'Credentials'
 authConfig = 'BasicAuth'' { toBasicAttribute = pure . Right }

 type ErrorTraits = [Status, RequiredHeader \"Content-Type\" Text, RequiredHeader \"WWW-Authenticate\" Text, Body Text]

 errorHandler :: ('Handler' h IO, Sets h ErrorTraits Response)
              => h (Linked req Request, 'BasicAuthError' e) Response
 errorHandler = 'respondUnauthorized' \"Basic\" \"MyRealm\"
 @

 we can add basic authentication to @myHandler@:

 @
 myHandlerWithAuth :: ('Handler' h IO, Get h ('BasicAuth' IO () 'Credentials') Request, Sets h ErrorTraits Response)
                   => 'RequestHandler' h req
 myHandlerWithAuth = 'basicAuth' authConfig errorHandler myHandler
 @

 The middlewares defined below take a 'BasicAuth'' parameter which is
 a newtype wrapper over a function of type @'Credentials' -> m (Either
 e a)@. This is used to convert the user supplied credentials to a
 value of type @a@ or fail with an error of type @e@. The next handler
 is invoked after this conversion and can access @a@ as a trait
 attribute.

 Middlewares marked as 'Required' take an additional error handling
 arrow as a parameter. This arrow is used when an error is encountered
 in authentication. This arrow receives the original request and a
 'BasicAuthError' as inputs and must produce a response as the output.

 Middlewares marked as 'Optional' do not have this additional error
 handling arrow. Instead, the trait attribute is of type @Either
 ('BasicAuthError' e) a@. The next handler will get the errors in this
 trait attribute and must handle it.
-}
module WebGear.Core.Trait.Auth.Basic (
  BasicAuth' (..),
  BasicAuth,
  Realm (..),
  Username (..),
  Password (..),
  Credentials (..),
  BasicAuthError (..),
  basicAuth,
  basicAuth',
  optionalBasicAuth,
  optionalBasicAuth',
) where

import Control.Arrow (ArrowChoice, arr)
import Data.ByteString (ByteString)
import Data.String (IsString)
import Data.Void (Void, absurd)
import GHC.TypeLits (Symbol)
import WebGear.Core.Handler
import WebGear.Core.Modifiers (Existence (..))
import WebGear.Core.Request (Request)
import WebGear.Core.Response (Response)
import WebGear.Core.Trait
import WebGear.Core.Trait.Auth.Common

-- | Trait for HTTP basic authentication: https://tools.ietf.org/html/rfc7617
newtype BasicAuth' (x :: Existence) (scheme :: Symbol) m e a = BasicAuth'
  { -- | Convert the credentials to the trait attribute or an error
    BasicAuth' x scheme m e a -> Credentials -> m (Either e a)
toBasicAttribute :: Credentials -> m (Either e a)
  }

-- | Trait for HTTP basic authentication with the "Basic" scheme.
type BasicAuth = BasicAuth' Required "Basic"

{- | Username for basic authentication. Valid usernames cannot contain
 \':\' characters.
-}
newtype Username = Username ByteString
  deriving newtype (Username -> Username -> Bool
(Username -> Username -> Bool)
-> (Username -> Username -> Bool) -> Eq Username
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Username -> Username -> Bool
$c/= :: Username -> Username -> Bool
== :: Username -> Username -> Bool
$c== :: Username -> Username -> Bool
Eq, Eq Username
Eq Username
-> (Username -> Username -> Ordering)
-> (Username -> Username -> Bool)
-> (Username -> Username -> Bool)
-> (Username -> Username -> Bool)
-> (Username -> Username -> Bool)
-> (Username -> Username -> Username)
-> (Username -> Username -> Username)
-> Ord Username
Username -> Username -> Bool
Username -> Username -> Ordering
Username -> Username -> Username
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Username -> Username -> Username
$cmin :: Username -> Username -> Username
max :: Username -> Username -> Username
$cmax :: Username -> Username -> Username
>= :: Username -> Username -> Bool
$c>= :: Username -> Username -> Bool
> :: Username -> Username -> Bool
$c> :: Username -> Username -> Bool
<= :: Username -> Username -> Bool
$c<= :: Username -> Username -> Bool
< :: Username -> Username -> Bool
$c< :: Username -> Username -> Bool
compare :: Username -> Username -> Ordering
$ccompare :: Username -> Username -> Ordering
$cp1Ord :: Eq Username
Ord, Int -> Username -> ShowS
[Username] -> ShowS
Username -> String
(Int -> Username -> ShowS)
-> (Username -> String) -> ([Username] -> ShowS) -> Show Username
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Username] -> ShowS
$cshowList :: [Username] -> ShowS
show :: Username -> String
$cshow :: Username -> String
showsPrec :: Int -> Username -> ShowS
$cshowsPrec :: Int -> Username -> ShowS
Show, ReadPrec [Username]
ReadPrec Username
Int -> ReadS Username
ReadS [Username]
(Int -> ReadS Username)
-> ReadS [Username]
-> ReadPrec Username
-> ReadPrec [Username]
-> Read Username
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Username]
$creadListPrec :: ReadPrec [Username]
readPrec :: ReadPrec Username
$creadPrec :: ReadPrec Username
readList :: ReadS [Username]
$creadList :: ReadS [Username]
readsPrec :: Int -> ReadS Username
$creadsPrec :: Int -> ReadS Username
Read, String -> Username
(String -> Username) -> IsString Username
forall a. (String -> a) -> IsString a
fromString :: String -> Username
$cfromString :: String -> Username
IsString)

-- | Password for basic authentication.
newtype Password = Password ByteString
  deriving newtype (Password -> Password -> Bool
(Password -> Password -> Bool)
-> (Password -> Password -> Bool) -> Eq Password
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Password -> Password -> Bool
$c/= :: Password -> Password -> Bool
== :: Password -> Password -> Bool
$c== :: Password -> Password -> Bool
Eq, Eq Password
Eq Password
-> (Password -> Password -> Ordering)
-> (Password -> Password -> Bool)
-> (Password -> Password -> Bool)
-> (Password -> Password -> Bool)
-> (Password -> Password -> Bool)
-> (Password -> Password -> Password)
-> (Password -> Password -> Password)
-> Ord Password
Password -> Password -> Bool
Password -> Password -> Ordering
Password -> Password -> Password
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Password -> Password -> Password
$cmin :: Password -> Password -> Password
max :: Password -> Password -> Password
$cmax :: Password -> Password -> Password
>= :: Password -> Password -> Bool
$c>= :: Password -> Password -> Bool
> :: Password -> Password -> Bool
$c> :: Password -> Password -> Bool
<= :: Password -> Password -> Bool
$c<= :: Password -> Password -> Bool
< :: Password -> Password -> Bool
$c< :: Password -> Password -> Bool
compare :: Password -> Password -> Ordering
$ccompare :: Password -> Password -> Ordering
$cp1Ord :: Eq Password
Ord, Int -> Password -> ShowS
[Password] -> ShowS
Password -> String
(Int -> Password -> ShowS)
-> (Password -> String) -> ([Password] -> ShowS) -> Show Password
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Password] -> ShowS
$cshowList :: [Password] -> ShowS
show :: Password -> String
$cshow :: Password -> String
showsPrec :: Int -> Password -> ShowS
$cshowsPrec :: Int -> Password -> ShowS
Show, ReadPrec [Password]
ReadPrec Password
Int -> ReadS Password
ReadS [Password]
(Int -> ReadS Password)
-> ReadS [Password]
-> ReadPrec Password
-> ReadPrec [Password]
-> Read Password
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Password]
$creadListPrec :: ReadPrec [Password]
readPrec :: ReadPrec Password
$creadPrec :: ReadPrec Password
readList :: ReadS [Password]
$creadList :: ReadS [Password]
readsPrec :: Int -> ReadS Password
$creadsPrec :: Int -> ReadS Password
Read, String -> Password
(String -> Password) -> IsString Password
forall a. (String -> a) -> IsString a
fromString :: String -> Password
$cfromString :: String -> Password
IsString)

-- | Basic authentication credentials retrieved from an HTTP request
data Credentials = Credentials
  { Credentials -> Username
credentialsUsername :: !Username
  , Credentials -> Password
credentialsPassword :: !Password
  }
  deriving stock (Credentials -> Credentials -> Bool
(Credentials -> Credentials -> Bool)
-> (Credentials -> Credentials -> Bool) -> Eq Credentials
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Credentials -> Credentials -> Bool
$c/= :: Credentials -> Credentials -> Bool
== :: Credentials -> Credentials -> Bool
$c== :: Credentials -> Credentials -> Bool
Eq, Eq Credentials
Eq Credentials
-> (Credentials -> Credentials -> Ordering)
-> (Credentials -> Credentials -> Bool)
-> (Credentials -> Credentials -> Bool)
-> (Credentials -> Credentials -> Bool)
-> (Credentials -> Credentials -> Bool)
-> (Credentials -> Credentials -> Credentials)
-> (Credentials -> Credentials -> Credentials)
-> Ord Credentials
Credentials -> Credentials -> Bool
Credentials -> Credentials -> Ordering
Credentials -> Credentials -> Credentials
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Credentials -> Credentials -> Credentials
$cmin :: Credentials -> Credentials -> Credentials
max :: Credentials -> Credentials -> Credentials
$cmax :: Credentials -> Credentials -> Credentials
>= :: Credentials -> Credentials -> Bool
$c>= :: Credentials -> Credentials -> Bool
> :: Credentials -> Credentials -> Bool
$c> :: Credentials -> Credentials -> Bool
<= :: Credentials -> Credentials -> Bool
$c<= :: Credentials -> Credentials -> Bool
< :: Credentials -> Credentials -> Bool
$c< :: Credentials -> Credentials -> Bool
compare :: Credentials -> Credentials -> Ordering
$ccompare :: Credentials -> Credentials -> Ordering
$cp1Ord :: Eq Credentials
Ord, Int -> Credentials -> ShowS
[Credentials] -> ShowS
Credentials -> String
(Int -> Credentials -> ShowS)
-> (Credentials -> String)
-> ([Credentials] -> ShowS)
-> Show Credentials
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Credentials] -> ShowS
$cshowList :: [Credentials] -> ShowS
show :: Credentials -> String
$cshow :: Credentials -> String
showsPrec :: Int -> Credentials -> ShowS
$cshowsPrec :: Int -> Credentials -> ShowS
Show, ReadPrec [Credentials]
ReadPrec Credentials
Int -> ReadS Credentials
ReadS [Credentials]
(Int -> ReadS Credentials)
-> ReadS [Credentials]
-> ReadPrec Credentials
-> ReadPrec [Credentials]
-> Read Credentials
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Credentials]
$creadListPrec :: ReadPrec [Credentials]
readPrec :: ReadPrec Credentials
$creadPrec :: ReadPrec Credentials
readList :: ReadS [Credentials]
$creadList :: ReadS [Credentials]
readsPrec :: Int -> ReadS Credentials
$creadsPrec :: Int -> ReadS Credentials
Read)

-- | Error retrieving basic authentication credentials
data BasicAuthError e
  = BasicAuthHeaderMissing
  | BasicAuthSchemeMismatch
  | BasicAuthCredsBadFormat
  | BasicAuthAttributeError e
  deriving stock (BasicAuthError e -> BasicAuthError e -> Bool
(BasicAuthError e -> BasicAuthError e -> Bool)
-> (BasicAuthError e -> BasicAuthError e -> Bool)
-> Eq (BasicAuthError e)
forall e. Eq e => BasicAuthError e -> BasicAuthError e -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BasicAuthError e -> BasicAuthError e -> Bool
$c/= :: forall e. Eq e => BasicAuthError e -> BasicAuthError e -> Bool
== :: BasicAuthError e -> BasicAuthError e -> Bool
$c== :: forall e. Eq e => BasicAuthError e -> BasicAuthError e -> Bool
Eq, Int -> BasicAuthError e -> ShowS
[BasicAuthError e] -> ShowS
BasicAuthError e -> String
(Int -> BasicAuthError e -> ShowS)
-> (BasicAuthError e -> String)
-> ([BasicAuthError e] -> ShowS)
-> Show (BasicAuthError e)
forall e. Show e => Int -> BasicAuthError e -> ShowS
forall e. Show e => [BasicAuthError e] -> ShowS
forall e. Show e => BasicAuthError e -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BasicAuthError e] -> ShowS
$cshowList :: forall e. Show e => [BasicAuthError e] -> ShowS
show :: BasicAuthError e -> String
$cshow :: forall e. Show e => BasicAuthError e -> String
showsPrec :: Int -> BasicAuthError e -> ShowS
$cshowsPrec :: forall e. Show e => Int -> BasicAuthError e -> ShowS
Show, ReadPrec [BasicAuthError e]
ReadPrec (BasicAuthError e)
Int -> ReadS (BasicAuthError e)
ReadS [BasicAuthError e]
(Int -> ReadS (BasicAuthError e))
-> ReadS [BasicAuthError e]
-> ReadPrec (BasicAuthError e)
-> ReadPrec [BasicAuthError e]
-> Read (BasicAuthError e)
forall e. Read e => ReadPrec [BasicAuthError e]
forall e. Read e => ReadPrec (BasicAuthError e)
forall e. Read e => Int -> ReadS (BasicAuthError e)
forall e. Read e => ReadS [BasicAuthError e]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BasicAuthError e]
$creadListPrec :: forall e. Read e => ReadPrec [BasicAuthError e]
readPrec :: ReadPrec (BasicAuthError e)
$creadPrec :: forall e. Read e => ReadPrec (BasicAuthError e)
readList :: ReadS [BasicAuthError e]
$creadList :: forall e. Read e => ReadS [BasicAuthError e]
readsPrec :: Int -> ReadS (BasicAuthError e)
$creadsPrec :: forall e. Read e => Int -> ReadS (BasicAuthError e)
Read)

instance Trait (BasicAuth' Required scheme m e a) Request where
  type Attribute (BasicAuth' Required scheme m e a) Request = a

instance TraitAbsence (BasicAuth' Required scheme m e a) Request where
  type Absence (BasicAuth' Required scheme m e a) Request = BasicAuthError e

instance Trait (BasicAuth' Optional scheme m e a) Request where
  type Attribute (BasicAuth' Optional scheme m e a) Request = Either (BasicAuthError e) a

instance TraitAbsence (BasicAuth' Optional scheme m e a) Request where
  type Absence (BasicAuth' Optional scheme m e a) Request = Void

basicAuthMiddleware ::
  (Get h (BasicAuth' x scheme m e t) Request, ArrowChoice h) =>
  BasicAuth' x scheme m e t ->
  h (Linked req Request, Absence (BasicAuth' x scheme m e t) Request) Response ->
  Middleware h req (BasicAuth' x scheme m e t : req)
basicAuthMiddleware :: BasicAuth' x scheme m e t
-> h (Linked req Request,
      Absence (BasicAuth' x scheme m e t) Request)
     Response
-> Middleware h req (BasicAuth' x scheme m e t : req)
basicAuthMiddleware BasicAuth' x scheme m e t
authCfg h (Linked req Request, Absence (BasicAuth' x scheme m e t) Request)
  Response
errorHandler RequestHandler h (BasicAuth' x scheme m e t : req)
nextHandler =
  proc Linked req Request
request -> do
    Either
  (Absence (BasicAuth' x scheme m e t) Request)
  (Linked (BasicAuth' x scheme m e t : req) Request)
result <- BasicAuth' x scheme m e t
-> h (Linked req Request)
     (Either
        (Absence (BasicAuth' x scheme m e t) Request)
        (Linked (BasicAuth' x scheme m e t : req) Request))
forall t (ts :: [*]) (h :: * -> * -> *) a.
Get h t a =>
t -> h (Linked ts a) (Either (Absence t a) (Linked (t : ts) a))
probe BasicAuth' x scheme m e t
authCfg -< Linked req Request
request
    case Either
  (Absence (BasicAuth' x scheme m e t) Request)
  (Linked (BasicAuth' x scheme m e t : req) Request)
result of
      Left Absence (BasicAuth' x scheme m e t) Request
err -> h (Linked req Request, Absence (BasicAuth' x scheme m e t) Request)
  Response
errorHandler -< (Linked req Request
request, Absence (BasicAuth' x scheme m e t) Request
err)
      Right Linked (BasicAuth' x scheme m e t : req) Request
val -> RequestHandler h (BasicAuth' x scheme m e t : req)
nextHandler -< Linked (BasicAuth' x scheme m e t : req) Request
val

{- | Middleware to add basic authentication protection for a handler.

 Example usage:

 > basicAuth cfg errorHandler nextHandler

 The @errorHandler@ is invoked if the credentials are invalid or
 missing. The @nextHandler@ is invoked if the credentials were
 retrieved successfully.
-}
basicAuth ::
  forall m e t h req.
  (Get h (BasicAuth' Required "Basic" m e t) Request, ArrowChoice h) =>
  -- | Authentication configuration
  BasicAuth m e t ->
  -- | Error handler
  h (Linked req Request, BasicAuthError e) Response ->
  Middleware h req (BasicAuth m e t : req)
basicAuth :: BasicAuth m e t
-> h (Linked req Request, BasicAuthError e) Response
-> Middleware h req (BasicAuth m e t : req)
basicAuth = BasicAuth m e t
-> h (Linked req Request, BasicAuthError e) Response
-> Middleware h req (BasicAuth m e t : req)
forall (scheme :: Symbol) (m :: * -> *) e t (h :: * -> * -> *)
       (req :: [*]).
(Get h (BasicAuth' 'Required scheme m e t) Request,
 ArrowChoice h) =>
BasicAuth' 'Required scheme m e t
-> h (Linked req Request, BasicAuthError e) Response
-> Middleware h req (BasicAuth' 'Required scheme m e t : req)
basicAuth'

{- | Similar to `basicAuth` but supports a custom authentication scheme.

 Example usage:

 > basicAuth' @"scheme" cfg errorHandler nextHandler
-}
basicAuth' ::
  forall scheme m e t h req.
  (Get h (BasicAuth' Required scheme m e t) Request, ArrowChoice h) =>
  -- | Authentication configuration
  BasicAuth' Required scheme m e t ->
  -- | Error handler
  h (Linked req Request, BasicAuthError e) Response ->
  Middleware h req (BasicAuth' Required scheme m e t : req)
basicAuth' :: BasicAuth' 'Required scheme m e t
-> h (Linked req Request, BasicAuthError e) Response
-> Middleware h req (BasicAuth' 'Required scheme m e t : req)
basicAuth' = BasicAuth' 'Required scheme m e t
-> h (Linked req Request, BasicAuthError e) Response
-> Middleware h req (BasicAuth' 'Required scheme m e t : req)
forall (h :: * -> * -> *) (x :: Existence) (scheme :: Symbol)
       (m :: * -> *) e t (req :: [*]).
(Get h (BasicAuth' x scheme m e t) Request, ArrowChoice h) =>
BasicAuth' x scheme m e t
-> h (Linked req Request,
      Absence (BasicAuth' x scheme m e t) Request)
     Response
-> Middleware h req (BasicAuth' x scheme m e t : req)
basicAuthMiddleware

{- | Middleware to add optional basic authentication protection for a handler.

 Example usage:

 > optionalBasicAuth cfg nextHandler

 This middleware will not fail if credentials are invalid or
 missing. Instead the trait attribute is of type @'Either'
 ('BasicAuthError' e) t@ so that the handler can process the
 authentication error appropriately.
-}
optionalBasicAuth ::
  forall m e t h req.
  (Get h (BasicAuth' Optional "Basic" m e t) Request, ArrowChoice h) =>
  -- | Authentication configuration
  BasicAuth' Optional "Basic" m e t ->
  Middleware h req (BasicAuth' Optional "Basic" m e t : req)
optionalBasicAuth :: BasicAuth' 'Optional "Basic" m e t
-> Middleware h req (BasicAuth' 'Optional "Basic" m e t : req)
optionalBasicAuth = BasicAuth' 'Optional "Basic" m e t
-> Middleware h req (BasicAuth' 'Optional "Basic" m e t : req)
forall (scheme :: Symbol) (m :: * -> *) e t (h :: * -> * -> *)
       (req :: [*]).
(Get h (BasicAuth' 'Optional scheme m e t) Request,
 ArrowChoice h) =>
BasicAuth' 'Optional scheme m e t
-> Middleware h req (BasicAuth' 'Optional scheme m e t : req)
optionalBasicAuth'

{- | Similar to `optionalBasicAuth` but supports a custom authentication
   scheme.

 Example usage:

 > optionalBasicAuth' @"scheme" cfg nextHandler
-}
optionalBasicAuth' ::
  forall scheme m e t h req.
  (Get h (BasicAuth' Optional scheme m e t) Request, ArrowChoice h) =>
  -- | Authentication configuration
  BasicAuth' Optional scheme m e t ->
  Middleware h req (BasicAuth' Optional scheme m e t : req)
optionalBasicAuth' :: BasicAuth' 'Optional scheme m e t
-> Middleware h req (BasicAuth' 'Optional scheme m e t : req)
optionalBasicAuth' BasicAuth' 'Optional scheme m e t
cfg = BasicAuth' 'Optional scheme m e t
-> h (Linked req Request,
      Absence (BasicAuth' 'Optional scheme m e t) Request)
     Response
-> Middleware h req (BasicAuth' 'Optional scheme m e t : req)
forall (h :: * -> * -> *) (x :: Existence) (scheme :: Symbol)
       (m :: * -> *) e t (req :: [*]).
(Get h (BasicAuth' x scheme m e t) Request, ArrowChoice h) =>
BasicAuth' x scheme m e t
-> h (Linked req Request,
      Absence (BasicAuth' x scheme m e t) Request)
     Response
-> Middleware h req (BasicAuth' x scheme m e t : req)
basicAuthMiddleware BasicAuth' 'Optional scheme m e t
cfg (h (Linked req Request,
    Absence (BasicAuth' 'Optional scheme m e t) Request)
   Response
 -> Middleware h req (BasicAuth' 'Optional scheme m e t : req))
-> h (Linked req Request,
      Absence (BasicAuth' 'Optional scheme m e t) Request)
     Response
-> Middleware h req (BasicAuth' 'Optional scheme m e t : req)
forall a b. (a -> b) -> a -> b
$ ((Linked req Request, Void) -> Response)
-> h (Linked req Request, Void) Response
forall (a :: * -> * -> *) b c. Arrow a => (b -> c) -> a b c
arr (Void -> Response
forall a. Void -> a
absurd (Void -> Response)
-> ((Linked req Request, Void) -> Void)
-> (Linked req Request, Void)
-> Response
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Linked req Request, Void) -> Void
forall a b. (a, b) -> b
snd)