{-# LANGUAGE BangPatterns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Strict #-} {-# LANGUAGE StrictData #-} module Backend.FunctionTable where import Control.Monad.Except import Control.Parallel import Environment import Primitives as Primitives import Backend.Utils import Types as Types import Utils import Wrap import Backend.Toplevel import Backend.Core import Backend.Sys import Backend.Sequent import Backend.Yacc import Backend.Reader import Backend.Prolog import Backend.Track import Backend.Load import Backend.Writer import Backend.Macros import Backend.Declarations import Backend.Types import Backend.TStar import Backend.PortInfo import Backend.LoadShen {- Copyright (c) 2015, Mark Tarver All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 3. The name of Mark Tarver may not be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY Mark Tarver ''AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL Mark Tarver BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -} functions = do insertFunction "shen.shen" (PL "shen.shen" kl_shen_shen) insertFunction "shen.loop" (PL "shen.loop" kl_shen_loop) insertFunction "shen.credits" (PL "shen.credits" kl_shen_credits) insertFunction "shen.initialise_environment" (PL "shen.initialise_environment" kl_shen_initialise_environment) insertFunction "shen.multiple-set" (wrapNamed "shen.multiple-set" kl_shen_multiple_set) insertFunction "destroy" (wrapNamed "destroy" kl_destroy) insertFunction "shen.read-evaluate-print" (PL "shen.read-evaluate-print" kl_shen_read_evaluate_print) insertFunction "shen.retrieve-from-history-if-needed" (wrapNamed "shen.retrieve-from-history-if-needed" kl_shen_retrieve_from_history_if_needed) insertFunction "shen.percent" (PL "shen.percent" kl_shen_percent) insertFunction "shen.exclamation" (PL "shen.exclamation" kl_shen_exclamation) insertFunction "shen.prbytes" (wrapNamed "shen.prbytes" kl_shen_prbytes) insertFunction "shen.update_history" (wrapNamed "shen.update_history" kl_shen_update_history) insertFunction "shen.toplineread" (PL "shen.toplineread" kl_shen_toplineread) insertFunction "shen.toplineread_loop" (wrapNamed "shen.toplineread_loop" kl_shen_toplineread_loop) insertFunction "shen.hat" (PL "shen.hat" kl_shen_hat) insertFunction "shen.newline" (PL "shen.newline" kl_shen_newline) insertFunction "shen.carriage-return" (PL "shen.carriage-return" kl_shen_carriage_return) insertFunction "tc" (wrapNamed "tc" kl_tc) insertFunction "shen.prompt" (PL "shen.prompt" kl_shen_prompt) insertFunction "shen.toplevel" (wrapNamed "shen.toplevel" kl_shen_toplevel) insertFunction "shen.find-past-inputs" (wrapNamed "shen.find-past-inputs" kl_shen_find_past_inputs) insertFunction "shen.make-key" (wrapNamed "shen.make-key" kl_shen_make_key) insertFunction "shen.trim-gubbins" (wrapNamed "shen.trim-gubbins" kl_shen_trim_gubbins) insertFunction "shen.space" (PL "shen.space" kl_shen_space) insertFunction "shen.tab" (PL "shen.tab" kl_shen_tab) insertFunction "shen.left-round" (PL "shen.left-round" kl_shen_left_round) insertFunction "shen.find" (wrapNamed "shen.find" kl_shen_find) insertFunction "shen.prefix?" (wrapNamed "shen.prefix?" kl_shen_prefixP) insertFunction "shen.print-past-inputs" (wrapNamed "shen.print-past-inputs" kl_shen_print_past_inputs) insertFunction "shen.toplevel_evaluate" (wrapNamed "shen.toplevel_evaluate" kl_shen_toplevel_evaluate) insertFunction "shen.typecheck-and-evaluate" (wrapNamed "shen.typecheck-and-evaluate" kl_shen_typecheck_and_evaluate) insertFunction "shen.pretty-type" (wrapNamed "shen.pretty-type" kl_shen_pretty_type) insertFunction "shen.extract-pvars" (wrapNamed "shen.extract-pvars" kl_shen_extract_pvars) insertFunction "shen.mult_subst" (wrapNamed "shen.mult_subst" kl_shen_mult_subst) insertFunction "shen.shen->kl" (wrapNamed "shen.shen->kl" kl_shen_shen_RBkl) insertFunction "shen.shen-syntax-error" (wrapNamed "shen.shen-syntax-error" kl_shen_shen_syntax_error) insertFunction "shen." (wrapNamed "shen." kl_shen_LBdefineRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBnameRB) insertFunction "shen.sysfunc?" (wrapNamed "shen.sysfunc?" kl_shen_sysfuncP) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsignatureRB) insertFunction "shen.curry-type" (wrapNamed "shen.curry-type" kl_shen_curry_type) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsignature_helpRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBrulesRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBruleRB) insertFunction "shen.fail_if" (wrapNamed "shen.fail_if" kl_shen_fail_if) insertFunction "shen.succeeds?" (wrapNamed "shen.succeeds?" kl_shen_succeedsP) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpatternsRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpatternRB) insertFunction "shen.constructor-error" (wrapNamed "shen.constructor-error" kl_shen_constructor_error) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsimple_patternRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpattern1RB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpattern2RB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBactionRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBguardRB) insertFunction "shen.compile_to_machine_code" (wrapNamed "shen.compile_to_machine_code" kl_shen_compile_to_machine_code) insertFunction "shen.record-source" (wrapNamed "shen.record-source" kl_shen_record_source) insertFunction "shen.compile_to_lambda+" (wrapNamed "shen.compile_to_lambda+" kl_shen_compile_to_lambdaPlus) insertFunction "shen.update-symbol-table" (wrapNamed "shen.update-symbol-table" kl_shen_update_symbol_table) insertFunction "shen.update-symbol-table-h" (wrapNamed "shen.update-symbol-table-h" kl_shen_update_symbol_table_h) insertFunction "shen.free_variable_check" (wrapNamed "shen.free_variable_check" kl_shen_free_variable_check) insertFunction "shen.extract_vars" (wrapNamed "shen.extract_vars" kl_shen_extract_vars) insertFunction "shen.extract_free_vars" (wrapNamed "shen.extract_free_vars" kl_shen_extract_free_vars) insertFunction "shen.free_variable_warnings" (wrapNamed "shen.free_variable_warnings" kl_shen_free_variable_warnings) insertFunction "shen.list_variables" (wrapNamed "shen.list_variables" kl_shen_list_variables) insertFunction "shen.strip-protect" (wrapNamed "shen.strip-protect" kl_shen_strip_protect) insertFunction "shen.linearise" (wrapNamed "shen.linearise" kl_shen_linearise) insertFunction "shen.flatten" (wrapNamed "shen.flatten" kl_shen_flatten) insertFunction "shen.linearise_help" (wrapNamed "shen.linearise_help" kl_shen_linearise_help) insertFunction "shen.linearise_X" (wrapNamed "shen.linearise_X" kl_shen_linearise_X) insertFunction "shen.aritycheck" (wrapNamed "shen.aritycheck" kl_shen_aritycheck) insertFunction "shen.aritycheck-name" (wrapNamed "shen.aritycheck-name" kl_shen_aritycheck_name) insertFunction "shen.aritycheck-action" (wrapNamed "shen.aritycheck-action" kl_shen_aritycheck_action) insertFunction "shen.aah" (wrapNamed "shen.aah" kl_shen_aah) insertFunction "shen.abstract_rule" (wrapNamed "shen.abstract_rule" kl_shen_abstract_rule) insertFunction "shen.abstraction_build" (wrapNamed "shen.abstraction_build" kl_shen_abstraction_build) insertFunction "shen.parameters" (wrapNamed "shen.parameters" kl_shen_parameters) insertFunction "shen.application_build" (wrapNamed "shen.application_build" kl_shen_application_build) insertFunction "shen.compile_to_kl" (wrapNamed "shen.compile_to_kl" kl_shen_compile_to_kl) insertFunction "shen.get-type" (wrapNamed "shen.get-type" kl_shen_get_type) insertFunction "shen.typextable" (wrapNamed "shen.typextable" kl_shen_typextable) insertFunction "shen.assign-types" (wrapNamed "shen.assign-types" kl_shen_assign_types) insertFunction "shen.atom-type" (wrapNamed "shen.atom-type" kl_shen_atom_type) insertFunction "shen.store-arity" (wrapNamed "shen.store-arity" kl_shen_store_arity) insertFunction "shen.reduce" (wrapNamed "shen.reduce" kl_shen_reduce) insertFunction "shen.reduce_help" (wrapNamed "shen.reduce_help" kl_shen_reduce_help) insertFunction "shen.+string?" (wrapNamed "shen.+string?" kl_shen_PlusstringP) insertFunction "shen.+vector" (wrapNamed "shen.+vector" kl_shen_Plusvector) insertFunction "shen.ebr" (wrapNamed "shen.ebr" kl_shen_ebr) insertFunction "shen.add_test" (wrapNamed "shen.add_test" kl_shen_add_test) insertFunction "shen.cond-expression" (wrapNamed "shen.cond-expression" kl_shen_cond_expression) insertFunction "shen.cond-form" (wrapNamed "shen.cond-form" kl_shen_cond_form) insertFunction "shen.encode-choices" (wrapNamed "shen.encode-choices" kl_shen_encode_choices) insertFunction "shen.case-form" (wrapNamed "shen.case-form" kl_shen_case_form) insertFunction "shen.embed-and" (wrapNamed "shen.embed-and" kl_shen_embed_and) insertFunction "shen.err-condition" (wrapNamed "shen.err-condition" kl_shen_err_condition) insertFunction "shen.sys-error" (wrapNamed "shen.sys-error" kl_shen_sys_error) insertFunction "thaw" (wrapNamed "thaw" kl_thaw) insertFunction "eval" (wrapNamed "eval" kl_eval) insertFunction "shen.eval-without-macros" (wrapNamed "shen.eval-without-macros" kl_shen_eval_without_macros) insertFunction "shen.proc-input+" (wrapNamed "shen.proc-input+" kl_shen_proc_inputPlus) insertFunction "shen.elim-def" (wrapNamed "shen.elim-def" kl_shen_elim_def) insertFunction "shen.add-macro" (wrapNamed "shen.add-macro" kl_shen_add_macro) insertFunction "shen.packaged?" (wrapNamed "shen.packaged?" kl_shen_packagedP) insertFunction "external" (wrapNamed "external" kl_external) insertFunction "shen.package-contents" (wrapNamed "shen.package-contents" kl_shen_package_contents) insertFunction "shen.walk" (wrapNamed "shen.walk" kl_shen_walk) insertFunction "compile" (wrapNamed "compile" kl_compile) insertFunction "fail-if" (wrapNamed "fail-if" kl_fail_if) insertFunction "@s" (wrapNamed "@s" kl_Ats) insertFunction "tc?" (PL "tc?" kl_tcP) insertFunction "ps" (wrapNamed "ps" kl_ps) insertFunction "stinput" (PL "stinput" kl_stinput) insertFunction "shen.+vector?" (wrapNamed "shen.+vector?" kl_shen_PlusvectorP) insertFunction "vector" (wrapNamed "vector" kl_vector) insertFunction "shen.fillvector" (wrapNamed "shen.fillvector" kl_shen_fillvector) insertFunction "vector?" (wrapNamed "vector?" kl_vectorP) insertFunction "vector->" (wrapNamed "vector->" kl_vector_RB) insertFunction "<-vector" (wrapNamed "<-vector" kl_LB_vector) insertFunction "shen.posint?" (wrapNamed "shen.posint?" kl_shen_posintP) insertFunction "limit" (wrapNamed "limit" kl_limit) insertFunction "symbol?" (wrapNamed "symbol?" kl_symbolP) insertFunction "shen.analyse-symbol?" (wrapNamed "shen.analyse-symbol?" kl_shen_analyse_symbolP) insertFunction "shen.alpha?" (wrapNamed "shen.alpha?" kl_shen_alphaP) insertFunction "shen.alphanums?" (wrapNamed "shen.alphanums?" kl_shen_alphanumsP) insertFunction "shen.alphanum?" (wrapNamed "shen.alphanum?" kl_shen_alphanumP) insertFunction "shen.digit?" (wrapNamed "shen.digit?" kl_shen_digitP) insertFunction "variable?" (wrapNamed "variable?" kl_variableP) insertFunction "shen.analyse-variable?" (wrapNamed "shen.analyse-variable?" kl_shen_analyse_variableP) insertFunction "shen.uppercase?" (wrapNamed "shen.uppercase?" kl_shen_uppercaseP) insertFunction "gensym" (wrapNamed "gensym" kl_gensym) insertFunction "concat" (wrapNamed "concat" kl_concat) insertFunction "@p" (wrapNamed "@p" kl_Atp) insertFunction "fst" (wrapNamed "fst" kl_fst) insertFunction "snd" (wrapNamed "snd" kl_snd) insertFunction "tuple?" (wrapNamed "tuple?" kl_tupleP) insertFunction "append" (wrapNamed "append" kl_append) insertFunction "@v" (wrapNamed "@v" kl_Atv) insertFunction "shen.@v-help" (wrapNamed "shen.@v-help" kl_shen_Atv_help) insertFunction "shen.copyfromvector" (wrapNamed "shen.copyfromvector" kl_shen_copyfromvector) insertFunction "hdv" (wrapNamed "hdv" kl_hdv) insertFunction "tlv" (wrapNamed "tlv" kl_tlv) insertFunction "shen.tlv-help" (wrapNamed "shen.tlv-help" kl_shen_tlv_help) insertFunction "assoc" (wrapNamed "assoc" kl_assoc) insertFunction "boolean?" (wrapNamed "boolean?" kl_booleanP) insertFunction "nl" (wrapNamed "nl" kl_nl) insertFunction "difference" (wrapNamed "difference" kl_difference) insertFunction "do" (wrapNamed "do" kl_do) insertFunction "element?" (wrapNamed "element?" kl_elementP) insertFunction "empty?" (wrapNamed "empty?" kl_emptyP) insertFunction "fix" (wrapNamed "fix" kl_fix) insertFunction "shen.fix-help" (wrapNamed "shen.fix-help" kl_shen_fix_help) insertFunction "put" (wrapNamed "put" kl_put) insertFunction "unput" (wrapNamed "unput" kl_unput) insertFunction "shen.remove-pointer" (wrapNamed "shen.remove-pointer" kl_shen_remove_pointer) insertFunction "shen.change-pointer-value" (wrapNamed "shen.change-pointer-value" kl_shen_change_pointer_value) insertFunction "get" (wrapNamed "get" kl_get) insertFunction "hash" (wrapNamed "hash" kl_hash) insertFunction "shen.mod" (wrapNamed "shen.mod" kl_shen_mod) insertFunction "shen.multiples" (wrapNamed "shen.multiples" kl_shen_multiples) insertFunction "shen.modh" (wrapNamed "shen.modh" kl_shen_modh) insertFunction "sum" (wrapNamed "sum" kl_sum) insertFunction "head" (wrapNamed "head" kl_head) insertFunction "tail" (wrapNamed "tail" kl_tail) insertFunction "hdstr" (wrapNamed "hdstr" kl_hdstr) insertFunction "intersection" (wrapNamed "intersection" kl_intersection) insertFunction "reverse" (wrapNamed "reverse" kl_reverse) insertFunction "shen.reverse_help" (wrapNamed "shen.reverse_help" kl_shen_reverse_help) insertFunction "union" (wrapNamed "union" kl_union) insertFunction "y-or-n?" (wrapNamed "y-or-n?" kl_y_or_nP) insertFunction "not" (wrapNamed "not" kl_not) insertFunction "subst" (wrapNamed "subst" kl_subst) insertFunction "explode" (wrapNamed "explode" kl_explode) insertFunction "shen.explode-h" (wrapNamed "shen.explode-h" kl_shen_explode_h) insertFunction "cd" (wrapNamed "cd" kl_cd) insertFunction "map" (wrapNamed "map" kl_map) insertFunction "shen.map-h" (wrapNamed "shen.map-h" kl_shen_map_h) insertFunction "length" (wrapNamed "length" kl_length) insertFunction "shen.length-h" (wrapNamed "shen.length-h" kl_shen_length_h) insertFunction "occurrences" (wrapNamed "occurrences" kl_occurrences) insertFunction "nth" (wrapNamed "nth" kl_nth) insertFunction "integer?" (wrapNamed "integer?" kl_integerP) insertFunction "shen.abs" (wrapNamed "shen.abs" kl_shen_abs) insertFunction "shen.magless" (wrapNamed "shen.magless" kl_shen_magless) insertFunction "shen.integer-test?" (wrapNamed "shen.integer-test?" kl_shen_integer_testP) insertFunction "mapcan" (wrapNamed "mapcan" kl_mapcan) insertFunction "==" (wrapNamed "==" kl_EqEq) insertFunction "abort" (PL "abort" kl_abort) insertFunction "bound?" (wrapNamed "bound?" kl_boundP) insertFunction "shen.string->bytes" (wrapNamed "shen.string->bytes" kl_shen_string_RBbytes) insertFunction "maxinferences" (wrapNamed "maxinferences" kl_maxinferences) insertFunction "inferences" (PL "inferences" kl_inferences) insertFunction "protect" (wrapNamed "protect" kl_protect) insertFunction "stoutput" (PL "stoutput" kl_stoutput) insertFunction "string->symbol" (wrapNamed "string->symbol" kl_string_RBsymbol) insertFunction "optimise" (wrapNamed "optimise" kl_optimise) insertFunction "os" (PL "os" kl_os) insertFunction "language" (PL "language" kl_language) insertFunction "version" (PL "version" kl_version) insertFunction "port" (PL "port" kl_port) insertFunction "porters" (PL "porters" kl_porters) insertFunction "implementation" (PL "implementation" kl_implementation) insertFunction "release" (PL "release" kl_release) insertFunction "package?" (wrapNamed "package?" kl_packageP) insertFunction "function" (wrapNamed "function" kl_function) insertFunction "shen.lookup-func" (wrapNamed "shen.lookup-func" kl_shen_lookup_func) insertFunction "shen.datatype-error" (wrapNamed "shen.datatype-error" kl_shen_datatype_error) insertFunction "shen." (wrapNamed "shen." kl_shen_LBdatatype_rulesRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBdatatype_ruleRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBside_conditionsRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBside_conditionRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBvariablePRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBexprRB) insertFunction "shen.remove-bar" (wrapNamed "shen.remove-bar" kl_shen_remove_bar) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpremisesRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsemicolon_symbolRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpremiseRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBconclusionRB) insertFunction "shen.sequent" (wrapNamed "shen.sequent" kl_shen_sequent) insertFunction "shen." (wrapNamed "shen." kl_shen_LBformulaeRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBcomma_symbolRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBformulaRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBtypeRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBdoubleunderlineRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsingleunderlineRB) insertFunction "shen.singleunderline?" (wrapNamed "shen.singleunderline?" kl_shen_singleunderlineP) insertFunction "shen.sh?" (wrapNamed "shen.sh?" kl_shen_shP) insertFunction "shen.doubleunderline?" (wrapNamed "shen.doubleunderline?" kl_shen_doubleunderlineP) insertFunction "shen.dh?" (wrapNamed "shen.dh?" kl_shen_dhP) insertFunction "shen.process-datatype" (wrapNamed "shen.process-datatype" kl_shen_process_datatype) insertFunction "shen.remember-datatype" (wrapNamed "shen.remember-datatype" kl_shen_remember_datatype) insertFunction "shen.rules->horn-clauses" (wrapNamed "shen.rules->horn-clauses" kl_shen_rules_RBhorn_clauses) insertFunction "shen.double->singles" (wrapNamed "shen.double->singles" kl_shen_double_RBsingles) insertFunction "shen.right-rule" (wrapNamed "shen.right-rule" kl_shen_right_rule) insertFunction "shen.left-rule" (wrapNamed "shen.left-rule" kl_shen_left_rule) insertFunction "shen.right->left" (wrapNamed "shen.right->left" kl_shen_right_RBleft) insertFunction "shen.rule->horn-clause" (wrapNamed "shen.rule->horn-clause" kl_shen_rule_RBhorn_clause) insertFunction "shen.rule->horn-clause-head" (wrapNamed "shen.rule->horn-clause-head" kl_shen_rule_RBhorn_clause_head) insertFunction "shen.mode-ify" (wrapNamed "shen.mode-ify" kl_shen_mode_ify) insertFunction "shen.rule->horn-clause-body" (wrapNamed "shen.rule->horn-clause-body" kl_shen_rule_RBhorn_clause_body) insertFunction "shen.construct-search-literals" (wrapNamed "shen.construct-search-literals" kl_shen_construct_search_literals) insertFunction "shen.csl-help" (wrapNamed "shen.csl-help" kl_shen_csl_help) insertFunction "shen.construct-search-clauses" (wrapNamed "shen.construct-search-clauses" kl_shen_construct_search_clauses) insertFunction "shen.construct-search-clause" (wrapNamed "shen.construct-search-clause" kl_shen_construct_search_clause) insertFunction "shen.construct-base-search-clause" (wrapNamed "shen.construct-base-search-clause" kl_shen_construct_base_search_clause) insertFunction "shen.construct-recursive-search-clause" (wrapNamed "shen.construct-recursive-search-clause" kl_shen_construct_recursive_search_clause) insertFunction "shen.construct-side-literals" (wrapNamed "shen.construct-side-literals" kl_shen_construct_side_literals) insertFunction "shen.construct-premiss-literal" (wrapNamed "shen.construct-premiss-literal" kl_shen_construct_premiss_literal) insertFunction "shen.construct-context" (wrapNamed "shen.construct-context" kl_shen_construct_context) insertFunction "shen.recursive_cons_form" (wrapNamed "shen.recursive_cons_form" kl_shen_recursive_cons_form) insertFunction "preclude" (wrapNamed "preclude" kl_preclude) insertFunction "shen.preclude-h" (wrapNamed "shen.preclude-h" kl_shen_preclude_h) insertFunction "include" (wrapNamed "include" kl_include) insertFunction "shen.include-h" (wrapNamed "shen.include-h" kl_shen_include_h) insertFunction "preclude-all-but" (wrapNamed "preclude-all-but" kl_preclude_all_but) insertFunction "include-all-but" (wrapNamed "include-all-but" kl_include_all_but) insertFunction "shen.synonyms-help" (wrapNamed "shen.synonyms-help" kl_shen_synonyms_help) insertFunction "shen.pushnew" (wrapNamed "shen.pushnew" kl_shen_pushnew) insertFunction "shen.demod-rule" (wrapNamed "shen.demod-rule" kl_shen_demod_rule) insertFunction "shen.demodulation-function" (wrapNamed "shen.demodulation-function" kl_shen_demodulation_function) insertFunction "shen.default-rule" (PL "shen.default-rule" kl_shen_default_rule) insertFunction "shen.yacc" (wrapNamed "shen.yacc" kl_shen_yacc) insertFunction "shen.yacc->shen" (wrapNamed "shen.yacc->shen" kl_shen_yacc_RBshen) insertFunction "shen.kill-code" (wrapNamed "shen.kill-code" kl_shen_kill_code) insertFunction "kill" (PL "kill" kl_kill) insertFunction "shen.analyse-kill" (wrapNamed "shen.analyse-kill" kl_shen_analyse_kill) insertFunction "shen.split_cc_rules" (wrapNamed "shen.split_cc_rules" kl_shen_split_cc_rules) insertFunction "shen.split_cc_rule" (wrapNamed "shen.split_cc_rule" kl_shen_split_cc_rule) insertFunction "shen.semantic-completion-warning" (wrapNamed "shen.semantic-completion-warning" kl_shen_semantic_completion_warning) insertFunction "shen.default_semantics" (wrapNamed "shen.default_semantics" kl_shen_default_semantics) insertFunction "shen.grammar_symbol?" (wrapNamed "shen.grammar_symbol?" kl_shen_grammar_symbolP) insertFunction "shen.yacc_cases" (wrapNamed "shen.yacc_cases" kl_shen_yacc_cases) insertFunction "shen.cc_body" (wrapNamed "shen.cc_body" kl_shen_cc_body) insertFunction "shen.syntax" (wrapNamed "shen.syntax" kl_shen_syntax) insertFunction "shen.list-stream" (wrapNamed "shen.list-stream" kl_shen_list_stream) insertFunction "shen.decons" (wrapNamed "shen.decons" kl_shen_decons) insertFunction "shen.insert-runon" (wrapNamed "shen.insert-runon" kl_shen_insert_runon) insertFunction "shen.strip-pathname" (wrapNamed "shen.strip-pathname" kl_shen_strip_pathname) insertFunction "shen.recursive_descent" (wrapNamed "shen.recursive_descent" kl_shen_recursive_descent) insertFunction "shen.variable-match" (wrapNamed "shen.variable-match" kl_shen_variable_match) insertFunction "shen.terminal?" (wrapNamed "shen.terminal?" kl_shen_terminalP) insertFunction "shen.jump_stream?" (wrapNamed "shen.jump_stream?" kl_shen_jump_streamP) insertFunction "shen.check_stream" (wrapNamed "shen.check_stream" kl_shen_check_stream) insertFunction "shen.jump_stream" (wrapNamed "shen.jump_stream" kl_shen_jump_stream) insertFunction "shen.semantics" (wrapNamed "shen.semantics" kl_shen_semantics) insertFunction "shen.snd-or-fail" (wrapNamed "shen.snd-or-fail" kl_shen_snd_or_fail) insertFunction "fail" (PL "fail" kl_fail) insertFunction "shen.pair" (wrapNamed "shen.pair" kl_shen_pair) insertFunction "shen.hdtl" (wrapNamed "shen.hdtl" kl_shen_hdtl) insertFunction "shen." (wrapNamed "shen." kl_shen_LBExclRB) insertFunction "" (wrapNamed "" kl_LBeRB) insertFunction "read-file-as-bytelist" (wrapNamed "read-file-as-bytelist" kl_read_file_as_bytelist) insertFunction "shen.read-file-as-bytelist-help" (wrapNamed "shen.read-file-as-bytelist-help" kl_shen_read_file_as_bytelist_help) insertFunction "read-file-as-string" (wrapNamed "read-file-as-string" kl_read_file_as_string) insertFunction "shen.rfas-h" (wrapNamed "shen.rfas-h" kl_shen_rfas_h) insertFunction "input" (wrapNamed "input" kl_input) insertFunction "input+" (wrapNamed "input+" kl_inputPlus) insertFunction "shen.monotype" (wrapNamed "shen.monotype" kl_shen_monotype) insertFunction "read" (wrapNamed "read" kl_read) insertFunction "it" (PL "it" kl_it) insertFunction "shen.read-loop" (wrapNamed "shen.read-loop" kl_shen_read_loop) insertFunction "shen.terminator?" (wrapNamed "shen.terminator?" kl_shen_terminatorP) insertFunction "lineread" (wrapNamed "lineread" kl_lineread) insertFunction "shen.lineread-loop" (wrapNamed "shen.lineread-loop" kl_shen_lineread_loop) insertFunction "shen.record-it" (wrapNamed "shen.record-it" kl_shen_record_it) insertFunction "shen.trim-whitespace" (wrapNamed "shen.trim-whitespace" kl_shen_trim_whitespace) insertFunction "shen.record-it-h" (wrapNamed "shen.record-it-h" kl_shen_record_it_h) insertFunction "shen.cn-all" (wrapNamed "shen.cn-all" kl_shen_cn_all) insertFunction "read-file" (wrapNamed "read-file" kl_read_file) insertFunction "read-from-string" (wrapNamed "read-from-string" kl_read_from_string) insertFunction "shen.read-error" (wrapNamed "shen.read-error" kl_shen_read_error) insertFunction "shen.compress-50" (wrapNamed "shen.compress-50" kl_shen_compress_50) insertFunction "shen." (wrapNamed "shen." kl_shen_LBst_inputRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBlsbRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBrsbRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBlcurlyRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBrcurlyRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBbarRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsemicolonRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBcolonRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBcommaRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBequalRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBminusRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBlrbRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBrrbRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBatomRB) insertFunction "shen.control-chars" (wrapNamed "shen.control-chars" kl_shen_control_chars) insertFunction "shen.code-point" (wrapNamed "shen.code-point" kl_shen_code_point) insertFunction "shen.after-codepoint" (wrapNamed "shen.after-codepoint" kl_shen_after_codepoint) insertFunction "shen.decimalise" (wrapNamed "shen.decimalise" kl_shen_decimalise) insertFunction "shen.digits->integers" (wrapNamed "shen.digits->integers" kl_shen_digits_RBintegers) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsymRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBalphanumsRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBalphanumRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBnumRB) insertFunction "shen.numbyte?" (wrapNamed "shen.numbyte?" kl_shen_numbyteP) insertFunction "shen." (wrapNamed "shen." kl_shen_LBalphaRB) insertFunction "shen.symbol-code?" (wrapNamed "shen.symbol-code?" kl_shen_symbol_codeP) insertFunction "shen." (wrapNamed "shen." kl_shen_LBstrRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBdbqRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBstrcontentsRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBbyteRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBstrcRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBnumberRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBERB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBlog10RB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBplusRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBstopRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpredigitsRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpostdigitsRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBdigitsRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBdigitRB) insertFunction "shen.byte->digit" (wrapNamed "shen.byte->digit" kl_shen_byte_RBdigit) insertFunction "shen.pre" (wrapNamed "shen.pre" kl_shen_pre) insertFunction "shen.post" (wrapNamed "shen.post" kl_shen_post) insertFunction "shen.expt" (wrapNamed "shen.expt" kl_shen_expt) insertFunction "shen." (wrapNamed "shen." kl_shen_LBst_input1RB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBst_input2RB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBcommentRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsinglelineRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBbackslashRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBanysingleRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBnon_returnRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBreturnRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBmultilineRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBtimesRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBanymultiRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBwhitespacesRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBwhitespaceRB) insertFunction "shen.cons_form" (wrapNamed "shen.cons_form" kl_shen_cons_form) insertFunction "shen.package-macro" (wrapNamed "shen.package-macro" kl_shen_package_macro) insertFunction "shen.record-exceptions" (wrapNamed "shen.record-exceptions" kl_shen_record_exceptions) insertFunction "shen.packageh" (wrapNamed "shen.packageh" kl_shen_packageh) insertFunction "shen." (wrapNamed "shen." kl_shen_LBdefprologRB) insertFunction "shen.prolog-error" (wrapNamed "shen.prolog-error" kl_shen_prolog_error) insertFunction "shen.next-50" (wrapNamed "shen.next-50" kl_shen_next_50) insertFunction "shen.decons-string" (wrapNamed "shen.decons-string" kl_shen_decons_string) insertFunction "shen.insert-predicate" (wrapNamed "shen.insert-predicate" kl_shen_insert_predicate) insertFunction "shen." (wrapNamed "shen." kl_shen_LBpredicateMultRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBclausesMultRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBclauseMultRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBheadMultRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBtermMultRB) insertFunction "shen.legitimate-term?" (wrapNamed "shen.legitimate-term?" kl_shen_legitimate_termP) insertFunction "shen.eval-cons" (wrapNamed "shen.eval-cons" kl_shen_eval_cons) insertFunction "shen." (wrapNamed "shen." kl_shen_LBbodyMultRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBliteralMultRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBendMultRB) insertFunction "cut" (wrapNamed "cut" kl_cut) insertFunction "shen.insert_modes" (wrapNamed "shen.insert_modes" kl_shen_insert_modes) insertFunction "shen.s-prolog" (wrapNamed "shen.s-prolog" kl_shen_s_prolog) insertFunction "shen.prolog->shen" (wrapNamed "shen.prolog->shen" kl_shen_prolog_RBshen) insertFunction "shen.s-prolog_clause" (wrapNamed "shen.s-prolog_clause" kl_shen_s_prolog_clause) insertFunction "shen.head_abstraction" (wrapNamed "shen.head_abstraction" kl_shen_head_abstraction) insertFunction "shen.complexity_head" (wrapNamed "shen.complexity_head" kl_shen_complexity_head) insertFunction "shen.complexity" (wrapNamed "shen.complexity" kl_shen_complexity) insertFunction "shen.product" (wrapNamed "shen.product" kl_shen_product) insertFunction "shen.s-prolog_literal" (wrapNamed "shen.s-prolog_literal" kl_shen_s_prolog_literal) insertFunction "shen.insert_deref" (wrapNamed "shen.insert_deref" kl_shen_insert_deref) insertFunction "shen.insert_lazyderef" (wrapNamed "shen.insert_lazyderef" kl_shen_insert_lazyderef) insertFunction "shen.group_clauses" (wrapNamed "shen.group_clauses" kl_shen_group_clauses) insertFunction "shen.collect" (wrapNamed "shen.collect" kl_shen_collect) insertFunction "shen.same_predicate?" (wrapNamed "shen.same_predicate?" kl_shen_same_predicateP) insertFunction "shen.compile_prolog_procedure" (wrapNamed "shen.compile_prolog_procedure" kl_shen_compile_prolog_procedure) insertFunction "shen.procedure_name" (wrapNamed "shen.procedure_name" kl_shen_procedure_name) insertFunction "shen.clauses-to-shen" (wrapNamed "shen.clauses-to-shen" kl_shen_clauses_to_shen) insertFunction "shen.catch-cut" (wrapNamed "shen.catch-cut" kl_shen_catch_cut) insertFunction "shen.catchpoint" (PL "shen.catchpoint" kl_shen_catchpoint) insertFunction "shen.cutpoint" (wrapNamed "shen.cutpoint" kl_shen_cutpoint) insertFunction "shen.nest-disjunct" (wrapNamed "shen.nest-disjunct" kl_shen_nest_disjunct) insertFunction "shen.lisp-or" (wrapNamed "shen.lisp-or" kl_shen_lisp_or) insertFunction "shen.prolog-aritycheck" (wrapNamed "shen.prolog-aritycheck" kl_shen_prolog_aritycheck) insertFunction "shen.linearise-clause" (wrapNamed "shen.linearise-clause" kl_shen_linearise_clause) insertFunction "shen.clause_form" (wrapNamed "shen.clause_form" kl_shen_clause_form) insertFunction "shen.explicit_modes" (wrapNamed "shen.explicit_modes" kl_shen_explicit_modes) insertFunction "shen.em_help" (wrapNamed "shen.em_help" kl_shen_em_help) insertFunction "shen.cf_help" (wrapNamed "shen.cf_help" kl_shen_cf_help) insertFunction "occurs-check" (wrapNamed "occurs-check" kl_occurs_check) insertFunction "shen.aum" (wrapNamed "shen.aum" kl_shen_aum) insertFunction "shen.continuation_call" (wrapNamed "shen.continuation_call" kl_shen_continuation_call) insertFunction "remove" (wrapNamed "remove" kl_remove) insertFunction "shen.remove-h" (wrapNamed "shen.remove-h" kl_shen_remove_h) insertFunction "shen.cc_help" (wrapNamed "shen.cc_help" kl_shen_cc_help) insertFunction "shen.make_mu_application" (wrapNamed "shen.make_mu_application" kl_shen_make_mu_application) insertFunction "shen.mu_reduction" (wrapNamed "shen.mu_reduction" kl_shen_mu_reduction) insertFunction "shen.rcons_form" (wrapNamed "shen.rcons_form" kl_shen_rcons_form) insertFunction "shen.remove_modes" (wrapNamed "shen.remove_modes" kl_shen_remove_modes) insertFunction "shen.ephemeral_variable?" (wrapNamed "shen.ephemeral_variable?" kl_shen_ephemeral_variableP) insertFunction "shen.prolog_constant?" (wrapNamed "shen.prolog_constant?" kl_shen_prolog_constantP) insertFunction "shen.aum_to_shen" (wrapNamed "shen.aum_to_shen" kl_shen_aum_to_shen) insertFunction "shen.chwild" (wrapNamed "shen.chwild" kl_shen_chwild) insertFunction "shen.newpv" (wrapNamed "shen.newpv" kl_shen_newpv) insertFunction "shen.resizeprocessvector" (wrapNamed "shen.resizeprocessvector" kl_shen_resizeprocessvector) insertFunction "shen.resize-vector" (wrapNamed "shen.resize-vector" kl_shen_resize_vector) insertFunction "shen.copy-vector" (wrapNamed "shen.copy-vector" kl_shen_copy_vector) insertFunction "shen.copy-vector-stage-1" (wrapNamed "shen.copy-vector-stage-1" kl_shen_copy_vector_stage_1) insertFunction "shen.copy-vector-stage-2" (wrapNamed "shen.copy-vector-stage-2" kl_shen_copy_vector_stage_2) insertFunction "shen.mk-pvar" (wrapNamed "shen.mk-pvar" kl_shen_mk_pvar) insertFunction "shen.pvar?" (wrapNamed "shen.pvar?" kl_shen_pvarP) insertFunction "shen.bindv" (wrapNamed "shen.bindv" kl_shen_bindv) insertFunction "shen.unbindv" (wrapNamed "shen.unbindv" kl_shen_unbindv) insertFunction "shen.incinfs" (PL "shen.incinfs" kl_shen_incinfs) insertFunction "shen.call_the_continuation" (wrapNamed "shen.call_the_continuation" kl_shen_call_the_continuation) insertFunction "shen.newcontinuation" (wrapNamed "shen.newcontinuation" kl_shen_newcontinuation) insertFunction "return" (wrapNamed "return" kl_return) insertFunction "shen.measure&return" (wrapNamed "shen.measure&return" kl_shen_measureAndreturn) insertFunction "unify" (wrapNamed "unify" kl_unify) insertFunction "shen.lzy=" (wrapNamed "shen.lzy=" kl_shen_lzyEq) insertFunction "shen.deref" (wrapNamed "shen.deref" kl_shen_deref) insertFunction "shen.lazyderef" (wrapNamed "shen.lazyderef" kl_shen_lazyderef) insertFunction "shen.valvector" (wrapNamed "shen.valvector" kl_shen_valvector) insertFunction "unify!" (wrapNamed "unify!" kl_unifyExcl) insertFunction "shen.lzy=!" (wrapNamed "shen.lzy=!" kl_shen_lzyEqExcl) insertFunction "shen.occurs?" (wrapNamed "shen.occurs?" kl_shen_occursP) insertFunction "identical" (wrapNamed "identical" kl_identical) insertFunction "shen.lzy==" (wrapNamed "shen.lzy==" kl_shen_lzyEqEq) insertFunction "shen.pvar" (wrapNamed "shen.pvar" kl_shen_pvar) insertFunction "bind" (wrapNamed "bind" kl_bind) insertFunction "fwhen" (wrapNamed "fwhen" kl_fwhen) insertFunction "call" (wrapNamed "call" kl_call) insertFunction "shen.call-help" (wrapNamed "shen.call-help" kl_shen_call_help) insertFunction "shen.intprolog" (wrapNamed "shen.intprolog" kl_shen_intprolog) insertFunction "shen.intprolog-help" (wrapNamed "shen.intprolog-help" kl_shen_intprolog_help) insertFunction "shen.intprolog-help-help" (wrapNamed "shen.intprolog-help-help" kl_shen_intprolog_help_help) insertFunction "shen.call-rest" (wrapNamed "shen.call-rest" kl_shen_call_rest) insertFunction "shen.start-new-prolog-process" (PL "shen.start-new-prolog-process" kl_shen_start_new_prolog_process) insertFunction "shen.insert-prolog-variables" (wrapNamed "shen.insert-prolog-variables" kl_shen_insert_prolog_variables) insertFunction "shen.insert-prolog-variables-help" (wrapNamed "shen.insert-prolog-variables-help" kl_shen_insert_prolog_variables_help) insertFunction "shen.initialise-prolog" (wrapNamed "shen.initialise-prolog" kl_shen_initialise_prolog) insertFunction "shen.f_error" (wrapNamed "shen.f_error" kl_shen_f_error) insertFunction "shen.tracked?" (wrapNamed "shen.tracked?" kl_shen_trackedP) insertFunction "track" (wrapNamed "track" kl_track) insertFunction "shen.track-function" (wrapNamed "shen.track-function" kl_shen_track_function) insertFunction "shen.insert-tracking-code" (wrapNamed "shen.insert-tracking-code" kl_shen_insert_tracking_code) insertFunction "step" (wrapNamed "step" kl_step) insertFunction "spy" (wrapNamed "spy" kl_spy) insertFunction "shen.terpri-or-read-char" (PL "shen.terpri-or-read-char" kl_shen_terpri_or_read_char) insertFunction "shen.check-byte" (wrapNamed "shen.check-byte" kl_shen_check_byte) insertFunction "shen.input-track" (wrapNamed "shen.input-track" kl_shen_input_track) insertFunction "shen.recursively-print" (wrapNamed "shen.recursively-print" kl_shen_recursively_print) insertFunction "shen.spaces" (wrapNamed "shen.spaces" kl_shen_spaces) insertFunction "shen.output-track" (wrapNamed "shen.output-track" kl_shen_output_track) insertFunction "untrack" (wrapNamed "untrack" kl_untrack) insertFunction "profile" (wrapNamed "profile" kl_profile) insertFunction "shen.profile-help" (wrapNamed "shen.profile-help" kl_shen_profile_help) insertFunction "unprofile" (wrapNamed "unprofile" kl_unprofile) insertFunction "shen.profile-func" (wrapNamed "shen.profile-func" kl_shen_profile_func) insertFunction "profile-results" (wrapNamed "profile-results" kl_profile_results) insertFunction "shen.get-profile" (wrapNamed "shen.get-profile" kl_shen_get_profile) insertFunction "shen.put-profile" (wrapNamed "shen.put-profile" kl_shen_put_profile) insertFunction "load" (wrapNamed "load" kl_load) insertFunction "shen.load-help" (wrapNamed "shen.load-help" kl_shen_load_help) insertFunction "shen.remove-synonyms" (wrapNamed "shen.remove-synonyms" kl_shen_remove_synonyms) insertFunction "shen.typecheck-and-load" (wrapNamed "shen.typecheck-and-load" kl_shen_typecheck_and_load) insertFunction "shen.typetable" (wrapNamed "shen.typetable" kl_shen_typetable) insertFunction "shen.assumetype" (wrapNamed "shen.assumetype" kl_shen_assumetype) insertFunction "shen.unwind-types" (wrapNamed "shen.unwind-types" kl_shen_unwind_types) insertFunction "shen.remtype" (wrapNamed "shen.remtype" kl_shen_remtype) insertFunction "shen.removetype" (wrapNamed "shen.removetype" kl_shen_removetype) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsigPlusrestRB) insertFunction "write-to-file" (wrapNamed "write-to-file" kl_write_to_file) insertFunction "pr" (wrapNamed "pr" kl_pr) insertFunction "shen.prh" (wrapNamed "shen.prh" kl_shen_prh) insertFunction "shen.write-char-and-inc" (wrapNamed "shen.write-char-and-inc" kl_shen_write_char_and_inc) insertFunction "print" (wrapNamed "print" kl_print) insertFunction "shen.prhush" (wrapNamed "shen.prhush" kl_shen_prhush) insertFunction "shen.mkstr" (wrapNamed "shen.mkstr" kl_shen_mkstr) insertFunction "shen.mkstr-l" (wrapNamed "shen.mkstr-l" kl_shen_mkstr_l) insertFunction "shen.insert-l" (wrapNamed "shen.insert-l" kl_shen_insert_l) insertFunction "shen.factor-cn" (wrapNamed "shen.factor-cn" kl_shen_factor_cn) insertFunction "shen.proc-nl" (wrapNamed "shen.proc-nl" kl_shen_proc_nl) insertFunction "shen.mkstr-r" (wrapNamed "shen.mkstr-r" kl_shen_mkstr_r) insertFunction "shen.insert" (wrapNamed "shen.insert" kl_shen_insert) insertFunction "shen.insert-h" (wrapNamed "shen.insert-h" kl_shen_insert_h) insertFunction "shen.app" (wrapNamed "shen.app" kl_shen_app) insertFunction "shen.arg->str" (wrapNamed "shen.arg->str" kl_shen_arg_RBstr) insertFunction "shen.list->str" (wrapNamed "shen.list->str" kl_shen_list_RBstr) insertFunction "shen.maxseq" (PL "shen.maxseq" kl_shen_maxseq) insertFunction "shen.iter-list" (wrapNamed "shen.iter-list" kl_shen_iter_list) insertFunction "shen.str->str" (wrapNamed "shen.str->str" kl_shen_str_RBstr) insertFunction "shen.vector->str" (wrapNamed "shen.vector->str" kl_shen_vector_RBstr) insertFunction "shen.print-vector?" (wrapNamed "shen.print-vector?" kl_shen_print_vectorP) insertFunction "shen.fbound?" (wrapNamed "shen.fbound?" kl_shen_fboundP) insertFunction "shen.tuple" (wrapNamed "shen.tuple" kl_shen_tuple) insertFunction "shen.iter-vector" (wrapNamed "shen.iter-vector" kl_shen_iter_vector) insertFunction "shen.atom->str" (wrapNamed "shen.atom->str" kl_shen_atom_RBstr) insertFunction "shen.funexstring" (PL "shen.funexstring" kl_shen_funexstring) insertFunction "shen.list?" (wrapNamed "shen.list?" kl_shen_listP) insertFunction "macroexpand" (wrapNamed "macroexpand" kl_macroexpand) insertFunction "shen.error-macro" (wrapNamed "shen.error-macro" kl_shen_error_macro) insertFunction "shen.output-macro" (wrapNamed "shen.output-macro" kl_shen_output_macro) insertFunction "shen.make-string-macro" (wrapNamed "shen.make-string-macro" kl_shen_make_string_macro) insertFunction "shen.input-macro" (wrapNamed "shen.input-macro" kl_shen_input_macro) insertFunction "shen.compose" (wrapNamed "shen.compose" kl_shen_compose) insertFunction "shen.compile-macro" (wrapNamed "shen.compile-macro" kl_shen_compile_macro) insertFunction "shen.prolog-macro" (wrapNamed "shen.prolog-macro" kl_shen_prolog_macro) insertFunction "shen.receive-terms" (wrapNamed "shen.receive-terms" kl_shen_receive_terms) insertFunction "shen.pass-literals" (wrapNamed "shen.pass-literals" kl_shen_pass_literals) insertFunction "shen.defprolog-macro" (wrapNamed "shen.defprolog-macro" kl_shen_defprolog_macro) insertFunction "shen.datatype-macro" (wrapNamed "shen.datatype-macro" kl_shen_datatype_macro) insertFunction "shen.intern-type" (wrapNamed "shen.intern-type" kl_shen_intern_type) insertFunction "shen.@s-macro" (wrapNamed "shen.@s-macro" kl_shen_Ats_macro) insertFunction "shen.synonyms-macro" (wrapNamed "shen.synonyms-macro" kl_shen_synonyms_macro) insertFunction "shen.curry-synonyms" (wrapNamed "shen.curry-synonyms" kl_shen_curry_synonyms) insertFunction "shen.nl-macro" (wrapNamed "shen.nl-macro" kl_shen_nl_macro) insertFunction "shen.assoc-macro" (wrapNamed "shen.assoc-macro" kl_shen_assoc_macro) insertFunction "shen.let-macro" (wrapNamed "shen.let-macro" kl_shen_let_macro) insertFunction "shen.abs-macro" (wrapNamed "shen.abs-macro" kl_shen_abs_macro) insertFunction "shen.cases-macro" (wrapNamed "shen.cases-macro" kl_shen_cases_macro) insertFunction "shen.timer-macro" (wrapNamed "shen.timer-macro" kl_shen_timer_macro) insertFunction "shen.tuple-up" (wrapNamed "shen.tuple-up" kl_shen_tuple_up) insertFunction "shen.put/get-macro" (wrapNamed "shen.put/get-macro" kl_shen_putDivget_macro) insertFunction "shen.function-macro" (wrapNamed "shen.function-macro" kl_shen_function_macro) insertFunction "shen.function-abstraction" (wrapNamed "shen.function-abstraction" kl_shen_function_abstraction) insertFunction "shen.function-abstraction-help" (wrapNamed "shen.function-abstraction-help" kl_shen_function_abstraction_help) insertFunction "undefmacro" (wrapNamed "undefmacro" kl_undefmacro) insertFunction "shen.findpos" (wrapNamed "shen.findpos" kl_shen_findpos) insertFunction "shen.remove-nth" (wrapNamed "shen.remove-nth" kl_shen_remove_nth) insertFunction "shen.initialise_arity_table" (wrapNamed "shen.initialise_arity_table" kl_shen_initialise_arity_table) insertFunction "arity" (wrapNamed "arity" kl_arity) insertFunction "systemf" (wrapNamed "systemf" kl_systemf) insertFunction "adjoin" (wrapNamed "adjoin" kl_adjoin) insertFunction "shen.symbol-table-entry" (wrapNamed "shen.symbol-table-entry" kl_shen_symbol_table_entry) insertFunction "shen.lambda-form" (wrapNamed "shen.lambda-form" kl_shen_lambda_form) insertFunction "shen.add-end" (wrapNamed "shen.add-end" kl_shen_add_end) insertFunction "specialise" (wrapNamed "specialise" kl_specialise) insertFunction "unspecialise" (wrapNamed "unspecialise" kl_unspecialise) insertFunction "declare" (wrapNamed "declare" kl_declare) insertFunction "shen.demodulate" (wrapNamed "shen.demodulate" kl_shen_demodulate) insertFunction "shen.variancy-test" (wrapNamed "shen.variancy-test" kl_shen_variancy_test) insertFunction "shen.variant?" (wrapNamed "shen.variant?" kl_shen_variantP) insertFunction "shen.typecheck" (wrapNamed "shen.typecheck" kl_shen_typecheck) insertFunction "shen.curry" (wrapNamed "shen.curry" kl_shen_curry) insertFunction "shen.special?" (wrapNamed "shen.special?" kl_shen_specialP) insertFunction "shen.extraspecial?" (wrapNamed "shen.extraspecial?" kl_shen_extraspecialP) insertFunction "shen.t*" (wrapNamed "shen.t*" kl_shen_tMult) insertFunction "shen.type-theory-enabled?" (PL "shen.type-theory-enabled?" kl_shen_type_theory_enabledP) insertFunction "enable-type-theory" (wrapNamed "enable-type-theory" kl_enable_type_theory) insertFunction "shen.prolog-failure" (wrapNamed "shen.prolog-failure" kl_shen_prolog_failure) insertFunction "shen.maxinfexceeded?" (PL "shen.maxinfexceeded?" kl_shen_maxinfexceededP) insertFunction "shen.errormaxinfs" (PL "shen.errormaxinfs" kl_shen_errormaxinfs) insertFunction "shen.udefs*" (wrapNamed "shen.udefs*" kl_shen_udefsMult) insertFunction "shen.th*" (wrapNamed "shen.th*" kl_shen_thMult) insertFunction "shen.t*-hyps" (wrapNamed "shen.t*-hyps" kl_shen_tMult_hyps) insertFunction "shen.show" (wrapNamed "shen.show" kl_shen_show) insertFunction "shen.line" (PL "shen.line" kl_shen_line) insertFunction "shen.show-p" (wrapNamed "shen.show-p" kl_shen_show_p) insertFunction "shen.show-assumptions" (wrapNamed "shen.show-assumptions" kl_shen_show_assumptions) insertFunction "shen.pause-for-user" (PL "shen.pause-for-user" kl_shen_pause_for_user) insertFunction "shen.typedf?" (wrapNamed "shen.typedf?" kl_shen_typedfP) insertFunction "shen.sigf" (wrapNamed "shen.sigf" kl_shen_sigf) insertFunction "shen.placeholder" (PL "shen.placeholder" kl_shen_placeholder) insertFunction "shen.base" (wrapNamed "shen.base" kl_shen_base) insertFunction "shen.by_hypothesis" (wrapNamed "shen.by_hypothesis" kl_shen_by_hypothesis) insertFunction "shen.t*-def" (wrapNamed "shen.t*-def" kl_shen_tMult_def) insertFunction "shen.t*-defh" (wrapNamed "shen.t*-defh" kl_shen_tMult_defh) insertFunction "shen.t*-defhh" (wrapNamed "shen.t*-defhh" kl_shen_tMult_defhh) insertFunction "shen.memo" (wrapNamed "shen.memo" kl_shen_memo) insertFunction "shen." (wrapNamed "shen." kl_shen_LBsigPlusrulesRB) insertFunction "shen." (wrapNamed "shen." kl_shen_LBnon_ll_rulesRB) insertFunction "shen.ue" (wrapNamed "shen.ue" kl_shen_ue) insertFunction "shen.ue-sig" (wrapNamed "shen.ue-sig" kl_shen_ue_sig) insertFunction "shen.ues" (wrapNamed "shen.ues" kl_shen_ues) insertFunction "shen.ue?" (wrapNamed "shen.ue?" kl_shen_ueP) insertFunction "shen.ue-h?" (wrapNamed "shen.ue-h?" kl_shen_ue_hP) insertFunction "shen.t*-rules" (wrapNamed "shen.t*-rules" kl_shen_tMult_rules) insertFunction "shen.t*-rule" (wrapNamed "shen.t*-rule" kl_shen_tMult_rule) insertFunction "shen.placeholders" (wrapNamed "shen.placeholders" kl_shen_placeholders) insertFunction "shen.newhyps" (wrapNamed "shen.newhyps" kl_shen_newhyps) insertFunction "shen.patthyps" (wrapNamed "shen.patthyps" kl_shen_patthyps) insertFunction "shen.result-type" (wrapNamed "shen.result-type" kl_shen_result_type) insertFunction "shen.t*-patterns" (wrapNamed "shen.t*-patterns" kl_shen_tMult_patterns) insertFunction "shen.t*-action" (wrapNamed "shen.t*-action" kl_shen_tMult_action) insertFunction "findall" (wrapNamed "findall" kl_findall) insertFunction "shen.findallhelp" (wrapNamed "shen.findallhelp" kl_shen_findallhelp) insertFunction "shen.remember" (wrapNamed "shen.remember" kl_shen_remember)