aboutsummaryrefslogtreecommitdiff
path: root/src/Sproxy/Application.hs
blob: 5de94741343a138aadc8c2bb479542f1f3395429 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Sproxy.Application (
  sproxy
, redirect
) where

import Blaze.ByteString.Builder (toByteString)
import Blaze.ByteString.Builder.ByteString (fromByteString)
import Control.Exception (Exception, Handler(..), SomeException, catches, displayException)
import Data.ByteString (ByteString)
import Data.ByteString as BS (break, intercalate)
import Data.ByteString.Char8 (pack, unpack)
import Data.ByteString.Lazy (fromStrict)
import Data.Conduit (Flush(Chunk), mapOutput)
import Data.HashMap.Strict as HM (HashMap, foldrWithKey, lookup)
import Data.List (find, partition)
import Data.Map as Map (delete, fromListWith, insert, insertWith, toList)
import Data.Maybe (fromJust, fromMaybe)
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Data.Word (Word16)
import Data.Word8 (_colon)
import Foreign.C.Types (CTime(..))
import Network.HTTP.Client.Conduit (bodyReaderSource)
import Network.HTTP.Conduit (requestBodySourceChunkedIO, requestBodySourceIO)
import Network.HTTP.Types (RequestHeaders, ResponseHeaders, methodGet, methodPost)
import Network.HTTP.Types.Header ( hConnection,
  hContentLength, hContentType, hCookie, hLocation, hTransferEncoding )
import Network.HTTP.Types.Status ( Status(..), badRequest400, forbidden403, found302,
  internalServerError500, methodNotAllowed405, movedPermanently301,
  networkAuthenticationRequired511, notFound404, ok200, seeOther303, temporaryRedirect307 )
import Network.Socket (NameInfoFlag(NI_NUMERICHOST), getNameInfo)
import Network.Wai.Conduit (sourceRequestBody, responseSource)
import System.FilePath.Glob (Pattern, match)
import System.Posix.Time (epochTime)
import Text.InterpolatedString.Perl6 (qc)
import Web.Cookie (Cookies, parseCookies, renderCookies)
import qualified Data.Aeson as JSON
import qualified Network.HTTP.Client as BE
import qualified Network.Wai as W
import qualified Web.Cookie as WC

import Sproxy.Application.Cookie ( AuthCookie(..), AuthUser,
  cookieDecode, cookieEncode, getEmail, getEmailUtf8, getFamilyNameUtf8,
  getGivenNameUtf8 )
import Sproxy.Application.OAuth2.Common (OAuth2Client(..))
import Sproxy.Config(BackendConf(..))
import Sproxy.Server.DB (Database, userAccess, userExists, userGroups)
import qualified Sproxy.Application.State as State
import qualified Sproxy.Logging as Log


redirect :: Word16 -> W.Application
redirect p req resp =
  case requestDomain req of
    Nothing -> badRequest "missing host" req resp
    Just domain -> do
      Log.info $ "redirecting to " ++ show location ++ ": " ++ showReq req
      resp $ W.responseBuilder status [(hLocation, location)] mempty
      where
        status = if W.requestMethod req == methodGet then movedPermanently301 else temporaryRedirect307
        newhost = if p == 443 then domain else domain <> ":" <> pack (show p)
        location = "https://" <> newhost <> W.rawPathInfo req <> W.rawQueryString req


sproxy :: ByteString -> Database -> HashMap Text OAuth2Client -> [(Pattern, BackendConf, BE.Manager)] -> W.Application
sproxy key db oa2 backends = logException $ \req resp -> do
  Log.debug $ "sproxy <<< " ++ showReq req
  case requestDomain req of
    Nothing -> badRequest "missing host" req resp
    Just domain ->
      case find (\(p, _, _) -> match p (unpack domain)) backends of
        Nothing -> notFound "backend" req resp
        Just (_, be, mgr) -> do
          let cookieName = pack $ beCookieName be
              cookieDomain = pack <$> beCookieDomain be
          case W.pathInfo req of
            ["robots.txt"] -> get robots req resp
            (".sproxy":proxy) ->
              case proxy of

                ["logout"] -> get (logout key cookieName cookieDomain) req resp

                ["oauth2", provider] ->
                    case HM.lookup provider oa2 of
                      Nothing -> notFound "OAuth2 provider" req resp
                      Just oa2c -> get (oauth2callback key db (provider, oa2c) be) req resp

                ["access"] -> do
                  now <- Just <$> epochTime
                  case extractCookie key now cookieName req of
                    Nothing -> authenticationRequired key oa2 req resp
                    Just (authCookie, _) -> post (checkAccess db authCookie) req resp

                _ -> notFound "proxy" req resp

            _ -> do
              now <- Just <$> epochTime
              case extractCookie key now cookieName req of
                Nothing -> authenticationRequired key oa2 req resp
                Just cs@(authCookie, _) ->
                  authorize db cs req >>= \case
                    Nothing   -> forbidden authCookie req resp
                    Just req' -> forward mgr req' resp


