bin/ansible-inventory: Turn debugging on.
[distorted-ansible] / bin / ansible-inventory
1 #! /usr/bin/cl-launch -X --
2 ;;; -*-lisp-*-
3
4 (cl:defpackage #:ansible-inventory
5 (:use #:common-lisp)
6 (:import-from #:cl-launch #:*arguments*))
7
8 (in-package #:ansible-inventory)
9
10 (declaim (optimize debug))
11
12 ;;;--------------------------------------------------------------------------
13 ;;; General utilities.
14
15 (defun compose (&rest funcs)
16 (reduce (lambda (f g)
17 (lambda (&rest args) (multiple-value-call g (apply f args))))
18 funcs :initial-value #'values))
19
20 ;;;--------------------------------------------------------------------------
21 ;;; JSON machinery.
22
23 (defvar *print-json-comma*)
24
25 (defun print-json-itemstart ()
26 (cond (*print-json-comma*
27 (princ ", ")
28 (pprint-newline :linear))
29 (t
30 (setf *print-json-comma* t))))
31
32 (defun print-json-map* (thunk)
33 (print-json-itemstart)
34 (princ "{ ")
35 (pprint-indent :block 2)
36 (pprint-newline :linear)
37 (pprint-logical-block (*standard-output* nil)
38 (let ((*print-json-comma* nil)) (funcall thunk)))
39 (princ " ")
40 (pprint-indent :block 0)
41 (pprint-newline :linear)
42 (princ "}"))
43
44 (defmacro print-json-map (&body body)
45 `(print-json-map* (lambda () ,@body)))
46
47 (defun print-json-list* (thunk)
48 (print-json-itemstart)
49 (princ "[")
50 (pprint-indent :block 2)
51 (pprint-newline :linear)
52 (pprint-logical-block (*standard-output* nil)
53 (let ((*print-json-comma* nil)) (funcall thunk)))
54 (pprint-indent :block 0)
55 (pprint-newline :linear)
56 (princ "]"))
57
58 (defmacro print-json-list (&body body)
59 `(print-json-list* (lambda () ,@body)))
60
61 (defun print-json-mapping* (label thunk)
62 (print-json-itemstart)
63 (pprint-logical-block (*standard-output* nil)
64 (let ((*print-json-comma* nil))
65 (print-json-simple label))
66 (princ ": ")
67 (pprint-newline :miser)
68 (let ((*print-json-comma* nil))
69 (funcall thunk))))
70
71 (defmacro print-json-mapping (label &body body)
72 `(print-json-mapping* ,label (lambda () ,@body)))
73
74 (defun print-json-simple (value)
75 (typecase value
76 (list (print-json-list (dolist (i value) (print-json-simple i))))
77 (hash-table (print-json-map (maphash (lambda (k v)
78 (print-json-mapping k
79 (print-json-simple v)))
80 value)))
81 (t
82 (print-json-itemstart)
83 (etypecase value
84 (integer (format t "~A" value))
85 (float (format t "~G" value))
86 (rational (format t "~G" (float value 0.0d0)))
87 (string (format t "~S" value))
88 ((eql t) (princ "true"))
89 ((eql nil) (princ "false"))
90 ((eql :undefined) (princ "undefined"))
91 (symbol (format t "~S" (string-downcase value)))))))
92
93 (defun print-json* (thunk)
94 (let ((*print-json-comma* nil))
95 (pprint-logical-block (*standard-output* nil)
96 (funcall thunk))
97 (terpri)))
98
99 (defmacro print-json (&body body)
100 `(print-json* (lambda () ,@body)))
101
102 ;;;--------------------------------------------------------------------------
103 ;;; Host definitions.
104
105 (defvar *hosts* (make-hash-table))
106
107 (export 'add-host)
108 (defun addhost (name alist)
109 (setf (gethash name *hosts*) alist))
110
111 (export 'defhost)
112 (defmacro defhost (name &body alist)
113 `(progn (addhost ',name ',alist) ',name))
114
115 (export 'host-plist)
116 (defun host-plist (name)
117 (multiple-value-bind (plist foundp) (gethash name *hosts*)
118 (unless foundp (error "Host ~S not found" name))
119 plist))
120
121 (export 'hostprop)
122 (defun hostprop (name prop &optional default)
123 (multiple-value-bind (found-name value tail)
124 (get-properties (host-plist name) (list prop))
125 (declare (ignore found-name))
126 (if tail
127 (values value t)
128 (values default nil))))
129 (defun (setf hostprop) (value name prop &optional default)
130 (declare (ignore default))
131 (let ((plist (host-plist name)))
132 (multiple-value-bind (found-name found-value tail)
133 (get-properties plist (list prop))
134 (declare (ignore found-name found-value))
135 (if tail
136 (setf (cadr tail) value)
137 (setf (gethash name *hosts*)
138 (cons prop (cons value plist))))
139 value)))
140
141 (export 'hostprop-default)
142 (defun hostprop-default (host prop value)
143 (multiple-value-bind (found-value foundp) (hostprop host prop)
144 (declare (ignore found-value))
145 (unless foundp (setf (hostprop host prop) value))))
146
147 (export 'hostpropp)
148 (defun hostpropp (host prop)
149 (multiple-value-bind (value foundp) (hostprop host prop)
150 (declare (ignore value))
151 foundp))
152
153 (export 'maphosts)
154 (defun maphosts (func)
155 (maphash (lambda (name plist)
156 (declare (ignore plist))
157 (funcall func name))
158 *hosts*))
159
160 (export 'dohosts)
161 (defmacro dohosts ((hostvar &optional valueform) &body body)
162 `(block nil (maphosts (lambda (,hostvar) ,@body)) ,valueform))
163
164 ;;;--------------------------------------------------------------------------
165 ;;; Group definitions.
166
167 (defvar *groups* nil)
168
169 (export 'add-group)
170 (defun add-group (name type func)
171 (let* ((found (assoc name *groups*))
172 (list (ecase type
173 (:predicate
174 (let ((list nil))
175 (dohosts (host list)
176 (when (funcall func host) (push host list)))))
177 (:list
178 (funcall func)))))
179 (if found
180 (setf (cdr found) list)
181 (push (cons name list) *groups*))))
182
183 (export 'defgroup)
184 (defmacro defgroup (name type args &body body)
185 `(progn (add-group ',name ,type
186 ,(ecase type
187 (:predicate
188 (destructuring-bind (hostvar) args
189 `(lambda (,hostvar) ,@body)))
190 (:list
191 (destructuring-bind () args
192 `(lambda () ,@body)))))
193 ',name))
194
195 ;;;--------------------------------------------------------------------------
196 ;;; Post-processing hooks.
197
198 (defstruct hook-entry
199 prio
200 func)
201
202 (export '(prio-props prio-groups))
203 (defconstant prio-props 10)
204 (defconstant prio-groups 20)
205
206 (defvar *hostproc-hooks* nil)
207
208 (export 'addhook)
209 (defun addhook (prio func)
210 (push (make-hook-entry :prio prio :func func) *hostproc-hooks*))
211
212 (export 'defhook)
213 (defmacro defhook ((prio) &body body)
214 `(addhook ,prio (lambda () ,@body)))
215
216 ;;;--------------------------------------------------------------------------
217 ;;; Read the input file and hook definitions.
218
219 (defvar *progname*
220 #.(or *compile-file-pathname* *load-pathname*))
221
222 (let ((pkg (make-package "ANSIBLE-INVENTORY-USER"
223 :use '("CL" "ANSIBLE-INVENTORY")))
224 (args *arguments*))
225 (loop (let* ((arg (pop args))
226 (len (length arg)))
227 (cond ((string= arg "--") (return))
228 ((string= arg "-") (push arg args) (return))
229 ((and (plusp (length arg))
230 (char= (char arg 0) #\-))
231 (do ((i 1 (1+ i)))
232 ((>= i len))
233 (flet ((getarg ()
234 (cond ((< (1+ i) len)
235 (prog1 (subseq arg (1+ i))
236 (setf i len)))
237 (args
238 (pop args))
239 (t
240 (error "missing argument"))))))
241 (case (char arg i)
242 (#\h (format t "usage: ~A FILE ...~%"
243 (pathname-name *progname*)))
244 (t (error "unknown option `-~A'" (char arg i))))))
245 (t (push arg args) (return)))))
246 (format t ";; remaining args = ~S~%" args)
247 (dolist (arg args)
248 (let ((*package* pkg))
249 (load arg :verbose nil))))
250
251 ;;;--------------------------------------------------------------------------
252 ;;; Run the hooks.
253
254 (setf *hostproc-hooks* (sort *hostproc-hooks* #'< :key #'hook-entry-prio))
255 (mapc (compose #'hook-entry-func #'funcall) *hostproc-hooks*)
256
257 ;;;--------------------------------------------------------------------------
258 ;;; Output the definitions.
259
260 (setf *print-right-margin* 77)
261 (print-json
262 (print-json-map
263 (print-json-mapping "all"
264 (print-json-list (maphosts #'print-json-simple)))
265 (dolist (assoc *groups*)
266 (print-json-mapping (car assoc)
267 (print-json-list
268 (mapc #'print-json-simple (cdr assoc)))))
269 (print-json-mapping "_meta"
270 (print-json-map
271 (print-json-mapping "hostvars"
272 (print-json-map
273 (maphash (lambda (host plist)
274 (print-json-mapping host
275 (print-json-map
276 (do ((plist plist (cddr plist)))
277 ((endp plist))
278 (print-json-mapping (car plist)
279 (print-json-simple (cadr plist)))))))
280 *hosts*)))))))
281
282 ;;;----- That's all, folks --------------------------------------------------