summaryrefslogtreecommitdiffstats
path: root/parser.y
Commit message (Collapse)AuthorAgeFilesLines
...
* Second round of bugfixing on the theme of the previous commit.Kaz Kylheku2014-03-201-19/+55
| | | | | | | | | | | | | | Here were are changing the output clause to recognize all special clause tokens that are not used in output and turning them into regular Lisp. So @(if a b c) in an output clause works once again, recognized as IF exprs_opt ')' syntax, and turned into Lisp. Other things work that didn't work before like @(and), @(or) and so forth. * parser.y (make_expr): New static function. (not_a_clause): New nonterminal. (out_clause): Remove error-catching productions for match-side clauses. (o_elems): Now consists of a mixture of o_elems and not_a_clause's.
* * parser.y (text): Allow the EMPTY token (the @(empty) syntax)Kaz Kylheku2014-03-151-1/+1
| | | | | | to be a text. * txr.1: Documented @(empty).
* * parser.y: nuke tabs.Kaz Kylheku2014-03-131-9/+9
|
* Implementing @(if)/@(elif)/@(else) in the pattern language.Kaz Kylheku2014-03-131-1/+35
| | | | | | | | | | | | | | | | Input side for now; output later. * parser.y (if_clause, elif_clauses_opt, else_clause_opt): New nonterminals. (IF, ELIF, ELSE): New tokens. (yybadtoken): Handle IF, ELIF, ELSE. * parser.l: Recognize and return new tokens IF, ELIF and ELSE. * txr.1: Documented. * genvim.txr: Updated with if, elsif and else directive keywords. * txr.vim: Regenerated
* * parser.l: Allowing ^ to be a quote character, and adjusting definitionKaz Kylheku2014-03-031-19/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | of identifiers to rule this out from being the first character of a symbol which has no prefix. Recognize the ^ character as a token in the NESTED state. * lib.c (obj_print, obj_pprint): Render sys:qquote as ^. * parser.y (choose_quote): Function removed. (n_expr): Recognize '^' as quasiquote. Removed all the "smart quote" hacks that try to make quote behave as quote or quasiquote, or try to cancel out unquotes and quotes. * tests/009/json.txr: Fixed to ^ quasiquote. * tests/010/reghash.txr: Likewise. * tests/011/macros-2.txr: Likewise. * tests/011/mandel.txr: Likewise. * tests/011/special-1.txr: Likewise. * txr.1: Updated docs. * genvim.txr: Revamped definitions for txr_ident and txl_ident so that unqualified identifiers cannot start with # or ^, but ones with @ or : in front can start with these characters. * txr.vim: Regenerated.
* * parser.y (unquotes_occur): Fix use of unquote_s rather than sys_unquote_sKaz Kylheku2014-03-021-1/+1
| | | | | | | | | which breaks backquote, caught by tests/010/reghash.txr. I thought fixed this already! But I must have made the change to y.tab.c rather than parser.y. * Makefile (lex.yy.c, y.tab.c): Make these files readonly to prevent unintended edits.
* New quasiquote idea: let's have two quasiquote macros sharing oneKaz Kylheku2014-03-011-7/+9
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | expander. One macro based on sys:qquote, sys:unquote and sys:splice, and the other based on qquote, unquote and splice in the user package. The read syntax puts out the sys: one. * eval.c (expand_qquote): Takes three additional arguments: the qquote, unquote and splice symbols to recognize. The invalid splice diagnostic is adjusted based on which backquote we are expanding. (me_qquote): Look at the symbol in the first position of the form and then expand either the internal quasiquote macro or the public one, passing the right symbols into expand_qquote. (eval_init): Register error-throwing stub functions for the sys_qquote_s, sys_unquote_s and sys_splice_s symbols. Register a macro for sys_qquote_s. * lib.c (sys_qquote_s, sys_unquote_s, sys_splice_s): New symbol variables. (obj_init): Initialize new variables. Change qquote_s, unquote_s and splice_s to user package. (obj_print, obj_pprint): Convert only sys_qquote_s, sys_unquote_s and sys_splice_s to the read syntax. The quote_s, unquote_s and splice_s symbols are not treated specially. * lib.h (sys_qquote_s, sys_unquote_s, sys_splice_s): Declared. * parser.y (n_expr): Use sys_qquote_s, sys_unquote_s and sys_splice_s rather than qquote_s, unquote_s and splice_s. (unquotes_occur): Likewise. * txr.1: Documented.
* * eval.c (expand_op): Use rlcp_tree when constructing theKaz Kylheku2014-02-261-5/+8
| | | | | | | | | | | | dwim_body, since the append2 copies list structure. * parser.y (n_exprs): propagate source loc info from both constituents, giving precedence to the left one, rather than just taking it from the left one and ignoring the second constituent. This fixes cases of missing location info. The left constituent n_expr is often a symbol, and those do not have location info. We want a case like like ((x) y) to take from (x), and (x (y)) to take it from (y), and so on.
* * parser.y (list): For @n_expr, get the source location infoKaz Kylheku2014-02-261-3/+5
| | | | | | | from the @ token. (n_expr): Bugfix: do not attribute a symbol with location info. (quasilit): Obtain location info from quasi_items, and only if that is unavailable, then from lineno.
* * parser.y (spec): Bugfix: SECRET_ESCAPE_E should use n_exprKaz Kylheku2014-02-251-12/+18
| | | | | | | | | | | | not expr. expr is subject to expand_meta. (n_expr): Do not associate source info with character literals. (expand_meta): Bugfix: when walking forms in a collecting loop, propagate the source info to them. Bugfix: attach source info to var and expr expansions. (rl): Rewritten in terms of rlset. (rlset): Only set source info for an object that doesn't already have it.
* * parser.y (modifiers): Bugfix: list element not subject to expansionKaz Kylheku2014-02-241-3/+17
| | | | | | of Lisp forms denoted by @. (expand_meta): Bugfix: failure to expand vars, which can be symbol macros now.
* * lib.c (obj_print, obj_pprint): Render quasi-quote hash andKaz Kylheku2014-02-241-7/+10
| | | | | | | | | | | | vector literals using their original notation. * parser.y (unquotes_occur): Takes new argument, level. Only finds quotes which are at the given quasiquoting level. Finally, this is the right semantics. In the first version of this function, we were not eager enough: we neglected to find unquotes that were wrapped in nested quasiquotes. Then we were too eager: finding any unquotes, even ones belonging to the inner backquotes. (vector, hash, choose_quote): Pass zero to unquotes_occur function.
* Symbol macros.Kaz Kylheku2014-02-241-4/+3
| | | | | | | | | | | | | | | | | | | | | | | | * eval.c (top_smb, defsymacro_s, symacrolet_s): New global variables. (lookup_symac, get_opt_param_syms, get_param_syms, op_defsymacro, expand_symacrolet, make_var_shadowing_env): New static functions. (expand_tree_cases, expand_catch_clause): Install shadowing environment so lexical bindings hide any symbol macrolets. (expand_place): Fix neglect to expand an atomic form, which breaks symbol macros used as places. (expand): Expand symbol macros, expand symacrolet binding forms. Make sure symbol macros are shadowed in the lexical binding constructs. Take advantage of return value of rlcp_tree in a few places. (macro_form_p): Support for symbol macros; bugfix: not handling default argument. (macroexpand_1): Streamlined, and support added for symbol macros. (eval_init): Protect top_smb from gc. Create new hash, stored in top_smb. Initialize defsymacro_s and symacrolet_s. Register op_defsymacro. * parser.y (rlcp_tree): Return the to form instead of useless t and nil. * txr.1: Documented.
* * parser.y: Allow the (. expr) syntax to denote expr.Kaz Kylheku2014-02-221-0/+1
| | | | | | | | | * eval.h: Declare existing lambda_s extern variable. * lib.c (obj_print, obj_pprint): print (lambda sym ...) as (lambda (. sym) ...) and (lambda sym) as (lambda (. sym)). * txr.1: document it.
* Preparation for lexical macros: we need to pass a macroKaz Kylheku2014-02-221-9/+12
| | | | | | | | | | | | | | | | | environment down through the expander call hierarchy. * eval.c (expand_opt_params, expand_params, expand_tree_cases, expand_tree_case, expand_forms, val expand_cond_pairs, val expand_place, expand_qquote, expand_vars, expand_quasi, expand_op, expand_catch_clause, expand_catch, expand): All expanders get new parameter, menv. expand_forms and expand handle a nil value of menv. (eval_intrinsic): Pass nil macro environment to expand. (eval_init): Update intrinsic registration for expand. * eval.h (expand, expand_forms): Declarations updated. * parser.y (expand_meta): Gets macro env parameter. (elem, o_elem, exprs, expr): Pass nil to expand_forms and expand_meta.
* * parser.y: Bugfix, I think. :) We do not need to call the expanderKaz Kylheku2014-02-221-1/+1
| | | | | | | | | for a Lisp expression in a quasistring, and doing so leads to a potentially incorrect double expansion because the whole thing will be expanded again, either by the TXR Lisp quasi operator's expander (if this is a quasiliteral in Lisp) or in the TXR pattern language, by expand_meta, which hunts down down @ expressions and expands them.
* * parser.y (unquotes_occur): Bugfix: we should not terminateKaz Kylheku2014-02-201-2/+0
| | | | | | | | the recursion early if we see a quote. This would be true if the only quotes were those generated by the parser based on calls to choose_quote. However, it breaks for something like an explicitly coded '(sys:quote ,form), which becomes (sys:quote (sys:quote ,form)), leaving a dangling unquote.
* Nice idea: how about a function which walks the tree structure andKaz Kylheku2014-02-161-0/+13
| | | | | | | | | | | | | | | | back-fills some missing source code location info. We apply this to macro expansions. If some error occurs in expanded code, this way it is referenced to the line where the macro *call* occurs. Not only is this better than nothing, it may be better than tracing it to the macro definition. Ideally, we would have both places: ("the error is in the code expanded from this macro, at this site"). * eval.c (expand): Use rlcp_tree to back-fill source info in macro expansion by taking it from the unexpanded form. * parser.h (rlcp_tree): Declared. * parser.y (rlcp_tree): New function.
* Bugfixes: not propagating source loc info in quasiliterals.Kaz Kylheku2014-02-161-8/+16
| | | | | | * eval.c (expand_quasi): Add some rlcp's here. * parser.y (o_var, quasi_items, o_elems_transform): Likewise.
* Whitespace.Kaz Kylheku2014-02-011-1/+1
|
* * eval.c (meta_meta_p, meta_meta_strip): New static functions.Kaz Kylheku2014-01-281-1/+4
| | | | | | | | | | | | | | | (transform_op): Recognize compounded metas, and strip one level off. (eval_init): Intern sys:expand function so we have access to the form expander from TXR Lisp. * lib.c (obj_print, obj_pprint): Fix: wasn't rendering metanumbers. * parser.y (list): Support @ in front of anything. If it's an atom, treat it similarly to a metasymbol or metanumber. * txr.1: Documented meta-meta arguments in nested op. * genvim.txr, txr.vim: Support coloring for compounded meta syntax.
* Lexing and parsing improvements, leaving things less hacky than before,Kaz Kylheku2014-01-271-41/+23
| | | | | | | | | | | | | | | | | | | | | | | albeit hacky. * parser.l (BSYM, NSYM): Regex definitions gone. (BT0, BT1, BT2, NT0, NT1, NT2): New regex definitions. (BTREG, BTKEY, NTREG, NTKEY): Rewritten, so that they cannot match a lone @ character as a symbol name. (grammar): Rules for returning METAPAR, METABKT and METAQUO are gone. Instead, we just recognize a @ in the NESTED and BRACED states and return it as a token. * parser.y (METAPAR, METABKT, METAQUO): Token types removed. (meta_expr): Nonterminal symbol removed. ('@'): New token type. (list): Quotes and splices handling removed from this rule. The new token '@' is handled here, on the other hand, because there are places that reference the list rule that need to support @ expressions. (n_expr): Reference to meta_expr removed. Quote, unquote and splice added here. (yybadtoken): Removed references to METAPAR, METABKT and METAQUO.
* * parser.y (yybadtoken): Handle METAQUO in switch.Kaz Kylheku2014-01-271-0/+1
|
* Implementing more correct treatment of meta formsKaz Kylheku2014-01-261-36/+62
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | like @[...] and @(...) occurring in the TXR pattern language. The previous behavior is that the parser always expands the interior of these forms when they occur. This is wrong. These forms only denote TXR Lisp (and so require expansion) when they occur in a directive, inside a sub-expression that is not already known to be Lisp. For instance in @(do @(op foo)), the inner @(op foo) should not be subject to expansion. The reason that the argument forms of @(do) are TXR Lisp. The @(op foo) form denotes (sys:expr foo), and that operator currently has no meaning; and so we should not expand it. The previous, buggy behavior would turn the @(op ..) into a @(lambda ...). Another example is @(bind a @(list @(op foo))) where @(list ...) denotes TXR Lisp and so the interior of the form should be expanded. However, the @(op foo) should not be expanded into @(lambda ...) Expanding @(...) forms is not currently harmful, but it interferes with code that wants to use the @(...) syntax for its own use, The solution involves adding shims in the parser so that the expansion is only applied when expressions are reduced to the top level within a directive, and then to walk the expressions, looking for the @ syntax and expanding only the outermost occurrence thereof. * parser.y (expand_meta): New static function. (n_exprs n_expr): New nonterminal symbols. (elem): The arguments of the list elem (representing a generic directive) now need to be put through expand_meta when it is not @(do ...) or @(require ...). (list): Use n_exprs instead of exprs. (meta_expr): Do not call expand, and use n_expr(s) instead of expr(s). (exprs, expr): These rules no become just a shim which expands the outer-most metas. The actual parsing is represented by n_expr and n_exprs ("n" stands for nested), which behave just like the old expr and exprs.
* Sigh; more lexical-syntactic hacks. This adds handlingKaz Kylheku2014-01-261-4/+13
| | | | | | | | | | for the @' combination, as in @(bind a @'(foo ,bar)) * parser.l: Handle the new METAQUO token. * parser.y (METAQUO): New token. (meta_expr): New "METAQUO expr" case. Added missing METABKT error handling case.
* Bugfix: @(require ...) not expanding forms.Kaz Kylheku2014-01-231-2/+5
| | | | | | | | | | * eval.c (expand_forms): Static function becomes external. (expand_form): Remove case which handles do_s. * eval.h (expand_forms): Declared. * parser.y (elem): Expand both do_s and require_s forms by using expand_forms.
* Changes to the list collection mechanism to improveKaz Kylheku2014-01-221-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | the extension of list operations over vectors and strings. * eval.c (do_eval_args, bindings_helper, op_each, subst_vars, supplement_op_syms, mapcarv, mappendv): Switch from list_collect_* macros to functions. * lib.c (copy_list): Switch from list_collect* macros to functions. Use list_collect_nconc for the final terminator. Doing a copy there with list_collect_append was actually wasteful, and now that list_collect_append calls copy_list in places, it triggered runaway recursion. (make_like): Bugfix: list_vector was used instead of vector_list. (to_seq, list_collect, list_collect_nconc, list_collect_append): New functions. (append2, appendv, nappend2, sub_list, replace_list, ldiff, remq, remql, remqual, remove_if, keep_if, proper_plist_to_alist, improper_plist_to_alist, split_str, split_str_set, tok_str, list_str, chain, andf, orf, lis_vector, mapcar, mapcon, mappend, merge, set_diff, env): Switch from list_collect* macros to functions. (replace_str, replace_vec): Allow single item replacement sequence. * lib.h (to_seq): Declared. (list_collect, list_collect_nconc, list_collect_append): Macros removed, replaced by function declarations of the same name. These functions return the new ptail since they cannot assign to it, requiring all uses to be updated to do the assignment of the returned value. (list_collect_decl): Use val rather than obj_t *. * match.c (vars_to_bindings, h_coll, subst_vars, extract_vars, extract_bindings, do_output_line, do_output, v_gather, v_collect): Switch from list_collect* macros to functions. * parser.y (o_elems_transform): Likewise. * regex.c (dv_compile_regex, regsub): Likewise. * txr.c (txr_main): Likewise.
* The lisp-parse function can now be called multiple timesKaz Kylheku2014-01-071-2/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | on the same stream to extract multiple objects; the requirement that the stream must hold exactly one complete Lisp object with no following material is now lifted. * parser.l (YY_INPUT): Modified the macro so that it reads no more than one character. Though this probably makes the lexer less efficient, it gives us the important property that the lexer does not scan ahead into the input stream, hogging data into its buffer which is then destroyed. This is essential if the lisp-parse function is to support multiple calls to pull objects one by one out of a stream. * parser.y (spec): Use YYACCEPT in the SECRET_ESCAPE_E clause for pulling a single expression out of the token stream. YYACCEPT is a trick for not invoking the $accept : spec . $end production which is implicitly built into the grammar, and which causes a token of lookahead to occur. This allows us to read a full expression without stealing any further token: but only if the grammar is structured right. (exprs): This phrase structure now handles the DOTDOT syntax. There is no such thing as an expr DOTDOT expr expression any more; it is in the list syntax (and not supported in the dot position). (expr): Remove DOTDOT syntax. * txr.1: Updated description of .. syntax, and relaxed the description of lisp-parse since it now allows multiple calls to extract multiple objects.
* * parser.y (yybadtoken): Handle HASH_H.Kaz Kylheku2013-12-171-0/+1
|
* * lib.c (intern): fix the previous diagnostic bug once more with moreKaz Kylheku2013-12-161-5/+4
| | | | | | | | | | feeling. * parser.l (grammar): Recognize package prefixes in symbol tokens. Got rid of special rule for handling lone colon. * parser.y (sym_helper): Catch undefined package as a parsing error rather allowing intern function to throw exception.
* Changing the tokenizer to get rid of IDENT, KEYWORD and METAVARKaz Kylheku2013-12-151-39/+74
| | | | | | | | | | | | | | | | | | | | | token categories, replaced by a single one called SYMTOK. Package prefixes are now recognized and processed in tokens. * lib.c (delete_package): Fix problem in no-such-package error case: it would always report nil as the name. (intern): Fix nonsensical error message: in the no-such-package case it would report that the symbol exists already. * parser.l (grammar): Occurences of KEYWORD, METAVAR, and IDENT scrubbed. All rules reporting any of these now return SYMTOK. The main one of these is greatly simplified. * parser.y (sym_helper): New function. (char_from_name): const qualifier inside param's type declaration. (grammar): IDENT, KEYWORD and METAVAR tokens are gone. New token SYMTOK. Grammar refactored around SYMTOK and using the new sym_helper function. (char_from_name): Updated.
* Support for parsing Lisp expression out of strings and streams.Kaz Kylheku2013-12-141-1/+2
| | | | | | | | | | | | | | | | | | | | | | New catenated streams make the Yacc hack possible. * eval.c (eval_init): Register lisp_parse as intrinsic. * parser.h (lisp_parse): Declared. * parser.l: New lexical hack to produce SECRET_ESCAPE_E token. (regex_parse): Move declaration before statements. (lisp_parse): New function. * parser.y (SECRET_ESCAPE_E): New token type. (spec): New production rule for single expression. * stream.c (cat_stream_print, cat_get_line, cat_get_char, cat_get_byte, cat_get_prop): New static functions. (cat_stream_ops): New static function. (make_catenated_stream): New function. * stream.h (make_catenated_stream): Declared.
* First cut at signal handling support.Kaz Kylheku2013-12-121-0/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | * Makefile (OBJS-y): Include signal.o if have_posix_sigs is "y". * configure (have_posix_sigs): New variable, set by detecting POSIX signal stuff. * dep.mk: Regenerated. * arith.c, debug.c, eval.c, filter.c, hash.c, match.c, parser.y, parser.l, rand.c, regex.c, syslog.c, txr.c, utf8.c: Include new signal.h header, now required by unwind, and the <signal.h> system header. * eval.c (exit_wrap): New function. (eval_init): New functions registered as intrinsics: exit_wrap, set_sig_handler, get_sig_handler, sig_check. * gc.c (release): Unused functions removed. * gc.h (release): Declaration removed. * lib.c (init): Call sig_init. * stream.c (set_putc, se_getc, se_fflush): New static functions. (stdio_put_char_callback, stdio_get_char_callback, stdio_put_byte, stdio_flush, stdio_get_byte): Use new functions to enable signals when blocked on I/O. (tail_strategy): Allow signals across sleep. (pipev_close): Allow signals across waitpid. (se_pclose): New static function. (pipe_close): Use new function to enable signals across pclose. * unwind.c (uw_unwind_to_exit_point): use extended_longjmp instead of longjmp. * unwind.h (struct uw_block, struct uw_catch): jb member changes from jmp_buf to extended_jmp_buf. (uw_block_begin, uw_simple_catch_begin, uw_catch_begin): Use extended_setjmp instead of setjmp. * signal.c: New file. * signal.h: New file.
* Bumping copyrights to 2014 and expressing them as year ranges.Kaz Kylheku2013-12-101-1/+1
| | | | Fixing some errors in copyright comments.
* * eval.c (eval_init): Update registration of regex-compileKaz Kylheku2013-12-061-5/+5
| | | | | | | | | | | | | | | | | | | to reflect that it has two arguments now. * parser.y (grammar): Update calls to regex_compile to pass two arguments. Since we don't expect regex_compile to parse, we specify the error stream as nil. (spec): The "secret syntax" for a regex is simplified not to include the slashes. This provides better diagnostics for unterminated syntax and requires less string processing to generate. Also, the form returned doesn't have the regex symbol consed onto it, which parse_regex just throws away. * regex.c (regex_compile): Now takes a stream argument. * regex.h (regex_compile): Declaration updated. * txr.1: Updated
* * eval.c (eval_init): Registered regex_parse as newKaz Kylheku2013-12-051-0/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | intrinsic function and std_null as new variable. * parser.h (yylex_destroy): Existing function declared. * parser.l (regex_parse): New function. New lexical syntax added which returns SECRET_ESCAPE_R. * parser.y (SECRET_ESCAPE_R): New token. (spec): Added syntactic variant which lets us smuggle a regex into the parser easily. * stream.c:x (std_null): New global variable. (null_stream_print): New static function. (null_ops): New static structure. (make_null_stream): New function. (stream_init): Protect and initialize std_null. * stream.h (std_null, make_null_stream): Declared. * txr.1: New features documented: regex-parse, *stdnull*. * txr.c (txr_main): Call yylex_destroy after parsing the program now that I know about this function; this can free up some memory.
* * match.c (v_collect): Implemented semantics for repeat symbol.Kaz Kylheku2012-05-171-11/+12
| | | | | | | | | | | | | | | | (dir_tables_init): Register dispatch for repeat to v_collect function. * parser.y (collect_repeat): New nonterminal symbol. (clause): Removed repeat_clause error case because that now clashes with the syntax in collect_clause. (collect_clause): Repeat syntax implemented, with help of collect_repeat. (out_clause): Error case for collect_clause removed due to syntactic clash. * txr.1: Added mention of @(collect :vars nil) and documented @(repeat) as the shorthand.
* * parser.y (regtoken): New nonterminal symbol.Kaz Kylheku2012-04-201-35/+21
| | | | | | | | | | | | | | | | (regterm): REGTOKEN production factored out to regtoken. (regclass): Reverted prior commmit's changes. (regclassterm): Reverted prior commit, removing REGTOKEN production for character classes, and introduced a regtoken production. So now the keyword symbols are part of the character class abstract syntax. (regtoken): New production rule. * regex.c (regex_space_chars): Converted to internal linkage. (char_set_compile): Handle token keywords in character class abstract syntax. * regex.h (regex_space_chars): External declaration removed.
* First cut at implementing \s, \d, \w, \S, \D and \W regex tokens.Kaz Kylheku2012-04-191-6/+37
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | * lib.c (init): Call regex_init. * parser.l: return new REGTOKEN kind. * parser.y (REGTOKEN): New token type. (REGTERM): Translate REGTERM to keyword. (regclass): Restructured to handle inherited nodes as lists. (regclassterm): Produce $$ as list. Add handling for REGTOKEN occurring inside character class by expanding it. This might not be the best approach. (yybadtoken): Handle REGTOKEN in switch. * regex.c (struct any_char_set, struct small_char_set, struct displaced_char_set, struct large_char_set, struct xlarge_char_set): New bitfield member, stat. (char_set_create): New parameter for indicating static char set. (char_set_destroy): Do not free a static char set. (char_set_compile): Pass zero to new parameter of char_set_create. (spaces): New static array. (space_cs, digit_cs, word_cs, cspace_cs, cdigit_cs, cword_cs): New static pointers to char_set_t. (init_special_char_sets, nfa_compile_given_set): New static function. (nfa_compile_regex, dv_compile_regex): Handle new character set token keywords. (space_k, digit_k, word_char_k, cspace_k, cdigit_k, cword_char_k, regex_space_chars): New variables. (regex_init): New function. * regex.h (space_k, digit_k, word_char_k, cspace_k, cdigit_k, cword_char_k, regex_space_chars, regex_init): Declared.
* * configure (uintptr): New variable. Indicates whether unsignedKaz Kylheku2012-03-191-1/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | version of intptr_t is available and should be generated in config.h as uintptr_t. * eval.c (eval_init): New intrinsic functions floatp, integerp, flo-str. * gc.c (finalize): Handle FLNUM case. Rearranged cases so that all trivially returning cases are together. (mark): Handle FLNUM case. * hash.c (hash_double): New function. (equal_hash): Handle FLNUM via hash_double. (eql_hash): Likewise. * lib.c: <math.h> is included. (float_s): New symbol variable. (code2type, equal): Handle FLNUM case in switch. (integerp): New function; does the same thing as integerp before. (numberp): Returns t for floats. (flo, floatp, flo_str): New functions. (obj_init): Initialize new float_s variable. (obj_print, obj_pprint): Handle FLNUM case in switch. Printing does not work yet; needs work in stream.c. * lib.h (enum type): New enumeration FLNUM. (struct flonum): New struct type. (union obj): New member, fl. (float_s, flo, floatp, integerp, flo_str): Declared. * parser.l (FLO): New token pattern definition. Scans to a NUMBER token. Corrected uses of yylval.num to yylval.val. * parser.y (%union): Removed num member from yystype.
* Support quasiquoting over vectors also, and a bugfix for hashKaz Kylheku2012-03-141-3/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | quasiquoting. We cannot use the same symbol for the literal form from the parser, and for the expanded form, because this creates a confusion when there are multiple nestings of quasiquote expansion. * eval.c (vector_lit_s, vector_list_s, hash_lit_s): New symbol variables. (hash_construct_s): Relocated here from hash.c. (expand_qquote): Part of bugfix: look for hash_lit_s instead of has_construct_s. Translate to a hash_construct_s form which is no longer recognizes as a hash literal. Implementing recognition of a quasiquote vector literal, handled similarly. (eval_init): Initialize vector_lit_s, vector_list_s, hash_list_s and hash_lit_s. Use vector_list_s when registering vector_list function. * eval.h (vector_lit_s, vector_list_s, hash_lit_s, hash_constuct_s): Declared. * hash.c (hash_construct_s): Variable removed and relocated into eval.c. (hash_init): Initialization of hash_construct_s removed. * hash.h (hash_construct_s): Declaration removed. * parser.y: (vector): Action updated to generate a (vec-lit ...) form if the object contains unquotes, otherwise generate a vector object. (hash): Generate hash-lit form, not a hash-construct form.
* Allow quasi-quoting over hash table literals,Kaz Kylheku2012-03-141-15/+8
| | | | | | | | | | | | | | | | | | | | to express dynamic hash table construction * eval.c (expand_qquote): Recognize hash-construct forms: expand the hash arguments and pairs separately, then rewrite to a new hash-construct form. (eval-init): hash-construct intrinsic function added. * hash.c (hash_construct_s): New symbol variable. (hash_construct): New function. (hash_init): Initialize hash_construct_s. * hash.h (hash_construct_s, hash_construct): Declared. * parser.y (hash): Rule rewritten to emit either a literal hash table object, or a hash-construct form, based on whether quasiquote unquotes occur within the syntax. (hash_from_notation): Function removed.
* Implementing #H((...) ...) read/print syntax for hash tables.Kaz Kylheku2012-03-141-2/+20
| | | | | | | | | | | | | | | | * hash.c (print_key_val, hash_print_op): New static functions. (hash_ops): hash_print_op wired in in place of cobj_print_op. * parser.l (HASH_H): New token recognized. * parser.y (HASH_H): New terminal symbol. (hash): New nonterminal symbol. (expr): Acquires hash as a constituent. (hash_from_notation): New static function. * txr.1: Hash syntax described. * txr.vim: Updated.
* Change: @(block) requires @(end) from now on.Kaz Kylheku2012-03-131-12/+29
| | | | | | | | | | | | | | | | | | | Blocks no longer extend to the end of the surrounding scope. * match.c (v_block): Rewrite for new syntax. * parser.l (BLOCK): New token type handled. * parser.y (BLOCK): New token. (block_clause): New nonterminal grammar symbol. (clause): Collateral fix: replaced a bunch of list(X, nao) forms with cons(X, nil). Introduced block_clause as a constituent of clause. * txr.1: Revamped documentation of block, and wrote about using blocks for reducing nested skips and reducing backtracking in general.
* Bugfix: rlcp function was incorrect for new way of storingKaz Kylheku2012-02-281-0/+6
| | | | | | | | | line number info. * parser.h (rlset): Declared. (rlcp): Use rlset. * parser.y (rlset): New function.
* Fixing long-time (pre-GIT) bug. The object (nil) was stupidly used toKaz Kylheku2012-02-261-28/+38
| | | | | | | | | | | | | | | | | | | | | represent empty optional output clauses, distinguishing them from missing clauses. This creates an ambiguity, so that an @(output) block which puts out a single empty line is treated as empty. Present but empty clauses are now represented by t. * match.c (do_output_line): Check for t and bail. (do_output): Check for t instead of (nil) and bail. * parser.y (o_elems_opt2): Nonterminal deleted. (out_clauses_opt): Empty case generates nil. (req_parts_opt): o_elems_opt2 replaced by o_elems_opt. (repeat_rep_helper): Function now keeps track of which clauses were specified. For those that were specified, but empty, it substitutes t. * tests/008/empty-clauses.expected: New file. * tests/008/empty-clauses.txr: New file.
* Bug #35625Kaz Kylheku2012-02-261-9/+27
| | | | | | | | | | | | | | | | | | | | | | * parser.l (BSCHR, BSYM, BTOK): New lexical definitions. (BRACED): New state. (grammar): Refactored so that braced variables are now handled in the BRACED state, allowing for lexical differences between braced variables and Lisp. This allows us to have the /regex/ syntax in braces, but /regex/ is just a symbol in the Lisp. The new #/ token is recognized and returned as HASH_SLASH. All rules reformatted to a more easily maintainble convention. * parser.y (HASH_SLASH): New token. (modifiers, lisp_regex): New nonterminals. (var): Grammar changed to use modifiers nonterminal instead of exprs. (var_op): Rule moved closer to var. (expr): Produces lisp_regex rather than regex. (yybadtoken): Handle HASH_SLASH in the switch statement. Bugfix: HASH_BACKSLASH was not handled. * txr.1: Documented #/regex/ syntax.
* * parser.y (clause): "Doh" moment. We don't need the specialKaz Kylheku2012-02-251-9/+1
| | | | | | | | transformation of the load syntax because the parent location is already associated with the syntax. * match.c (v_load): Pull out source location info from the form itself.
* * debug.c (debug): Use new way of getting line number.Kaz Kylheku2012-02-241-1/+1
| | | | | | | | | | | | | | * eval.c (eval_error): Use source_loc_str to get source location. * match.c (debuglf, sem_err, file_err): Likewise. * parser.h (source_loc_str): Declared. * parser.l (parse_init): form_to_ln_hash must be equal based now. * parser.y (rl): Store new form of read-time source location info. * txr.1: Documented load.
* First cut at @(load) directive. Incomplete: debug location infoKaz Kylheku2012-02-241-1/+9
| | | | | | | | | | | | | | | | | | | | | | | | needs to record file name, not only line number; absolute paths not handled, etc. * match.c (load_s): New symbol variable. (v_load): New static function. (syms_init): load_s initialized. (dir_tables_init): Load directive registered. * match.h (load_s): Declared. * parser.h (parse_reset): New function declared. * parser.l (spec_file_str): Global variable moved from txr.c. (parse_reset): New function. * parser.y (clause): Special handling for @(load ...) directive. parent file path inserted into the syntax at parse time, so when the load directive executes, it can load the file from the same directory as the parent file. * txr.c (spec_file_str): Global variable moved to parser.l.