robots :: W.Application
robots _ resp = resp $
  W.responseLBS ok200 [(hContentType, "text/plain; charset=utf-8")]
  "User-agent: *\nDisallow: /"


oauth2callback :: ByteString -> Database -> (Text, OAuth2Client) -> BackendConf -> W.Application
oauth2callback key db (provider, oa2c) be req resp =
  case param "code" of
    Nothing   -> badRequest "missing auth code" req resp
    Just code -> 
      case param "state" of
        Nothing    -> badRequest "missing auth state" req resp
        Just state ->
          case State.decode key state of
            Left msg   -> badRequest ("invalid state: " ++ msg) req resp
            Right path -> do
              au <- oauth2Authenticate oa2c code (redirectURL req provider)
              let email = getEmail au
              Log.info $ "login " ++ show email ++ " by " ++ show provider
              exists <- userExists db email
              if exists then authenticate key be au path req resp
                        else userNotFound au req resp
  where
    param p = do
      (_, v) <- find ((==) p . fst) $ W.queryString req
      v


-- XXX: RFC6265: the user agent MUST NOT attach more than one Cookie header field
extractCookie :: ByteString -> Maybe CTime -> ByteString -> W.Request -> Maybe (AuthCookie, Cookies)
extractCookie key now name req = do
  (_, cookies)   <- find ((==) hCookie . fst) $ W.requestHeaders req
  (auth, others) <- discriminate cookies
  case cookieDecode key auth of
    Left _ -> Nothing
    Right cookie -> if maybe True (acExpiry cookie >) now
      then Just (cookie, others) else Nothing
  where discriminate cs =
          case partition ((==) name . fst) $ parseCookies cs of
            ((_, x):_, xs) -> Just (x, xs)
            _              -> Nothing


authenticate :: ByteString -> BackendConf -> AuthUser -> ByteString -> W.Application
authenticate key be user path req resp = do
  now <- epochTime
  let domain = pack <$> beCookieDomain be
      expiry = now + CTime (beCookieMaxAge be)
      authCookie = AuthCookie { acUser = user, acExpiry = expiry }
      cookie = WC.def {
        WC.setCookieName = pack $ beCookieName be
      , WC.setCookieHttpOnly = True
      , WC.setCookiePath = Just "/"
      , WC.setCookieSameSite = Nothing
      , WC.setCookieSecure = True
      , WC.setCookieValue = cookieEncode key authCookie
      , WC.setCookieDomain = domain
      , WC.setCookieExpires = Just . posixSecondsToUTCTime . realToFrac $ expiry
      }
  resp $ W.responseLBS seeOther303 [
           (hLocation, "https://" <> fromJust (W.requestHeaderHost req) <> path)
         , ("Set-Cookie", toByteString $ WC.renderSetCookie cookie)
         ] ""


authorize :: Database -> (AuthCookie, Cookies) -> W.Request -> IO (Maybe W.Request)
authorize db (authCookie, otherCookies) req = do
  let
    user       = acUser authCookie
    domain     = decodeUtf8 . fromJust $ requestDomain req
    email      = getEmail user
    emailUtf8  = getEmailUtf8 user
    familyUtf8 = getFamilyNameUtf8 user
    givenUtf8  = getGivenNameUtf8 user
    method     = decodeUtf8 $ W.requestMethod req
    path       = decodeUtf8 $ W.rawPathInfo req
  grps <- userGroups db email domain path method
  if null grps then return Nothing
  else do
    ip <- pack . fromJust . fst <$> getNameInfo [NI_NUMERICHOST] True False (W.remoteHost req)
    return . Just $ req {
    W.requestHeaders = toList $
      insert "From" emailUtf8 $
      insert "X-Groups" (BS.intercalate "," $ encodeUtf8 <$> grps) $
      insert "X-Given-Name" givenUtf8 $
      insert "X-Family-Name" familyUtf8 $
      insert "X-Forwarded-Proto" "https" $
      insertWith (flip combine) "X-Forwarded-For" ip $
      setCookies otherCookies $
      fromListWith combine $ W.requestHeaders req
  }
  where
    combine a b = a <> "," <> b
    setCookies [] = delete hCookie
    setCookies cs = insert hCookie (toByteString . renderCookies $ cs)


