File: responders.rkt

package info (click to toggle)
racket 7.9%2Bdfsg1-2
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 178,684 kB
  • sloc: ansic: 282,112; lisp: 234,887; pascal: 70,954; sh: 27,112; asm: 16,268; makefile: 4,613; cpp: 2,715; ada: 1,681; javascript: 1,244; cs: 879; exp: 499; csh: 422; python: 274; xml: 106; perl: 104
file content (134 lines) | stat: -rw-r--r-- 5,203 bytes parent folder | download | duplicates (8)
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
#lang racket/base
(require racket/contract
         (for-syntax racket/base)
         racket/runtime-path
         net/url
         web-server/private/xexpr
         web-server/http/xexpr
         web-server/http/response-structs
         web-server/http/request-structs)

(define (format-stack-trace trace)
  `(pre
    ,@(for/list ([item (in-list trace)])
        (format "~a at:\n  ~a\n"
                (if (car item)
                    (car item)
                    "<unknown procedure>")
                (if (cdr item)
                    (format "line ~a, column ~a, in file ~a"
                            (srcloc-line (cdr item))
                            (srcloc-column (cdr item))
                            (srcloc-source (cdr item)))
                    "<unknown location>")))))

(define-runtime-path default-error-style-sheet
  "../default-web-root/htdocs/error.css")

(define (pretty-exception-response url exn)
  (response/xexpr
   #:code 500
   #:message #"Internal Server Error"
   `(html
     (head
      (title "Servlet Error")
      (link ([rel "stylesheet"] [href "/error.css"])))
     (body
      (div ([class "section"])
           (div ([class "title"]) "Exception")
           (p
            "The application raised an exception with the message:"
            (pre ,(if (exn:pretty? exn)
                      (exn:pretty-xexpr exn)
                      (exn-message exn))))
           (p
            "Stack trace:"
            ,(format-stack-trace
              (continuation-mark-set->context (exn-continuation-marks exn)))))))))


; file-response : nat str str [(cons sym str) ...] -> response
; The server should still start without the files there, so the
; configuration tool still runs.  (Alternatively, find an work around.)
(define (file-response code short text-file . headers)
  (response/full code short
                 (current-seconds) TEXT/HTML-MIME-TYPE
                 headers
                 (list (read-file text-file))))

; servlet-loading-responder : url tst -> response
; This is slightly tricky since the (interesting) content comes from the exception.
(define (servlet-loading-responder url exn)
  ((error-display-handler)
   (format "Servlet (@ ~a) didn't load:\n~a\n" (url->string url) (exn-message exn))
   exn)
  (pretty-exception-response url exn))

; gen-servlet-not-found : str -> url -> response
(define (gen-servlet-not-found file-not-found-file)
  (lambda (url)
    (file-response 404 #"Servlet not found" file-not-found-file)))

; servlet-error-response : url exn -> response
(define (servlet-error-responder url exn)
  ((error-display-handler)
   (format "Servlet (@ ~a) exception:\n~a\n" (url->string url) (exn-message exn))
   exn)
  (pretty-exception-response url exn))

; gen-servlet-responder : str -> url tst -> response
(define (gen-servlet-responder servlet-error-file)
  (lambda (url exn)
    ((error-display-handler)
     (format "Servlet (@ ~a) exception:\n~e\n" (url->string url) (exn-message exn))
     exn)
    (file-response 500 #"Servlet error" servlet-error-file)))

; gen-servlets-refreshed : str -> -> response
(define (gen-servlets-refreshed servlet-refresh-file)
  (lambda ()
    (file-response 200 #"Servlet cache refreshed" servlet-refresh-file)))

; gen-passwords-refreshed : str -> -> response
(define (gen-passwords-refreshed password-refresh-file)
  (lambda ()
    (file-response 200 #"Passwords refreshed" password-refresh-file)))

; gen-authentication-responder : str -> url (cons sym str) -> response
(define (gen-authentication-responder access-denied-file)
  (lambda (uri recommended-header)
    (file-response 401 #"Authorization Required" access-denied-file
                   recommended-header)))

; gen-protocol-responder : str -> str -> response
(define (gen-protocol-responder protocol-file)
  (lambda (error-message)
    (file-response 400 #"Malformed Request" protocol-file)))

; gen-file-not-found-responder : str -> req -> response
(define (gen-file-not-found-responder file-not-found-file)
  (lambda (req)
    (file-response 404 #"File not found" file-not-found-file)))

; gen-collect-garbage-responder : str -> -> response
(define (gen-collect-garbage-responder file)
  (lambda ()
    (file-response 200 #"Garbage collected" file)))

; read-file : str -> str
(define (read-file path)
  (call-with-input-file path
    (lambda (in) (read-bytes (file-size path) in))))

(provide/contract
 [file-response ((natural-number/c bytes? path-string?) () #:rest (listof header?) . ->* . response?)]
 [servlet-loading-responder (url? exn? . -> . response?)]
 [gen-servlet-not-found (path-string? . -> . (url? . -> . response?))]
 [servlet-error-responder (url? exn? . -> . response?)]
 [gen-servlet-responder (path-string? . -> . (url? exn? . -> . response?))]
 [gen-servlets-refreshed (path-string? . -> . (-> response?))]
 [gen-passwords-refreshed (path-string? . -> . (-> response?))]
 [gen-authentication-responder (path-string? . -> . (url? header? . -> . response?))]
 [gen-protocol-responder (path-string? . -> . (url? . -> . response?))]
 [gen-file-not-found-responder (path-string? . -> . (request? . -> . response?))]
 [gen-collect-garbage-responder (path-string? . -> . (-> response?))])