Skip to content

Commit 667855b

Browse files
committed
WIP: Major start on Parsec!
1 parent 72a2e1f commit 667855b

File tree

7 files changed

+1858
-0
lines changed

7 files changed

+1858
-0
lines changed

src/std/parsec-test.ss

Lines changed: 320 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,320 @@
1+
;;; -*- Gerbil -*-
2+
;;; (C) me at drewc.ca
3+
;;; :std/parsec unit-tests
4+
5+
(import :std/test
6+
:std/error
7+
:std/interactive
8+
:srfi/13
9+
:std/parser/stream
10+
:std/parser/base
11+
:std/monad/interface
12+
;;:std/monad/error
13+
:std/monad/list
14+
:std/monad/syntax
15+
"instance"
16+
"parsec/stream"
17+
"parsec/transformer"
18+
"parsec/combinators"
19+
"parsec/char"
20+
"parsec/syntax"
21+
(only-in :std/sugar hash try)
22+
(only-in :gerbil/core error-object? with-catch))
23+
(export parsec-test)
24+
(begin-foreign (include "~~lib/_gambit#.scm"))
25+
(defsyntax (test-inline stx)
26+
(syntax-case stx (>)
27+
((_ test-case: name rest ...)
28+
#'(test-case name (test-inline rest ...)))
29+
((_ > form > rest ...)
30+
#'(begin (displayln "... " 'form) form (test-inline > rest ...)))
31+
((_ > test result rest ...)
32+
#'(begin (check test => 'result) (test-inline rest ...)))
33+
((_) #!void)))
34+
35+
(set-test-verbose! #t)
36+
37+
(def parsec-test
38+
(test-suite "Test :std/parsec"
39+
(test-inline
40+
test-case: "Char Reader tests"
41+
> (def rdr (open-input-string "42!"))
42+
> (CharReader-peek-char rdr)
43+
#\4
44+
> (using (rdr : CharReader)
45+
(let ((one (rdr.read-char))
46+
(two (rdr.read-char)))
47+
(string->number (list->string [one two]))))
48+
42
49+
> (CharReader-read-char rdr)
50+
#\!
51+
> (CharReader-read-char rdr)
52+
#!eof
53+
)
54+
55+
(test-inline
56+
test-case: "Location tests"
57+
> (interface (testLoc CharReader Location))
58+
> (def rdr (open-input-string "42\n!"))
59+
> (using (l rdr : Location) (location-line (l.location)))
60+
0
61+
> (testLoc-read-char rdr)
62+
#\4
63+
> (using ((r rdr : testLoc)
64+
(loc (r.location) : location))
65+
loc.xoff)
66+
1
67+
> (using ((r rdr : testLoc)
68+
(loc (r.location) : location))
69+
(let* ((a (r.read-char))
70+
(l0 loc.line)
71+
(off1 (r.xoff))
72+
(c2 (location-col (r.location)))
73+
(b (r.read-char))
74+
(l1 (location-line (r.location)))
75+
(c (r.peek-char))
76+
(_ (r.read-char))
77+
(off2 (r.xoff))
78+
(eof (r.read-char))
79+
(off3 (r.xoff)))
80+
81+
[a off1 l0 c2 b l1 c off2 eof off3]))
82+
(#\2 2 0 2 #\newline 1 #\! 4 #!eof 4)
83+
84+
)
85+
(test-inline
86+
test-case: "Token tests"
87+
> (interface (testTok Token Location))
88+
> (def port (open-input-string "(def ltuae 42)"))
89+
90+
> (testTok-xoff port)
91+
0
92+
> (testTok-token port char-alphabetic?)
93+
#f
94+
> (testTok-xoff port)
95+
0
96+
> (testTok-token port (? (or char-alphabetic? char-numeric?)))
97+
#f
98+
> (testTok-token port (? (not (or char-alphabetic? char-numeric?))))
99+
#\(
100+
> (testTok-xoff port)
101+
1
102+
)
103+
104+
105+
(test-inline
106+
test-case: "Stream tests"
107+
> (def port (open-input-string "42\n is the answer"))
108+
> (def stream (make-buffered-char-reader port))
109+
> [(Location-xoff port) (Location-xoff stream)]
110+
(0 0)
111+
> (location-col (Location-location stream))
112+
0
113+
> (CharReader-peek-char stream)
114+
#\4
115+
> [(Location-xoff port) (Location-xoff stream)]
116+
(0 0)
117+
> (CharReader-read-char stream)
118+
#\4
119+
> [(Location-xoff port) (Location-xoff stream)]
120+
(1 1)
121+
> (BufferedCharReader-put-back stream #\4)
122+
> [(Location-xoff port) (Location-xoff stream)]
123+
(1 0)
124+
125+
> (Token-token stream)
126+
#\4
127+
> (Token-token stream char-numeric?)
128+
#\2
129+
> [(Location-xoff port) (Location-xoff stream)]
130+
(2 2)
131+
> (Token-token stream)
132+
#\newline
133+
> (using (stream :- buffered-char-reader) stream.lines)
134+
(3)
135+
> (Token-token stream)
136+
#\space
137+
> (location-line (Location-location stream))
138+
1
139+
> (location-col (Location-location stream))
140+
1
141+
> (Token-token stream)
142+
#\i
143+
> (location-col (Location-location stream))
144+
2
145+
> (using (stream : BufferedCharReader)
146+
(stream.put-back #\f)
147+
(stream.put-back #\f))
148+
> (location-line (Location-location stream))
149+
0
150+
> (location-col (Location-location stream))
151+
1
152+
153+
)
154+
(test-inline
155+
test-case: "Lookahead Stream tests"
156+
> (def port (open-input-string "42\n is the answer"))
157+
> (def bstream (make-buffered-char-reader port))
158+
> (def stream (make-lookahead-char-stream bstream))
159+
160+
> (lookahead-char-stream-lo stream)
161+
0
162+
> (buffered-char-reader-hi bstream)
163+
0
164+
> (Token-token stream)
165+
#\4
166+
> (Token-token (make-lookahead-char-stream bstream))
167+
#\4
168+
> (lookahead-char-stream-lo stream)
169+
1
170+
> (Token-token stream)
171+
#\2
172+
> (Token-token (make-lookahead-char-stream bstream))
173+
#\4
174+
> (Location-xoff stream)
175+
2
176+
> (Location-xoff bstream)
177+
0
178+
> (Token-token bstream)
179+
#\4
180+
)
181+
(test-inline
182+
test-case: "ParsecT tests"
183+
> (defrule (use p body ...) (using (p (make-parsecT) : ParsecT) body ...))
184+
> (with ([[ret . state]] (use p (p.run (p.return 42) "")))
185+
(check-eqv? ret 42)
186+
(Location-xoff state))
187+
0
188+
> (map car (use p (p.run (p.return 42) "as")))
189+
(42)
190+
> (map car (use p (p.run (p.plus (p.return 42) (p.return 42)) "42")))
191+
(42 42)
192+
> (map car (use p (p.run (p.or (p.return 42) (p.return 42)) "42")))
193+
(42)
194+
> (caar (use p (p.run (p.or (p.return 42) (p.return 43)) "")))
195+
42
196+
> (caar (use p (p.run (p.or (p.>> (p.return 42) (p.fail)) (p.return 43)) "")))
197+
43
198+
> (caar (use p (p.run (p.or (p.read-char) (p.return 43)) "heh")))
199+
#\h
200+
> (use p (p.run (p.or (p.>> (p.read-char) (p.fail)) (p.return 43)) "heh"))
201+
()
202+
203+
)
204+
205+
(test-inline
206+
test-case: "Combinator tests"
207+
> (def current-parser (make-parameter (ParsecCombinators (make-parsecT))))
208+
> (defrule (parse id body ...) (using (id (current-parser) :- ParsecCombinators) body ...))
209+
> (def (test-or a b input)
210+
(parse _ (_.run (_.or a b) input)))
211+
> (caar (parse _ (test-or (_.any-token) (_.return 42) "asdf")))
212+
#\a
213+
> (caar (parse _ (test-or (_.satisfy char-numeric?) (_.return 42) "asdf")))
214+
42
215+
> (parse _ (test-or (du _ c <- (_.any-token)
216+
(if (char-numeric? c) (_.return c) (_.zero)))
217+
(_.return 42)
218+
"fourty-two"))
219+
() ;; null is one message that represent failure and what zero does by
220+
;; default
221+
;> (def current-parser (make-parameter (ParsecCombinators (make-parsecT))))
222+
> (defrule (u id body ...) (using (id (current-parser) :- ParsecCombinators) body ...))
223+
> (caar ((u t (let (la #f)
224+
(t.or
225+
(t.try (du t second <- (t.>> (t.any-token) (t.any-token))
226+
(begin (set! la second)(t.throw "This Failed"))))
227+
(du t first <- (t.any-token)
228+
(t.return [la first]))))) (open-input-string "asdf")))
229+
(#\s #\a)
230+
> (def token
231+
(du (_ (make-parsecT) : ParsecChar)
232+
c <- (_.letter)
233+
cs <- (_.many (_.or (_.letter) (_.char #\_)))
234+
(_.return (list->string (cons c cs)))))
235+
236+
> (caar (parse _ (_.run token "foo_bar bad")))
237+
"foo_bar"
238+
> (caar (parse _ (_.run token "x+y")))
239+
"x"
240+
241+
242+
243+
> (caar (parse _ (_.run (_.many (_.any-token)) "asd")))
244+
(#\a #\s #\d)
245+
246+
> (caar (parse _ (_.run (_.many1 (_.any-token)) "asd")))
247+
(#\a #\s #\d)
248+
249+
> (caar (parse _ (_.run (_.many-till (_.any-token) (_.satisfy (cut char=? <> #\:))) "asd:")))
250+
(#\a #\s #\d)
251+
> (u parse (caar (parse.run (parse.any-token) "a")))
252+
#\a
253+
> (u parse (parse.run (parse.any-token) ""))
254+
()
255+
> (u parse (caar (parse.run (parse.or (parse.any-token) (parse.return 42)) "")))
256+
42
257+
258+
259+
> (caar (parse _ (_.run (_.satisfy char-numeric?) "42")))
260+
#\4
261+
> (parse _ (_.run (_.satisfy char-numeric?) "fourtwo"))
262+
()
263+
264+
265+
266+
)
267+
268+
(test-inline
269+
test-case: "Dot tests"
270+
> (caar (do-parse (.run (.return 42) "")))
271+
42
272+
> (def-parse FourTwo (.char #\4) (.char #\2) (.return 42))
273+
> (caar (do-parse (.run FourTwo "42")))
274+
42
275+
276+
)
277+
(test-inline
278+
test-case: "Character Parsing tests"
279+
> (caar (do-parse (.run (.string "asd") "asdfjkl;")))
280+
"asd"
281+
> (caar (do-parse (.run (.string "asd" char-ci=?) "AsDfjkl;")))
282+
"AsD"
283+
284+
)
285+
(test-inline
286+
test-case: "Org Syntax Parsing tests"
287+
> (def-parse EOL (.or (.eof) (.newline)))
288+
289+
> (def-parse KEY
290+
(.>> (.string "#+")
291+
(.many-till
292+
(.satisfy (? (not char-whitespace?)))
293+
(.string ": "))))
294+
> (def-parse VALUE (.many-till (.any-token) EOL))
295+
296+
> (def-parse KEYWORD
297+
key <- (.liftM list->string KEY)
298+
value <- (.liftM list->string VALUE)
299+
(.return ['keyword key: key value: value]))
300+
301+
> (run-parser KEYWORD "#+TITLE: Org Mode keyword!")
302+
(keyword key: "TITLE" value: "Org Mode keyword!")
303+
304+
305+
306+
307+
308+
309+
310+
311+
312+
313+
)
314+
315+
316+
317+
318+
319+
320+
))

0 commit comments

Comments
 (0)