1;+
2; NAME:
3;       FXBREADM
4; PURPOSE:
5;       Read multiple columns/rows from a disk FITS binary table file.
6; EXPLANATION :
7;       A call to FXBREADM will read data from multiple rows and
8;       multiple columns in a single procedure call.  Up to forty-nine
9;       columns may be read in a single pass; the number of rows is
10;       limited essentially by available memory.  The file should have
11;       already been opened with FXBOPEN.  FXBREADM optimizes reading
12;       multiple columns by first reading a large chunk of data from
13;       the FITS file directly, and then slicing the data into columns
14;       within memory.  FXBREADM can read variable-length arrays (see
15;       below).
16;
17;       The number of columns is limited to 49 if data are passed by
18;       positional argument.  However, this limitation can be overcome
19;       by having FXBREADM return the data in an array of pointers.
20;       The user should set the PASS_METHOD keyword to 'POINTER', and an
21;       array of pointers to the data will be returned in the POINTERS keyword.
22;       The  user is responsible for freeing the pointers; however,
23;       FXBREADM will reuse any pointers  passed into the procedure, and
24;       hence any pointed-to data will be destroyed.
25;
26;       FXBREADM can also read variable-length columns from FITS
27;       binary tables.  Since such data is not of a fixed size, it is
28;       returned as a structure.  The structure has the following
29;       elements:
30;
31;              VARICOL:    ;; Flag: variable length column (= 1)
32;              N_ELEMENTS: ;; Total number of elements returned
33;              TYPE:       ;; IDL data type code (integer)
34;              N_ROWS:     ;; Number of rows read from table (integer)
35;              INDICES:    ;; Indices of each row's data (integer array)
36;              DATA:       ;; Raw data elements (variable type array)
37;
38;       In order to gain access to the Ith row's data, one should
39;       examine DATA(INDICES(I):INDICES(I+1)-1), which is similar in
40;       construct to the REVERSE_INDICES keyword of the HISTOGRAM
41;       function.
42;
43; CALLING SEQUENCE:
44;       FXBREADM, UNIT, COL, DATA1, [ DATA2, ... DATA48, ROW=, BUFFERSIZE = ]
45;           /NOIEEE, /NOSCALE, /VIRTUAL, NANVALUE=, PASS_METHOD = POINTERS=,
46;           ERRMSG = , WARNMSG = , STATUS = , /DEFAULT_FLOAT]
47;
48; INPUT PARAMETERS :
49;       UNIT    = Logical unit number corresponding to the file containing the
50;                 binary table.
51;       COL     = An array of columns in the binary table to read data
52;                 from, either as character strings containing column
53;                 labels (TTYPE), or as numerical column indices
54;                 starting from column one.
55; Outputs     :
56;       DATA1, DATA2...DATA48 = A named variable to accept the data values, one
57;                 for each column.  The columns are stored in order of the
58;                 list in COL.  If the read operation fails for a
59;                 particular column, then the corresponding output Dn
60;                 variable is not altered.  See the STATUS keyword.
61;                 Ignored if PASS_METHOD is 'POINTER'.
62;
63; OPTIONAL INPUT KEYWORDS:
64;       ROW     = Either row number in the binary table to read data from,
65;                 starting from row one, or a two element array containing a
66;                 range of row numbers to read.  If not passed, then the entire
67;                 column is read in.
68;       /DEFAULT_FLOAT = If set, then scaling with TSCAL/TZERO is done with
69;                 floating point rather than double precision.
70;       /NOIEEE = If set, then then IEEE floating point data will not
71;                be converted to the host floating point format (and
72;                this by definition implies NOSCALE).  The user is
73;                responsible for their own floating point conversion.
74;       /NOSCALE = If set, then the output data will not be scaled using the
75;                 optional TSCAL and TZERO keywords in the FITS header.
76;                 Default is to scale.
77;       VIRTUAL = If set, and COL is passed as a name rather than a number,
78;                 then if the program can't find a column with that name, it
79;                 will then look for a keyword with that name in the header.
80;                 Such a keyword would then act as a "virtual column", with the
81;                 same value for every row.
82;       DIMENSIONS = FXBREADM ignores this keyword.  It is here for
83;	          compatibility only.
84;       NANVALUE= Value signalling data dropout.  All points corresponding to
85;                 IEEE NaN (not-a-number) are converted to this number.
86;                 Ignored unless DATA is of type float, double-precision or
87;                 complex.
88;       PASS_METHOD = A scalar string indicating method of passing
89;                 data from FXBREADM.  Either 'ARGUMENT' (indicating
90;                 pass by positional argument), or 'POINTER' (indicating
91;                 passing an array of pointers by the POINTERS
92;                 keyword).
93;                 Default: 'ARGUMENT'
94;       POINTERS = If PASS_METHOD is 'POINTER' then an array of IDL
95;                 pointers is returned in this keyword, one for each
96;                 requested column.    Any pointers passed into FXBREADM will
97;                 have their pointed-to data destroyed.  Ultimately the
98;                 user is responsible for deallocating pointers.
99;       BUFFERSIZE = Raw data are transferred from the file in chunks
100;                 to conserve memory.  This is the size in bytes of
101;                 each chunk.  If a value of zero is given, then all
102;                 of the data are transferred in one pass.  Default is
103;                 32768 (32 kB).
104; OPTIONAL OUTPUT KEYWORDS:
105;       ERRMSG  = If defined and passed, then any error messages will be
106;                 returned to the user in this parameter rather than
107;                 depending on the MESSAGE routine in IDL.  If no errors are
108;                 encountered, then a null string is returned.  In order to
109;                 use this feature, ERRMSG must be defined first, e.g.
110;
111;                       ERRMSG = ''
112;                       FXBREAD, ERRMSG=ERRMSG, ...
113;                       IF ERRMSG NE '' THEN ...
114;       WARNMSG = Messages which are considered to be non-fatal
115;                 "warnings" are returned in this output string.
116;                 Note that if some but not all columns are
117;                 unreadable, this is considered to be non-fatal.
118;       STATUS  = An output array containing the status for each
119;                 column read, 1 meaning success and 0 meaning failure.
120;
121; Calls       :
122;       FXPAR(), WHERENAN()
123; Common      :
124;       Uses common block FXBINTABLE--see "fxbintable.pro" for more
125;       information.
126; Restrictions:
127;       The binary table file must have been opened with FXBOPEN.
128;
129;       The data must be consistent with the column definition in the binary
130;       table header.
131;
132;       The row number must be consistent with the number of rows stored in the
133;       binary table header.
134;
135;       Generally speaking, FXBREADM will be faster than iterative
136;       calls to FXBREAD when (a) a large number of columns is to be
137;       read or (b) the size in bytes of each cell is small, so that
138;       the overhead of the FOR loop in FXBREAD becomes significant.
139;
140; SIDE EFFECTS:
141;       If there are no elements to read in (the number of elements is zero),
142;       then the program sets !ERR to -1, and DATA is unmodified.
143;
144; Category    :
145;       Data Handling, I/O, FITS, Generic.
146; Prev. Hist. :
147;       C. Markwardt, based in concept on FXBREAD version 12 from
148;                              IDLASTRO, but with significant and
149;                              major changes to accommodate the
150;                              multiple row/column technique.  Mostly
151;                              the parameter checking and general data
152;                              flow remain.
153;       C. Markwardt, updated to read variable length arrays, and to
154;                              pass columns by handle or pointer.
155;                              20 Jun 2001
156;       C. Markwardt, try to conserve memory when creating the arrays
157;                              13 Oct 2001
158;   Handle case of GE 50 columns, C. Markwardt, 18 Apr 2002
159;   Handle case where TSCAL/TZERO changes type of column,
160;       C. Markwardt, 23 Feb 2003
161;   Fix bug in handling of FOUND and numeric columns,
162;       C. Markwardt 12 May 2003
163;   Removed pre-V5.0 HANDLE options  W. Landsman July 2004
164;   Fix bug when HANDLE options were removed, July 2004
165;   Handle special cases of TSCAL/TZERO which emulate unsigned
166;      integers, Oct 2003
167;   Add DEFAULT_FLOAT keyword to select float values instead of double
168;      for TSCAL'ed, June 2004
169;   Read 64bit integer columns, E. Hivon, Mar 2008
170;   Add support for columns with TNULLn keywords, C. Markwardt, Apr 2010
171;   Add support for files larger than 2 GB, C. Markwardt, 2012-04-17
172;   Use V6 notation, remove IEEE_TO_HOST  W. Landsman Mar 2014
173;
174;-
175;
176
177
178;; This is a utility routine which converts the data from raw bytes to
179;; IDL variables.
180PRO FXBREADM_CONV, BB, DD, CTYPE, PERROW, NROWS, $
181                   NOIEEE=NOIEEE, NOSCALE=NOSCALE, VARICOL=VARICOL, $
182                   NANVALUE=NANVALUE, TZERO=TZERO, TSCAL=TSCAL, $
183                   TNULL_VALUE=TNULL, TNULL_FLAG=TNULLQ, $
184                   DEFAULT_FLOAT=DF
185
186  COMMON FXBREADM_CONV_COMMON, DTYPENAMES
187  IF N_ELEMENTS(DTYPENAMES) EQ 0 THEN $
188    DTYPENAMES = [ '__BAD', 'BYTE', 'FIX', 'LONG', $
189                   'FLOAT', 'DOUBLE', 'COMPLEX', 'STRING', $
190                   '__BAD', 'DCOMPLEX', '__BAD', '__BAD', '__BAD', '__BAD', 'LONG64' ]
191
192  TYPENAME = DTYPENAMES[CTYPE]
193
194  IF CTYPE EQ 7 THEN BEGIN
195      DD = STRING(TEMPORARY(BB))
196  ENDIF ELSE BEGIN
197      DD = CALL_FUNCTION(TYPENAME, TEMPORARY(BB), 0, PERROW*NROWS)
198  ENDELSE
199  IF N_ELEMENTS(DD) EQ 1 THEN DD = [DD]
200  DD = REFORM(DD, PERROW, NROWS, /OVERWRITE)
201
202  ;; Now perform any type-specific conversions, etc.
203  COUNT = 0L
204  CASE 1 OF
205      ;; Integer types
206      (CTYPE EQ 2 || CTYPE EQ 3 || ctype eq 14): BEGIN
207          IF ~KEYWORD_SET(NOIEEE) || KEYWORD_SET(VARICOL) THEN $
208            SWAP_ENDIAN_INPLACE, DD, /SWAP_IF_LITTLE
209          ;; Check for TNULL values
210          ;; We will convert to NAN values later (or if the user
211          ;; requested a different value we will use that)
212          IF KEYWORD_SET(TNULLQ) THEN BEGIN
213              W = WHERE(DD EQ TNULL,COUNT)
214              IF N_ELEMENTS(NANVALUE) EQ 0 THEN NANVALUE = !VALUES.D_NAN
215          ENDIF
216      END
217
218      ;; Floating and complex types
219      (CTYPE GE 4 || CTYPE LE 6 || CTYPE EQ 9): BEGIN
220          IF ~KEYWORD_SET(NOIEEE) THEN BEGIN
221              IF N_ELEMENTS(NANVALUE) GT 0 THEN W=WHERENAN(DD,COUNT)
222              SWAP_ENDIAN_INPLACE, DD, /SWAP_IF_LITTLE
223          ENDIF
224      END
225
226      ;; String types (CTYPE EQ 7) have already been converted
227      ;; in the above CALL_FUNCTION.  No further conversion
228      ;; is necessary here.
229  ENDCASE
230
231;
232;  If the parameters TZERO and TSCAL are non-trivial, then adjust the array by
233;  these values.
234;
235  IF ((~KEYWORD_SET(NOIEEE) && ~KEYWORD_SET(NOSCALE)) && $
236      (~KEYWORD_SET(VARICOL)) && $
237      (N_ELEMENTS(TZERO) EQ 1 && N_ELEMENTS(TSCAL) EQ 1)) THEN BEGIN
238
239      IF KEYWORD_SET(DF) THEN BEGIN
240          ;; Default to float
241          TSCAL = FLOAT(TSCAL)
242          TZERO = FLOAT(TZERO)
243      ENDIF
244
245      IF CTYPE EQ 2 AND TSCAL[0] EQ 1 AND TZERO[0] EQ 32768 THEN BEGIN
246          ;; SPECIAL CASE: Unsigned 16-bit integer
247          DD = UINT(DD) - UINT(32768)
248      ENDIF ELSE IF CTYPE EQ 3 AND TSCAL[0] EQ 1 AND $
249        TZERO[0] EQ 2147483648D THEN BEGIN
250          ;; SPECIAL CASE: Unsigned 32-bit integer
251          DD = ULONG(DD) - ULONG(2147483648)
252      ENDIF ELSE BEGIN
253          IF (TSCAL[0] NE 0) && (TSCAL[0] NE 1) THEN DD = TSCAL[0]*DD
254          IF TZERO[0] NE 0 THEN DD = DD + TZERO[0]
255      ENDELSE
256  ENDIF
257
258;
259;  Store NANVALUE everywhere where the data corresponded to IEEE NaN.
260;
261  IF COUNT GT 0 && N_ELEMENTS(NANVALUE) GT 0 THEN DD[W] = NANVALUE
262
263END
264
265PRO FXBREADM, UNIT, COL, $
266              D0,  D1,  D2,  D3,  D4,  D5,  D6,  D7,  D8,  D9, $
267              D10, D11, D12, D13, D14, D15, D16, D17, D18, D19, $
268              D20, D21, D22, D23, D24, D25, D26, D27, D28, D29, $
269              D30, D31, D32, D33, D34, D35, D36, D37, D38, D39, $
270              D40, D41, D42, D43, D44, D45, D46, D47, $
271              ROW=ROW, VIRTUAL=VIR, DIMENSIONS=DIM, $
272              NOSCALE=NOSCALE, NOIEEE=NOIEEE, DEFAULT_FLOAT=DEFAULT_FLOAT, $
273              PASS_METHOD=PASS_METHOD, POINTERS=POINTERS, $
274              NANVALUE=NANVALUE, BUFFERSIZE=BUFFERSIZE, $
275              ERRMSG=ERRMSG, WARNMSG=WARNMSG, STATUS=OUTSTATUS
276
277@fxbintable
278        ON_ERROR, 2
279;
280;  Check the number of parameters.
281;
282        IF N_PARAMS() LT 2 THEN BEGIN
283                MESSAGE = 'Syntax:  FXBREADM, UNIT, COL, D0, D1, ... [, ROW= ]'
284                IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
285                        ERRMSG = MESSAGE
286                        RETURN
287                END ELSE MESSAGE, MESSAGE
288        ENDIF
289        IF N_ELEMENTS(BUFFERSIZE) EQ 0 THEN BUFFERSIZE = 32768L
290
291;
292;  COL may be one of several descriptors:
293;     * a list of column numbers, beginning with 1
294;     * a list of column names
295;
296        MYCOL = [ COL ]    ; Make sure it is an array
297
298        SC = SIZE(MYCOL)
299        NUMCOLS = N_ELEMENTS(MYCOL)
300        OUTSTATUS = LONARR(NUMCOLS)
301        COLNAMES = 'D'+STRTRIM(LINDGEN(NUMCOLS),2)
302
303;
304;  Determine whether the data is to be extracted as pointers or arguments
305;
306        IF N_ELEMENTS(PASS_METHOD) EQ 0 THEN PASS_METHOD = 'ARGUMENT'
307        PASS = STRUPCASE(STRTRIM(PASS_METHOD[0],2))
308        IF PASS NE 'ARGUMENT' AND PASS NE 'POINTER' THEN BEGIN
309            MESSAGE = 'ERROR: PASS_METHOD must be ARGUMENT or POINTER'
310            IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
311                ERRMSG = MESSAGE
312                RETURN
313            END ELSE MESSAGE, MESSAGE
314        ENDIF
315
316        NP = N_ELEMENTS(POINTERS)
317        IF PASS EQ 'POINTER' THEN BEGIN
318            IF NP EQ 0 THEN POINTERS = PTRARR(NUMCOLS, /ALLOCATE_HEAP)
319            NP = N_ELEMENTS(POINTERS)
320            SZ = SIZE(POINTERS)
321            IF SZ[SZ[0]+1] NE 10 THEN BEGIN
322                MESSAGE = 'ERROR: POINTERS must be an array of pointers'
323                IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
324                        ERRMSG = MESSAGE
325                        RETURN
326                END ELSE MESSAGE, MESSAGE
327            ENDIF
328
329;
330;  Expand the pointer array if necessary
331;
332            IF NP LT NUMCOLS THEN $
333              POINTERS = [POINTERS[*], PTRARR(NUMCOLS-NP, /ALLOCATE_HEAP)]
334            NP = N_ELEMENTS(POINTERS)
335
336;
337;  Make sure there are no null pointers, which cannot be assigned to.
338;
339            WH = WHERE(PTR_VALID(POINTERS) EQ 0, CT)
340            IF CT GT 0 THEN POINTERS[WH] = PTRARR(CT, /ALLOCATE_HEAP)
341
342        ENDIF
343
344
345;
346;  Find the logical unit number in the FXBINTABLE common block.
347;
348        ILUN = WHERE(LUN EQ UNIT,NLUN)
349        ILUN = ILUN[0]
350        IF NLUN EQ 0 THEN BEGIN
351                MESSAGE = 'Unit ' + STRTRIM(UNIT,2) +   $
352                        ' not opened properly'
353                IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
354                        ERRMSG = MESSAGE
355                        RETURN
356                END ELSE MESSAGE, MESSAGE
357        ENDIF
358
359;
360;  Check the number of columns.  It should be fewer than 49
361;
362        IF PASS EQ 'ARGUMENT' THEN BEGIN
363            IF NUMCOLS GT 49 THEN BEGIN
364                MESSAGE = 'Maximum of 49 columns exceeded'
365                IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
366                    ERRMSG = MESSAGE
367                    RETURN
368                END ELSE MESSAGE, MESSAGE
369            ENDIF
370            IF N_PARAMS()-2 LT NUMCOLS AND N_ELEMENTS(ERRMSG) EQ 0 THEN BEGIN
371                MESSAGE, 'WARNING: number of data parameters less than columns', $
372                  /INFO
373            ENDIF
374        ENDIF
375
376        ICOL    = LONARR(NUMCOLS)
377        VIRTUAL = BYTARR(NUMCOLS)
378        VIRTYPE = LONARR(NUMCOLS)
379        FOUND   = BYTARR(NUMCOLS)
380        VARICOL = BYTARR(NUMCOLS)
381        NOTFOUND = ''
382        NNOTFOUND = 0L
383        IF N_ELEMENTS(WARNMSG) NE 0 THEN WARNMSG = ''
384
385;
386;  If COL is of type string, then search for a column with that label.
387;
388        IF SC[SC[0]+1] EQ 7 THEN BEGIN
389            MYCOL = STRUPCASE(STRTRIM(MYCOL,2))
390            FOR I = 0, NUMCOLS-1 DO BEGIN
391                XCOL = WHERE(TTYPE[*,ILUN] EQ MYCOL[I], NCOL)
392                ICOL[I] = XCOL[0]
393;
394;  If the column was not found, and VIRTUAL was set, then search for a keyword
395;  by that name.
396;
397                IF NCOL GT 0 THEN FOUND[I] = 1
398                IF NOT FOUND[I] AND KEYWORD_SET(VIR) THEN BEGIN
399                    HEADER = HEAD[*,ILUN]
400                    VALUE = FXPAR(HEADER,MYCOL[I], Count = N_VALUE)
401                    IF N_VALUE GE 0 THEN BEGIN
402                        RESULT = EXECUTE(COLNAMES[I]+' = VALUE')
403                        SV = SIZE(VALUE)
404                        VIRTYPE[I] = SV[SV[0]+1]
405                        VIRTUAL[I] = 1
406                        FOUND[I] = 1
407                    ENDIF
408                ENDIF ELSE IF ~FOUND[I] THEN BEGIN
409                    IF NOTFOUND EQ '' THEN NOTFOUND = MYCOL[I] $
410                    ELSE NOTFOUND = NOTFOUND +', ' + MYCOL[I]
411                    NNOTFOUND++
412                ENDIF
413
414            ENDFOR
415
416            IF NNOTFOUND EQ NUMCOLS THEN BEGIN
417                MESSAGE = 'ERROR: None of the requested columns were found'
418                IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
419                    ERRMSG = MESSAGE
420                    RETURN
421                END ELSE MESSAGE, MESSAGE
422            ENDIF ELSE IF NNOTFOUND GT 0 THEN BEGIN
423                MESSAGE = 'WARNING: Columns ' + NOTFOUND + ' were not found'
424                IF N_ELEMENTS(WARNMSG) NE 0 THEN WARNMSG = MESSAGE $
425                ELSE MESSAGE, MESSAGE, /INFO
426            ENDIF
427
428;
429;  Otherwise, a numerical column was passed.  Check its value.
430;
431        ENDIF ELSE BEGIN
432            ICOL[*] = LONG(MYCOL) - 1
433            FOUND[*] = 1
434        ENDELSE
435
436;  Step through each column index
437        MESSAGE = ''
438        FOR I = 0, NUMCOLS-1 DO BEGIN
439            IF ~FOUND[I] THEN GOTO, LOOP_END_COLCHECK
440            IF VIRTUAL[I] THEN GOTO, LOOP_END_COLCHECK
441
442            IF (ICOL[I] LT 0) OR (ICOL[I] GE TFIELDS[ILUN]) THEN BEGIN
443                MESSAGE = MESSAGE + '; COL "'+STRTRIM(MYCOL[I],2)+$
444                  '" must be between 1 and ' +  $
445                  STRTRIM(TFIELDS[ILUN],2)
446                FOUND[I] = 0
447            ENDIF
448;
449;  If there are no elements in the array, then set !ERR to -1.
450;
451            IF FOUND[I] AND N_ELEM[ICOL[I],ILUN] EQ 0 THEN BEGIN
452                FOUND[I] = 0
453                MESSAGE = MESSAGE + '; Number of elements to read in "'+$
454                  STRTRIM(MYCOL[I],2)+'" is zero'
455;                !ERR = -1
456;                RETURN
457            ENDIF
458
459;
460;  Flag variable-length columns
461;
462            IF MAXVAL[ICOL[I],ILUN] GT 0 THEN BEGIN
463                FOUND[I] = 1
464                VARICOL[I] = 1
465            ENDIF
466
467            LOOP_END_COLCHECK:
468
469        ENDFOR
470
471;
472;  Check to be sure that there are columns to be read
473;
474        W  = WHERE(FOUND EQ 1, COUNT)
475        WV = WHERE(FOUND EQ 1 OR VARICOL EQ 1, WVCOUNT)
476        IF WVCOUNT EQ 0 THEN BEGIN
477            STRPUT, MESSAGE, ':', 0
478            MESSAGE = 'ERROR: No requested columns could be read'+MESSAGE
479            IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
480                ERRMSG = MESSAGE
481                RETURN
482            END ELSE MESSAGE, MESSAGE
483        ENDIF ELSE IF MESSAGE NE '' THEN BEGIN
484            STRPUT, MESSAGE, ':', 0
485            MESSAGE = 'WARNING: Some columns could not be read'+MESSAGE
486            IF N_ELEMENTS(WARNMSG) NE 0 THEN WARNMSG = MESSAGE $
487            ELSE MESSAGE, MESSAGE, /INFO
488        ENDIF
489
490;
491;  If ROW was not passed, then set it equal to the entire range.  Otherwise,
492;  extract the range.
493;
494        IF N_ELEMENTS(ROW) EQ 0 THEN ROW = [1LL, NAXIS2[ILUN]]
495        CASE N_ELEMENTS(ROW) OF
496                1:  ROW2 = LONG64(ROW[0])
497                2:  ROW2 = LONG64(ROW[1])
498                ELSE:  BEGIN
499                        MESSAGE = 'ROW must have one or two elements'
500                        IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
501                                ERRMSG = MESSAGE
502                                RETURN
503                        END ELSE MESSAGE, MESSAGE
504                        END
505        ENDCASE
506        ROW1 = LONG64(ROW[0])
507;
508;  If ROW represents a range, then make sure that the row range is legal, and
509;  that reading row ranges is allowed (i.e., the column is not variable length.
510;
511        IF ROW1 NE ROW2 THEN BEGIN
512                MAXROW = NAXIS2[ILUN]
513                IF (ROW1 LT 1) OR (ROW1 GT MAXROW) THEN BEGIN
514                        MESSAGE = 'ROW[0] must be between 1 and ' +     $
515                                STRTRIM(MAXROW,2)
516                        IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
517                                ERRMSG = MESSAGE
518                                RETURN
519                        END ELSE MESSAGE, MESSAGE
520                END ELSE IF (ROW2 LT ROW1) OR (ROW2 GT MAXROW) THEN BEGIN
521                        MESSAGE = 'ROW[1] must be between ' +   $
522                                STRTRIM(ROW1,2) + ' and ' + STRTRIM(MAXROW,2)
523                        IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
524                                ERRMSG = MESSAGE
525                                RETURN
526                        END ELSE MESSAGE, MESSAGE
527                ENDIF
528;
529;  Otherwise, if ROW is a single number, then just make sure it's valid.
530;
531        END ELSE BEGIN
532                IF (ROW1 LT 1) OR (ROW1 GT NAXIS2[ILUN]) THEN BEGIN
533                        MESSAGE = 'ROW must be between 1 and ' +        $
534                                STRTRIM(NAXIS2[ILUN],2)
535                        IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
536                                ERRMSG = MESSAGE
537                                RETURN
538                        END ELSE MESSAGE, MESSAGE
539                ENDIF
540        ENDELSE
541
542;
543;  Compose information about the output
544;
545        HEADER = HEAD[*,ILUN]
546        COLNDIM = LONARR(NUMCOLS)
547        COLDIM  = LONARR(NUMCOLS, 20) ;; Maximum of 20 dimensions in output
548        COLTYPE = LONARR(NUMCOLS)
549        BOFF1   = LONARR(NUMCOLS)
550        BOFF2   = LONARR(NUMCOLS)
551        TNULL_FLG = INTARR(NUMCOLS) ;; 1 if TNULLn column is present
552        TNULL_VAL = DBLARR(NUMCOLS) ;; value of TNULLn column if present
553        NROWS = ROW2-ROW1+1
554        FOR I = 0L, NUMCOLS-1 DO BEGIN
555
556            IF ~FOUND[I] THEN GOTO, LOOP_END_DIMS
557            ;;  Data type of the input.
558            IF VIRTUAL[I] THEN BEGIN
559                ; Virtual column: read from keyword itself
560                COLTYPE[I] = VIRTYPE[I]
561                GOTO, LOOP_END_DIMS
562            ENDIF ELSE IF VARICOL[I] THEN BEGIN
563                ; Variable length column: 2-element long
564                COLTYPE[I] = 3
565                DIMS = [1L, 2L]
566            ENDIF ELSE BEGIN
567                COLTYPE[I] = IDLTYPE[ICOL[I],ILUN]
568                DIMS = N_DIMS[*,ICOL[I],ILUN]
569            ENDELSE
570
571            NDIMS = DIMS[0]
572            DIMS  = DIMS[1:NDIMS]
573
574            IF NDIMS EQ 1 AND DIMS[0] EQ 1 THEN BEGIN
575
576                ;; Case of only one output element, try to return a
577                ;; scalar.  Otherwise, it is a vector equal to the
578                ;; number of rows to be read
579
580                COLNDIM[I] = 1L
581                COLDIM[I,0] = NROWS
582            ENDIF ELSE BEGIN
583
584                COLNDIM[I] = NDIMS
585                COLDIM[I,0:(NDIMS-1)] = DIMS
586                IF NROWS GT 1 THEN BEGIN
587                    COLDIM[I,NDIMS] = NROWS
588                    COLNDIM[I]++
589                ENDIF
590
591            ENDELSE
592
593            ;; For strings, the number of characters is the first
594            ;; dimension.  This information is useless to us now,
595            ;; since the STRING() type cast which will appear below
596            ;; handles the array conversion automatically.
597            IF COLTYPE[I] EQ 7 THEN BEGIN
598                IF COLNDIM[I] GT 1 THEN BEGIN
599                    COLDIM[I,0:COLNDIM[I]-2] = COLDIM[I,1:COLNDIM[I]-1]
600                    COLDIM[I,COLNDIM[I]-1]   = 0
601                    COLNDIM[I] = COLNDIM[I] - 1
602                ENDIF ELSE BEGIN  ;; Case of a single row
603                    COLNDIM[I] = 1L
604                    COLDIM[I,0] = NROWS
605                ENDELSE
606            ENDIF
607
608            ;; Byte offsets
609            BOFF1[I] = BYTOFF[ICOL[I],ILUN]
610            IF ICOL[I] EQ TFIELDS[ILUN]-1 THEN $
611              BOFF2[I] = NAXIS1[ILUN]-1 $
612            ELSE $
613              BOFF2[I] = BYTOFF[ICOL[I]+1,ILUN]-1
614
615            ;; TNULLn keywords for integer type columns
616            IF (COLTYPE[I] GE 1 AND COLTYPE[I] LE 3) OR $
617              (COLTYPE[I] GE 12 AND COLTYPE[I] LE 15) THEN BEGIN
618                TNULLn = 'TNULL'+STRTRIM(ICOL[I]+1,2)
619                VALUE = FXPAR(HEADER,TNULLn, Count = N_VALUE)
620                IF N_VALUE GT 0 THEN BEGIN
621                    TNULL_FLG[I] = 1
622                    TNULL_VAL[I] = VALUE
623                ENDIF
624            ENDIF
625
626            LOOP_END_DIMS:
627
628        ENDFOR
629
630;
631;  Construct any virtual columns first
632;
633        WC = WHERE(FOUND EQ 1 AND VIRTUAL EQ 1, WCCOUNT)
634        FOR I = 0L, WCCOUNT-1 DO BEGIN
635            ;; If it's virtual, then the value only needs to be
636            ;; replicated
637            EXTCMD = COLNAMES[WC[I]]+'= REPLICATE(D'+COLNAMES[WC[I]]+',NROWS)'
638            ;; Run the command that selects the data
639            RESULT = EXECUTE(EXTCMD)
640            IF RESULT EQ 0 THEN BEGIN
641                MESSAGE = 'ERROR: Could not extract data (column '+$
642                  STRTRIM(MYCOL[WC[I]],2)+')'
643                IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
644                    ERRMSG = MESSAGE
645                    RETURN
646                ENDIF ELSE MESSAGE, MESSAGE
647            ENDIF
648            OUTSTATUS[I] = 1
649        ENDFOR
650
651
652;  Skip to processing variable-length columns if all other columns are virtual
653        WC = WHERE(FOUND EQ 1 AND VIRTUAL EQ 0, WCCOUNT)
654        IF WCCOUNT EQ 0 THEN GOTO, PROC_CLEANUP
655
656;  Create NANVALUES, the template to use when a NAN is found
657        IF N_ELEMENTS(NANVALUE) GE NUMCOLS THEN BEGIN
658            NANVALUES = NANVALUE[0:NUMCOLS-1]
659        ENDIF ELSE IF N_ELEMENTS(NANVALUE) GT 0 THEN BEGIN
660            NANVALUES = REPLICATE(NANVALUE[0], NUMCOLS)
661            NANVALUES[0] = NANVALUE
662            I = N_ELEMENTS(NANVALUE)
663            IF I LT NUMCOLS THEN $
664              NANVALUES[I:*] = NANVALUE[0]
665        ENDIF
666
667;
668;  Find the position of the first byte of the data array in the file.
669;
670        OFFSET0 = NHEADER[ILUN] + NAXIS1[ILUN]*(ROW1-1LL)
671        POS = 0LL
672        NROWS0 = NROWS
673        J = 0LL
674        FIRST = 1
675        ;; Here, we constrain the buffer to be at least 16 rows long.
676        ;; If we fill up 32 kB with fewer than 16 rows, then there
677        ;; must be a lot of (big) columns in this table.  It's
678        ;; probably a candidate for using FXBREAD instead.
679        BUFFROWS = LONG((BUFFERSIZE/NAXIS1[ILUN]) > 16L)
680        IF BUFFERSIZE LE 0 THEN BUFFROWS = NROWS0
681
682;
683;  Loop through the data in chunks
684;
685        WHILE NROWS GT 0 DO BEGIN
686        J++
687        NR  = NROWS < BUFFROWS
688        OFFSET1 = NAXIS1[ILUN]*POS
689
690;
691;  Proceed by reading a byte array from the input data file
692;  FXBREADM reads all columns from the specified rows, and
693;  sorts out the details of which bytes belong to which columns
694;  in the next FOR loop.
695;
696        BB = BYTARR(NAXIS1[ILUN], NR)
697        POINT_LUN, UNIT, OFFSET0+OFFSET1
698        READU, UNIT, BB
699;        FXGSEEK, UNIT, OFFSET0+OFFSET1
700;        FXGREAD, UNIT, BB
701
702;
703;  Now select out the desired columns
704;
705        FOR I = 0, NUMCOLS-1 DO BEGIN
706
707            ;; Extract the proper rows and columns
708            IF ~FOUND[I] THEN GOTO, LOOP_END_STORE
709            IF VIRTUAL[I]   THEN GOTO, LOOP_END_STORE
710
711            ;; Extract the data from the byte array and convert it
712            ;; The inner CALL_FUNCTION is to one of the coercion
713            ;; functions, such as FIX(), DOUBLE(), STRING(), etc.,
714            ;; which is called with an offset to force a conversion
715            ;; from bytes to the data type.
716            ;; The outer CALL_FUNCTION is to REFORM(), which makes
717            ;; sure that the data structure is correct.
718            ;;
719            DIMS = COLDIM[I,0:COLNDIM[I]-1]
720            PERROW = ROUND(PRODUCT(DIMS)/NROWS0)
721
722            IF N_ELEMENTS(NANVALUES) GT 0 THEN $
723              EXTRA={NANVALUE: NANVALUES[I]}
724
725            FXBREADM_CONV, BB[BOFF1[I]:BOFF2[I], *], DD, COLTYPE[I], PERROW, NR,$
726              NOIEEE=KEYWORD_SET(NOIEEE), NOSCALE=KEYWORD_SET(NOSCALE), $
727              TZERO=TZERO[ICOL[I], ILUN], TSCAL=TSCAL[ICOL[I], ILUN], $
728              VARICOL=VARICOL[I], DEFAULT_FLOAT=DEFAULT_FLOAT, $
729              TNULL_VALUE=TNULL_VAL[I], TNULL_FLAG=TNULL_FLG[I], $
730              _EXTRA=EXTRA
731
732            ;; Initialize the output variable on the first chunk
733            IF FIRST THEN BEGIN
734                SZ = SIZE(DD)
735                ;; NOTE: type could have changed if TSCAL/TZERO were used
736                COLTYPEI = SZ(SZ[0]+1)
737                RESULT = EXECUTE(COLNAMES[I]+' = 0')
738                RESULT = EXECUTE(COLNAMES[I]+' = '+$
739                                 'MAKE_ARRAY(PERROW, NROWS0, TYPE=COLTYPEI)')
740                RESULT = EXECUTE(COLNAMES[I]+' = '+$
741                         'REFORM('+COLNAMES[I]+', PERROW, NROWS0,/OVERWRITE)')
742            ENDIF
743
744            ;; Finally, store this in the output variable
745            RESULT = EXECUTE(COLNAMES[I]+'[0,POS] = DD')
746            DD = 0
747            IF RESULT EQ 0 THEN BEGIN
748                MESSAGE = 'ERROR: Could not compose output data '+COLNAMES[I]
749                IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
750                    ERRMSG = MESSAGE
751                    RETURN
752                ENDIF ELSE MESSAGE, MESSAGE
753            ENDIF
754
755            OUTSTATUS[I] = 1
756
757            LOOP_END_STORE:
758        ENDFOR
759
760        FIRST = 0
761        NROWS = NROWS - NR
762        POS   = POS + NR
763        ENDWHILE
764
765;
766;  Read the variable-length columns from the heap.  Adjacent data are
767;  coalesced into one read operation.  Note: this technique is thus
768;  optimal for extensions with only one variable-length column.  If
769;  there are more than one then coalescence will not occur.
770;
771
772        ;; Width of the various data types in bytes
773        WIDARR = [0L, 1L, 2L, 4L, 4L, 8L, 8L, 1L, 0L,16L, 0L]
774        WV = WHERE(OUTSTATUS EQ 1 AND VARICOL EQ 1, WVCOUNT)
775        FOR J = 0, WVCOUNT-1 DO BEGIN
776            I = WV[J]
777            RESULT = EXECUTE('PDATA = '+COLNAMES[I])
778            NVALS = PDATA[0,*]          ;; Number of values in each row
779            NTOT  = ROUND(TOTAL(NVALS)) ;; Total number of values
780            IF NTOT EQ 0 THEN BEGIN
781                DD = {N_ELEMENTS: 0L, N_ROWS: NROWS0, $
782                      INDICES: LON64ARR(NROWS0+1), DATA: 0L}
783                GOTO, FILL_VARICOL
784            ENDIF
785
786            ;; Compute the width in bytes of the data value
787            TYPE = IDLTYPE[ICOL[I], ILUN]
788            WID = LONG64(WIDARR[TYPE < 10])
789            IF WID EQ 0 THEN BEGIN
790                OUTSTATUS[I] = 0
791                MESSAGE = 'ERROR: Column '+COLNAMES[I]+' has unknown data type'
792                IF N_ELEMENTS(ERRMSG) NE 0 THEN BEGIN
793                        ERRMSG = MESSAGE
794                        RETURN
795                END ELSE MESSAGE, MESSAGE
796            ENDIF
797
798            ;; Coalesce the data pointers
799            BOFF1 = LONG64(PDATA[1,*])
800            BOFF2 = BOFF1 + NVALS*WID
801            WH = WHERE(BOFF1[1:*] NE BOFF2, CT)
802            IF CT GT 0 THEN BI = [-1LL, WH, N_ELEMENTS(BOFF1)-1] $
803            ELSE            BI = [-1LL,     N_ELEMENTS(BOFF1)-1]
804            CT = CT + 1
805
806            ;; Create the output array
807            BC = BOFF2[BI[1:*]] - BOFF1[BI[0:CT-1]+1] ;; Byte count
808            NB = ROUND(TOTAL(BC))                     ;; Total # bytes
809            BB = BYTARR(NB)                           ;; Byte array
810
811            ;; Initialize the counter variables used in the read-loop
812            CC = 0LL & CC1 = 0LL & K = 0LL
813            BUFFROWS = ROUND(BUFFERSIZE/WID) > 128L
814            BASE = LONG64(NHEADER[ILUN]+HEAP[ILUN])
815
816            ;; Read data from file
817            WHILE CC LT NB DO BEGIN
818                NB1 = (BC[K]-CC1) < BUFFROWS
819                BB1 = BYTARR(NB1)
820
821                POINT_LUN, UNIT, BASE+BOFF1[BI[K]+1]+CC1
822                READU, UNIT, BB1
823;                FXGSEEK, UNIT, BASE+BOFF1[BI[K]+1]+CC1
824;                FXGREAD, UNIT, BB1
825                BB[CC] = TEMPORARY(BB1)
826
827                CC  = CC  + NB1
828                CC1 = CC1 + NB1
829                IF CC1 EQ BC[K] THEN BEGIN
830                    K = K + 1
831                    CC1 = 0L
832                ENDIF
833            ENDWHILE
834
835            ;; Convert the data
836            IF N_ELEMENTS(NANVALUES) GT 0 THEN $
837              EXTRA={NANVALUE: NANVALUES[I]}
838
839            FXBREADM_CONV, BB, DD, TYPE, NTOT, 1L, $
840              NOIEEE=KEYWORD_SET(NOIEEE), NOSCALE=KEYWORD_SET(NOSCALE), $
841              TZERO=TZERO[ICOL[I], ILUN], TSCAL=TSCAL[ICOL[I], ILUN], $
842              DEFAULT_FLOAT=DEFAULT_FLOAT, _EXTRA=EXTRA
843
844            ;; Ensure the correct dimensions, now that we know them
845            COLNDIM[I] = 1
846            COLDIM[I,0] = NTOT
847
848            ;; Construct the indices; unfortunately we need to make an
849            ;; accumulant with a FOR loop
850            INDICES = LON64ARR(NROWS0+1)
851            FOR K = 1LL, NROWS0 DO $
852              INDICES[K] = INDICES[K-1] + NVALS[K-1]
853
854            ;; Construct a structure with additional data
855            DD = {N_ELEMENTS: NTOT, N_ROWS: NROWS0, TYPE: TYPE, $
856                  INDICES: INDICES, DATA: TEMPORARY(DD)}
857
858            FILL_VARICOL:
859            RESULT = EXECUTE(COLNAMES[I] +' = TEMPORARY(DD)')
860        ENDFOR
861
862;
863;  Compose the output columns, which might need reforming
864;
865        FOR I = 0, NUMCOLS-1 DO BEGIN
866            IF OUTSTATUS[I] NE 1 THEN GOTO, LOOP_END_FINAL
867
868            ;; Extract the dimensions and name of the column data
869            DIMS = COLDIM[I,0:COLNDIM[I]-1]
870            NEL  = PRODUCT(DIMS)
871            CNAME = COLNAMES[I]
872            IF VARICOL[I] THEN CNAME = CNAME + '.DATA'
873
874            ;; Compose the reforming part
875            IF NEL EQ 1 THEN $
876              CMD = CNAME+'[0]' $
877            ELSE $
878              CMD = 'REFORM(TEMPORARY('+CNAME+'),DIMS,/OVERWRITE)'
879
880            ;; Variable-length columns return extra information
881            IF VARICOL[I] THEN BEGIN
882                CMD = ('{VARICOL:    1,'+$
883                       ' N_ELEMENTS: '+COLNAMES[I]+'.N_ELEMENTS, '+$
884                       ' TYPE:       '+COLNAMES[I]+'.TYPE, '+$
885                       ' N_ROWS:     '+COLNAMES[I]+'.N_ROWS, '+$
886                       ' INDICES:    '+COLNAMES[I]+'.INDICES, '+$
887                       ' DATA:       '+CMD+'}')
888            ENDIF
889
890            ;; Assign to pointer, or re-assign to column
891            IF PASS EQ 'ARGUMENT' THEN $
892              CMD = COLNAMES[I]+' = ' + CMD $
893            ELSE IF PASS EQ 'POINTER' THEN $
894              CMD = '*(POINTERS[I]) = ' + CMD
895
896            RESULT = EXECUTE(CMD)
897            LOOP_END_FINAL:
898        ENDFOR
899
900        PROC_CLEANUP:
901;
902        IF N_ELEMENTS(ERRMSG) NE 0 THEN ERRMSG = ''
903        RETURN
904
905        END
906