1        FUNCTION FXPAR, HDR, NAME, ABORT, COUNT=MATCHES, COMMENT=COMMENTS, $
2                        START=START, PRECHECK=PRECHECK, POSTCHECK=POSTCHECK, $
3                        NOCONTINUE = NOCONTINUE, DATATYPE=DATATYPE, $
4                        NULL=K_NULL, NAN=NAN, MISSING=MISSING
5;+
6; NAME:
7;        FXPAR()
8; PURPOSE:
9;       Obtain the value of a parameter in a FITS header.
10; EXPLANATION:
11;       The first 8 chacters of each element of HDR are searched for a match to
12;       NAME.  If the keyword is one of those allowed to take multiple values
13;       ("HISTORY", "COMMENT", or "        " (blank)), then the value is taken
14;       as the next 72 characters.  Otherwise, it is assumed that the next
15;       character is "=", and the value (and optional comment) is then parsed
16;       from the last 71 characters.  An error occurs if there is no parameter
17;       with the given name.
18;
19;       If the value is too long for one line, it may be continued on to the
20;       the next input card, using the CONTINUE Long String Keyword convention.
21;       For more info, http://fits.gsfc.nasa.gov/registry/continue_keyword.html
22;
23;
24;       Complex numbers are recognized as two numbers separated by one or more
25;       space characters.
26;
27;       If a numeric value has no decimal point (or E or D) it is returned as
28;       type LONG.  If it contains more than 8 numerals, or contains the
29;       character 'D', then it is returned as type DOUBLE.  Otherwise it is
30;       returned as type FLOAT.    If an integer is too large to be stored as
31;       type LONG, then it is returned as DOUBLE.
32;
33;       If a keyword is in the header and has no value, then the default
34;       missing value is returned as explained below.  This can be
35;       distinguished from the case where the keyword is not found by the fact
36;       that COUNT=0 in that case, while existing keywords without a value will
37;       be returned with COUNT=1 or more.
38;
39; CALLING SEQUENCE:
40;       Result = FXPAR( HDR, NAME  [, ABORT, COUNT=, COMMENT=, /NOCONTINUE ] )
41;
42;       Result = FXPAR(HEADER,'DATE')           ;Finds the value of DATE
43;       Result = FXPAR(HEADER,'NAXIS*')         ;Returns array dimensions as
44;                                               ;vector
45; REQUIRED INPUTS:
46;       HDR     = FITS header string array (e.g. as returned by FXREAD).  Each
47;                 element should have a length of 80 characters
48;       NAME    = String name of the parameter to return.  If NAME is of the
49;                 form 'keyword*' then an array is returned containing values
50;                 of keywordN where N is an integer.  The value of keywordN
51;                 will be placed in RESULT(N-1).  The data type of RESULT will
52;                 be the type of the first valid match of keywordN
53;                 found, unless DATATYPE is given.
54; OPTIONAL INPUT:
55;       ABORT   = String specifying that FXPAR should do a RETALL if a
56;                 parameter is not found.  ABORT should contain a string to be
57;                 printed if the keyword parameter is not found.  If not
58;                 supplied, FXPAR will return with a negative !err if a keyword
59;                 is not found.
60; OUTPUT:
61;       The returned value of the function is the value(s) associated with the
62;       requested keyword in the header array.
63;
64;       If the parameter is complex, double precision, floating point, long or
65;       string, then the result is of that type.  Apostrophes are stripped from
66;       strings.  If the parameter is logical, 1 is returned for T, and 0 is
67;       returned for F.
68;
69;       If NAME was of form 'keyword*' then a vector of values are returned.
70;
71; OPTIONAL INPUT KEYWORDS:
72;       DATATYPE = A scalar value, indicating the type of vector
73;                  data.  All keywords will be cast to this type.
74;                  Default: based on first keyword.
75;                  Example: DATATYPE=0.0D (cast data to double precision)
76;       START   = A best-guess starting position of the sought-after
77;                 keyword in the header.  If specified, then FXPAR
78;                 first searches for scalar keywords in the header in
79;                 the index range bounded by START-PRECHECK and
80;                 START+POSTCHECK.  This can speed up keyword searches
81;                 in large headers.  If the keyword is not found, then
82;                 FXPAR searches the entire header.
83;
84;                 If not specified then the entire header is searched.
85;                 Searches of the form 'keyword*' also search the
86;                 entire header and ignore START.
87;
88;                 Upon return START is changed to be the position of
89;                 the newly found keyword.  Thus the best way to
90;                 search for a series of keywords is to search for
91;                 them in the order they appear in the header like
92;                 this:
93;
94;                       START = 0L
95;                       P1 = FXPAR('P1', START=START)
96;                       P2 = FXPAR('P2', START=START)
97;
98;       PRECHECK = If START is specified, then PRECHECK is the number
99;                  of keywords preceding START to be searched.
100;                  Default: 5
101;       POSTCHECK = If START is specified, then POSTCHECK is the number
102;                   of keywords after START to be searched.
103;                   Default: 20
104;       /NOCONTINUE = If set, then continuation lines will not be read, even
105;                 if present in the header
106;       MISSING = By default, this routine returns 0 when keyword values are
107;                 not found.  This can be overridden by using the MISSING
108;                 keyword, e.g. MISSING=-1.
109;       /NAN    = If set, then return Not-a-Number (!values.f_nan) for missing
110;                 values.  Ignored if keyword MISSING is present.
111;       /NULL   = If set, then return !NULL (undefined) for missing values.
112;                 Ignored if MISSING or /NAN is present, or if earlier than IDL
113;                 version 8.0.  If multiple values would be returned, then
114;                 MISSING= or /NAN should be used instead of /NULL, making sure
115;                 that the datatype is consistent with the non-missing values,
116;                 e.g. MISSING='' for strings, MISSING=-1 for integers, or
117;                 MISSING=-1.0 or /NAN for floating point.  /NAN should not be
118;                 used if the datatype would otherwise be integer.
119; OPTIONAL OUTPUT KEYWORD:
120;       COUNT   = Optional keyword to return a value equal to the number of
121;                 parameters found by FXPAR.
122;       COMMENTS= Array of comments associated with the returned values.
123;
124; PROCEDURE CALLS:
125;       GETTOK(), VALID_NUM
126; SIDE EFFECTS:
127;
128;       The system variable !err is set to -1 if parameter not found, 0 for a
129;       scalar value returned.  If a vector is returned it is set to the number
130;       of keyword matches found.    This use of !ERR is deprecated.
131;
132;       If a keyword occurs more than once in a header, a warning is given,
133;       and the first occurence is used.  However, if the keyword is "HISTORY",
134;       "COMMENT", or "        " (blank), then multiple values are returned.
135;
136; NOTES:
137;	The functions SXPAR() and FXPAR() are nearly identical, although
138;	FXPAR() has slightly more sophisticated parsing.   There is no
139;	particular reason for having two nearly identical procedures, but
140;	both are too widely used to drop either one.
141;
142; REVISION HISTORY:
143;       Version 1, William Thompson, GSFC, 12 April 1993.
144;               Adapted from SXPAR
145;       Version 2, William Thompson, GSFC, 14 October 1994
146;               Modified to use VALID_NUM instead of STRNUMBER.  Inserted
147;               additional call to VALID_NUM to trap cases where character
148;               strings did not contain quotation marks.
149;       Version 3, William Thompson, GSFC, 22 December 1994
150;               Fixed bug with blank keywords, following suggestion by Wayne
151;               Landsman.
152;       Version 4, Mons Morrison, LMSAL, 9-Jan-98
153;               Made non-trailing ' for string tag just be a warning (not
154;               a fatal error).  It was needed because "sxaddpar" had an
155;               error which did not write tags properly for long strings
156;               (over 68 characters)
157;       Version 5, Wayne Landsman GSFC, 29 May 1998
158;               Fixed potential problem with overflow of LONG values
159;       Version 6, Craig Markwardt, GSFC, 28 Jan 1998,
160;               Added CONTINUE parsing
161;       Version 7, Craig Markwardt, GSFC, 18 Nov 1999,
162;               Added START, PRE/POSTCHECK keywords for better
163;               performance
164;       Version 8, Craig Markwardt, GSFC, 08 Oct 2003,
165;               Added DATATYPE keyword to cast vector keywords type
166;       Version 9, Paul Hick, 22 Oct 2003, Corrected bug (NHEADER-1)
167;       Version 10, W. Landsman, GSFC  2 May 2012
168;               Keywords of form "name_0" could confuse vector extractions
169;       Version 11 W. Landsman, GSFC 24 Apr 2014
170;               Don't convert LONG64 numbers to to double precision
171;       Version 12, William Thompson, 13-Aug-2014
172;               Add keywords MISSING, /NAN, and /NULL
173;		Version 13, W. Landsman 25-Jan-2018
174;				Return ULONG64 integer if LONG64 would overflow
175;-
176;------------------------------------------------------------------------------
177;
178;  Check the number of parameters.
179;
180        IF N_PARAMS() LT 2 THEN BEGIN
181            PRINT,'Syntax:  result =  FXPAR( HDR, NAME  [, ABORT ])'
182            RETURN, -1
183        ENDIF
184;
185;  Determine the default value for missing data.
186;
187        CASE 1 OF
188            N_ELEMENTS(MISSING) EQ 1: MISSING_VALUE = MISSING
189            KEYWORD_SET(NAN): MISSING_VALUE = !VALUES.F_NAN
190            KEYWORD_SET(K_NULL) AND !VERSION.RELEASE GE '8.': $
191              DUMMY = EXECUTE('MISSING_VALUE = !NULL')
192            ELSE: MISSING_VALUE = 0
193        ENDCASE
194        VALUE = MISSING_VALUE
195;
196;  Determine the abort condition.
197;
198        IF N_PARAMS() LE 2 THEN BEGIN
199            ABORT_RETURN = 0
200            ABORT = 'FITS Header'
201        END ELSE ABORT_RETURN = 1
202        IF ABORT_RETURN THEN ON_ERROR,1 ELSE ON_ERROR,2
203;
204;  Check for valid header.  Check header for proper attributes.
205;
206        S = SIZE(HDR)
207        IF ( S[0] NE 1 ) OR ( S[2] NE 7 ) THEN $
208            MESSAGE,'FITS Header (first parameter) must be a string array'
209;
210;  Convert the selected keyword NAME to uppercase.
211;
212        NAM = STRTRIM( STRUPCASE(NAME) )
213;
214;  Determine if NAME is of form 'keyword*'.  If so, then strip off the '*', and
215;  set the VECTOR flag.  One must consider the possibility that NAM is an empty
216;  string.
217;
218        NAMELENGTH1 = (STRLEN(NAM) - 1) > 1
219        IF STRPOS( NAM, '*' ) EQ NAMELENGTH1 THEN BEGIN
220            NAM = STRMID( NAM, 0, NAMELENGTH1)
221            VECTOR = 1                          ;Flag for vector output
222            NAME_LENGTH = STRLEN(NAM)           ;Length of name
223            NUM_LENGTH = 8 - NAME_LENGTH        ;Max length of number portion
224            IF NUM_LENGTH LE 0 THEN MESSAGE,    $
225                'Keyword length must be 8 characters or less'
226;
227;  Otherwise, extend NAME with blanks to eight characters.
228;
229        ENDIF ELSE BEGIN
230            WHILE STRLEN(NAM) LT 8 DO NAM = NAM + ' '
231            VECTOR = 0
232        ENDELSE
233;
234;  If of the form 'keyword*', then find all instances of 'keyword' followed by
235;  a number.  Store the positions of the located keywords in NFOUND, and the
236;  value of the number field in NUMBER.
237;
238        IF N_ELEMENTS(START)     EQ 0 THEN START = -1L
239        START = LONG(START[0])
240        IF NOT VECTOR AND START GE 0 THEN BEGIN
241            IF N_ELEMENTS(PRECHECK)  EQ 0 THEN PRECHECK = 5
242            IF N_ELEMENTS(POSTCHECK) EQ 0 THEN POSTCHECK = 20
243            NHEADER = N_ELEMENTS(HDR)
244            MN = (START - PRECHECK)  > 0
245            MX = (START + POSTCHECK) < (NHEADER-1)      ;Corrected bug
246            KEYWORD = STRMID(HDR[MN:MX], 0, 8)
247        ENDIF ELSE BEGIN
248            RESTART:
249            START   = -1L
250            KEYWORD = STRMID( HDR, 0, 8)
251        ENDELSE
252
253        IF VECTOR THEN BEGIN
254            NFOUND = WHERE(STRPOS(KEYWORD,NAM) GE 0, MATCHES)
255            IF ( MATCHES GT 0 ) THEN BEGIN
256                NUMST= STRMID(HDR[NFOUND], NAME_LENGTH, NUM_LENGTH)
257                NUMBER = INTARR(MATCHES)-1
258                FOR I = 0, MATCHES-1 DO         $
259                    IF VALID_NUM( NUMST[I], NUM) THEN NUMBER[I] = NUM
260                IGOOD = WHERE(NUMBER GE 0, MATCHES)
261                IF MATCHES GT 0 THEN BEGIN
262                    NFOUND = NFOUND[IGOOD]
263                    NUMBER = NUMBER[IGOOD]
264 		    G = WHERE(NUMBER GT 0, MATCHES)
265 		    IF MATCHES GT 0 THEN NUMBER = NUMBER[G]
266		ENDIF
267            ENDIF
268;
269;  Otherwise, find all the instances of the requested keyword.  If more than
270;  one is found, and NAME is not one of the special cases, then print an error
271;  message.
272;
273        ENDIF ELSE BEGIN
274            NFOUND = WHERE(KEYWORD EQ NAM, MATCHES)
275            IF MATCHES EQ 0 AND START GE 0 THEN GOTO, RESTART
276            IF START GE 0 THEN NFOUND = NFOUND + MN
277            IF (MATCHES GT 1) AND (NAM NE 'HISTORY ') AND               $
278                (NAM NE 'COMMENT ') AND (NAM NE '') THEN        $
279                MESSAGE,/INFORMATIONAL, 'WARNING- Keyword ' +   $
280                NAM + 'located more than once in ' + ABORT
281            IF (MATCHES GT 0) THEN START = NFOUND[MATCHES-1]
282        ENDELSE
283;
284;  Extract the parameter field from the specified header lines.  If one of the
285;  special cases, then done.
286;
287        IF MATCHES GT 0 THEN BEGIN
288            VALUE = MISSING_VALUE
289            LINE = HDR[NFOUND]
290            SVALUE = STRTRIM( STRMID(LINE,9,71),2)
291            IF (NAM EQ 'HISTORY ') OR (NAM EQ 'COMMENT ') OR    $
292                    (NAM EQ '        ') THEN BEGIN
293                VALUE = STRTRIM( STRMID(LINE,8,72),2)
294                COMMENTS = STRARR(N_ELEMENTS(VALUE))
295;
296;  Otherwise, test to see if the parameter contains a string, signalled by
297;  beginning with a single quote character (') (apostrophe).
298;
299            END ELSE FOR I = 0,MATCHES-1 DO BEGIN
300                IF ( STRMID(SVALUE[I],0,1) EQ "'" ) THEN BEGIN
301                    TEST = STRMID( SVALUE[I],1,STRLEN( SVALUE[I] )-1)
302                    NEXT_CHAR = 0
303                    OFF = 0
304                    VALUE = ''
305;
306;  Find the next apostrophe.
307;
308NEXT_APOST:
309                    ENDAP = STRPOS(TEST, "'", NEXT_CHAR)
310                    IF ENDAP LT 0 THEN MESSAGE,         $
311                        'WARNING: Value of '+NAME+' invalid in '+ABORT+ " (no trailing ')", /info
312                    VALUE = VALUE + STRMID( TEST, NEXT_CHAR, ENDAP-NEXT_CHAR )
313;
314;  Test to see if the next character is also an apostrophe.  If so, then the
315;  string isn't completed yet.  Apostrophes in the text string are signalled as
316;  two apostrophes in a row.
317;
318                    IF STRMID( TEST, ENDAP+1, 1) EQ "'" THEN BEGIN
319                        VALUE = VALUE + "'"
320                        NEXT_CHAR = ENDAP+2
321                        GOTO, NEXT_APOST
322                    ENDIF
323;
324;  Extract the comment, if any.
325;
326                    SLASH = STRPOS(TEST, "/", ENDAP)
327                    IF SLASH LT 0 THEN COMMENT = '' ELSE        $
328                        COMMENT = STRMID(TEST, SLASH+1, STRLEN(TEST)-SLASH-1)
329
330;
331; CM 19 Sep 1997
332; This is a string that could be continued on the next line.  Check this
333; possibility with the following four criteria: *1) Ends with '&'
334; (2) Next line is CONTINUE  (3) LONGSTRN keyword is present (recursive call to
335;  FXPAR) 4. /NOCONTINE is not set
336
337    IF NOT KEYWORD_SET(NOCONTINUE) THEN BEGIN
338                    OFF = OFF + 1
339                    VAL = STRTRIM(VALUE,2)
340
341                    IF (STRLEN(VAL) GT 0) AND $
342                      (STRMID(VAL, STRLEN(VAL)-1, 1) EQ '&') AND $
343                      (STRMID(HDR[NFOUND[I]+OFF],0,8) EQ 'CONTINUE') THEN BEGIN
344                       IF (SIZE(FXPAR(HDR, 'LONGSTRN',/NOCONTINUE)))[1] EQ 7 THEN BEGIN
345                      VALUE = STRMID(VAL, 0, STRLEN(VAL)-1)
346                      TEST = HDR[NFOUND[I]+OFF]
347                      TEST = STRMID(TEST, 8, STRLEN(TEST)-8)
348                      TEST = STRTRIM(TEST, 2)
349                      IF STRMID(TEST, 0, 1) NE "'" THEN MESSAGE, $
350                        'ERROR: Invalidly CONTINUEd string in '+ABORT
351                      NEXT_CHAR = 1
352                      GOTO, NEXT_APOST
353                    ENDIF
354                   ENDIF
355    ENDIF
356
357;
358;  If not a string, then separate the parameter field from the comment field.
359;  If there is no value field, then use the default "missing" value.
360;
361                ENDIF ELSE BEGIN
362                    VALUE = MISSING_VALUE
363                    TEST = SVALUE[I]
364                    IF TEST EQ '' THEN BEGIN
365                        COMMENT = ''
366                        GOTO, GOT_VALUE
367                    ENDIF
368                    SLASH = STRPOS(TEST, "/")
369                    IF SLASH GE 0 THEN BEGIN
370                        COMMENT = STRMID(TEST, SLASH+1, STRLEN(TEST)-SLASH-1)
371                        IF SLASH GT 0 THEN TEST = STRMID(TEST, 0, SLASH) ELSE $
372                            GOTO, GOT_VALUE
373                    END ELSE COMMENT = ''
374;
375;  Find the first word in TEST.  Is it a logical value ('T' or 'F')?
376;
377                    TEST2 = TEST
378                    VALUE = GETTOK(TEST2,' ')
379                    TEST2 = STRTRIM(TEST2,2)
380                    IF ( VALUE EQ 'T' ) THEN BEGIN
381                        VALUE = 1
382                    END ELSE IF ( VALUE EQ 'F' ) THEN BEGIN
383                        VALUE = 0
384                    END ELSE BEGIN
385;
386;  Test to see if a complex number.  It's a complex number if the value and the
387;  next word, if any, both are valid numbers.
388;
389                        IF STRLEN(TEST2) EQ 0 THEN GOTO, NOT_COMPLEX
390                        VALUE2 = GETTOK(TEST2,' ')
391                        IF VALID_NUM(VALUE,VAL1) AND VALID_NUM(VALUE2,VAL2) $
392                                THEN BEGIN
393                            VALUE = COMPLEX(VAL1,VAL2)
394                            GOTO, GOT_VALUE
395                        ENDIF
396;
397;  Not a complex number.  Decide if it is a floating point, double precision,
398;  or integer number.  If an error occurs, then a string value is returned.
399;  If the integer is not within the range of a valid long value, then it will
400;  be converted to a double.
401;
402NOT_COMPLEX:
403                        ON_IOERROR, GOT_VALUE
404                        VALUE = TEST
405                        IF NOT VALID_NUM(VALUE) THEN GOTO, GOT_VALUE
406                        IF (STRPOS(VALUE,'.') GE 0) OR (STRPOS(VALUE,'E') $
407                                GE 0) OR (STRPOS(VALUE,'D') GE 0) THEN BEGIN
408                            IF ( STRPOS(VALUE,'D') GT 0 ) OR $
409                                    ( STRLEN(VALUE) GE 8 ) THEN BEGIN
410                            	VALUE = DOUBLE(VALUE)
411                                END ELSE VALUE = FLOAT(VALUE)
412                        ENDIF ELSE BEGIN
413                            LMAX = 2.0D^31 - 1.0D
414                            LMIN = -2.0D^31       ;Typo fixed Feb 2010
415                            IF STRMID(VALUE,0,1) NE '-' THEN BEGIN
416                            	VALUE = ULONG64(VALUE)
417                            	IF VALUE LT ULONG64(2)^63-1 THEN VALUE = LONG64(VALUE)
418                            ENDIF ELSE VALUE = LONG64(VALUE)
419                            if (VALUE GE LMIN) and (VALUE LE LMAX) THEN $
420                                VALUE = LONG(VALUE)
421                        ENDELSE
422
423;
424GOT_VALUE:
425                        ON_IOERROR, NULL
426                    ENDELSE
427                ENDELSE         ; if string
428;
429;  Add to vector if required.
430;
431                IF VECTOR THEN BEGIN
432                    MAXNUM = MAX(NUMBER)
433                    IF ( I EQ 0 ) THEN BEGIN
434                        IF N_ELEMENTS(DATATYPE) EQ 0 THEN BEGIN
435                            ;; Data type determined from keyword
436                            SZ_VALUE = SIZE(VALUE)
437                        ENDIF ELSE BEGIN
438                            ;; Data type requested by user
439                            SZ_VALUE = SIZE(DATATYPE[0])
440                        ENDELSE
441                        RESULT = MAKE_ARRAY( MAXNUM, TYPE=SZ_VALUE[1])
442                        COMMENTS = STRARR(MAXNUM)
443                    ENDIF
444                    RESULT[   NUMBER[I]-1 ] =  VALUE
445                    COMMENTS[ NUMBER[I]-1 ] =  COMMENT
446                ENDIF ELSE BEGIN
447                    COMMENTS = COMMENT
448                ENDELSE
449            ENDFOR
450;
451;  Set the value of !ERR for the number of matches for vectors, or simply 0
452;  otherwise.
453;
454            IF VECTOR THEN BEGIN
455                !ERR = MATCHES
456                RETURN, RESULT
457            ENDIF ELSE !ERR = 0
458;
459;  Error point for keyword not found.
460;
461        ENDIF ELSE BEGIN
462            IF ABORT_RETURN THEN MESSAGE,'Keyword '+NAM+' not found in '+ABORT
463            !ERR = -1
464        ENDELSE
465;
466        RETURN, VALUE
467        END
468