chiark / gitweb /
Various changes of a plausible nature.
[ssr] / StraySrc / Libraries / Sapphire / choices / s / options
1 ;
2 ; choices.options.s
3 ;
4 ; Read options from an options chunk (MDW)
5 ;
6 ; © 1995 Straylight
7 ;
8
9 ;----- Standard header ------------------------------------------------------
10
11                 GET     libs:header
12                 GET     libs:swis
13
14                 GET     libs:stream
15
16 ;----- External dependencies ------------------------------------------------
17
18                 GET     sapphire:chunk
19                 GET     sapphire:divide
20                 GET     sapphire:flex
21                 GET     sapphire:string
22
23
24                 GET     sapphire:xfer.xsave
25
26 ;----- Main code ------------------------------------------------------------
27
28                 AREA    |Sapphire$$Code|,CODE,READONLY
29
30 ; --- options_read ---
31 ;
32 ; On entry:     R0 == chunk file handle
33 ;               R1 == pointer to a chunk name
34 ;               R2 == pointer to options definition
35 ;               R3,R4 specify address of output block
36 ;
37 ; On exit:      --
38 ;
39 ; Use:          Claims the specified options chunk, and reads the data in
40 ;               it into a binary block.  Because the output data might be
41 ;               in a flex block, the two registers R3,R4 which define its
42 ;               address work as follows:
43 ;
44 ;               R3 == address or offset of data
45 ;               R4 == -1 if R3 is address, else flex anchor address
46
47                 EXPORT  options_read
48 options_read    ROUT
49
50                 STMFD   R13!,{R0-R10,R14}       ;Save some registers
51                 MOV     R5,R3                   ;Move output block address
52                 MOV     R6,R4                   ;Somewhere safe
53                 MOV     R3,R2                   ;Put definition in R10
54                 MOV     R4,#0                   ;I have no workspace
55                 ADR     R2,options__saver       ;Point to options saver
56                 BL      chunk_claim             ;Claim this chunk
57                 BVS     %90options_read         ;If it failed, return
58
59                 STMIB   R1,{R3,R5,R6}           ;Save def and output block
60                 STMFD   R13!,{R1}               ;Look after this address
61
62                 ; --- Start work on parsing the block ---
63
64                 CMP     R6,#-1                  ;Is this a flex block?
65                 LDRNE   R6,[R6]                 ;Yes -- load the anchor
66                 ADDNE   R5,R6,R5                ;And find the output address
67                 MOV     R6,R5                   ;Copy address over to R6
68
69                 MOV     R0,R1                   ;Point to flex anchor
70                 BL      flex_size               ;Find the block size
71                 LDR     R4,[R1]                 ;Load the block base
72                 ADD     R5,R4,R0                ;Find limit of anchor
73
74                 ; --- State 0: Newline ---
75
76 opt__newline    ADR     R7,%f00                 ;Where to go on newline
77                 ADR     R8,opt__end             ;Where to go on EOF
78                 ADR     R9,opt__comment         ;Where to go on comment
79                 ADR     R10,%f00                ;Where to go on whitespace
80 00              BL      opt__nextChar           ;Get another character
81                 ADR     R7,opt__newline         ;Start all over on newline
82
83                 ; --- State 1: Read an option name ---
84
85 opt__optName    MOV     R1,R11                  ;Find start of name buffer
86                 ADR     R10,opt__equals         ;On whitespace, find equals
87 00              STRB    R0,[R1],#1              ;Save this first byte
88                 BL      opt__nextChar           ;Get the next byte ready
89                 CMP     R0,#'='                 ;Is this an equals
90                 BNE     %b00                    ;Otherwise branch back
91                 B       opt__wsArg              ;Yes -- skip ws and get arg
92
93                 ; --- State 2: Skip optional `=' sign ---
94
95 opt__equals     BL      opt__nextChar           ;Get another character
96                 CMP     R0,#'='                 ;Is this an equals
97                 BNE     opt__arg                ;No -- start on the argument
98
99                 ; --- State 3: Skip leading whitespace on argument ---
100
101 opt__wsArg      ADR     R10,%f00                ;On whitespace, loop
102 00              BL      opt__nextChar           ;Get another character
103
104                 ; --- State 4: Read the argument ---
105                 ;
106                 ; Here we just sort out what to do next; we don't actually
107                 ; read anything.
108
109 opt__arg        MOV     R14,#0                  ;Null terminate the name
110                 STRB    R14,[R1],#1             ;Stuff that on the end
111
112                 BL      str_buffer              ;Get a string buffer
113                 MOV     R2,R1                   ;Look after its address
114
115                 ADR     R7,opt__readArg         ;Stop reading at newline
116                 ADR     R8,opt__readArg         ;Or at end of file
117
118                 CMP     R0,#'`'                 ;A leading backquote is...
119                 MOVEQ   R0,#'''                 ;... the same as a quote
120                 CMPNE   R0,#'''                 ;Is string in single quotes?
121                 CMPNE   R0,#'"'                 ;Is string in double quotes?
122                 BEQ     opt__quote              ;Yes -- handle that
123
124                 ; --- State 5: Read undelimited argument ---
125
126 opt__undelim    ADR     R9,opt__readArg         ;Stop at comment chars too
127                 ADR     R10,%f00                ;But whitespace is important
128 00              STRB    R0,[R1],#1              ;Store byte in buffer
129                 BL      opt__nextChar           ;Get another character
130                 B       %b00                    ;And keep on going
131
132                 ; --- State 6: Read quote delimited argument ---
133                 ;
134                 ; Here we don't use the normal nextChar system, because (a)
135                 ; we'd need to turn most of it off, and (b) I need a
136                 ; register!
137
138 opt__quote      MOV     R14,R0                  ;Look after delimiter
139
140 00              CMP     R4,R5                   ;Finished yet?
141                 LDRCCB  R0,[R4],#1              ;Load a byte from the block
142                 MOVCS   R0,#-1                  ;Otherwise say it's -1
143
144                 CMP     R0,#&0A                 ;Found a newline here?
145                 CMPNE   R0,#-1                  ;Or the end of file?
146                 BEQ     opt__readArg            ;Yes -- stop going then
147
148                 CMP     R0,R14                  ;Is this a quote character?
149                 STRNEB  R0,[R1],#1              ;No -- stuff it in the buffer
150                 BNE     %b00                    ;And leap backwards
151
152                 CMP     R4,R5                   ;Finished yet?
153                 LDRCCB  R0,[R4],#1              ;Load a byte from the block
154                 MOVCS   R0,#-1                  ;Otherwise say it's -1
155                 CMP     R0,R14                  ;Is the quote doubled?
156                 STREQB  R0,[R1],#1              ;Yes -- stuff in the buffer
157                 BEQ     %b00                    ;And leap backwards
158
159                 ; --- State 7: Skip the rest of the line ---
160                 ;
161                 ; We must have (a) reached the end of the line/file, (b)
162                 ; found a comment start, or (c) finished a delimited string.
163                 ; In all these cases we should skip on until the start of
164                 ; a line (unless we're already there, of course).
165
166 opt__readArg    CMP     R0,#&0A                 ;Was that a line end?
167                 CMPNE   R0,#-1                  ;Or the end of it all?
168                 CMPNE   R4,R5                   ;Finished yet?
169                 LDRNEB  R0,[R4],#1              ;Load a byte from the block
170                 BNE     opt__readArg            ;And see if we skip that too
171
172                 ; --- State 8: Finally we can get on with the search ---
173
174 opt__search     MOV     R14,#0                  ;Terminate the string
175                 STRB    R14,[R1],#1             ;Store that on the end
176
177                 MOV     R10,R3                  ;Find the option block base
178 00              ADD     R0,R10,#opt_name        ;Find the option name
179                 MOV     R1,R11                  ;Point to our option name
180                 BL      str_icmp                ;Compare the strings
181                 BEQ     opt__read               ;Match -- handle that
182                 LDMIA   R10,{R7,R8}             ;Load flags and size
183                 TST     R7,#optFlag_last        ;Is this the last entry?
184                 ADDEQ   R10,R10,R8              ;No -- move on to next one
185                 BEQ     %b00                    ;And loop back again
186                 B       opt__newline            ;No joy -- try the next line
187
188                 ; --- Found a matching block -- call parser ---
189
190 opt__read       LDMIA   R10,{R0,R1,R7,R8}       ;Load all the data out
191                 TST     R7,#optFlag_ignore      ;Are we meant to read this?
192                 BNE     opt__newline            ;No -- ignore it then
193                 MOV     R1,R2                   ;Point to argument string
194                 MOV     R2,R8                   ;Look after the type addr
195                 ADD     R8,R10,#opt_name        ;Point to official name
196                 ADD     R10,R6,R7               ;Find binary rep buffer
197                 MOV     R9,R8                   ;Point to name start
198                 MOV     R7,R0                   ;And get the flags word
199
200 00              LDRB    R14,[R9],#1             ;Load byte from name
201                 CMP     R14,#&20                ;Is this the end yet?
202                 BCS     %b00                    ;No -- keep looking then
203                 ADD     R9,R9,#3                ;Now word align pointer
204                 BIC     R9,R9,#3                ;This is type-specific ptr
205
206                 MOV     R0,#optReason_read      ;Tell routine to read
207                 MOV     R14,PC                  ;Set up return address
208                 MOV     PC,R2                   ;And call the routine
209                 B       opt__newline            ;And try the next line
210
211                 ; --- Read a comment ---
212
213 opt__comment    CMP     R4,R5                   ;Finished yet?
214                 LDRNEB  R0,[R4],#1              ;Load a byte from the block
215                 CMPNE   R0,#&0A                 ;Was that a line end?
216                 BNE     opt__comment            ;And see if we skip that too
217                 B       opt__newline            ;Try the next line now
218
219                 ; --- Reached the very end finally ---
220
221 opt__end        LDMFD   R13!,{R0}               ;Load the anchor block
222                 MOV     R1,#0                   ;Don't free -- just reduce
223                 BL      flex_extend             ;No longer need this
224                 MOV     R14,#0                  ;Zero the anchor now
225                 STR     R14,[R0,#0]             ;To make things happy
226
227 90options_read  LDMFD   R13!,{R0-R10,PC}^       ;Return to caller at last
228
229                 ; --- opt__nextChar ---
230                 ;
231                 ; In a somewhat strange attempt to keep code size down, we
232                 ; do checking for lots of strange characters here.  Addresses
233                 ; of bits of code to call on newlines, comments etc. are
234                 ; held in registers.  Most of the time, then, you don't
235                 ; even need an explicit loop.  For example
236                 ;
237                 ;   ADR R10,{PC}+4
238                 ;   BL opt__nextChar
239                 ;
240                 ; skips whitespace all by itself.
241
242 opt__nextChar   CMP     R4,R5                   ;Finished yet?
243                 LDRCCB  R0,[R4],#1              ;Load a byte from the block
244                 MOVCS   R0,#-1                  ;Otherwise say it's -1
245
246                 CMP     R0,#';'                 ;Maybe this is a comment
247                 CMPNE   R0,#'#'                 ;Or maybe a different comment
248                 CMPNE   R0,#'|'                 ;Or yet another one
249                 MOVEQ   PC,R9                   ;Yes -- handle that then
250                 CMP     R0,#&0A                 ;Found a newline here?
251                 MOVEQ   PC,R7                   ;Yes -- don't mind that
252                 CMP     R0,#-1                  ;Is this end-of-file?
253                 MOVEQ   PC,R8                   ;Yes -- tidy up then
254                 CMP     R0,#&20                 ;Is this a space
255                 CMPNE   R0,#&09                 ;Or maybe a tab
256                 MOVEQ   PC,R10                  ;Yes -- handle that
257                 MOVS    PC,R14                  ;Otherwise return to caller
258
259                 LTORG
260
261 ; --- options__saver ---
262 ;
263 ; On entry:     R0 == address of chunk anchor
264 ;               R10 == pointer to options definition
265 ;
266 ; On exit:      May return an error
267 ;
268 ; Use:          Saves a binary block of data as textual options.
269
270 options__saver  ROUT
271
272                 STMFD   R13!,{R0-R10,R14}       ;Save loads of registers
273                 LDMIB   R0,{R4-R6}              ;Load data from the anchor
274                 CMP     R6,#-1                  ;Is data in a flex block?
275                 LDRNE   R6,[R6,#0]              ;Yes -- load block base
276                 ADDNE   R5,R6,R5                ;And add that to the offset
277                 MOV     R6,R5                   ;Put base in different reg
278
279                 ; --- Start work now ---
280
281 10              LDMFD   R4,{R7-R10}             ;Load values from table
282                 MOV     R2,R10                  ;Look after call address
283                 ADD     R10,R6,R9               ;Find the binary data field
284                 ADD     R9,R4,#opt_name         ;Find the option name
285                 ADD     R4,R4,R8                ;Move on to next block
286                 MOV     R8,R9                   ;Point to the name again
287
288 00              LDRB    R14,[R9],#1             ;Load byte from the name
289                 CMP     R14,#&20                ;Reached the end yet?
290                 BCS     %b00                    ;No -- keep looking
291                 ADD     R9,R9,#3                ;Word align to find the
292                 BIC     R9,R9,#3                ;Type-specific data
293
294                 MOV     R0,#optReason_write     ;Tell parser to write
295                 MOV     R14,PC                  ;Set up return address
296                 MOV     PC,R2                   ;And call the routine
297                 MOVVC   R0,#&0A                 ;Write final newline
298                 BLVC    xsave_byte              ;Write that out
299                 BVS     %99options__saver       ;If it failed, stop now
300                 TST     R7,#optFlag_last        ;Was that the last block?
301                 BEQ     %b10                    ;No -- skip back then
302
303                 MOV     R0,#&0A                 ;Terminate with two newlines
304                 BL      xsave_byte              ;Write that out
305                 LDMVCFD R13!,{R0-R10,R14}       ;Restore registers
306                 BICVCS  PC,R14,#V_flag          ;And return with no errors
307
308 99              ADD     R13,R13,#4              ;Don't restore R0 on exit
309                 LDMFD   R13!,{R1-R10,R14}       ;Restore registers
310                 ORRS    PC,R14,#V_flag          ;And return with the error
311
312                 LTORG
313
314 ; --- options_write ---
315 ;
316 ; On entry:     R0 == terminator character to write, 0 for none, or -1 for
317 ;                       quoting with 's
318 ;               R1 == pointer to name to save
319 ;
320 ; On exit:      May return an error
321 ;
322 ; Use:          Writes out an option name, terminated with the character
323 ;               given in R0 (which will normally be a space or an `=' sign).
324
325                 EXPORT  options_write
326 options_write   ROUT
327
328                 STMFD   R13!,{R0-R2,R14}        ;Save some registers
329                 MOV     R2,R0                   ;Look after terminator
330
331                 CMP     R2,#-1                  ;Are we quoting strings?
332                 MOVEQ   R0,#'''                 ;Yes -- write initial '
333                 BLEQ    xsave_byte              ;Write that out
334                 BVS     %90options_write        ;If it failed, return error
335
336 00              LDRB    R0,[R1],#1              ;Load next byte of string
337                 CMP     R0,#&20                 ;Is this the end yet?
338                 BCC     %f00                    ;Yes -- deal with that
339                 BL      xsave_byte              ;Write that out
340                 BVS     %90options_write        ;If it failed, return error
341                 CMP     R2,#-1                  ;Are we quoting?
342                 CMPEQ   R0,#'''                 ;Writing a quote?
343                 BNE     %b00                    ;No -- skip back then
344                 BL      xsave_byte              ;Write out a second quote
345                 BVC     %b00                    ;And loop back round
346                 BVS     %90options_write        ;If it failed, return error
347
348 00              CMP     R2,#-1                  ;Are we quoting?
349                 MOVEQ   R2,#'''                 ;Yes -- terminate with '
350                 MOVS    R0,R2                   ;Get terminator char
351                 BLNE    xsave_byte              ;Write that byte out
352                 LDMVCFD R13!,{R0-R2,R14}        ;If OK, restore registers
353                 BICVCS  PC,R14,#V_flag          ;And return without error
354
355 90options_write ADD     R13,R13,#4              ;Don't restore R0 on exit
356                 LDMFD   R13!,{R1,R2,R14}        ;Restore registers
357                 ORRS    PC,R14,#V_flag          ;And return
358
359                 LTORG
360
361 ;----- Standard data types --------------------------------------------------
362
363 ; --- optType_string ---
364 ;
365 ; Flags:        --
366 ;
367 ; Data:         (word) buffer size of string
368 ;
369 ; Use:          Handles string data.  The binary representation is a ctrl
370 ;               terminated string.  The textual representation is a sequence
371 ;               of characters, which is always output in single quotes,
372 ;               although this is not necessary for the input.  The string
373 ;               will be truncated to fit in the buffer during reading.
374
375                 EXPORT  optType_string
376 optType_string  ROUT
377
378                 CMP     R0,#2                   ;Do I understand this?
379                 ADDCC   PC,PC,R0,LSL #2         ;Yes -- dispatch then
380                 MOVS    PC,R14                  ;Otherwise just return
381
382                 B       %50optType_string       ;Read a string
383
384                 ; --- Write the string out ---
385
386                 STMFD   R13!,{R14}              ;Save some registers
387                 MOV     R0,#'='                 ;Write a trailing `=' sign
388                 MOV     R1,R8                   ;Point to option name
389                 BL      options_write           ;Write the name out
390                 MOVVC   R0,#-1                  ;Now quote output string
391                 MOVVC   R1,R10                  ;Get string to write
392                 BLVC    options_write           ;Write the string out too
393                 LDMFD   R13!,{PC}               ;And return to caller
394
395                 ; --- Read a string in ---
396
397 50              LDR     R2,[R9,#0]              ;Load the buffer size
398 00              LDRB    R0,[R1],#1              ;Load next byte from string
399                 CMP     R0,#&20                 ;Is this the end yet?
400                 SUBCSS  R2,R2,#1                ;No -- decrement size
401                 MOVCC   R0,#0                   ;If at end, write a 0
402                 STRB    R0,[R10],#1             ;Write that out nicely
403                 BCS     %b00                    ;And loop round for more
404                 MOVS    PC,R14                  ;Return to caller finally
405
406                 LTORG
407
408 ; --- optType_integer ---
409 ;
410 ; Flags:        bit 8 == use given default base
411 ;
412 ; Data:         (word) default base, if bit 8 set
413 ;
414 ; Use:          Handles integer data.  The binary representation is a 32-
415 ;               bit integer value.  The textual representation is the normal
416 ;               RISC OS style of numbers (i.e. the base_value notation is
417 ;               supported).  Numbers are always output in the default base
418 ;               given (or in decimal if there is none given).  Numbers
419 ;               being read may always have a sign; numbers will only be
420 ;               output with a sign if the default base is decimal.  Uppercase
421 ;               letters will be used for output, but any case is acceptable
422 ;               for input.
423 ;
424 ;               Special prefixes allowed are `%' for binary and `&' for hex.
425 ;               Such numbers are always output with these prefixes.
426
427                 EXPORT  optType_integer
428 optType_integer ROUT
429
430                 CMP     R0,#2                   ;Do I understand this?
431                 ADDCC   PC,PC,R0,LSL #2         ;Yes -- dispatch then
432                 MOVS    PC,R14                  ;Otherwise just return
433
434                 B       %50optType_integer      ;Read an integer
435
436                 ; --- Write an integer ---
437
438                 STMFD   R13!,{R3-R5,R14}        ;Save some registers
439                 MOV     R0,#'='                 ;Write a trailing `=' sign
440                 MOV     R1,R8                   ;Point to the option name
441                 BL      options_write           ;Write the name out
442                 LDMVSFD R13!,{R3-R5,PC}         ;If it failed, die
443
444                 ; --- Write out a suitable prefix ---
445
446                 TST     R7,#(1<<8)              ;Is there a base given?
447                 LDRNE   R5,[R9],#4              ;Yes -- load the base
448                 MOVEQ   R5,#10                  ;Otherwise use decimal
449                 LDR     R3,[R10,#0]             ;Load the integer
450
451                 CMP     R5,#10                  ;Writing in decimal?
452                 TSTEQ   R3,#(1<<31)             ;And the number's positive?
453                 BEQ     %10optType_integer      ;Yes -- skip onwards
454
455                 MOV     R0,#0                   ;Initially, no char to write
456                 CMP     R5,#10                  ;Now, is it decimal?
457                 EOREQ   R0,R0,#'-' :EOR: '&'    ;Yes -- write a `-'
458                 RSBEQ   R3,R3,#0                ;And also negate it
459                 CMPNE   R5,#16                  ;Or maybe hex?
460                 EOREQ   R0,R0,#'&' :EOR: '%'    ;Yes -- write a `&'
461                 CMPNE   R5,#2                   ;Or lastly binary?
462                 EOREQ   R0,R0,#'%'              ;Yes -- write a `%'
463                 BLEQ    xsave_byte              ;Write that byte out
464                 LDMVSFD R13!,{R3-R5,PC}         ;If it failed, die
465                 BEQ     %10optType_integer      ;And skip onwards
466
467                 MOV     R0,R5                   ;Get the base in decimal
468                 MOV     R1,R11                  ;Point into scratchpad
469                 MOV     R2,#256                 ;Give typical size for this
470                 SWI     OS_ConvertInteger4      ;Convert it to an integer
471                 MOV     R1,R11                  ;Point to the buffer
472 00              LDRB    R0,[R1],#1              ;Load next byte
473                 CMP     R0,#&20                 ;Finished yet?
474                 MOVCC   R0,#'_'                 ;Yes -- finish with `_'
475                 BL      xsave_byte              ;Write out the byte
476                 LDMVSFD R13!,{R3-R5,PC}         ;If it failed, die
477                 BCS     %b00                    ;And keep on going
478
479                 ; --- Build the string in the scratchpad ---
480
481 10              MOV     R4,R11                  ;Start a pointer into R11
482                 MOV     R0,R3                   ;Get the number to write
483 00              MOV     R1,R5                   ;Get the base too
484                 BL      div_unsigned            ;Get next digit in R1
485                 ADD     R1,R1,#'0'              ;Turn into a digit
486                 CMP     R1,#'9'+1               ;Is it too big for this?
487                 ADDCS   R1,R1,#'A'-'9'-1        ;Yes -- turn into letter
488                 STRB    R1,[R4],#1              ;Save in next byte of R11
489                 CMP     R0,#0                   ;Have we finished yet?
490                 BNE     %b00                    ;No -- do another digit then
491
492                 ; --- Now write out the digits ---
493                 ;
494                 ; They're all in the scratchpad in *reverse* order.
495
496 00              LDRB    R0,[R4,#-1]!            ;Load next character
497                 BL      xsave_byte              ;Write that out nicely
498                 LDMVSFD R13!,{R3-R5,PC}         ;If it failed, die
499                 CMP     R4,R11                  ;Have we finished yet?
500                 BHI     %b00                    ;No -- do the rest then
501
502                 LDMFD   R13!,{R3-R5,PC}^        ;Return to caller
503
504                 ; --- Read an integer in ---
505
506 50              STMFD   R13!,{R3-R5,R14}        ;Save a register
507                 MOV     R5,R1                   ;Look after string pointer
508
509                 TST     R7,#(1<<8)              ;Is there a base given?
510                 LDRNE   R3,[R9],#4              ;Yes -- load the base
511                 MOVEQ   R3,#10                  ;Otherwise use decimal
512                 MOV     R1,#0                   ;Value starts at 0
513                 MOV     R2,#0                   ;Keep decimal check in case
514                 MOV     R4,#0                   ;Clear a flags word
515
516 00              LDRB    R0,[R5],#1              ;Load next byte
517                 CMP     R0,#'&'                 ;Check for base prefix
518                 CMPNE   R0,#'%'                 ;Either will do
519                 BEQ     %60optType_integer      ;Yes -- handle that then
520                 CMP     R0,#'_'                 ;Was that a base spec?
521                 BEQ     %65optType_integer      ;Yes -- handle that then
522                 CMP     R0,#'-'                 ;Is it a minus sign?
523                 CMPNE   R0,#'+'                 ;Might as well allow + too
524                 BEQ     %70optType_integer      ;Yes -- deal with it
525
526                 SUB     R14,R0,#'A'             ;First check letters
527                 CMP     R14,#26                 ;Is this in range?
528                 SUBCS   R14,R0,#'a'             ;No -- also do lowercase
529                 CMPCS   R14,#26                 ;Check that too
530                 ORRCC   R4,R4,#(1<<0)           ;Yes -- can't be a base then
531                 ADDCC   R14,R14,#10             ;Put into letter position
532                 SUBCS   R14,R0,#'0'             ;Otherwise check digits
533                 CMPCS   R14,#10                 ;Make sure of them too
534                 BCS     %90optType_integer      ;Got something strange
535
536                 CMP     R14,#10                 ;Is it a valid base 10 digit?
537                 ADDCC   R2,R2,R2,LSL #2         ;Also accumulate base 10 vsn
538                 ADDCC   R2,R14,R2,LSL #1        ;In case of a base
539                 ORRCC   R4,R4,#(1<<2)           ;Yup -- got a decimal digit
540                 ORRCS   R4,R4,#(1<<4)           ;Otherwise say this is bad
541
542                 TST     R4,#(1<<3)              ;Is accumulator OK?
543                 BNE     %b00                    ;No -- don't change it
544                 CMP     R14,R3                  ;Is it OK in our base?
545                 MLACC   R1,R3,R1,R14            ;Accumulate result
546                 ORRCC   R4,R4,#(1<<1)           ;Yup -- got a real digit
547                 ORRCS   R4,R4,#(1<<3)           ;Otherwise say this is bad
548                 B       %b00                    ;If it was a digit, loop
549
550                 ; --- Change of base with shorthand base char ---
551
552 60              TST     R4,#&3f                 ;Any digits read so far?
553                 BNE     %90optType_integer      ;Yes -- this is naughty then
554                 CMP     R0,#'&'                 ;Entering hex mode?
555                 MOVEQ   R3,#16                  ;Yes -- base 16 then
556                 MOVNE   R3,#2                   ;No -- base 2 is the other
557                 ORR     R4,R4,#(1<<5)           ;Say we have a firm base
558                 B       %b00                    ;Now go back to read digits
559
560                 ; --- Change of base with `_' thing ---
561
562 65              TST     R4,#(1<<4) + (1<<5)     ;Check base is valid, and...
563                 BNE     %90optType_integer      ;we haven't got one already
564                 TST     R4,#(1<<2)              ;Make sure we read a digit
565                 BEQ     %90optType_integer      ;No -- nothing to do then
566                 MOV     R3,R2                   ;Make decimal number the base
567                 ORR     R4,R4,#(1<<5)           ;Say we have a firm base
568                 BIC     R4,R4,#(1<<1) + (1<<3)  ;Clear accumulator flags
569                 MOV     R1,#0                   ;And clear accumulator
570                 B       %b00                    ;Now go back to read digits
571
572                 ; --- Read a `-' or `+' sign ---
573
574 70              TST     R4,#&7f                 ;Any digits read so far?
575                 BNE     %90optType_integer      ;Yes -- this is naughty then
576                 ORR     R4,R4,#(1<<6)           ;Say we read a sign
577                 CMP     R0,#'-'                 ;Is it a minus?
578                 ORREQ   R4,R4,#(1<<7)           ;Yes -- set `-' flag then
579                 B       %b00                    ;Now go back to read digits
580
581                 ; --- We've stopped -- if we read something, store it ---
582
583 90              TST     R4,#(1<<7)              ;Must we negate the result?
584                 RSBNE   R1,R1,#0                ;Yes -- do this
585                 TST     R4,#(1<<1)              ;Did we read anything?
586                 STRNE   R1,[R10,#0]             ;Yes -- stuff it away then
587                 LDMFD   R13!,{R3-R5,PC}^        ;And return to caller
588
589                 LTORG
590
591 ; --- optType_literal ---
592 ;
593 ; Flags:        --
594 ;
595 ; Data:         (string) data to write out (*null* terminated)
596 ;
597 ; Use:          Reads nothing; leave the name blank.  Writes out the data
598 ;               literally.  Note that an extra linefeed is added to the
599 ;               end, so don't overdo it.
600
601                 EXPORT  optType_literal
602 optType_literal ROUT
603
604                 CMP     R0,#2                   ;Do I understand this?
605                 ADDCC   PC,PC,R0,LSL #2         ;Yes -- dispatch then
606                 MOVS    PC,R14                  ;Otherwise just return
607
608                 MOVS    PC,R14                  ;You can't read a literal
609
610                 ; --- Write the literal data ---
611
612                 STMFD   R13!,{R14}              ;Save a register
613 00              LDRB    R0,[R9],#1              ;Load a byte
614                 CMP     R0,#0                   ;Is that the end?
615                 BLNE    xsave_byte              ;No -- write out the byte
616                 LDMVSFD R13!,{PC}               ;If it failed, return
617                 BNE     %b00                    ;If not finished, loop
618                 LDMFD   R13!,{PC}^              ;Return when done
619
620                 LTORG
621
622 ; --- optType_enum ---
623 ;
624 ; Flags:        bit 8 == quote output string
625 ;               bit 9 == don't put an `=' sign in output
626 ;
627 ; Data:         See below
628 ;
629 ; Use:          The data is a collection of ctrl-terminated strings, itself
630 ;               terminated by a zero-length entry.  The textual
631 ;               representation is one of these strings, or an abbreviation
632 ;               of one.  The binary representation is a word containing the
633 ;               index into the list.
634
635                 EXPORT  optType_enum
636 optType_enum    ROUT
637
638                 CMP     R0,#2                   ;Do I understand this?
639                 ADDCC   PC,PC,R0,LSL #2         ;Yes -- dispatch then
640                 MOVS    PC,R14                  ;Otherwise just return
641
642                 B       %50optType_enum         ;Read one of the strings
643
644                 ; --- Write the appropriate string ---
645
646                 STMFD   R13!,{R2,R14}           ;Stack a register
647                 MOV     R0,R9                   ;Point to the table
648                 LDR     R1,[R10,#0]             ;Load the current value
649                 BL      str_index               ;Find the correct string
650                 LDMCCFD R13!,{R2,PC}^           ;If that failed, do nothing
651                 MOV     R2,R0                   ;Look after the index
652
653                 TST     R7,#(1<<9)              ;Do we want an equals?
654                 MOVEQ   R0,#'='                 ;Write an equals after name
655                 MOVNE   R0,#' '                 ;Or maybe a space instead
656                 MOV     R1,R8                   ;Point to option name
657                 BL      options_write           ;Write that out
658                 LDMVSFD R13!,{R2,PC}            ;If it failed, return
659                 ANDS    R0,R7,#(1<<8)           ;Are we quoting strings?
660                 MOVNE   R0,#-1                  ;Yes -- quote output
661                 MOV     R1,R2                   ;Point to the string
662                 BL      options_write           ;Write that out
663                 LDMFD   R13!,{R2,PC}            ;And return to caller
664
665                 ; --- Read one of the strings ---
666
667 50optType_enum  STMFD   R13!,{R14}              ;Stack a register
668                 MOV     R0,R9                   ;Point to the table
669                 BL      str_match               ;Look up the string
670                 STRCS   R0,[R10,#0]             ;If found, store index
671                 LDMFD   R13!,{PC}^              ;And return to caller
672
673                 LTORG
674
675 ; --- optType_bool ---
676 ;
677 ; Flags:        bit 8 == make flag active low
678 ;               bit 9 == use `on'/`off' rather than `true'/`false'; also
679 ;                       suppresses the `=' sign
680 ;
681 ; Data:         (word) bit mask to OR or BIC within word
682 ;
683 ; Use:          Handles a boolean option.  It will translate between the
684 ;               strings `true' or `false' and a bit (or set of bits) within
685 ;               a word.
686
687                 EXPORT  optType_bool
688 optType_bool    ROUT
689
690                 CMP     R0,#2                   ;Do I understand this?
691                 ADDCC   PC,PC,R0,LSL #2         ;Yes -- dispatch then
692                 MOVS    PC,R14                  ;Otherwise just return
693
694                 B       %50optType_bool         ;Read one of the strings
695
696                 ; --- Write a boolean value ---
697
698                 STMFD   R13!,{R14}              ;Save a register
699                 TST     R7,#(1<<9)              ;Write on/off, not true/false
700                 MOVNE   R0,#' '                 ;Yes -- use a space then
701                 MOVEQ   R0,#'='                 ;Else terminate with an `='
702                 MOV     R1,R8                   ;Point to the option name
703                 BL      options_write           ;Write that out
704                 LDMVSFD R13!,{PC}               ;If it failed, return
705
706                 LDR     R0,[R10,#0]             ;Load the flags word
707                 LDR     R14,[R9],#4             ;Load the mask
708                 TST     R7,#(1<<8)              ;Is flag active low?
709                 EORNE   R0,R0,R14               ;Yes -- toggle it then
710                 ANDS    R1,R0,R14               ;Is the option set?
711                 MOVNE   R1,#1                   ;Yes -- use true string
712                 TST     R7,#(1<<9)              ;Write on/off, not true/false
713                 ORRNE   R1,R1,#2                ;Yes -- use second set then
714                 ADR     R0,opt__boolTbl         ;Point to boolean table
715                 BL      str_index               ;Find correct string
716                 MOV     R1,R0                   ;Point to the string it found
717                 MOV     R0,#0                   ;Don't terminate string
718                 BL      options_write           ;Write that out
719                 LDMFD   R13!,{PC}               ;And return
720
721                 ; --- Read a boolean value ---
722
723 50optType_bool  STMFD   R13!,{R14}              ;Save a register
724                 ADR     R0,opt__boolTbl         ;Point to the table
725                 BL      str_match               ;Match a string
726                 LDMCCFD R13!,{PC}^              ;If no match, return
727                 TST     R0,#1                   ;Is the value false?
728                 LDR     R0,[R10,#0]             ;Load the flags word
729                 LDR     R14,[R9],#4             ;Load the mask
730                 BICEQ   R0,R0,R14               ;False -- clear flag
731                 ORRNE   R0,R0,R14               ;True -- set flag
732                 TST     R7,#(1<<8)              ;Is flag active low?
733                 EORNE   R0,R0,R14               ;Yes -- toggle it then
734                 STR     R0,[R10,#0]             ;Save new flags back
735                 LDMFD   R13!,{PC}^              ;And return
736
737 opt__boolTbl    DCB     "false",0,      "true",0
738                 DCB     "off",0,        "on",0
739                 DCB     "no",0,         "yes",0
740                 DCB     0
741
742                 LTORG
743
744 ; --- optType_version ---
745 ;
746 ; Flags:        --
747 ;
748 ; Data:         --
749 ;
750 ; Use:          Converts between version number strings (of the form
751 ;               <int>[.[<digit>[<digit>]]]) and integers.  The version
752 ;               number is stored multiplied by 100.
753
754                 EXPORT  optType_version
755 optType_version ROUT
756
757                 CMP     R0,#2                   ;Do I understand this?
758                 ADDCC   PC,PC,R0,LSL #2         ;Yes -- dispatch then
759                 MOVS    PC,R14                  ;Otherwise just return
760
761                 B       %50optType_version      ;Read a version number
762
763                 ; --- Write a version number ---
764
765                 STMFD   R13!,{R2-R4,R14}        ;Save some registers
766
767                 MOV     R0,#'='                 ;Write an equals sign
768                 MOV     R1,R8                   ;Point to option name
769                 BL      options_write           ;Write that string out
770                 LDMVSFD R13!,{R2-R4,PC}         ;If it failed, return
771
772                 LDR     R0,[R10,#0]             ;Load the version value
773                 BL      div10                   ;Get bottom minor vsn digit
774                 MOV     R4,R1                   ;Look after that
775                 BL      div10                   ;Get top minor vsn digit
776                 MOV     R3,R1                   ;Look after that too
777                 MOV     R2,R0                   ;And get major version
778                 MOV     R1,R11                  ;Output to scratchpad
779                 ADR     R0,opt__vsnSkel         ;Point to skeleton string
780                 BL      str_subst               ;Build the output string
781
782                 MOV     R1,R0                   ;Point to output string
783                 MOV     R0,#0                   ;Don't terminate this
784                 BL      options_write           ;Write that out nicely
785                 LDMFD   R13!,{R2-R4,PC}         ;And return to caller
786
787 opt__vsnSkel    DCB     "%i0.%i1%i2",0
788
789                 ; --- Read a version number ---
790
791 50              STMFD   R13!,{R2,R14}           ;Save some registers
792
793                 ; --- Read major version ---
794
795                 MOV     R2,#0                   ;Start an accumulator
796                 MOV     R0,#0                   ;Clear some flags
797 00              LDRB    R14,[R1],#1             ;Load next byte of input
798                 CMP     R14,#'.'                ;Is this the separator?
799                 BEQ     %f00                    ;Yes -- sip forwards then
800                 SUB     R14,R14,#'0'            ;Turn into an integer
801                 CMP     R14,#10                 ;Is it in range?
802                 ORRCC   R0,R0,#1                ;Yes -- we have a valid vsn
803                 ADDCC   R2,R2,R2,LSL #2         ;So accumulate major vsn
804                 ADDCC   R2,R14,R2,LSL #1
805                 BCC     %b00                    ;And loop back again
806
807                 ; --- Found something unexpected ---
808
809                 TST     R0,#1                   ;Do we have a version number?
810                 ADDNE   R2,R2,R2,LSL #2         ;Multiply major version by 5
811                 ADDNE   R2,R2,R2,LSL #2         ;And again (x25)
812                 MOVNE   R2,R2,LSL #2            ;And by 4 (x100)
813                 STRNE   R2,[R10,#0]             ;And write out this value
814                 LDMFD   R13!,{R2,PC}^           ;Return to caller finally
815
816                 ; --- Read minor version number ---
817
818 00              LDRB    R14,[R1],#1             ;Load next byte of input
819                 SUB     R14,R14,#'0'            ;Turn into an integer
820                 CMP     R14,#10                 ;Is it in range?
821                 MOVCS   R14,#0                  ;No -- treat it as zero then
822                 ADD     R2,R2,R2,LSL #2         ;Accumulate *anyway*; this
823                 ADD     R2,R14,R2,LSL #1        ;puts zeroes on the end
824                 LDRCCB  R14,[R1],#1             ;Maybe load the next one
825                 SUBCC   R14,R14,#'0'            ;Turn into an integer
826                 CMPCC   R14,#10                 ;Is it in range?
827                 MOVCS   R14,#0                  ;No -- treat it as zero then
828                 ADD     R2,R2,R2,LSL #2         ;Accumulate again
829                 ADD     R2,R14,R2,LSL #1
830                 STR     R2,[R10,#0]             ;And write out this value
831                 LDMFD   R13!,{R2,PC}^           ;Return to caller finally
832
833                 LTORG
834
835 ;----- Data structures ------------------------------------------------------
836
837 ; --- Options definition block ---
838
839                 ^       0
840 opt_flags       #       4                       ;Flags for this item
841 opt_length      #       4                       ;Size of this table entry
842 opt_offset      #       4                       ;Offset in block of data
843 opt_type        #       4                       ;Address of type handler
844 opt_name        #       0                       ;Name of this option
845
846 ; --- Option block flags ---
847
848 optFlag_last    EQU     (1<<0)                  ;This is the last block
849 optFlag_ignore  EQU     (1<<1)                  ;Don't read this option
850
851 ; --- Integer type flags ---
852
853 intFlag_base    EQU     (1<<8)                  ;Default base specified
854
855 ; --- Enumeration type flags ---
856
857 enumFlag_quote  EQU     (1<<8)                  ;Quote the output string
858 enumFlag_noEq   EQU     (1<<9)                  ;Don't output an `=' sign
859
860 ; --- Boolean type flags ---
861
862 boolFlag_cpl    EQU     (1<<8)                  ;Flag is complemented
863 boolFlag_onOff  EQU     (1<<9)                  ;Use `on'/`off' notation
864
865 ; --- Type handler reason codes ---
866 ;
867 ; All enter with:
868 ;
869 ;  R0 == reason code
870 ;  R7 == flags read from table
871 ;  R8 == address of option name
872 ;  R9 == address of type-specific data
873 ; R10 == address of binary option
874
875                 ^       0
876 optReason_read  #       1                       ;Read from option string
877                                                 ;R1 == pointer to string
878
879 optReason_write #       1                       ;Write data to xsave file
880
881 ;----- That's all, folks ----------------------------------------------------
882
883                 END