CSV reader task entered
[CommonLispStat.git] / src / data / data-clos.lisp
blob00ffdfddfc4d2f005ca4debc6650801576757659
1 ;;; -*- mode: lisp -*-
3 ;;; Time-stamp: <2009-04-01 17:59:55 tony>
4 ;;; Creation: <2008-03-12 17:18:42 blindglobe@gmail.com>
5 ;;; File: data-clos.lisp
6 ;;; Author: AJ Rossini <blindglobe@gmail.com>
7 ;;; Copyright: (c)2008, AJ Rossini. BSD, LLGPL, or GPLv2, depending
8 ;;; on how it arrives.
10 ;;; Purpose: Data packaging and access for Common Lisp Statistics.
11 ;;; This redoes data storage structures in a CLOS based
12 ;;; framework.
13 ;;;
15 ;;; What is this talk of 'release'? Klingons do not make software
16 ;;; 'releases'. Our software 'escapes', leaving a bloody trail of
17 ;;; designers and quality assurance people in its wake.
19 (in-package :lisp-stat-data-clos)
21 ;;; No real basis for work, there is a bit of new-ness and R-ness to
22 ;;; this work. In particular, the notion of relation is key and
23 ;;; integral to the analysis. Tables are related and matched vectors,
24 ;;; for example. "column" vectors are related observations (by
25 ;;; measure/recording) while "row" vectors are related readings (by
26 ;;; case)
28 ;;; Relational structure -- can we capture a completely unnormalized
29 ;;; data strucutre to propose possible modeling approaches, and
30 ;;; propose appropriate models and inferential strategies?
32 ;;; So we want a verb-driven API for data collection construction. We
33 ;;; should encode independence or lack of, as possible.
35 ;;; Need to figure out typed vectors. We then map a series of typed
36 ;;; vectors over to tables where columns are equal typed. In a sense,
37 ;;; this is a relation (1-1) of equal-typed arrays. For the most
38 ;;; part, this ends up making the R data.frame into a relational
39 ;;; building block (considering 1-1 mappings using row ID as a
40 ;;; relation). Is this a worthwhile generalization?
42 ;;; verbs vs semantics for DS conversion -- consider the possibily of
43 ;;; how adverbs and verbs relate, where to put which semantically to
44 ;;; allow for general approach.
46 ;;; eg. Kasper's talk on the FUSION collection of parsers.
48 ;;;
49 ;;; Need to consider modification APIs
50 ;;; actions are:
51 ;;; - import
52 ;;; - get/set row names (case names)
53 ;;; - column names (variable names)
54 ;;; - dataset values
55 ;;; - annotation/metadata
56 ;;; - make sure that we do coherency checking in the exported
57 ;;; - functions.
58 ;;; - ...
59 ;;; - reshapeData/reformat/reshapr a reformed version of the dataset (no
60 ;;; additional input).
61 ;;; - either overwriting or not, i.e. with or without copy.
62 ;;; - check consistency of resulting data with metadata and related
63 ;;; data information.
64 ;;; -
67 ;;; Misc Functions (to move into a lisp data manipulation support package)
69 ;; the next two should be merged into a general replicator pattern.
70 (defun gen-seq (n &optional (start 1))
71 "Generates an integer sequence of length N starting at START. Used
72 for indexing."
73 (if (>= n start)
74 (append (gen-seq (- n 1) start) (list n))))
76 (defun repeat-seq (n item)
77 "FIXME: There has to be a better way -- I'm sure of it!
78 (repeat-seq 3 \"d\") ; => (\"d\" \"d\" \"d\")
79 (repeat-seq 3 'd) ; => ('d 'd 'd)"
80 (if (>= n 1)
81 (append (repeat-seq (1- n) item) (list item))))
83 (defun strsym->indexnum (df strsym)
84 "Returns a number indicating the DF column labelled by STRSYM.
85 Probably should be a method dispatching on DATAFRAME-LIKE type."
86 (position strsym (varlabels df)))
88 (defun string->number (str)
89 "Convert a string <str> representing a number to a number. A second value is
90 returned indicating the success of the conversion.
91 Examples:
92 (string->number \"123\") ; => 123 t
93 (string->number \"1.23\") ; => 1.23 t"
94 (let ((*read-eval* nil))
95 (let ((num (read-from-string str)))
96 (values num (numberp num)))))
101 (equal 'testme 'testme)
102 (defparameter *test-pos* 'testme)
103 (position *test-pos* (list 'a 'b 'testme 'c))
104 (position #'(lambda (x) (equal x "testme")) (list "a" "b" "testme" "c"))
105 (position #'(lambda (x) (equal x 1)) (list 2 1 3 4))
109 ;;; abstract dataframe class
111 (defclass dataframe-like (matrix-like)
113 ;; Matrix-like (from lisp-matrix) is basically a rectangular table
114 ;; without storage. We emulate that, and add storage, row/column
115 ;; labels, and within-column-typing.
117 ;; STORE is the storage component. We ignore this in the DATAFRAME-LIKE
118 ;; class, as it is the primary differentiator, driving how access
119 ;; (getting/setting) is done. We create methods depending on the
120 ;; storage component, which access data as appropriate. See
121 ;; DATAFRAME-ARRAY for an example implementation.
122 ;; the rest of this is metadata. In particular, we should find a
123 ;; more flexible, compact way to store this.
124 (case-labels :initform nil
125 :initarg :case-labels
126 :type list
127 :accessor case-labels
128 :documentation "labels used for describing cases (doc
129 metadata), possibly used for merging.")
130 (var-labels :initform nil
131 :initarg :var-labels
132 :type list
133 :accessor var-labels
134 :documentation "Variable names.")
135 (var-types :initform nil
136 :initarg :var-types
137 :type list
138 :accessor var-types
139 :documentation "variable types to ensure fit")
140 (documentation-string :initform nil
141 :initarg :doc
142 :accessor doc-string
143 :documentation "additional information,
144 potentially uncomputable, possibly metadata, about dataframe-like
145 instance."))
146 (:documentation "Abstract class for standard statistical analysis
147 dataset for independent data. Rows are considered
148 to be independent, matching observations. Columns
149 are considered to be type-consistent, match a
150 variable with distribution. inherits from
151 lisp-matrix base MATRIX-LIKE class.
153 DATAFRAME-LIKE is the basic cases by variables
154 framework. Need to embed this within other
155 structures which allow for generalized relations.
156 Goal is to ensure that relations imply and drive
157 the potential for statistical relativeness such as
158 correlation, interference, and similar concepts."))
161 ;;; Generics specialized above matrix-like, particularly for
162 ;;; dataframe-like objects. Need methods for any storage
163 ;;; implementation.
165 (defgeneric dataframe-dimensions (df)
166 (:documentation "")
167 (:method ((df dataframe-like))
168 (error "dispatch on virtual class.")))
170 (defgeneric dataframe-dimension (df index)
171 (:documentation "")
172 (:method ((df dataframe-like) index)
173 (elt (dataframe-dimensions df) index)))
175 (defgeneric dfref (df index1 index2)
176 (:documentation "scalar access with selection of possible return object types.")
177 (:method ((df dataframe-like) index1 index2)
178 (error "Need real class with real storage to reference elements.")))
180 (defgeneric set-dfref (df index1 index2 val)
181 (:documentation "setter for dfref")
182 (:method ((df dataframe-like) index1 index2 val)
183 (error "Need real class with real storage to reference elements.")))
185 (defsetf dfref set-dfref)
187 (defgeneric dfselect (df &key cases vars indices)
188 (:documentation "access to sub-dataframes. Always returns a dataframe.")
189 (:method ((df dataframe-like) &key cases vars indices)
190 (error "Need real class with real storage to reference elements.")))
192 ;;; Specializing on superclasses...
193 ;;; Access and Extraction: implementations needed for any storage
194 ;;; type. But here, just to point out that we've got a specializing
195 ;;; virtual subclass (DATAFRAME-LIKE specializing MATRIX-LIKE).
197 (defmethod nrows ((df dataframe-like))
198 "specializes on inheritance from matrix-like in lisp-matrix."
199 (error "Need implementation; can't dispatch on virtual class DATAFRAME-LIKE."))
201 (defmethod ncols ((df dataframe-like))
202 "specializes on inheritance from matrix-like in lisp-matrix."
203 (error "Need implementation; can't dispatch on virtual class DATAFRAME-LIKE."))
205 ;; Testing consistency/coherency.
207 (defgeneric consistent-dataframe-p (df)
208 (:documentation "methods to check for consistency.")
209 (:method ((df dataframe-like))
210 (and
211 ;; ensure dimensionality
212 (= (length (var-labels df)) (ncols df)) ; array-dimensions (dataset df))
213 (= (length (case-labels df)) (nrows df))
214 ;; when dims sane, check-type for each variable
215 (progn
216 (dotimes (i (nrows df))
217 (dotimes (j (ncols df))
218 ;; below, dfref bombs if not a df-like subclass...
219 (typep (dfref df i j) (nth j (var-types df)))))
220 t))))
224 (defun ensure-consistent-datatable-type (dt lot)
225 "given a datatable and a listoftypes, ensure that the datatble
226 variables are consistent."
227 (destructuring-bind (n p) ;; why use let when we can be cool? Sigh.
228 (array-dimensions dt)
229 (dotimes (i n)
230 (dotimes (j p)
231 (check-type (aref dt i j) (elt lot j))))))
235 ;;; GENERAL FUNCTIONS WHICH DISPATCH ON INTERNAL METHODS OR ARGS
237 ;;; Q: change the following to generic functions and dispatch on
238 ;;; array, matrix, and dataframe? Others?
239 (defun make-labels (initstr num)
240 "generate a list of strings which can be used as labels, i.e. something like
241 '(\"a1\" \"a2\" \"a3\")."
242 (check-type initstr string)
243 (mapcar #'(lambda (x y) (concatenate 'string x y))
244 (repeat-seq num initstr)
245 (mapcar #'(lambda (x) (format nil "~A" x)) (gen-seq num))))
248 (make-labels 'c 2)
249 (make-labels "c" 4)
252 (defun ncase-store (store)
253 (etypecase store
254 (array (array-dimension store 0))
255 (matrix-like (nrows store))))
257 (defun nvars-store (store)
258 (etypecase store
259 (array (array-dimension store 1))
260 (matrix-like (ncols store))))
263 (defun make-dataframe (newdata
264 &key (vartypes nil)
265 (caselabels nil) (varlabels nil)
266 (doc "no docs"))
267 "Helper function to use instead of make-instance to assure
268 construction of proper DF-array."
269 (check-type newdata (or matrix-like array))
270 (check-type caselabels sequence)
271 (check-type varlabels sequence)
272 (check-type doc string)
273 (let ((ncases (ncase-store newdata))
274 (nvars (nvars-store newdata)))
275 (if caselabels (assert (= ncases (length caselabels))))
276 (if varlabels (assert (= nvars (length varlabels))))
277 (let ((newcaselabels (if caselabels
278 caselabels
279 (make-labels "C" ncases)))
280 (newvarlabels (if varlabels
281 varlabels
282 (make-labels "V" nvars))))
283 (etypecase newdata
284 (array
285 (make-instance 'dataframe-array
286 :storage newdata
287 :nrows (length newcaselabels)
288 :ncols (length newvarlabels)
289 :case-labels newcaselabels
290 :var-labels newvarlabels
291 :var-types vartypes))
292 (matrix-like
293 (make-instance 'dataframe-matrixlike
294 :storage newdata
295 :nrows (length newcaselabels)
296 :ncols (length newvarlabels)
297 :case-labels newcaselabels
298 :var-labels newvarlabels
299 :var-types vartypes))))))
302 (make-dataframe #2A((1.2d0 1.3d0) (2.0d0 4.0d0)))
303 (make-dataframe #2A(('a 1) ('b 2)))
304 (dfref (make-dataframe #2A(('a 1) ('b 2))) 0 1)
305 (dfref (make-dataframe #2A(('a 1) ('b 2))) 1 0)
306 (make-dataframe 4) ; ERROR, should we allow?
307 (make-dataframe #2A((4)))
308 (make-dataframe (rand 10 5)) ;; ERROR, but should work!
312 (defun row-order-as-list (ary)
313 "Pull out data in row order into a list."
314 (let ((result (list))
315 (nrows (nth 0 (array-dimensions ary)))
316 (ncols (nth 1 (array-dimensions ary))))
317 (dotimes (i ncols)
318 (dotimes (j nrows)
319 (append result (aref ary i j))))))
321 (defun col-order-as-list (ary)
322 "Pull out data in row order into a list."
323 (let ((result (list))
324 (nrows (nth 0 (array-dimensions ary)))
325 (ncols (nth 1 (array-dimensions ary))))
326 (dotimes (i nrows)
327 (dotimes (j ncols)
328 (append result (aref ary i j))))))
330 (defun transpose-array (ary)
331 "map NxM to MxN."
332 (make-array (reverse (array-dimensions ary))
333 :initial-contents (col-order-as-list ary)))
335 ;;; THE FOLLOWING 2 dual-sets done to provide error checking
336 ;;; possibilities on top of the generic function structure. Not
337 ;;; intended as make-work!
339 (defun varlabels (df)
340 "Variable-name handling for DATAFRAME-LIKE. Needs error checking."
341 (var-labels df))
343 (defun set-varlabels (df vl)
344 "Variable-name handling for DATAFRAME-LIKE. Needs error checking."
345 (if (= (length (var-labels df))
346 (length vl))
347 (setf (var-labels df) vl)
348 (error "wrong size.")))
350 (defsetf varlabels set-varlabels)
352 ;;; Case-name handling for Tables. Needs error checking.
353 (defun caselabels (df)
354 "Case-name handling for DATAFRAME-LIKE. Needs error checking."
355 (case-labels df))
357 (defun set-caselabels (df cl)
358 "Case-name handling for DATAFRAME-LIKE. Needs error checking."
359 (if (= (length (case-labels df))
360 (length cl))
361 (setf (case-labels df) cl)
362 (error "wrong size.")))
364 (defsetf caselabels set-caselabels)
366 ;;;;;;;;;;;; IMPLEMENTATIONS, with appropriate methods.
367 ;; See also:
368 ;; (documentation 'dataframe-like 'type)
370 ;;;;; DATAFRAME-ARRAY
372 (defclass dataframe-array (dataframe-like)
373 ((store :initform nil
374 :initarg :storage
375 :type (array * *)
376 :accessor dataset
377 :documentation "Data storage: typed as array."))
378 (:documentation "example implementation of dataframe-like using storage
379 based on lisp arrays. An obvious alternative could be a
380 dataframe-matrix-like which uses the lisp-matrix classes."))
382 (defmethod nrows ((df dataframe-array))
383 "specializes on inheritance from matrix-like in lisp-matrix."
384 (array-dimension (dataset df) 0))
386 (defmethod ncols ((df dataframe-array))
387 "specializes on inheritance from matrix-like in lisp-matrix."
388 (array-dimension (dataset df) 1))
390 (defmethod dfref ((df dataframe-array)
391 (index1 number) (index2 number))
392 "Returns a scalar in array, in the same vein as aref, mref, vref, etc.
393 idx1/2 is row/col or case/var."
394 (aref (dataset df) index1 index2))
396 (defmethod set-dfref ((df dataframe-array) (index1 number) (index2 number) val)
397 "set value for df-ar."
398 ;; (check-type val (elt (var-type df) index2))
399 (setf (aref (dataset df) index1 index2) val))
401 (defparameter *default-dataframe-class* 'dataframe-array)
403 (defmethod dfselect ((df dataframe-array)
404 &key cases vars indices)
405 "Extract the OR of cases, vars, or have a list of indices to extract"
406 (declare (ignore indices))
407 (let ((newdf (make-instance *default-dataframe-class*
408 :storage (make-array (list (length cases) (length vars)))
409 :nrows (length cases)
410 :ncols (length vars)
412 :case-labels (select-list caselist (case-labels df))
413 :var-labels (select-list varlist (var-labels df))
414 :var-types (select-list varlist (vartypes df))
417 (dotimes (i (length cases))
418 (dotimes (j (length vars))
419 (setf (dfref newdf i j)
420 (dfref df
421 (position (elt cases i) (case-labels df))
422 (position (elt vars j) (var-labels df))))))))
424 ;;;;; DATAFRAME-MATRIXLIKE
426 (defclass dataframe-matrixlike (dataframe-like)
427 ((store :initform nil
428 :initarg :storage
429 :type matrix-like
430 :accessor dataset
431 :documentation "Data storage: typed as matrix-like
432 (numerical only)."))
433 (:documentation "example implementation of dataframe-like using storage
434 based on lisp-matrix structures."))
436 (defmethod nrows ((df dataframe-matrixlike))
437 "specializes on inheritance from matrix-like in lisp-matrix."
438 (matrix-dimension (dataset df) 0))
440 (defmethod ncols ((df dataframe-matrixlike))
441 "specializes on inheritance from matrix-like in lisp-matrix."
442 (matrix-dimension (dataset df) 1))
444 (defmethod dfref ((df dataframe-matrixlike)
445 (index1 number) (index2 number))
446 "Returns a scalar in array, in the same vein as aref, mref, vref, etc.
447 idx1/2 is row/col or case/var."
448 (mref (dataset df) index1 index2))
450 (defmethod set-dfref ((df dataframe-matrixlike)
451 (index1 number) (index2 number) val)
452 "Sets a value for df-ml."
453 ;; NEED TO CHECK TYPE!
454 ;; (check-type val (elt (vartype df) index2))
455 (setf (mref (dataset df) index1 index2) val))
459 ;;;;;; IMPLEMENTATION INDEPENDENT FUNCTIONS AND METHODS
460 ;;;;;; (use only dfref, nrows, ncols and similar dataframe-like
461 ;;;;;; components as core).
463 (defun dfref-var (df index return-type)
464 "Returns the data in a single variable as type.
465 type = sequence, vector, vector-like (if valid numeric type) or dataframe."
466 (ecase return-type
467 (('list)
468 (map 'list
469 #'(lambda (x) (dfref df index x))
470 (gen-seq (nth 2 (array-dimensions (dataset df))))))
471 (('vector) t)
472 (:vector-like t)
473 (:matrix-like t)
474 (:dataframe t)))
476 (defun dfref-case (df index return-type)
477 "Returns row as sequence."
478 (ecase return-type
479 (:list
480 (map 'list
481 #'(lambda (x) (dfref df x index))
482 (gen-seq (nth 1 (array-dimensions (dataset df))))))
483 (:vector t)
484 (:vector-like t)
485 (:matrix-like t)
486 (:dataframe t)))
488 ;; FIXME
489 (defun dfref-2indexlist (df indexlist1 indexlist2 &key (return-type :array))
490 "return an array, row X col dims. FIXME TESTME"
491 (case return-type
492 (:array
493 (let ((my-pre-array (list)))
494 (dolist (x indexlist1)
495 (dolist (y indexlist2)
496 (append my-pre-array (dfref df x y))))
497 (make-array (list (length indexlist1)
498 (length indexlist2))
499 :initial-contents my-pre-array)))
500 (:dataframe
501 (make-instance 'dataframe-array
502 :storage (make-array
503 (list (length indexlist1)
504 (length indexlist2))
505 :initial-contents (dataset df))
506 ;; ensure copy for this and following
507 :doc (doc-string df)
508 ;; the following 2 need to be subseted based on
509 ;; the values of indexlist1 and indexlist2
510 :case-labels (case-labels df)
511 :var-labels (var-labels df)))))
513 ;;; Do we establish methods for dataframe-like, which specialize to
514 ;;; particular instances of storage?
516 (defmethod print-object ((object dataframe-like) stream)
517 (print-unreadable-object (object stream :type t)
518 (format stream " ~d x ~d" (nrows object) (ncols object))
519 (terpri stream)
520 ;; (format stream "~T ~{~S ~T~}" (var-labels object))
521 (dotimes (j (ncols object)) ; print labels
522 (write-char #\tab stream)
523 (write-char #\tab stream)
524 (format stream "~T~A~T" (nth j (var-labels object))))
525 (dotimes (i (nrows object)) ; print obs row
526 (terpri stream)
527 (format stream "~A:~T" (nth i (case-labels object)))
528 (dotimes (j (ncols object))
529 (write-char #\tab stream) ; (write-char #\space stream)
530 ;; (write (dfref object i j) :stream stream)
531 (format stream "~7,3E" (dfref object i j)) ; if works, need to include a general output mechanism control
532 ))))
535 (defun print-structure-relational (ds)
536 "example of what we want the methods to look like. Should be sort
537 of like a graph of spreadsheets if the storage is a relational
538 structure."
539 (dolist (k (relations ds))
540 (let ((currentRelationSet (getRelation ds k)))
541 (print-as-row (var-labels currentRelationSet))
542 (let ((j -1))
543 (dolist (i (case-labels currentRelationSet))
544 (print-as-row
545 (append (list i)
546 (dfref-obsn (dataset currentRelationSet)
547 (incf j)))))))))
549 (defun testecase (s)
550 (ecase s
551 ((scalar) 1)
552 ((asd asdf) 2)))
554 (testecase 'scalar)
555 (testecase 'asd)
556 (testecase 'asdf)
557 (testecase 'as)