1:- module(lexer, []). 2
3:- op(800, fy, *). 4:- op(800, fy, ?). 5
7
9term(Opts) -->
10 ?shebang(Opts),
11 *token(Opts),
12 ?layout_text_sequence(Opts).
17read_term_(Opts) --> 18 term(Opts) 19 , end(Opts). 20
23token_(Opts, token_(Tree), A, Z) :-
24 ( nonvar(A) ->
25 ( layout_text_sequence(Opts, LTS_Tree, A, B),
26 Inner = [LTS_Tree, Token_Tree]
27 ; A = B,
28 Inner = [Token_Tree] )
29 ; otherwise ->
30 Tree =.. [_, Inner],
31 ( Inner = [LTS_Tree, Token_Tree] ->
32 layout_text_sequence(Opts, LTS_Tree, A, B)
33 ; Inner = open_token(_) ->
34 Inner = Token_Tree,
35 A = B
36 ; Inner = [Token_Tree] ->
37 A = B)
38 ),
39 ( name_token(Opts, Token_Tree, B, Z),
40 Tree = name(Inner)
41 ; variable_token(Opts, Token_Tree, B, Z),
42 Tree = variable(Inner)
43 ; integer_token(Opts, Token_Tree, B, Z),
44 Tree = integer(Inner)
45 ; float_number_token(Opts, Token_Tree, B, Z),
46 Tree = float_number(Inner)
47 ; double_quoted_list_token(Opts, Token_Tree, B, Z),
48 Tree = double_quoted_list(Inner)
49 ; close_token(Token_Tree, B, Z),
50 Tree = close(Inner)
51 ; open_list_token(Token_Tree, B, Z),
52 Tree = open_list(Inner)
53 ; close_list_token(Token_Tree, B, Z),
54 Tree = close_list(Inner)
55 ; open_curly_token(Token_Tree, B, Z),
56 Tree = open_curly(Inner)
57 ; close_curly_token(Token_Tree, B, Z),
58 Tree = close_curly(Inner)
59 ; head_tail_separator_token(Token_Tree, B, Z),
60 Tree = ht_sep(Inner)
61 ; comma_token(Token_Tree, B, Z),
62 Tree = comma(Inner)
63 ; open_token(Token_Tree, B, Z),
64 ( Inner = [LTS_Tree, Token_Tree] ->
65 Tree = open(Inner)
66 ; otherwise ->
67 Tree = open_ct(Token_Tree)
68 )
69 ; back_quoted_string_token(Opts, Token_Tree, B, Z),
70 Tree = back_quoted_string(Inner)
71 ; end_token(Token_Tree, B, Z),
72 Tree = end(Inner)
73 ).
74
151
152end(Opts) --> 153 ?layout_text_sequence(Opts) 154 , end_token. 155
157
158layout_text_sequence(Opts) --> 159 layout_text(Opts) 160 , *layout_text(Opts). 161
162layout_text(Opts) --> 163 layout_char 164 | comment(Opts). 165
(Opts) --> 167 single_line_comment(Opts) 168 | bracketed_comment(Opts). (Opts0, single_line_comment([ELCC_Tree,CT_Tree,NLC_Tree]), A, Z) :-
177 merge_options([disallow_chars(['\n'])], Opts0, Opts),
178 end_line_comment_char(ELCC_Tree, A, B),
179 comment_text(Opts, CT_Tree, B, C),
180 ( (C == Z ; NLC_Tree == end_of_file) ->
181 NLC_Tree = end_of_file,
182 C = Z
183 ; otherwise ->
184 new_line_char(NLC_Tree, C, Z)
185 ).
186
(Opts) --> 188 comment_open 189 , comment_text(Opts) 190 , comment_close.
192
--> 195 comment_1_char 196 , comment_2_char. 197
--> 199 comment_2_char 200 , comment_1_char. % 6.4.1
201
202comment_text(Opts) wrap_text --> % 6.4.1
203 *char(Opts). 204
--> 206 ['/'].
207
--> 209 ['*'].
210
211/* 6.4.2 Names */
212
213name token Opts --> % 6.4.2
214 letter_digit_token(Opts) % 6.4.2
215 | graphic_token(Opts) % 6.4.2
216 | quoted_token(Opts) % 6.4.2
217 | semicolon_token % 6.4.2
218 | cut_token. 219
220letter_digit_token(Opts) --> 221 small_letter_char(Opts) 222 , *alphanumeric_char(Opts). 223
224graphic_token(Opts) --> 225 graphic_token_char(Opts) 226 , *graphic_token_char(Opts).
228
229
230
231
233graphic_token_char(Opts) --> 234 graphic_char(Opts) 235 | backslash_char. 236
237quoted_token(Opts) --> 238 single_quote_char 239 , *single_quoted_item(Opts) 240 , single_quote_char. 241
242single_quoted_item(Opts) --> 243 single_quoted_character(Opts) 244 | continuation_escape_sequence. 245
246continuation_escape_sequence --> 247 backslash_char 248 , new_line_char. 249
250semicolon_token --> 251 semicolon_char. 252
253cut_token --> 254 cut_char. 255
257
258single_quoted_character(Opts) --> 259 non_quote_char(Opts). 260single_quoted_character(_Opts) --> 261 single_quote_char 262 , single_quote_char. 263single_quoted_character(_Opts) --> 264 double_quote_char. 265single_quoted_character(_Opts) --> 266 back_quote_char. 267
268double_quoted_character(Opts) --> 269 non_quote_char(Opts). 270double_quoted_character(_Opts) --> 271 single_quote_char. 272double_quoted_character(_Opts) --> 273 double_quote_char 274 , double_quote_char. 275double_quoted_character(_Opts) --> 276 back_quote_char. 277
278
279back_quoted_character(Opts) --> 280 non_quote_char(Opts). 281back_quoted_character(_Opts) --> 282 single_quote_char. 283back_quoted_character(_Opts) --> 284 double_quote_char. 285back_quoted_character(_Opts) --> 286 back_quote_char 287 , back_quote_char. 288
300non_quote_char(Opts, non_quote_char(PT), A, Z) :-
301 ( graphic_char(Opts, PT, A, Z)
302 ; alphanumeric_char(Opts, PT, A, Z)
303 ; solo_char(PT, A, Z)
304 ; space_char(PT, A, Z)
305 ; meta_escape_sequence(PT, A, Z)
306 ; control_escape_sequence(Opts, PT, A, Z)
307 ; octal_escape_sequence(Opts, PT, A, Z)
308 ; hexadecimal_escape_sequence(Opts, PT, A, Z)
309 ; option(allow_tab_as_quote_char(Allow_Tab_As_Quote_Char), Opts, no),
310 yes(Allow_Tab_As_Quote_Char),
311 horizontal_tab_char(PT, A, Z)
312 ; option(allow_newline_as_quote_char(Allow_Newline_As_Quote_Char), Opts, no),
313 yes(Allow_Newline_As_Quote_Char),
314 new_line_char(PT, A, Z)
315 ; option(allow_unicode_character_escape(Allow_Unicode_Character_Escape), Opts, no),
316 yes(Allow_Unicode_Character_Escape),
317 unicode_escape_sequence(Opts, PT, A, Z)
318 ).
319
320meta_escape_sequence --> 321 backslash_char 322 , meta_char. 323
324control_escape_sequence(Opts) --> 325 backslash_char 326 , symbolic_control_char(Opts). 327
328symbolic_control_char(_Opts) --> 329 symbolic_alert_char 330 | symbolic_backspace_char 331 | symbolic_carriage_return_char 332 | symbolic_form_feed_char 333 | symbolic_horizontal_tab_char 334 | symbolic_new_line_char 335 | symbolic_vertical_tab_char. 336
337symbolic_control_char(Opts, symbolic_control_char(symbolic_no_output_char('c')), ['c'|Z], Z) :-
338 option(allow_symbolic_no_output_char_c(Allow_Control_Char), Opts, no),
339 yes(Allow_Control_Char).
340
341symbolic_control_char(Opts, symbolic_control_char(symbolic_escape_char('e')), ['e'|Z], Z) :-
342 option(allow_symbolic_escape_char_e(Allow_Control_Char), Opts, no),
343 yes(Allow_Control_Char).
344
345symbolic_control_char(Opts, symbolic_control_char(symbolic_space_char('s')), ['s'|Z], Z) :-
346 option(allow_symbolic_space_char_s(Allow_Control_Char), Opts, no),
347 yes(Allow_Control_Char).
348
349symbolic_alert_char --> 350 ['a'].
351
352symbolic_backspace_char --> 353 ['b'].
354
355symbolic_carriage_return_char --> 356 ['r'].
357
358symbolic_form_feed_char --> 359 ['f'].
360
361symbolic_horizontal_tab_char --> 362 ['t'].
363
364symbolic_new_line_char --> 365 ['n'].
366
367symbolic_vertical_tab_char --> 368 ['v'].
376octal_escape_sequence(Opts, octal_escape_sequence([PT_Backslash_Char,PT_Octal_Digit_Char|Digits]), A, Z) :-
377 backslash_char(PT_Backslash_Char, A, B),
378 octal_digit_char(PT_Octal_Digit_Char, B, C),
379 octal_escape_sequence_df(Opts, Digits-Digits, C, D, R),
380 ( R = [PT_Backslash_Char],
381 backslash_char(PT_Backslash_Char, D, Z)
382 ; R = [],
383 option(allow_missing_closing_backslash_in_character_escape(Allow_Missing_Closing_Backslash_In_Character_Escape), Opts, no),
384 yes(Allow_Missing_Closing_Backslash_In_Character_Escape),
385 D = Z
386 ).
387
388octal_escape_sequence_df(Opts, Ls0-[PT_Octal_Digit_Char|Ls1e], A, Z, R) :-
389 octal_digit_char(PT_Octal_Digit_Char, A, B),
390 !,
391 octal_escape_sequence_df(Opts, Ls0-Ls1e, B, Z, R).
392octal_escape_sequence_df(_Opts, _-R, A, A, R).
393
402hexadecimal_escape_sequence(Opts, hexadecimal_escape_sequence([PT_Backslash_Char,PT_Symbolic_Hexadecimal_Char,PT_Hexadecimal_Digit_Char|Digits]), A, Z) :-
403 backslash_char(PT_Backslash_Char, A, B),
404 symbolic_hexadecimal_char(PT_Symbolic_Hexadecimal_Char, B, C),
405 hexadecimal_digit_char(PT_Hexadecimal_Digit_Char, C, D),
406 hexadecimal_escape_sequence_df(Opts, Digits-Digits, D, E, R),
407 ( R = [PT_Backslash_Char],
408 backslash_char(PT_Backslash_Char, E, Z)
409 ; R = [],
410 option(allow_missing_closing_backslash_in_character_escape(Allow_Missing_Closing_Backslash_In_Character_Escape), Opts, no),
411 yes(Allow_Missing_Closing_Backslash_In_Character_Escape),
412 E = Z
413 ).
414
415hexadecimal_escape_sequence_df(Opts, Ls0-[PT_Hexadecimal_Digit_Char|Ls1e], A, Z, R) :-
416 hexadecimal_digit_char(PT_Hexadecimal_Digit_Char, A, B),
417 !,
418 hexadecimal_escape_sequence_df(Opts, Ls0-Ls1e, B, Z, R).
419hexadecimal_escape_sequence_df(_Opts, _-R, A, A, R).
420
421
422
423symbolic_hexadecimal_char --> 424 ['x'].
425
426unicode_escape_sequence(_Opts, unicode_escape_sequence([PT_Backslash_Char, PT_Symbolic_Unicode_Char, PT_Hex1, PT_Hex2, PT_Hex3, PT_Hex4]), A, Z) :-
427 backslash_char(PT_Backslash_Char, A, B),
428 symbolic_unicode4_char(PT_Symbolic_Unicode_Char, B, C),
429 hexadecimal_digit_char(PT_Hex1, C, D),
430 hexadecimal_digit_char(PT_Hex2, D, E),
431 hexadecimal_digit_char(PT_Hex3, E, F),
432 hexadecimal_digit_char(PT_Hex4, F, Z).
433
434unicode_escape_sequence(_Opts, unicode_escape_sequence([PT_Backslash_Char, PT_Symbolic_Unicode_Char, PT_Hex1, PT_Hex2, PT_Hex3, PT_Hex4, PT_Hex5, PT_Hex6, PT_Hex7, PT_Hex8]), A, Z) :-
435 backslash_char(PT_Backslash_Char, A, B),
436 symbolic_unicode8_char(PT_Symbolic_Unicode_Char, B, C),
437 hexadecimal_digit_char(PT_Hex1, C, D),
438 hexadecimal_digit_char(PT_Hex2, D, E),
439 hexadecimal_digit_char(PT_Hex3, E, F),
440 hexadecimal_digit_char(PT_Hex4, F, G),
441 hexadecimal_digit_char(PT_Hex5, G, H),
442 hexadecimal_digit_char(PT_Hex6, H, I),
443 hexadecimal_digit_char(PT_Hex7, I, J),
444 hexadecimal_digit_char(PT_Hex8, J, Z).
445
446symbolic_unicode8_char -->
447 ['U'].
448
449symbolic_unicode4_char -->
450 ['u'].
451
452
453/* 6.4.3 Variables */
454
455variable token Opts --> % 6.4.3
456 anonymous_variable(Opts) % 6.4.3
457 | named_variable(Opts). 458
459anonymous_variable(_Opts) --> 460 variable_indicator_char. 461
462named_variable(Opts) --> 463 variable_indicator_char 464 , alphanumeric_char(Opts) 465 , *alphanumeric_char(Opts).
473named_variable(Opts, named_variable(Tree), A, Z) :-
474 option(var_prefix(Var_Prefix), Opts),
475 no(Var_Prefix),
476 Tree=[Capital_Letter_Tree|Sequence_List],
477 capital_letter_char(Opts, Capital_Letter_Tree, A, B),
478 call_sequence_ground(sequence(*, alphanumeric_char(Opts), T), T, [], Sequence_List, B, Z).
479
480variable_indicator_char --> 481 underscore_char. % 6.5.2
482
483
484/* 6.4.4 Integer numbers */
485
486integer token Opts --> % 6.4.3
487 integer_constant_(Opts) % 6.4.4
488 | character_code_constant(Opts) % 6.4.4
489 | binary_constant(Opts) % 6.4.4
490 | octal_constant(Opts) % 6.4.4
491 | hexadecimal_constant(Opts). 492
496integer_constant_(Opts0, integer_constant(PT), A, Z) :-
497 merge_options([is_integer(yes)], Opts0, Opts),
498 integer_constant(Opts, integer_constant(PT), A, Z).
504integer_constant(Opts, integer_constant([PT_Decimal_Digit_Char|PT_Rest]), A, Z) :-
505 decimal_digit_char(PT_Decimal_Digit_Char, A, B),
506 integer_constant_df(Opts, PT_Rest-PT_Rest, B, Z).
507
508integer_constant_df(Opts, Ls0-[PT_Decimal_Digit_Char|Ls1e], A, Z) :-
509 decimal_digit_char(PT_Decimal_Digit_Char, A, B),
510 !,
511 integer_constant_df(Opts, Ls0-Ls1e, B, Z).
512integer_constant_df(Opts, Ls0-[PT_Underscore_Char, PT_Decimal_Digit_Char|Ls1e], A, Z) :-
513 option(is_integer(yes), Opts, no),
514 underscore_char(PT_Underscore_Char, A, B),
515 option(allow_digit_groups_with_underscore(Allow_Digit_Groups_With_Underscore), Opts, no),
516 yes(Allow_Digit_Groups_With_Underscore),
517 decimal_digit_char(PT_Decimal_Digit_Char, B, C),
518 !,
519 integer_constant_df(Opts, Ls0-Ls1e, C, Z).
520integer_constant_df(Opts, Ls0-[PT_Underscore_Char, PT_Bracketed_Comment, PT_Decimal_Digit_Char|Ls1e], A, Z) :-
521 option(is_integer(yes), Opts, no),
522 underscore_char(PT_Underscore_Char, A, B),
523 option(allow_digit_groups_with_underscore(Allow_Digit_Groups_With_Underscore), Opts, no),
524 yes(Allow_Digit_Groups_With_Underscore),
525 bracketed_comment(Opts, PT_Bracketed_Comment, B, C),
526 decimal_digit_char(PT_Decimal_Digit_Char, C, D),
527 !,
528 integer_constant_df(Opts, Ls0-Ls1e, D, Z).
529integer_constant_df(Opts, Ls0-[PT_Space_Char, PT_Decimal_Digit_Char|Ls1e], A, Z) :-
530 option(is_integer(yes), Opts, no),
531 space_char(PT_Space_Char, A, B),
532 option(allow_digit_groups_with_space(Allow_Digit_Groups_With_Space), Opts, no),
533 yes(Allow_Digit_Groups_With_Space),
534 decimal_digit_char(PT_Decimal_Digit_Char, B, C),
535 !,
536 integer_constant_df(Opts, Ls0-Ls1e, C, Z).
537integer_constant_df(_Opts, _-[], A, A).
538
539
540character_code_constant(Opts) --> 541 ['0']
542 , single_quote_char 543 , single_quoted_character(Opts). 544
545character_code_constant(Opts, character_code_constant(['0', PT_Single_Quote_Char, single_quoted_character(single_quote_char('\''))]), A, Z) :-
546 A = ['0'|B],
547 single_quote_char(PT_Single_Quote_Char, B, C),
548 option(allow_single_quote_char_in_character_code_constant(Allow_Single_Quote_Char_In_Character_Code_Constant), Opts, no),
549 yes(Allow_Single_Quote_Char_In_Character_Code_Constant),
550 C = ['\''|Z].
557binary_constant(Opts, binary_constant([PT_Binary_Constant_Indicator, PT_Binary_Digit_Char|PT_Rest]), A, Z) :-
558 binary_constant_indicator(PT_Binary_Constant_Indicator, A, B),
559 binary_digit_char(PT_Binary_Digit_Char, B, C),
560 binary_constant_df(Opts, PT_Rest-PT_Rest, C, Z).
561
562binary_constant_df(Opts, Ls0-[PT_Binary_Digit_Char|Ls1e], A, Z) :-
563 binary_digit_char(PT_Binary_Digit_Char, A, B),
564 !,
565 binary_constant_df(Opts, Ls0-Ls1e, B, Z).
566binary_constant_df(Opts, Ls0-[PT_Underscore_Char, PT_Binary_Digit_Char|Ls1e], A, Z) :-
567 underscore_char(PT_Underscore_Char, A, B),
568 option(allow_digit_groups_with_underscore(Allow_Digit_Groups_With_Underscore), Opts, no),
569 yes(Allow_Digit_Groups_With_Underscore),
570 binary_digit_char(PT_Binary_Digit_Char, B, C),
571 !,
572 binary_constant_df(Opts, Ls0-Ls1e, C, Z).
573binary_constant_df(Opts, Ls0-[PT_Underscore_Char, PT_Bracketed_Comment, PT_Binary_Digit_Char|Ls1e], A, Z) :-
574 underscore_char(PT_Underscore_Char, A, B),
575 option(allow_digit_groups_with_underscore(Allow_Digit_Groups_With_Underscore), Opts, no),
576 yes(Allow_Digit_Groups_With_Underscore),
577 bracketed_comment(Opts, PT_Bracketed_Comment, B, C),
578 binary_digit_char(PT_Binary_Digit_Char, C, D),
579 !,
580 binary_constant_df(Opts, Ls0-Ls1e, D, Z).
581binary_constant_df(Opts, Ls0-[PT_Space_Char, PT_Binary_Digit_Char|Ls1e], A, Z) :-
582 space_char(PT_Space_Char, A, B),
583 option(allow_digit_groups_with_space(Allow_Digit_Groups_With_Space), Opts, no),
584 yes(Allow_Digit_Groups_With_Space),
585 binary_digit_char(PT_Binary_Digit_Char, B, C),
586 !,
587 binary_constant_df(Opts, Ls0-Ls1e, C, Z).
588binary_constant_df(_Opts, _-[], A, A).
589
590
591binary_constant_indicator --> 592 ['0', 'b'].
599octal_constant(Opts, octal_constant([PT_Octal_Constant_Indicator, PT_Octal_Digit_Char|PT_Rest]), A, Z) :-
600 octal_constant_indicator(PT_Octal_Constant_Indicator, A, B),
601 octal_digit_char(PT_Octal_Digit_Char, B, C),
602 octal_constant_df(Opts, PT_Rest-PT_Rest, C, Z).
603
604octal_constant_df(Opts, Ls0-[PT_Octal_Digit_Char|Ls1e], A, Z) :-
605 octal_digit_char(PT_Octal_Digit_Char, A, B),
606 !,
607 octal_constant_df(Opts, Ls0-Ls1e, B, Z).
608octal_constant_df(Opts, Ls0-[PT_Underscore_Char, PT_Octal_Digit_Char|Ls1e], A, Z) :-
609 underscore_char(PT_Underscore_Char, A, B),
610 option(allow_digit_groups_with_underscore(Allow_Digit_Groups_With_Underscore), Opts, no),
611 yes(Allow_Digit_Groups_With_Underscore),
612 octal_digit_char(PT_Octal_Digit_Char, B, C),
613 !,
614 octal_constant_df(Opts, Ls0-Ls1e, C, Z).
615octal_constant_df(Opts, Ls0-[PT_Underscore_Char, PT_Bracketed_Comment, PT_Octal_Digit_Char|Ls1e], A, Z) :-
616 underscore_char(PT_Underscore_Char, A, B),
617 option(allow_digit_groups_with_underscore(Allow_Digit_Groups_With_Underscore), Opts, no),
618 yes(Allow_Digit_Groups_With_Underscore),
619 bracketed_comment(Opts, PT_Bracketed_Comment, B, C),
620 octal_digit_char(PT_Octal_Digit_Char, C, D),
621 !,
622 octal_constant_df(Opts, Ls0-Ls1e, D, Z).
623octal_constant_df(Opts, Ls0-[PT_Space_Char, PT_Octal_Digit_Char|Ls1e], A, Z) :-
624 space_char(PT_Space_Char, A, B),
625 option(allow_digit_groups_with_space(Allow_Digit_Groups_With_Space), Opts, no),
626 yes(Allow_Digit_Groups_With_Space),
627 octal_digit_char(PT_Octal_Digit_Char, B, C),
628 !,
629 octal_constant_df(Opts, Ls0-Ls1e, C, Z).
630octal_constant_df(_Opts, _-[], A, A).
631
632octal_constant_indicator --> 633 ['0', 'o'].
640hexadecimal_constant(Opts, hexadecimal_constant([PT_Hexadecimal_Constant_Indicator, PT_Hexadecimal_Digit_Char|PT_Rest]), A, Z) :-
641 hexadecimal_constant_indicator(PT_Hexadecimal_Constant_Indicator, A, B),
642 hexadecimal_digit_char(PT_Hexadecimal_Digit_Char, B, C),
643 hexadecimal_constant_df(Opts, PT_Rest-PT_Rest, C, Z).
644
645hexadecimal_constant_df(Opts, Ls0-[PT_Hexadecimal_Digit_Char|Ls1e], A, Z) :-
646 hexadecimal_digit_char(PT_Hexadecimal_Digit_Char, A, B),
647 !,
648 hexadecimal_constant_df(Opts, Ls0-Ls1e, B, Z).
649hexadecimal_constant_df(Opts, Ls0-[PT_Underscore_Char, PT_Hexadecimal_Digit_Char|Ls1e], A, Z) :-
650 underscore_char(PT_Underscore_Char, A, B),
651 option(allow_digit_groups_with_underscore(Allow_Digit_Groups_With_Underscore), Opts, no),
652 yes(Allow_Digit_Groups_With_Underscore),
653 hexadecimal_digit_char(PT_Hexadecimal_Digit_Char, B, C),
654 !,
655 hexadecimal_constant_df(Opts, Ls0-Ls1e, C, Z).
656hexadecimal_constant_df(Opts, Ls0-[PT_Underscore_Char, PT_Bracketed_Comment, PT_Hexadecimal_Digit_Char|Ls1e], A, Z) :-
657 underscore_char(PT_Underscore_Char, A, B),
658 option(allow_digit_groups_with_underscore(Allow_Digit_Groups_With_Underscore), Opts, no),
659 yes(Allow_Digit_Groups_With_Underscore),
660 bracketed_comment(Opts, PT_Bracketed_Comment, B, C),
661 hexadecimal_digit_char(PT_Hexadecimal_Digit_Char, C, D),
662 !,
663 hexadecimal_constant_df(Opts, Ls0-Ls1e, D, Z).
664hexadecimal_constant_df(Opts, Ls0-[PT_Space_Char, PT_Hexadecimal_Digit_Char|Ls1e], A, Z) :-
665 space_char(PT_Space_Char, A, B),
666 option(allow_digit_groups_with_space(Allow_Digit_Groups_With_Space), Opts, no),
667 yes(Allow_Digit_Groups_With_Space),
668 hexadecimal_digit_char(PT_Hexadecimal_Digit_Char, B, C),
669 !,
670 hexadecimal_constant_df(Opts, Ls0-Ls1e, C, Z).
671hexadecimal_constant_df(_Opts, _-[], A, A).
672
673hexadecimal_constant_indicator --> 674 ['0', 'x'].
675
683float_number_token(Opts, float_number_token(Atom, [PT_Integer_Constant|G]), A, Z) :-
684 integer_constant(Opts, PT_Integer_Constant, A, B),
685 option(allow_integer_exponential_notation(Allow_Integer_Exponential_Notation), Opts, no),
686 ( yes(Allow_Integer_Exponential_Notation) ->
687 call_sequence_ground(sequence('?', fraction, F), F, J, G, B, C)
688 ; otherwise ->
689 G = [PT_Fraction|J],
690 fraction(PT_Fraction, B, C)
691 ),
692 call_sequence_ground(sequence('?', exponent(Opts), I), I, [], J, C, Z),
693 ( var(Atom) ->
694 append(Chars, Z, A),
695 atom_chars(Atom, Chars)
696 ; true
697 ).
698
699fraction --> 700 decimal_point_char 701 , decimal_digit_char 702 , *decimal_digit_char. 703
704exponent(Opts) --> 705 exponent_char 706 , sign 707 , integer_constant(Opts). 708
709sign --> 710 negative_sign_char. 711sign --> 712 ?positive_sign_char. 713
714positive_sign_char --> 715 ['+'].
716
717negative_sign_char --> 718 ['-'].
719
720decimal_point_char --> 721 ['.'].
722
723exponent_char --> 724 ['e']
725 | ['E'].
726
727/* 6.4.6 Double quoted lists */
728
729double_quoted_list token Opts --> % 6.4.6
730 double_quote_char % 6.5.5
731 , *double_quoted_item(Opts) % 6.4.6
732 , double_quote_char. 733
734double_quoted_item(Opts) --> 735 double_quoted_character(Opts) 736 | continuation_escape_sequence. % 6.4.2
737
738/* 6.4.7 Back quoted strings */
739
740back_quoted_string token Opts --> % 6.4.7
741 back_quote_char % 6.5.5
742 , *back_quoted_item(Opts) % 6.4.7
743 , back_quote_char. 744
745back_quoted_item(Opts) --> 746 back_quoted_character(Opts) 747 | continuation_escape_sequence. 748
750
751open_token --> 752 open_char. 753
754close_token --> 755 close_char. 756
757open_list_token --> 758 open_list_char. 759
760close_list_token --> 761 close_list_char. 762
763open_curly_token --> 764 open_curly_char. 765
766close_curly_token --> 767 close_curly_char. 768
769head_tail_separator_token --> 770 head_tail_separator_char. 771
772comma_token --> 773 comma_char. 774
775end_token --> 776 end_char. 777
778end_char --> 779 ['.'].
780
782
783char(Opts, char(Tree), A, Z) :-
784 char_(Opts, char_(Tree), A, Z),
785 ( A = [C|Z] ->
786 option(disallow_chars(Disallowed), Opts, []),
787 \+ member(C, Disallowed)
788 ; otherwise ->
789 true
790 ).
791
792char_(Opts) --> 793 graphic_char(Opts) 794 | alphanumeric_char(Opts) 795 | solo_char 796 | layout_char 797 | meta_char. 798
800
801graphic_char_(_Opts) --> 802 ['#']
803 | ['$']
804 | ['&']
805 | ['*']
806 | ['+']
807 | ['-']
808 | ['.']
809 | ['/']
810 | [':']
811 | ['<']
812 | ['=']
813 | ['>']
814 | ['?']
815 | ['@']
816 | ['^']
817 | ['~'].
818
819graphic_char(Opts, graphic_char(Char), [Char|Z], Z) :-
820 ( graphic_char_(Opts, graphic_char_(Char), [Char|Z], Z),
821 !
822 ; option(allow_unicode(Allow_Unicode), Opts, no),
823 yes(Allow_Unicode),
824 Char \= '\\',
825 char_type(Char, prolog_symbol) ).
826
828
829alphanumeric_char(Opts) --> 830 alpha_char(Opts) 831 | decimal_digit_char. 832
833alpha_char(Opts) --> 834 underscore_char 835 | letter_char(Opts). 836
837letter_char(Opts) --> 838 capital_letter_char(Opts) 839 | small_letter_char(Opts). 840
841small_letter_char_(_Opts) --> 842 ['a']
843 | ['b']
844 | ['c']
845 | ['d']
846 | ['e']
847 | ['f']
848 | ['g']
849 | ['h']
850 | ['i']
851 | ['j']
852 | ['k']
853 | ['l']
854 | ['m']
855 | ['n']
856 | ['o']
857 | ['p']
858 | ['q']
859 | ['r']
860 | ['s']
861 | ['t']
862 | ['u']
863 | ['v']
864 | ['w']
865 | ['x']
866 | ['y']
867 | ['z'].
868
869small_letter_char(Opts, small_letter_char(Char), [Char|Z], Z) :-
870 ( small_letter_char_(Opts, small_letter_char_(Char), [Char|Z], Z),
871 !
872 ; option(allow_unicode(Allow_Unicode), Opts, no),
873 yes(Allow_Unicode),
874 char_type(Char, lower) ).
875
876capital_letter_char_(_Opts) --> 877 ['A']
878 | ['B']
879 | ['C']
880 | ['D']
881 | ['E']
882 | ['F']
883 | ['G']
884 | ['H']
885 | ['I']
886 | ['J']
887 | ['K']
888 | ['L']
889 | ['M']
890 | ['N']
891 | ['O']
892 | ['P']
893 | ['Q']
894 | ['R']
895 | ['S']
896 | ['T']
897 | ['U']
898 | ['V']
899 | ['W']
900 | ['X']
901 | ['Y']
902 | ['Z'].
903
904capital_letter_char(Opts, capital_letter_char(Char), [Char|Z], Z) :-
905 ( capital_letter_char_(Opts, capital_letter_char_(Char), [Char|Z], Z),
906 !
907 ; option(allow_unicode(Allow_Unicode), Opts, no),
908 yes(Allow_Unicode),
909 char_type(Char, upper) ).
910
911decimal_digit_char --> 912 ['0']
913 | ['1']
914 | ['2']
915 | ['3']
916 | ['4']
917 | ['5']
918 | ['6']
919 | ['7']
920 | ['8']
921 | ['9'].
922
923binary_digit_char --> 924 ['0']
925 | ['1'].
926
927octal_digit_char --> 928 ['0']
929 | ['1']
930 | ['2']
931 | ['3']
932 | ['4']
933 | ['5']
934 | ['6']
935 | ['7'].
936
937hexadecimal_digit_char --> 938 ['0']
939 | ['1']
940 | ['2']
941 | ['3']
942 | ['4']
943 | ['5']
944 | ['6']
945 | ['7']
946 | ['8']
947 | ['9']
948 | ['A']
949 | ['a']
950 | ['B']
951 | ['b']
952 | ['C']
953 | ['c']
954 | ['D']
955 | ['d']
956 | ['E']
957 | ['e']
958 | ['F']
959 | ['f'].
960
961underscore_char --> 962 ['_'].
963
965
966solo_char --> 967 cut_char 968 | open_char 969 | close_char 970 | comma_char 971 | semicolon_char 972 | open_list_char 973 | close_list_char 974 | open_curly_char 975 | close_curly_char 976 | head_tail_separator_char 977 | end_line_comment_char. 978
979cut_char --> 980 ['!'].
981
982open_char --> 983 ['('].
984
985close_char --> 986 [')'].
987
988comma_char --> 989 [','].
990
991semicolon_char --> 992 [';'].
993
994open_list_char --> 995 ['['].
996
997close_list_char --> 998 [']'].
999
1000open_curly_char --> 1001 ['{'].
1002
1003close_curly_char --> 1004 ['}'].
1005
1006head_tail_separator_char --> 1007 ['|'].
1008
--> 1010 ['%'].
1011
1012
1014
1015layout_char --> 1016 space_char 1017 | horizontal_tab_char 1018 | new_line_char. 1019
1020space_char --> 1021 [' '].
1022
1023horizontal_tab_char --> 1024 ['\t']. 1025
1026new_line_char --> 1027 ['\n'] 1028 | ['\r','\n'].
1029
1031
1032meta_char --> 1033 backslash_char 1034 | single_quote_char 1035 | double_quote_char 1036 | back_quote_char. 1037
1038backslash_char --> 1039 ['\\'].
1040
1041single_quote_char --> 1042 ['\''].
1043
1044double_quote_char --> 1045 ['"'].
1046
1047back_quote_char --> 1048 ['`'].
1049
1050
1052
1053shebang(Opts0, shebang(['#','!',PT_Comment_Text,PT_New_Line_Char]), ['#','!'|A], Z) :-
1054 option(allow_shebang(Allow_Shebang), Opts0, no),
1055 yes(Allow_Shebang),
1056 merge_options([disallow_chars(['\n'])], Opts0, Opts),
1057 comment_text(Opts, PT_Comment_Text, A, B),
1058 ( (B == Z ; NLC_Tree == end_of_file) ->
1059 NLC_Tree = end_of_file,
1060 B = Z
1061 ; otherwise ->
1062 new_line_char(PT_New_Line_Char, B, Z)
1063 )