(PROCLAIM '(OPTIMIZE SPEED))
(IMPORT-MODULE "includer")

(IMPORT-MODULE "scanner")

(IMPORT-MODULE "pile")

(IMPORT-MODULE "parser")

(IMPORT-MODULE "ast")

(IN-PACKAGE "BOOTTRAN")

(PROVIDE "translator")

(EXPORT '|evalBootFile|)

(DEFPARAMETER |$currentModuleName| NIL)

(DEFPARAMETER |$foreignsDefsForCLisp| NIL)

(DEFUN |genModuleFinalization| (|stream|)
  (PROG (|init|)
    (DECLARE (SPECIAL |$currentModuleName| |$foreignsDefsForCLisp|))
    (RETURN
      (COND
        ((|%hasFeature| :CLISP)
         (COND
           ((NULL |$foreignsDefsForCLisp|) NIL)
           ((NULL |$currentModuleName|)
            (|coreError| "current module has no name"))
           (T (SETQ |init|
                    (CONS 'DEFUN
                          (CONS (INTERN (CONCAT |$currentModuleName|
                                         '|InitCLispFFI|))
                                (CONS NIL
                                      (CONS
                                       (LIST 'MAPC
                                        (LIST 'FUNCTION 'FMAKUNBOUND)
                                        (LIST 'QUOTE
                                         (LET
                                          ((|bfVar#2| NIL)
                                           (|bfVar#3| NIL)
                                           (|bfVar#1|
                                            |$foreignsDefsForCLisp|)
                                           (|d| NIL))
                                           (LOOP
                                             (COND
                                               ((OR (ATOM |bfVar#1|)
                                                 (PROGN
                                                   (SETQ |d|
                                                    (CAR |bfVar#1|))
                                                   NIL))
                                                (RETURN |bfVar#2|))
                                               ((NULL |bfVar#2|)
                                                (SETQ |bfVar#2|
                                                 #0=(CONS (CADR |d|)
                                                     NIL))
                                                (SETQ |bfVar#3|
                                                 |bfVar#2|))
                                               (T
                                                (RPLACD |bfVar#3| #0#)
                                                (SETQ |bfVar#3|
                                                 (CDR |bfVar#3|))))
                                             (SETQ |bfVar#1|
                                              (CDR |bfVar#1|))))))
                                       (LET
                                        ((|bfVar#5| NIL)
                                         (|bfVar#6| NIL)
                                         (|bfVar#4|
                                          |$foreignsDefsForCLisp|)
                                         (|d| NIL))
                                         (LOOP
                                           (COND
                                             ((OR (ATOM |bfVar#4|)
                                               (PROGN
                                                 (SETQ |d|
                                                  (CAR |bfVar#4|))
                                                 NIL))
                                              (RETURN |bfVar#5|))
                                             ((NULL |bfVar#5|)
                                              (SETQ |bfVar#5|
                                               #1=(CONS
                                                   (LIST 'EVAL
                                                    (LIST 'QUOTE |d|))
                                                   NIL))
                                              (SETQ |bfVar#6|
                                               |bfVar#5|))
                                             (T (RPLACD |bfVar#6| #1#)
                                              (SETQ |bfVar#6|
                                               (CDR |bfVar#6|))))
                                           (SETQ |bfVar#4|
                                            (CDR |bfVar#4|)))))))))
              (REALLYPRETTYPRINT |init| |stream|))))
        (T NIL)))))

(DEFUN |genOptimizeOptions| (|stream|)
  (REALLYPRETTYPRINT
      (LIST 'PROCLAIM
            (LIST 'QUOTE (CONS 'OPTIMIZE |$LispOptimizeOptions|)))
      |stream|))

(DEFUN |AxiomCore|::|%sysInit| ()
  (PROGN
    (SETQ *LOAD-VERBOSE* NIL)
    (COND
      ((|%hasFeature| :GCL)
       (SETF (SYMBOL-VALUE
                 (|bfColonColon| 'COMPILER '*COMPILE-VERBOSE*))
             NIL)
       (SETF (SYMBOL-VALUE
                 (|bfColonColon| 'COMPILER
                     'SUPPRESS-COMPILER-WARNINGS*))
             NIL)
       (SETF (SYMBOL-VALUE
                 (|bfColonColon| 'COMPILER 'SUPPRESS-COMPILER-NOTES*))
             T)))))

(DECLAIM (FTYPE (FUNCTION (|%Thing|) |%Thing|) |setCurrentPackage|))

(DEFUN |setCurrentPackage| (|x|) (SETQ *PACKAGE* |x|))

(DECLAIM (FTYPE (FUNCTION (|%String|) |%Thing|) |shoeCOMPILE-FILE|))

(DEFUN |shoeCOMPILE-FILE| (|lspFileName|)
  (COMPILE-FILE |lspFileName|))

(DEFUN BOOTTOCL (|fn| |out|)
  (PROG (|result| |callingPackage|)
    (RETURN
      (UNWIND-PROTECT
        (PROGN
          (|startCompileDuration|)
          (SETQ |callingPackage| *PACKAGE*)
          (IN-PACKAGE "BOOTTRAN")
          (SETQ |result| (BOOTTOCLLINES NIL |fn| |out|))
          (|setCurrentPackage| |callingPackage|)
          |result|)
        (|endCompileDuration|)))))

(DEFUN BOOTCLAM (|fn| |out|)
  (DECLARE (SPECIAL |$bfClamming|))
  (PROGN (SETQ |$bfClamming| T) (BOOTCLAMLINES NIL |fn| |out|)))

(DEFUN BOOTCLAMLINES (|lines| |fn| |out|)
  (BOOTTOCLLINES |lines| |fn| |out|))

(DEFUN BOOTTOCLLINES (|lines| |fn| |outfn|)
  (PROG (|infn|)
    (RETURN
      (PROGN
        (SETQ |infn| (|shoeAddbootIfNec| |fn|))
        (|shoeOpenInputFile| |a| |infn|
            (|shoeClLines| |a| |fn| |lines| |outfn|))))))

(DEFUN |shoeClLines| (|a| |fn| |lines| |outfn|)
  (DECLARE (SPECIAL |$GenVarCounter|))
  (COND
    ((NULL |a|) (|shoeNotFound| |fn|))
    (T (SETQ |$GenVarCounter| 0)
       (|shoeOpenOutputFile| |stream| |outfn|
           (PROGN
             (|genOptimizeOptions| |stream|)
             (LET ((|bfVar#7| |lines|) (|line| NIL))
               (LOOP
                 (COND
                   ((OR (ATOM |bfVar#7|)
                        (PROGN (SETQ |line| (CAR |bfVar#7|)) NIL))
                    (RETURN NIL))
                   (T (|shoeFileLine| |line| |stream|)))
                 (SETQ |bfVar#7| (CDR |bfVar#7|))))
             (|shoeFileTrees| (|shoeTransformStream| |a|) |stream|)
             (|genModuleFinalization| |stream|)))
       |outfn|)))

(DEFUN BOOTTOCLC (|fn| |out|)
  (PROG (|result| |callingPackage|)
    (RETURN
      (UNWIND-PROTECT
        (PROGN
          (|startCompileDuration|)
          (SETQ |callingPackage| *PACKAGE*)
          (IN-PACKAGE "BOOTTRAN")
          (SETQ |result| (BOOTTOCLCLINES NIL |fn| |out|))
          (|setCurrentPackage| |callingPackage|)
          |result|)
        (|endCompileDuration|)))))

(DEFUN BOOTTOCLCLINES (|lines| |fn| |outfn|)
  (PROG (|infn|)
    (RETURN
      (PROGN
        (SETQ |infn| (|shoeAddbootIfNec| |fn|))
        (|shoeOpenInputFile| |a| |infn|
            (|shoeClCLines| |a| |fn| |lines| |outfn|))))))

(DEFUN |shoeClCLines| (|a| |fn| |lines| |outfn|)
  (DECLARE (SPECIAL |$GenVarCounter|))
  (COND
    ((NULL |a|) (|shoeNotFound| |fn|))
    (T (SETQ |$GenVarCounter| 0)
       (|shoeOpenOutputFile| |stream| |outfn|
           (PROGN
             (|genOptimizeOptions| |stream|)
             (LET ((|bfVar#8| |lines|) (|line| NIL))
               (LOOP
                 (COND
                   ((OR (ATOM |bfVar#8|)
                        (PROGN (SETQ |line| (CAR |bfVar#8|)) NIL))
                    (RETURN NIL))
                   (T (|shoeFileLine| |line| |stream|)))
                 (SETQ |bfVar#8| (CDR |bfVar#8|))))
             (|shoeFileTrees|
                 (|shoeTransformToFile| |stream|
                     (|shoeInclude|
                         (|bAddLineNumber| (|bRgen| |a|) (|bIgen| 0))))
                 |stream|)
             (|genModuleFinalization| |stream|)))
       |outfn|)))

(DECLAIM (FTYPE (FUNCTION (|%String|) |%Thing|) BOOTTOMC))

(DEFUN BOOTTOMC (|fn|)
  (PROG (|result| |infn| |callingPackage|)
    (DECLARE (SPECIAL |$GenVarCounter|))
    (RETURN
      (PROGN
        (SETQ |callingPackage| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |$GenVarCounter| 0)
        (SETQ |infn| (|shoeAddbootIfNec| |fn|))
        (SETQ |result|
              (|shoeOpenInputFile| |a| |infn| (|shoeMc| |a| |fn|)))
        (|setCurrentPackage| |callingPackage|)
        |result|))))

(DEFUN |shoeMc| (|a| |fn|)
  (COND
    ((NULL |a|) (|shoeNotFound| |fn|))
    (T (|shoePCompileTrees| (|shoeTransformStream| |a|))
       (|shoeConsole| (CONCAT |fn| " COMPILED AND LOADED")))))

(DEFUN |evalBootFile| (|fn|)
  (PROG (|outfn| |infn| |b|)
    (RETURN
      (PROGN
        (SETQ |b| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |infn| (|shoeAddbootIfNec| |fn|))
        (SETQ |outfn|
              (CONCAT (|shoeRemovebootIfNec| |fn|) "."
                      *LISP-SOURCE-FILETYPE*))
        (|shoeOpenInputFile| |a| |infn|
            (|shoeClLines| |a| |infn| NIL |outfn|))
        (|setCurrentPackage| |b|)
        (LOAD |outfn|)))))

(DECLAIM (FTYPE (FUNCTION (|%String|) |%Thing|) BO))

(DEFUN BO (|fn|)
  (PROG (|infn| |b|)
    (DECLARE (SPECIAL |$GenVarCounter|))
    (RETURN
      (PROGN
        (SETQ |b| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |$GenVarCounter| 0)
        (SETQ |infn| (|shoeAddbootIfNec| |fn|))
        (|shoeOpenInputFile| |a| |infn| (|shoeToConsole| |a| |fn|))
        (|setCurrentPackage| |b|)))))

(DEFUN BOCLAM (|fn|)
  (PROG (|result| |infn| |callingPackage|)
    (DECLARE (SPECIAL |$bfClamming| |$GenVarCounter|))
    (RETURN
      (PROGN
        (SETQ |callingPackage| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |$GenVarCounter| 0)
        (SETQ |$bfClamming| T)
        (SETQ |infn| (|shoeAddbootIfNec| |fn|))
        (SETQ |result|
              (|shoeOpenInputFile| |a| |infn|
                  (|shoeToConsole| |a| |fn|)))
        (|setCurrentPackage| |callingPackage|)
        |result|))))

(DEFUN |shoeToConsole| (|a| |fn|)
  (COND
    ((NULL |a|) (|shoeNotFound| |fn|))
    (T (|shoeConsoleTrees|
           (|shoeTransformToConsole|
               (|shoeInclude|
                   (|bAddLineNumber| (|bRgen| |a|) (|bIgen| 0))))))))

(DEFUN STOUT (|string|) (PSTOUT (LIST |string|)))

(DEFUN |string2BootTree| (|string|)
  (PROG (|result| |a| |callingPackage|)
    (DECLARE (SPECIAL |$GenVarCounter|))
    (RETURN
      (PROGN
        (SETQ |callingPackage| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |$GenVarCounter| 0)
        (SETQ |a| (|shoeTransformString| (LIST |string|)))
        (SETQ |result|
              (COND
                ((|bStreamNull| |a|) NIL)
                (T (|stripm| (CAR |a|) |callingPackage|
                       (FIND-PACKAGE "BOOTTRAN")))))
        (|setCurrentPackage| |callingPackage|)
        |result|))))

(DEFUN STEVAL (|string|)
  (PROG (|result| |fn| |a| |callingPackage|)
    (DECLARE (SPECIAL |$GenVarCounter|))
    (RETURN
      (PROGN
        (SETQ |callingPackage| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |$GenVarCounter| 0)
        (SETQ |a| (|shoeTransformString| (LIST |string|)))
        (SETQ |result|
              (COND
                ((|bStreamNull| |a|) NIL)
                (T (SETQ |fn|
                         (|stripm| (CAR |a|) *PACKAGE*
                             (FIND-PACKAGE "BOOTTRAN")))
                   (EVAL |fn|))))
        (|setCurrentPackage| |callingPackage|)
        |result|))))

(DEFUN STTOMC (|string|)
  (PROG (|result| |a| |callingPackage|)
    (DECLARE (SPECIAL |$GenVarCounter|))
    (RETURN
      (PROGN
        (SETQ |callingPackage| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |$GenVarCounter| 0)
        (SETQ |a| (|shoeTransformString| (LIST |string|)))
        (SETQ |result|
              (COND
                ((|bStreamNull| |a|) NIL)
                (T (|shoePCompile| (CAR |a|)))))
        (|setCurrentPackage| |callingPackage|)
        |result|))))

(DEFUN |shoeCompileTrees| (|s|)
  (LOOP
    (COND
      ((|bStreamNull| |s|) (RETURN NIL))
      (T (|shoeCompile| (CAR |s|)) (SETQ |s| (CDR |s|))))))

(DECLAIM (FTYPE (FUNCTION (|%Ast|) |%Thing|) |shoeCompile|))

(DEFUN |shoeCompile| (|fn|)
  (PROG (|body| |bv| |ISTMP#2| |name| |ISTMP#1|)
    (RETURN
      (COND
        ((AND (CONSP |fn|) (EQ (CAR |fn|) 'DEFUN)
              (PROGN
                (SETQ |ISTMP#1| (CDR |fn|))
                (AND (CONSP |ISTMP#1|)
                     (PROGN
                       (SETQ |name| (CAR |ISTMP#1|))
                       (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                       (AND (CONSP |ISTMP#2|)
                            (PROGN
                              (SETQ |bv| (CAR |ISTMP#2|))
                              (SETQ |body| (CDR |ISTMP#2|))
                              T))))))
         (COMPILE |name| (CONS 'LAMBDA (CONS |bv| |body|))))
        (T (EVAL |fn|))))))

(DEFUN |shoeTransform| (|str|)
  (|bNext| #'|shoeTreeConstruct|
           (|bNext| #'|shoePileInsert|
                    (|bNext| #'|shoeLineToks| |str|))))

(DEFUN |shoeTransformString| (|s|)
  (|shoeTransform| (|shoeInclude| (|bAddLineNumber| |s| (|bIgen| 0)))))

(DEFUN |shoeTransformStream| (|s|)
  (|shoeTransformString| (|bRgen| |s|)))

(DEFUN |shoeTransformToConsole| (|str|)
  (|bNext| #'|shoeConsoleItem|
           (|bNext| #'|shoePileInsert|
                    (|bNext| #'|shoeLineToks| |str|))))

(DEFUN |shoeTransformToFile| (|fn| |str|)
  (|bFileNext| |fn|
      (|bNext| #'|shoePileInsert| (|bNext| #'|shoeLineToks| |str|))))

(DEFUN |shoeConsoleItem| (|str|)
  (PROG (|dq|)
    (RETURN
      (PROGN
        (SETQ |dq| (CAR |str|))
        (|shoeConsoleLines| (|shoeDQlines| |dq|))
        (CONS (|shoeParseTrees| |dq|) (CDR |str|))))))

(DEFUN |bFileNext| (|fn| |s|)
  (|bDelay| #'|bFileNext1| (LIST |fn| |s|)))

(DEFUN |bFileNext1| (|fn| |s|)
  (PROG (|dq|)
    (RETURN
      (COND
        ((|bStreamNull| |s|) (LIST '|nullstream|))
        (T (SETQ |dq| (CAR |s|))
           (|shoeFileLines| (|shoeDQlines| |dq|) |fn|)
           (|bAppend| (|shoeParseTrees| |dq|)
               (|bFileNext| |fn| (CDR |s|))))))))

(DEFUN |shoeParseTrees| (|dq|)
  (PROG (|toklist|)
    (RETURN
      (PROGN
        (SETQ |toklist| (|dqToList| |dq|))
        (COND ((NULL |toklist|) NIL) (T (|shoeOutParse| |toklist|)))))))

(DEFUN |shoeTreeConstruct| (|str|)
  (CONS (|shoeParseTrees| (CAR |str|)) (CDR |str|)))

(DEFUN |shoeDQlines| (|dq|)
  (PROG (|b| |a|)
    (RETURN
      (PROGN
        (SETQ |a| (CDAAR (|shoeLastTokPosn| |dq|)))
        (SETQ |b| (CDAAR (|shoeFirstTokPosn| |dq|)))
        (|streamTake| (+ (- |a| |b|) 1)
            (CAR (|shoeFirstTokPosn| |dq|)))))))

(DEFUN |streamTake| (|n| |s|)
  (COND
    ((|bStreamNull| |s|) NIL)
    ((EQL |n| 0) NIL)
    (T (CONS (CAR |s|) (|streamTake| (- |n| 1) (CDR |s|))))))

(DEFUN |shoeFileLines| (|lines| |fn|)
  (PROGN
    (|shoeFileLine| " " |fn|)
    (LET ((|bfVar#9| |lines|) (|line| NIL))
      (LOOP
        (COND
          ((OR (ATOM |bfVar#9|)
               (PROGN (SETQ |line| (CAR |bfVar#9|)) NIL))
           (RETURN NIL))
          (T (|shoeFileLine| (|shoeAddComment| |line|) |fn|)))
        (SETQ |bfVar#9| (CDR |bfVar#9|))))
    (|shoeFileLine| " " |fn|)))

(DEFUN |shoeConsoleLines| (|lines|)
  (PROGN
    (|shoeConsole| " ")
    (LET ((|bfVar#10| |lines|) (|line| NIL))
      (LOOP
        (COND
          ((OR (ATOM |bfVar#10|)
               (PROGN (SETQ |line| (CAR |bfVar#10|)) NIL))
           (RETURN NIL))
          (T (|shoeConsole| (|shoeAddComment| |line|))))
        (SETQ |bfVar#10| (CDR |bfVar#10|))))
    (|shoeConsole| " ")))

(DEFUN |shoeFileLine| (|x| |stream|)
  (PROGN (WRITE-LINE |x| |stream|) |x|))

(DEFUN |shoeFileTrees| (|s| |st|)
  (PROG (|a|)
    (RETURN
      (LOOP
        (COND
          ((|bStreamNull| |s|) (RETURN NIL))
          (T (SETQ |a| (CAR |s|))
             (COND
               ((AND (CONSP |a|) (EQ (CAR |a|) '+LINE))
                (|shoeFileLine| (CADR |a|) |st|))
               (T (REALLYPRETTYPRINT |a| |st|) (TERPRI |st|)))
             (SETQ |s| (CDR |s|))))))))

(DEFUN |shoePPtoFile| (|x| |stream|)
  (PROGN (SHOENOTPRETTYPRINT |x| |stream|) |x|))

(DEFUN |shoeConsoleTrees| (|s|)
  (PROG (|fn|)
    (RETURN
      (LOOP
        (COND
          ((|bStreamPackageNull| |s|) (RETURN NIL))
          (T (SETQ |fn|
                   (|stripm| (CAR |s|) *PACKAGE*
                       (FIND-PACKAGE "BOOTTRAN")))
             (REALLYPRETTYPRINT |fn|) (SETQ |s| (CDR |s|))))))))

(DEFUN |shoeAddComment| (|l|) (CONCAT "; " (CAR |l|)))

(DEFUN |shoeOutParse| (|stream|)
  (PROG (|found|)
    (DECLARE (SPECIAL |$bpParenCount| |$bpCount| |$returns| |$typings|
                      |$wheredefs| |$op| |$ttok| |$stok| |$stack|
                      |$inputStream|))
    (RETURN
      (PROGN
        (SETQ |$inputStream| |stream|)
        (SETQ |$stack| NIL)
        (SETQ |$stok| NIL)
        (SETQ |$ttok| NIL)
        (SETQ |$op| NIL)
        (SETQ |$wheredefs| NIL)
        (SETQ |$typings| NIL)
        (SETQ |$returns| NIL)
        (SETQ |$bpCount| 0)
        (SETQ |$bpParenCount| 0)
        (|bpFirstTok|)
        (SETQ |found|
              (LET ((#0=#:G1356
                        (CATCH :OPEN-AXIOM-CATCH-POINT (|bpOutItem|))))
                (COND
                  ((AND (CONSP #0#)
                        (EQUAL (CAR #0#) :OPEN-AXIOM-CATCH-POINT))
                   (COND
                     ((EQUAL (CAR #1=(CDR #0#))
                             '(|BootParserException|))
                      (LET ((|e| (CDR #1#))) |e|))
                     (T (THROW :OPEN-AXIOM-CATCH-POINT #0#))))
                  (T #0#))))
        (COND
          ((EQ |found| 'TRAPPED) NIL)
          ((NOT (|bStreamNull| |$inputStream|)) (|bpGeneralErrorHere|)
           NIL)
          ((NULL |$stack|) (|bpGeneralErrorHere|) NIL)
          (T (CAR |$stack|)))))))

(DEFUN |genDeclaration| (|n| |t|)
  (PROG (|t'| |vars| |argTypes| |ISTMP#2| |valType| |ISTMP#1|)
    (RETURN
      (COND
        ((AND (CONSP |t|) (EQ (CAR |t|) '|%Mapping|)
              (PROGN
                (SETQ |ISTMP#1| (CDR |t|))
                (AND (CONSP |ISTMP#1|)
                     (PROGN
                       (SETQ |valType| (CAR |ISTMP#1|))
                       (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                       (AND (CONSP |ISTMP#2|) (NULL (CDR |ISTMP#2|))
                            (PROGN
                              (SETQ |argTypes| (CAR |ISTMP#2|))
                              T))))))
         (COND
           ((|bfTupleP| |argTypes|) (SETQ |argTypes| (CDR |argTypes|))))
         (COND
           ((AND |argTypes| (SYMBOLP |argTypes|))
            (SETQ |argTypes| (LIST |argTypes|))))
         (LIST 'DECLAIM
               (LIST 'FTYPE (LIST 'FUNCTION |argTypes| |valType|) |n|)))
        ((AND (CONSP |t|) (EQ (CAR |t|) '|%Forall|)
              (PROGN
                (SETQ |ISTMP#1| (CDR |t|))
                (AND (CONSP |ISTMP#1|)
                     (PROGN
                       (SETQ |vars| (CAR |ISTMP#1|))
                       (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                       (AND (CONSP |ISTMP#2|) (NULL (CDR |ISTMP#2|))
                            (PROGN (SETQ |t'| (CAR |ISTMP#2|)) T))))))
         (COND
           ((NULL |vars|) (|genDeclaration| |n| |t'|))
           (T (COND ((SYMBOLP |vars|) (SETQ |vars| (LIST |vars|))))
              (|genDeclaration| |n|
                  (|applySubst|
                      (LET ((|bfVar#12| NIL) (|bfVar#13| NIL)
                            (|bfVar#11| |vars|) (|v| NIL))
                        (LOOP
                          (COND
                            ((OR (ATOM |bfVar#11|)
                                 (PROGN
                                   (SETQ |v| (CAR |bfVar#11|))
                                   NIL))
                             (RETURN |bfVar#12|))
                            ((NULL |bfVar#12|)
                             (SETQ |bfVar#12|
                                   #0=(CONS (CONS |v| '*) NIL))
                             (SETQ |bfVar#13| |bfVar#12|))
                            (T (RPLACD |bfVar#13| #0#)
                               (SETQ |bfVar#13| (CDR |bfVar#13|))))
                          (SETQ |bfVar#11| (CDR |bfVar#11|))))
                      |t'|)))))
        (T (LIST 'DECLAIM (LIST 'TYPE |t| |n|)))))))

(DEFUN |translateSignatureDeclaration| (|d|)
  (CASE (CAR |d|)
    (|%Signature|
        (LET ((|n| (CADR |d|)) (|t| (CADDR |d|)))
          (|genDeclaration| |n| |t|)))
    (T (|coreError| "signature expected"))))

(DEFUN |translateToplevelExpression| (|expr|)
  (PROG (|expr'|)
    (DECLARE (SPECIAL |$InteractiveMode|))
    (RETURN
      (PROGN
        (SETQ |expr'|
              (CDR (CDR (|shoeCompTran| (LIST 'LAMBDA NIL |expr|)))))
        (LET ((|bfVar#14| |expr'|) (|t| NIL))
          (LOOP
            (COND
              ((OR (ATOM |bfVar#14|)
                   (PROGN (SETQ |t| (CAR |bfVar#14|)) NIL))
               (RETURN NIL))
              ((AND (CONSP |t|) (EQ (CAR |t|) 'DECLARE))
               (IDENTITY (RPLACA |t| 'DECLAIM))))
            (SETQ |bfVar#14| (CDR |bfVar#14|))))
        (SETQ |expr'|
              (COND
                ((< 1 (LENGTH |expr'|)) (CONS 'PROGN |expr'|))
                (T (CAR |expr'|))))
        (COND
          (|$InteractiveMode| |expr'|)
          (T (|shoeEVALANDFILEACTQ| |expr'|)))))))

(DEFUN |exportNames| (|ns|)
  (COND
    ((NULL |ns|) NIL)
    (T (LIST (LIST 'EXPORT (LIST 'QUOTE |ns|))))))

(DEFUN |inAllContexts| (|x|)
  (LIST 'EVAL-WHEN (LIST :COMPILE-TOPLEVEL :LOAD-TOPLEVEL :EXECUTE)
        |x|))

(DEFUN |translateToplevel| (|b| |export?|)
  (PROG (|lhs| |t| |ISTMP#2| |sig| |n| |ISTMP#1| |xs|)
    (DECLARE (SPECIAL |$activeNamespace| |$InteractiveMode|
                      |$constantIdentifiers| |$foreignsDefsForCLisp|
                      |$currentModuleName|))
    (RETURN
      (COND
        ((ATOM |b|) (LIST |b|))
        ((AND (CONSP |b|) (EQ (CAR |b|) 'TUPLE)) (SETQ |xs| (CDR |b|))
         (|coreError| "invalid AST"))
        (T (CASE (CAR |b|)
             (|%Signature|
                 (LET ((|op| (CADR |b|)) (|t| (CADDR |b|)))
                   (LIST (|genDeclaration| |op| |t|))))
             (|%Definition|
                 (LET ((|op| (CADR |b|)) (|args| (CADDR |b|))
                       (|body| (CADDDR |b|)))
                   (CDR (|bfDef| |op| |args| |body|))))
             (|%Module|
                 (LET ((|m| (CADR |b|)) (|ns| (CADDR |b|))
                       (|ds| (CADDDR |b|)))
                   (PROGN
                     (SETQ |$currentModuleName| |m|)
                     (SETQ |$foreignsDefsForCLisp| NIL)
                     (CONS (LIST 'PROVIDE (SYMBOL-NAME |m|))
                           (|append| (|exportNames| |ns|)
                               (LET ((|bfVar#16| NIL) (|bfVar#17| NIL)
                                     (|bfVar#15| |ds|) (|d| NIL))
                                 (LOOP
                                   (COND
                                     ((OR (ATOM |bfVar#15|)
                                       (PROGN
                                         (SETQ |d| (CAR |bfVar#15|))
                                         NIL))
                                      (RETURN |bfVar#16|))
                                     ((NULL |bfVar#16|)
                                      (SETQ |bfVar#16|
                                       #0=(CONS
                                           (CAR
                                            (|translateToplevel| |d| T))
                                           NIL))
                                      (SETQ |bfVar#17| |bfVar#16|))
                                     (T (RPLACD |bfVar#17| #0#)
                                      (SETQ |bfVar#17|
                                       (CDR |bfVar#17|))))
                                   (SETQ |bfVar#15| (CDR |bfVar#15|)))))))))
             (|%Import|
                 (LET ((|m| (CADR |b|)))
                   (COND
                     ((AND (CONSP |m|) (EQ (CAR |m|) '|%Namespace|)
                           (PROGN
                             (SETQ |ISTMP#1| (CDR |m|))
                             (AND (CONSP |ISTMP#1|)
                                  (NULL (CDR |ISTMP#1|))
                                  (PROGN (SETQ |n| (CAR |ISTMP#1|)) T))))
                      (LIST (|inAllContexts|
                                (LIST 'USE-PACKAGE (SYMBOL-NAME |n|)))))
                     (T (COND
                          ((NOT (STRING= (|getOptionValue| '|import|)
                                         "skip"))
                           (|bootImport| (SYMBOL-NAME |m|))))
                        (LIST (LIST 'IMPORT-MODULE (SYMBOL-NAME |m|)))))))
             (|%ImportSignature|
                 (LET ((|x| (CADR |b|)) (|sig| (CADDR |b|)))
                   (|genImportDeclaration| |x| |sig|)))
             (|%TypeAlias|
                 (LET ((|lhs| (CADR |b|)) (|rhs| (CADDR |b|)))
                   (LIST (|genTypeAlias| |lhs| |rhs|))))
             (|%ConstantDefinition|
                 (LET ((|lhs| (CADR |b|)) (|rhs| (CADDR |b|)))
                   (PROGN
                     (SETQ |sig| NIL)
                     (COND
                       ((AND (CONSP |lhs|)
                             (EQ (CAR |lhs|) '|%Signature|)
                             (PROGN
                               (SETQ |ISTMP#1| (CDR |lhs|))
                               (AND (CONSP |ISTMP#1|)
                                    (PROGN
                                      (SETQ |n| (CAR |ISTMP#1|))
                                      (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                                      (AND (CONSP |ISTMP#2|)
                                       (NULL (CDR |ISTMP#2|))
                                       (PROGN
                                         (SETQ |t| (CAR |ISTMP#2|))
                                         T))))))
                        (SETQ |sig| (|genDeclaration| |n| |t|))
                        (SETQ |lhs| |n|)))
                     (SETQ |$constantIdentifiers|
                           (CONS |lhs| |$constantIdentifiers|))
                     (LIST (LIST 'DEFCONSTANT |lhs| |rhs|)))))
             (|%Assignment|
                 (LET ((|lhs| (CADR |b|)) (|rhs| (CADDR |b|)))
                   (PROGN
                     (SETQ |sig| NIL)
                     (COND
                       ((AND (CONSP |lhs|)
                             (EQ (CAR |lhs|) '|%Signature|)
                             (PROGN
                               (SETQ |ISTMP#1| (CDR |lhs|))
                               (AND (CONSP |ISTMP#1|)
                                    (PROGN
                                      (SETQ |n| (CAR |ISTMP#1|))
                                      (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                                      (AND (CONSP |ISTMP#2|)
                                       (NULL (CDR |ISTMP#2|))
                                       (PROGN
                                         (SETQ |t| (CAR |ISTMP#2|))
                                         T))))))
                        (SETQ |sig| (|genDeclaration| |n| |t|))
                        (SETQ |lhs| |n|)))
                     (COND
                       (|$InteractiveMode|
                           (LIST (LIST 'SETF |lhs| |rhs|)))
                       (T (LIST (LIST 'DEFPARAMETER |lhs| |rhs|)))))))
             (|%Macro|
                 (LET ((|op| (CADR |b|)) (|args| (CADDR |b|))
                       (|body| (CADDDR |b|)))
                   (|bfMDef| |op| |args| |body|)))
             (|%Structure|
                 (LET ((|t| (CADR |b|)) (|alts| (CADDR |b|)))
                   (LET ((|bfVar#19| NIL) (|bfVar#20| NIL)
                         (|bfVar#18| |alts|) (|alt| NIL))
                     (LOOP
                       (COND
                         ((OR (ATOM |bfVar#18|)
                              (PROGN
                                (SETQ |alt| (CAR |bfVar#18|))
                                NIL))
                          (RETURN |bfVar#19|))
                         ((NULL |bfVar#19|)
                          (SETQ |bfVar#19|
                                #1=(CONS (|bfCreateDef| |alt|) NIL))
                          (SETQ |bfVar#20| |bfVar#19|))
                         (T (RPLACD |bfVar#20| #1#)
                            (SETQ |bfVar#20| (CDR |bfVar#20|))))
                       (SETQ |bfVar#18| (CDR |bfVar#18|))))))
             (|%Namespace|
                 (LET ((|n| (CADR |b|)))
                   (PROGN
                     (SETQ |$activeNamespace| (SYMBOL-NAME |n|))
                     (LIST (LIST 'IN-PACKAGE (SYMBOL-NAME |n|))))))
             (|%Lisp| (LET ((|s| (CADR |b|)))
                        (|shoeReadLispString| |s| 0)))
             (T (LIST (|translateToplevelExpression| |b|)))))))))

(DEFUN |shoeAddbootIfNec| (|s|) (|shoeAddStringIfNec| ".boot" |s|))

(DEFUN |shoeRemovebootIfNec| (|s|)
  (|shoeRemoveStringIfNec| ".boot" |s|))

(DEFUN |shoeAddStringIfNec| (|str| |s|)
  (PROG (|a|)
    (RETURN
      (PROGN
        (SETQ |a| (STRPOS |str| |s| 0 NIL))
        (COND ((NULL |a|) (CONCAT |s| |str|)) (T |s|))))))

(DEFUN |shoeRemoveStringIfNec| (|str| |s|)
  (PROG (|n|)
    (RETURN
      (PROGN
        (SETQ |n| (SEARCH |str| |s| :FROM-END T))
        (COND ((NULL |n|) |s|) (T (|subString| |s| 0 |n|)))))))

(DEFUN DEFUSE (|fn|)
  (PROG (|infn|)
    (RETURN
      (PROGN
        (SETQ |infn| (CONCAT |fn| ".boot"))
        (|shoeOpenInputFile| |a| |infn| (|shoeDfu| |a| |fn|))))))

(DEFPARAMETER |$bootDefined| NIL)

(DEFPARAMETER |$bootDefinedTwice| NIL)

(DEFPARAMETER |$bootUsed| NIL)

(DEFPARAMETER |$lispWordTable| NIL)

(DEFUN |shoeDfu| (|a| |fn|)
  (PROG (|out|)
    (DECLARE (SPECIAL |$bfClamming| |$GenVarCounter|
                      |$bootDefinedTwice| |$bootUsed| |$bootDefined|
                      |$lispWordTable|))
    (RETURN
      (COND
        ((NULL |a|) (|shoeNotFound| |fn|))
        (T (SETQ |$lispWordTable| (MAKE-HASHTABLE 'EQ))
           (DO-SYMBOLS (|i| (FIND-PACKAGE 'LISP))
             (HPUT |$lispWordTable| |i| T))
           (SETQ |$bootDefined| (MAKE-HASHTABLE 'EQ))
           (SETQ |$bootUsed| (MAKE-HASHTABLE 'EQ))
           (SETQ |$bootDefinedTwice| NIL) (SETQ |$GenVarCounter| 0)
           (SETQ |$bfClamming| NIL)
           (|shoeDefUse| (|shoeTransformStream| |a|))
           (SETQ |out| (CONCAT |fn| ".defuse"))
           (|shoeOpenOutputFile| |stream| |out|
               (|shoeReport| |stream|))
           |out|)))))

(DEFUN |shoeReport| (|stream|)
  (PROG (|b| |a|)
    (DECLARE (SPECIAL |$bootDefinedTwice| |$bootUsed| |$bootDefined|))
    (RETURN
      (PROGN
        (|shoeFileLine| "DEFINED and not USED" |stream|)
        (SETQ |a|
              (LET ((|bfVar#22| NIL) (|bfVar#23| NIL)
                    (|bfVar#21| (HKEYS |$bootDefined|)) (|i| NIL))
                (LOOP
                  (COND
                    ((OR (ATOM |bfVar#21|)
                         (PROGN (SETQ |i| (CAR |bfVar#21|)) NIL))
                     (RETURN |bfVar#22|))
                    (T (AND (NOT (GETHASH |i| |$bootUsed|))
                            (COND
                              ((NULL |bfVar#22|)
                               (SETQ |bfVar#22| #0=(CONS |i| NIL))
                               (SETQ |bfVar#23| |bfVar#22|))
                              (T (RPLACD |bfVar#23| #0#)
                                 (SETQ |bfVar#23| (CDR |bfVar#23|)))))))
                  (SETQ |bfVar#21| (CDR |bfVar#21|)))))
        (|bootOut| (SSORT |a|) |stream|)
        (|shoeFileLine| "             " |stream|)
        (|shoeFileLine| "DEFINED TWICE" |stream|)
        (|bootOut| (SSORT |$bootDefinedTwice|) |stream|)
        (|shoeFileLine| "             " |stream|)
        (|shoeFileLine| "USED and not DEFINED" |stream|)
        (SETQ |a|
              (LET ((|bfVar#25| NIL) (|bfVar#26| NIL)
                    (|bfVar#24| (HKEYS |$bootUsed|)) (|i| NIL))
                (LOOP
                  (COND
                    ((OR (ATOM |bfVar#24|)
                         (PROGN (SETQ |i| (CAR |bfVar#24|)) NIL))
                     (RETURN |bfVar#25|))
                    (T (AND (NOT (GETHASH |i| |$bootDefined|))
                            (COND
                              ((NULL |bfVar#25|)
                               (SETQ |bfVar#25| #1=(CONS |i| NIL))
                               (SETQ |bfVar#26| |bfVar#25|))
                              (T (RPLACD |bfVar#26| #1#)
                                 (SETQ |bfVar#26| (CDR |bfVar#26|)))))))
                  (SETQ |bfVar#24| (CDR |bfVar#24|)))))
        (LET ((|bfVar#27| (SSORT |a|)) (|i| NIL))
          (LOOP
            (COND
              ((OR (ATOM |bfVar#27|)
                   (PROGN (SETQ |i| (CAR |bfVar#27|)) NIL))
               (RETURN NIL))
              (T (SETQ |b| (CONCAT (PNAME |i|) " is used in "))
                 (|bootOutLines| (SSORT (GETHASH |i| |$bootUsed|))
                     |stream| |b|)))
            (SETQ |bfVar#27| (CDR |bfVar#27|))))))))

(DEFUN |shoeDefUse| (|s|)
  (LOOP
    (COND
      ((|bStreamPackageNull| |s|) (RETURN NIL))
      (T (|defuse| NIL (CAR |s|)) (SETQ |s| (CDR |s|))))))

(DEFUN |defuse| (|e| |x|)
  (PROG (|niens| |nee| |LETTMP#1| |exp| |ISTMP#5| |id| |ISTMP#4|
                 |ISTMP#3| |body| |bv| |ISTMP#2| |name| |ISTMP#1|)
    (DECLARE (SPECIAL |$bootUsed| |$bootDefinedTwice| |$bootDefined|
                      |$used|))
    (RETURN
      (PROGN
        (SETQ |x| (|stripm| |x| *PACKAGE* (FIND-PACKAGE "BOOTTRAN")))
        (SETQ |$used| NIL)
        (SETQ |LETTMP#1|
              (COND
                ((AND (CONSP |x|) (EQ (CAR |x|) 'DEFUN)
                      (PROGN
                        (SETQ |ISTMP#1| (CDR |x|))
                        (AND (CONSP |ISTMP#1|)
                             (PROGN
                               (SETQ |name| (CAR |ISTMP#1|))
                               (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                               (AND (CONSP |ISTMP#2|)
                                    (PROGN
                                      (SETQ |bv| (CAR |ISTMP#2|))
                                      (SETQ |body| (CDR |ISTMP#2|))
                                      T))))))
                 (LIST |name| (CONS 'LAMBDA (CONS |bv| |body|))))
                ((AND (CONSP |x|) (EQ (CAR |x|) 'DEFMACRO)
                      (PROGN
                        (SETQ |ISTMP#1| (CDR |x|))
                        (AND (CONSP |ISTMP#1|)
                             (PROGN
                               (SETQ |name| (CAR |ISTMP#1|))
                               (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                               (AND (CONSP |ISTMP#2|)
                                    (PROGN
                                      (SETQ |bv| (CAR |ISTMP#2|))
                                      (SETQ |body| (CDR |ISTMP#2|))
                                      T))))))
                 (LIST |name| (CONS 'LAMBDA (CONS |bv| |body|))))
                ((AND (CONSP |x|) (EQ (CAR |x|) 'EVAL-WHEN)
                      (PROGN
                        (SETQ |ISTMP#1| (CDR |x|))
                        (AND (CONSP |ISTMP#1|)
                             (PROGN
                               (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                               (AND (CONSP |ISTMP#2|)
                                    (NULL (CDR |ISTMP#2|))
                                    (PROGN
                                      (SETQ |ISTMP#3| (CAR |ISTMP#2|))
                                      (AND (CONSP |ISTMP#3|)
                                       (EQ (CAR |ISTMP#3|) 'SETQ)
                                       (PROGN
                                         (SETQ |ISTMP#4|
                                          (CDR |ISTMP#3|))
                                         (AND (CONSP |ISTMP#4|)
                                          (PROGN
                                            (SETQ |id| (CAR |ISTMP#4|))
                                            (SETQ |ISTMP#5|
                                             (CDR |ISTMP#4|))
                                            (AND (CONSP |ISTMP#5|)
                                             (NULL (CDR |ISTMP#5|))
                                             (PROGN
                                               (SETQ |exp|
                                                (CAR |ISTMP#5|))
                                               T))))))))))))
                 (LIST |id| |exp|))
                ((AND (CONSP |x|) (EQ (CAR |x|) 'SETQ)
                      (PROGN
                        (SETQ |ISTMP#1| (CDR |x|))
                        (AND (CONSP |ISTMP#1|)
                             (PROGN
                               (SETQ |id| (CAR |ISTMP#1|))
                               (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                               (AND (CONSP |ISTMP#2|)
                                    (NULL (CDR |ISTMP#2|))
                                    (PROGN
                                      (SETQ |exp| (CAR |ISTMP#2|))
                                      T))))))
                 (LIST |id| |exp|))
                (T (LIST 'TOP-LEVEL |x|))))
        (SETQ |nee| (CAR |LETTMP#1|))
        (SETQ |niens| (CADR |LETTMP#1|))
        (COND
          ((GETHASH |nee| |$bootDefined|)
           (SETQ |$bootDefinedTwice|
                 (COND
                   ((EQ |nee| 'TOP-LEVEL) |$bootDefinedTwice|)
                   (T (CONS |nee| |$bootDefinedTwice|)))))
          (T (HPUT |$bootDefined| |nee| T)))
        (|defuse1| |e| |niens|)
        (LET ((|bfVar#28| |$used|) (|i| NIL))
          (LOOP
            (COND
              ((OR (ATOM |bfVar#28|)
                   (PROGN (SETQ |i| (CAR |bfVar#28|)) NIL))
               (RETURN NIL))
              (T (HPUT |$bootUsed| |i|
                       (CONS |nee| (GETHASH |i| |$bootUsed|)))))
            (SETQ |bfVar#28| (CDR |bfVar#28|))))))))

(DEFUN |defuse1| (|e| |y|)
  (PROG (|ndol| |dol| |LETTMP#1| |b| |a| |ISTMP#1|)
    (DECLARE (SPECIAL |$bootDefined| |$used|))
    (RETURN
      (COND
        ((ATOM |y|)
         (COND
           ((SYMBOLP |y|)
            (SETQ |$used|
                  (COND
                    ((|symbolMember?| |y| |e|) |$used|)
                    ((|symbolMember?| |y| |$used|) |$used|)
                    ((|defusebuiltin| |y|) |$used|)
                    (T (UNION (LIST |y|) |$used|)))))
           (T NIL)))
        ((AND (CONSP |y|) (EQ (CAR |y|) 'LAMBDA)
              (PROGN
                (SETQ |ISTMP#1| (CDR |y|))
                (AND (CONSP |ISTMP#1|)
                     (PROGN
                       (SETQ |a| (CAR |ISTMP#1|))
                       (SETQ |b| (CDR |ISTMP#1|))
                       T))))
         (|defuse1| (|append| (|unfluidlist| |a|) |e|) |b|))
        ((AND (CONSP |y|) (EQ (CAR |y|) 'PROG)
              (PROGN
                (SETQ |ISTMP#1| (CDR |y|))
                (AND (CONSP |ISTMP#1|)
                     (PROGN
                       (SETQ |a| (CAR |ISTMP#1|))
                       (SETQ |b| (CDR |ISTMP#1|))
                       T))))
         (SETQ |LETTMP#1| (|defSeparate| |a|))
         (SETQ |dol| (CAR |LETTMP#1|)) (SETQ |ndol| (CADR |LETTMP#1|))
         (LET ((|bfVar#29| |dol|) (|i| NIL))
           (LOOP
             (COND
               ((OR (ATOM |bfVar#29|)
                    (PROGN (SETQ |i| (CAR |bfVar#29|)) NIL))
                (RETURN NIL))
               (T (HPUT |$bootDefined| |i| T)))
             (SETQ |bfVar#29| (CDR |bfVar#29|))))
         (|defuse1| (|append| |ndol| |e|) |b|))
        ((AND (CONSP |y|) (EQ (CAR |y|) 'QUOTE)) (SETQ |a| (CDR |y|))
         NIL)
        ((AND (CONSP |y|) (EQ (CAR |y|) '+LINE)) (SETQ |a| (CDR |y|))
         NIL)
        (T (LET ((|bfVar#30| |y|) (|i| NIL))
             (LOOP
               (COND
                 ((OR (ATOM |bfVar#30|)
                      (PROGN (SETQ |i| (CAR |bfVar#30|)) NIL))
                  (RETURN NIL))
                 (T (|defuse1| |e| |i|)))
               (SETQ |bfVar#30| (CDR |bfVar#30|)))))))))

(DEFUN |defSeparate| (|x|)
  (PROG (|x2| |x1| |LETTMP#1| |f|)
    (RETURN
      (COND
        ((NULL |x|) (LIST NIL NIL))
        (T (SETQ |f| (CAR |x|))
           (SETQ |LETTMP#1| (|defSeparate| (CDR |x|)))
           (SETQ |x1| (CAR |LETTMP#1|)) (SETQ |x2| (CADR |LETTMP#1|))
           (COND
             ((|bfBeginsDollar| |f|) (LIST (CONS |f| |x1|) |x2|))
             (T (LIST |x1| (CONS |f| |x2|)))))))))

(DEFUN |unfluidlist| (|x|)
  (PROG (|y| |ISTMP#1|)
    (RETURN
      (COND
        ((NULL |x|) NIL)
        ((ATOM |x|) (LIST |x|))
        ((AND (CONSP |x|) (EQ (CAR |x|) '&REST)
              (PROGN
                (SETQ |ISTMP#1| (CDR |x|))
                (AND (CONSP |ISTMP#1|) (NULL (CDR |ISTMP#1|))
                     (PROGN (SETQ |y| (CAR |ISTMP#1|)) T))))
         (LIST |y|))
        (T (CONS (CAR |x|) (|unfluidlist| (CDR |x|))))))))

(DEFUN |defusebuiltin| (|x|)
  (DECLARE (SPECIAL |$lispWordTable|))
  (GETHASH |x| |$lispWordTable|))

(DEFUN |bootOut| (|l| |outfn|)
  (LET ((|bfVar#31| |l|) (|i| NIL))
    (LOOP
      (COND
        ((OR (ATOM |bfVar#31|) (PROGN (SETQ |i| (CAR |bfVar#31|)) NIL))
         (RETURN NIL))
        (T (|shoeFileLine| (CONCAT "   " (PNAME |i|)) |outfn|)))
      (SETQ |bfVar#31| (CDR |bfVar#31|)))))

(DEFUN CLESSP (|s1| |s2|) (NOT (SHOEGREATERP |s1| |s2|)))

(DEFUN SSORT (|l|) (SORT |l| #'CLESSP))

(DEFUN |bootOutLines| (|l| |outfn| |s|)
  (PROG (|a|)
    (RETURN
      (COND
        ((NULL |l|) (|shoeFileLine| |s| |outfn|))
        (T (SETQ |a| (PNAME (CAR |l|)))
           (COND
             ((< 70 (+ (LENGTH |s|) (LENGTH |a|)))
              (|shoeFileLine| |s| |outfn|)
              (|bootOutLines| |l| |outfn| " "))
             (T (|bootOutLines| (CDR |l|) |outfn| (CONCAT |s| " " |a|)))))))))

(DEFUN XREF (|fn|)
  (PROG (|infn|)
    (RETURN
      (PROGN
        (SETQ |infn| (CONCAT |fn| ".boot"))
        (|shoeOpenInputFile| |a| |infn| (|shoeXref| |a| |fn|))))))

(DEFUN |shoeXref| (|a| |fn|)
  (PROG (|out|)
    (DECLARE (SPECIAL |$bfClamming| |$GenVarCounter| |$bootUsed|
                      |$bootDefined| |$lispWordTable|))
    (RETURN
      (COND
        ((NULL |a|) (|shoeNotFound| |fn|))
        (T (SETQ |$lispWordTable| (MAKE-HASHTABLE 'EQ))
           (DO-SYMBOLS (|i| (FIND-PACKAGE 'LISP))
             (HPUT |$lispWordTable| |i| T))
           (SETQ |$bootDefined| (MAKE-HASHTABLE 'EQ))
           (SETQ |$bootUsed| (MAKE-HASHTABLE 'EQ))
           (SETQ |$GenVarCounter| 0) (SETQ |$bfClamming| NIL)
           (|shoeDefUse| (|shoeTransformStream| |a|))
           (SETQ |out| (CONCAT |fn| ".xref"))
           (|shoeOpenOutputFile| |stream| |out|
               (|shoeXReport| |stream|))
           |out|)))))

(DEFUN |shoeXReport| (|stream|)
  (PROG (|a| |c|)
    (DECLARE (SPECIAL |$bootUsed|))
    (RETURN
      (PROGN
        (|shoeFileLine| "USED and where DEFINED" |stream|)
        (SETQ |c| (SSORT (HKEYS |$bootUsed|)))
        (LET ((|bfVar#32| |c|) (|i| NIL))
          (LOOP
            (COND
              ((OR (ATOM |bfVar#32|)
                   (PROGN (SETQ |i| (CAR |bfVar#32|)) NIL))
               (RETURN NIL))
              (T (SETQ |a| (CONCAT (PNAME |i|) " is used in "))
                 (|bootOutLines| (SSORT (GETHASH |i| |$bootUsed|))
                     |stream| |a|)))
            (SETQ |bfVar#32| (CDR |bfVar#32|))))))))

(DEFUN |shoeItem| (|str|)
  (PROG (|dq|)
    (RETURN
      (PROGN
        (SETQ |dq| (CAR |str|))
        (CONS (LIST (LET ((|bfVar#34| NIL) (|bfVar#35| NIL)
                          (|bfVar#33| (|shoeDQlines| |dq|))
                          (|line| NIL))
                      (LOOP
                        (COND
                          ((OR (ATOM |bfVar#33|)
                               (PROGN
                                 (SETQ |line| (CAR |bfVar#33|))
                                 NIL))
                           (RETURN |bfVar#34|))
                          ((NULL |bfVar#34|)
                           (SETQ |bfVar#34| #0=(CONS (CAR |line|) NIL))
                           (SETQ |bfVar#35| |bfVar#34|))
                          (T (RPLACD |bfVar#35| #0#)
                             (SETQ |bfVar#35| (CDR |bfVar#35|))))
                        (SETQ |bfVar#33| (CDR |bfVar#33|)))))
              (CDR |str|))))))

(DEFUN |stripm| (|x| |pk| |bt|)
  (COND
    ((ATOM |x|)
     (COND
       ((SYMBOLP |x|)
        (COND
          ((EQUAL (SYMBOL-PACKAGE |x|) |bt|) (INTERN (PNAME |x|) |pk|))
          (T |x|)))
       (T |x|)))
    (T (CONS (|stripm| (CAR |x|) |pk| |bt|)
             (|stripm| (CDR |x|) |pk| |bt|)))))

(DEFUN |shoePCompile| (|fn|)
  (PROG (|body| |bv| |ISTMP#2| |name| |ISTMP#1|)
    (RETURN
      (PROGN
        (SETQ |fn| (|stripm| |fn| *PACKAGE* (FIND-PACKAGE "BOOTTRAN")))
        (COND
          ((AND (CONSP |fn|) (EQ (CAR |fn|) 'DEFUN)
                (PROGN
                  (SETQ |ISTMP#1| (CDR |fn|))
                  (AND (CONSP |ISTMP#1|)
                       (PROGN
                         (SETQ |name| (CAR |ISTMP#1|))
                         (SETQ |ISTMP#2| (CDR |ISTMP#1|))
                         (AND (CONSP |ISTMP#2|)
                              (PROGN
                                (SETQ |bv| (CAR |ISTMP#2|))
                                (SETQ |body| (CDR |ISTMP#2|))
                                T))))))
           (COMPILE |name| (CONS 'LAMBDA (CONS |bv| |body|))))
          (T (EVAL |fn|)))))))

(DEFUN |shoePCompileTrees| (|s|)
  (LOOP
    (COND
      ((|bStreamNull| |s|) (RETURN NIL))
      (T (REALLYPRETTYPRINT (|shoePCompile| (CAR |s|)))
         (SETQ |s| (CDR |s|))))))

(DEFUN |bStreamPackageNull| (|s|)
  (PROG (|b| |a|)
    (RETURN
      (PROGN
        (SETQ |a| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |b| (|bStreamNull| |s|))
        (|setCurrentPackage| |a|)
        |b|))))

(DEFUN PSTTOMC (|string|)
  (DECLARE (SPECIAL |$GenVarCounter|))
  (PROGN
    (SETQ |$GenVarCounter| 0)
    (|shoePCompileTrees| (|shoeTransformString| |string|))))

(DEFUN BOOTLOOP ()
  (PROG (|stream| |b| |a|)
    (RETURN
      (PROGN
        (SETQ |a| (READ-LINE))
        (COND
          ((EQL (LENGTH |a|) 0)
           (WRITE-LINE "Boot Loop; to exit type ] ") (BOOTLOOP))
          (T (SETQ |b| (|shoePrefix?| ")console" |a|))
             (COND
               (|b| (SETQ |stream| *TERMINAL-IO*)
                    (PSTTOMC (|bRgen| |stream|)) (BOOTLOOP))
               ((CHAR= (SCHAR |a| 0) (|char| '])) NIL)
               (T (PSTTOMC (LIST |a|)) (BOOTLOOP)))))))))

(DEFUN BOOTPO ()
  (PROG (|stream| |b| |a|)
    (RETURN
      (PROGN
        (SETQ |a| (READ-LINE))
        (COND
          ((EQL (LENGTH |a|) 0)
           (WRITE-LINE "Boot Loop; to exit type ] ") (BOOTPO))
          (T (SETQ |b| (|shoePrefix?| ")console" |a|))
             (COND
               (|b| (SETQ |stream| *TERMINAL-IO*)
                    (PSTOUT (|bRgen| |stream|)) (BOOTPO))
               ((CHAR= (SCHAR |a| 0) (|char| '])) NIL)
               (T (PSTOUT (LIST |a|)) (BOOTPO)))))))))

(DEFUN PSTOUT (|string|)
  (PROG (|result| |callingPackage|)
    (DECLARE (SPECIAL |$GenVarCounter|))
    (RETURN
      (PROGN
        (SETQ |callingPackage| *PACKAGE*)
        (IN-PACKAGE "BOOTTRAN")
        (SETQ |$GenVarCounter| 0)
        (SETQ |result|
              (|shoeConsoleTrees| (|shoeTransformString| |string|)))
        (|setCurrentPackage| |callingPackage|)
        |result|))))

(DEFUN |defaultBootToLispFile| (|file|)
  (CONCAT (|pathBasename| |file|) ".clisp"))

(DEFUN |getIntermediateLispFile| (|file| |options|)
  (PROG (|out|)
    (RETURN
      (PROGN
        (SETQ |out| (NAMESTRING (|getOutputPathname| |options|)))
        (COND
          (|out| (CONCAT (|shoeRemoveStringIfNec|
                             (CONCAT "." |$effectiveFaslType|) |out|)
                         ".clisp"))
          (T (|defaultBootToLispFile| |file|)))))))

(DEFUN |translateBootFile| (|progname| |options| |file|)
  (PROG (|outFile|)
    (RETURN
      (PROGN
        (SETQ |outFile|
              (OR (|getOutputPathname| |options|)
                  (|defaultBootToLispFile| |file|)))
        (BOOTTOCL |file| (ENOUGH-NAMESTRING |outFile|))))))

(DEFUN |retainFile?| (|ext|)
  (COND
    ((OR (MEMBER (|Option| '|all|) |$FilesToRetain|)
         (MEMBER (|Option| '|yes|) |$FilesToRetain|))
     T)
    ((MEMBER (|Option| '|no|) |$FilesToRetain|) NIL)
    (T (MEMBER (|Option| |ext|) |$FilesToRetain|))))

(DEFUN |compileBootHandler| (|progname| |options| |file|)
  (PROG (|objFile| |intFile|)
    (RETURN
      (PROGN
        (SETQ |intFile|
              (BOOTTOCL |file|
                  (|getIntermediateLispFile| |file| |options|)))
        (COND
          ((NOT (EQL (|errorCount|) 0)) NIL)
          (|intFile|
              (SETQ |objFile|
                    (|compileLispHandler| |progname| |options|
                        |intFile|))
              (COND
                ((NOT (|retainFile?| '|lisp|)) (DELETE-FILE |intFile|)))
              |objFile|)
          (T NIL))))))

(EVAL-WHEN (:EXECUTE :LOAD-TOPLEVEL)
  (|associateRequestWithFileType| (|Option| "translate") "boot"
      #'|translateBootFile|))

(EVAL-WHEN (:EXECUTE :LOAD-TOPLEVEL)
  (|associateRequestWithFileType| (|Option| "compile") "boot"
      #'|compileBootHandler|))

(DEFUN |loadNativeModule| (|m|)
  (COND
    ((|%hasFeature| :SBCL)
     (FUNCALL (|bfColonColon| 'SB-ALIEN 'LOAD-SHARED-OBJECT) |m|
              :DONT-SAVE T))
    ((|%hasFeature| :CLISP)
     (EVAL (LIST (|bfColonColon| 'FFI 'DEFAULT-FOREIGN-LIBRARY) |m|)))
    ((|%hasFeature| :ECL)
     (EVAL (LIST (|bfColonColon| 'FFI 'LOAD-FOREIGN-LIBRARY) |m|)))
    ((|%hasFeature| :CLOZURE)
     (EVAL (LIST (|bfColonColon| 'CCL 'OPEN-SHARED-LIBRARY) |m|)))
    (T (|coreError|
           "don't know how to load a dynamically linked module"))))

(DEFUN |loadSystemRuntimeCore| ()
  (COND
    ((OR (|%hasFeature| :ECL) (|%hasFeature| :GCL)) NIL)
    (T (|loadNativeModule|
           (CONCAT "libopen-axiom-core" |$NativeModuleExt|)))))