-
Notifications
You must be signed in to change notification settings - Fork 0
/
mal.lisp
156 lines (126 loc) · 5.86 KB
/
mal.lisp
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
;;; mal.lisp - Compatability with MAL, implemented in lisp.
;; This is essentially prepended to any program the user tries to run,
;; and implements functions that are expected by any MAL implementation.
;;
;; More general functions can be found in stdlib.lisp.
;;
;; Traditionally we use `car` and `cdr` for accessing the first and rest
;; elements of a list. For readability it might be nice to vary that
(set! first (fn* (x:list)
"Return the first element of the specified list. This is an alias for 'car'."
(car x)))
(set! rest (fn* (x:list)
"Return all elements of the specified list, except the first. This is an alias for 'cdr'."
(cdr x)))
;; Some simple tests of numbers
(set! zero? (fn* (n)
"Return true if the number supplied as the first argument to this function is equal to zero."
(= n 0)))
(set! one? (fn* (n)
"Return true if the number supplied as the argument to this function is equal to one."
(= n 1)))
(set! even? (fn* (n)
"Return true if the number supplied as the argument to this function is even."
(zero? (% n 2))))
(set! odd? (fn* (n)
"Return true if the number supplied as the argument to this function is odd."
(! (even? n))))
;; is the given argument "true", or "false"?
(def! true? (fn* (arg)
"Return true if the argument supplied to this function is true."
(if (eq #t arg) true false)))
(def! false? (fn* (arg)
"Return true if the argument supplied to this function is false."
(if (eq #f arg) true false)))
;; Run an arbitrary series of statements, if the given condition is true.
;;
;; This is the more general/useful version of the "if2" macro, which
;; we demonstrate in mtest.lisp.
;;
;; Sample usage:
;;
;; (when (= 1 1) (print "OK") (print "Still OK") (print "final statement"))
;;
(defmacro! when (fn* (pred &rest)
"when is a macro which runs the specified body, providing the specified predicate is true. It is similar to an if-statement, however there is no provision for an 'else' clause, and the body specified may contain more than once expression to be evaluated."
`(if ~pred (do ~@rest))))
;;
;; If the specified predicate is true, then run the body.
;;
;; NOTE: This recurses, so it will eventually explode the stack.
;;
(defmacro! while (fn* (condition &body)
"while is a macro which repeatedly runs the specified body, while the condition returns a true-result"
(let* (inner-sym (gensym))
`(let* (~inner-sym (fn* ()
(if ~condition
(do
~@body
(~inner-sym)))))
(~inner-sym)))))
;;
;; cond is a useful thing to have.
;;
(defmacro! cond (fn* (&xs)
"cond is a macro which accepts a list of conditions and results, and returns the value of the first matching condition. It is similar in functionality to a C case-statement."
(if (> (length xs) 0)
(list 'if (first xs)
(if (> (length xs) 1)
(nth xs 1)
(error "An odd number of forms to (cond..)"))
(cons 'cond (rest (rest xs)))))))
;; A useful helper to apply a given function to each element of a list.
(set! apply (fn* (lst:list fun:function)
"Return the result of calling the specified function on every element in the given list"
(if (nil? lst)
()
(do
(fun (car lst))
(apply (cdr lst) fun)))))
;; Return the length of the given list.
(set! length (fn* (arg)
"Return the length of the supplied list. See-also strlen."
(if (list? arg)
(do
(if (nil? arg) 0
(inc (length (cdr arg)))))
0
)))
;; Alias to (length)
(set! count (fn* (arg)
"Return the length of the supplied list. This is an alias for (length)."
(length arg)))
;; Find the Nth item of a list
(set! nth (fn* (lst:list i:number)
"Return the Nth item of the specified list.
Note that offset starts from 0, rather than 1, for the first item."
(if (> i (length lst))
(error "Out of bounds on list-length")
(if (= 0 i)
(car lst)
(nth (cdr lst) (- i 1))))))
(set! map (fn* (xs:list f:function)
"Return a list with the contents of evaluating the given function on every item of the supplied list."
(if (nil? xs)
()
(cons (f (car xs)) (map (cdr xs) f)))))
;; This is required for our quote/quasiquote/unquote/splice-unquote handling
;;
;; Testing is hard, but
;;
;; (define lst (quote (b c))) ; b c
;; (print (quasiquote (a lst d))) ; (a lst d)
;; (print (quasiquote (a (unquote lst) d))) ; (a (b c) d)
;; (print (quasiquote (a (splice-unquote lst) d))) ; (a b c d)
;;
(set! concat (fn* (seq1 seq2)
"Join two lists"
(if (nil? seq1)
seq2
(cons (car seq1) (concat (cdr seq1) seq2)))))
;;
;; Read a file
;;
(def! load-file (fn* (filename)
"Load and execute the contents of the supplied filename."
(eval (join (list "(do " (slurp filename) "\nnil)")))))