checkAccess :: Database -> AuthCookie -> W.Application
checkAccess db authCookie req resp = do
  let email = getEmail . acUser $ authCookie
      domain = decodeUtf8 . fromJust $ requestDomain req
  body <- W.strictRequestBody req
  case JSON.eitherDecode' body of
    Left err -> badRequest err req resp
    Right inq -> do
      Log.debug $ "access <<< " ++ show inq
      tags <- userAccess db email domain inq
      Log.debug $ "access >>> " ++ show tags
      resp $ W.responseLBS ok200 [(hContentType, "application/json")] (JSON.encode tags)


-- XXX If something seems strange, think about HTTP/1.1 <-> HTTP/1.0.
-- FIXME For HTTP/1.0 backends we might need an option
-- FIXME in config file. HTTP Client does HTTP/1.1 by default.
forward :: BE.Manager -> W.Application
forward mgr req resp = do
  let beReq = BE.defaultRequest
        { BE.method = W.requestMethod req
        , BE.path = W.rawPathInfo req
        , BE.queryString = W.rawQueryString req
        , BE.requestHeaders = modifyRequestHeaders $ W.requestHeaders req
        , BE.redirectCount = 0
        , BE.decompress = const False
        , BE.requestBody = case W.requestBodyLength req of
            W.ChunkedBody   -> requestBodySourceChunkedIO (sourceRequestBody req)
            W.KnownLength l -> requestBodySourceIO (fromIntegral l) (sourceRequestBody req)
        }
      msg = unpack (BE.method beReq <> " " <> BE.path beReq <> BE.queryString beReq)
  Log.debug $ "BACKEND <<< " ++ msg ++ " " ++ show (BE.requestHeaders beReq)
  BE.withResponse beReq mgr $ \res -> do
        let status = BE.responseStatus res
            headers = BE.responseHeaders res
            body = mapOutput (Chunk . fromByteString) . bodyReaderSource $ BE.responseBody res
            logging = if statusCode status `elem` [ 400, 500 ] then
                      Log.warn else Log.debug
        logging $ "BACKEND >>> " ++ show (statusCode status) ++ " on " ++ msg ++ " " ++ show headers ++ "\n"
        resp $ responseSource status (modifyResponseHeaders headers) body


modifyRequestHeaders :: RequestHeaders -> RequestHeaders
modifyRequestHeaders = filter (\(n, _) -> n `notElem` ban)
  where
    ban =
      [
        hConnection
      , hContentLength    -- XXX This is set automtically before sending request to backend
      , hTransferEncoding -- XXX Likewise
      ]


modifyResponseHeaders :: ResponseHeaders -> ResponseHeaders
modifyResponseHeaders = filter (\(n, _) -> n `notElem` ban)
  where
    ban =
      [
        hConnection
      -- XXX WAI docs say we MUST NOT add (keep) Content-Length, Content-Range, and Transfer-Encoding,
      -- XXX but we use streaming body, which may add Transfer-Encoding only.
      -- XXX Thus we keep Content-* headers.
      , hTransferEncoding
      ]


authenticationRequired :: ByteString -> HashMap Text OAuth2Client -> W.Application
authenticationRequired key oa2 req resp = do
  Log.info $ "511 Unauthenticated: " ++ showReq req
  resp $ W.responseLBS networkAuthenticationRequired511 [(hContentType, "text/html; charset=utf-8")] page
  where
    path = if W.requestMethod req == methodGet
           then W.rawPathInfo req <> W.rawQueryString req
           else "/"
    state = State.encode key path
    authLink :: Text -> OAuth2Client -> ByteString -> ByteString
    authLink provider oa2c html = 
      let u = oauth2AuthorizeURL oa2c state (redirectURL req provider)
          d = pack $ oauth2Description oa2c
      in [qc|{html}<p><a href="{u}">Authenticate with {d}</a></p>|]
    authHtml = foldrWithKey authLink "" oa2
    page = fromStrict [qc|
<!DOCTYPE html>
<html lang="en">
  <head>
    <meta charset="utf-8">
    <title>Authentication required</title>
  </head>
  <body style="text-align:center;">
  <h1>Authentication required</h1>
  {authHtml}
  </body>
</html>
|]


forbidden :: AuthCookie -> W.Application
forbidden ac req resp = do
  Log.info $ "403 Forbidden: " ++ show email ++ ": " ++ showReq req
  resp $ W.responseLBS forbidden403 [(hContentType, "text/html; charset=utf-8")] page
  where
    email = getEmailUtf8 . acUser $ ac
    page = fromStrict [qc|
<!DOCTYPE html>
<html lang="en">
  <head>
    <meta charset="utf-8">
    <title>Access Denied</title>
  </head>
  <body>
  <h1>Access Denied</h1>
    <p>You are currently logged in as <strong>{email}</strong></p>
    <p><a href="/.sproxy/logout">Logout</a></p>
  </body>
</html>
|]


userNotFound :: AuthUser -> W.Application
userNotFound au _ resp = do
  Log.info $ "404 User not found: " ++ show email
  resp $ W.responseLBS notFound404 [(hContentType, "text/html; charset=utf-8")] page
  where
    email = getEmailUtf8 au
    page = fromStrict [qc|
<!DOCTYPE html>
<html lang="en">
  <head>
    <meta charset="utf-8">
    <title>Access Denied</title>
  </head>
  <body>
  <h1>Access Denied</h1>
    <p>You are not allowed to login as <strong>{email}</strong></p>
    <p><a href="/">Main page</a></p>
  </body>
</html>
|]


logout :: ByteString -> ByteString -> Maybe ByteString -> W.Application
logout key cookieName cookieDomain req resp = do
  let host = fromJust $ W.requestHeaderHost req
  case extractCookie key Nothing cookieName req of
    Nothing -> resp $ W.responseLBS found302 [ (hLocation, "https://" <> host) ] ""
    Just _  -> do
        let cookie = WC.def {
              WC.setCookieName = cookieName
            , WC.setCookieHttpOnly = True
            , WC.setCookiePath = Just "/"
            , WC.setCookieSameSite = Just WC.sameSiteStrict
            , WC.setCookieSecure = True
            , WC.setCookieValue = "goodbye"
            , WC.setCookieDomain = cookieDomain
            , WC.setCookieExpires = Just . posixSecondsToUTCTime . realToFrac $ CTime 0
            }
        resp $ W.responseLBS found302 [
                 (hLocation, "https://" <> host)
               , ("Set-Cookie", toByteString $ WC.renderSetCookie cookie)
               ] ""


badRequest ::String -> W.Application
badRequest msg req resp = do
  Log.warn $ "400 Bad Request (" ++ msg ++ "): " ++ showReq req
  resp $ W.responseLBS badRequest400 [] "Bad Request"


notFound ::String -> W.Application
notFound msg req resp = do
  Log.warn $ "404 Not Found (" ++ msg ++ "): " ++ showReq req
  resp $ W.responseLBS notFound404 [] "Not Found"


logException :: W.Middleware
logException app req resp =
  catches (app req resp) [
    Handler internalError
  ]
  where
    internalError :: SomeException -> IO W.ResponseReceived
    internalError = response internalServerError500

    response :: Exception e => Status -> e -> IO W.ResponseReceived
    response st e = do
      Log.error $ show (statusCode st) ++ " " ++ unpack (statusMessage st)
                ++ ": " ++ displayException e ++ " on " ++ showReq req
      resp $ W.responseLBS st [(hContentType, "text/plain")] (fromStrict $ statusMessage st)



get :: W.Middleware
get app req resp
  | W.requestMethod req == methodGet = app req resp
  | otherwise = do
    Log.warn $ "405 Method Not Allowed: " ++ showReq req
    resp $ W.responseLBS methodNotAllowed405 [("Allow", "GET")] "Method Not Allowed"


post :: W.Middleware
post app req resp
  | W.requestMethod req == methodPost = app req resp
  | otherwise = do
    Log.warn $ "405 Method Not Allowed: " ++ showReq req
    resp $ W.responseLBS methodNotAllowed405 [("Allow", "POST")] "Method Not Allowed"


redirectURL :: W.Request -> Text -> ByteString
redirectURL req provider =
  "https://" <> fromJust (W.requestHeaderHost req)
             <> "/.sproxy/oauth2/" <> encodeUtf8 provider


requestDomain :: W.Request -> Maybe ByteString
requestDomain req = do
  h <- W.requestHeaderHost req
  return . fst . BS.break (== _colon) $ h


-- XXX: make sure not to reveal the cookie, which can be valid (!)
showReq :: W.Request -> String
showReq req = 
    unpack ( W.requestMethod req <> " "
           <> fromMaybe "<no host>" (W.requestHeaderHost req)
           <> W.rawPathInfo req <> W.rawQueryString req <> " " )
    ++ show (W.httpVersion req) ++ " "
    ++ show (fromMaybe "-" $ W.requestHeaderReferer req) ++ " "
    ++ show (fromMaybe "-" $ W.requestHeaderUserAgent req)
    ++ " from " ++ show (W.remoteHost req)