(defpackage "AxiomCore"
#+:common-lisp (:use "COMMON-LISP")
#-:common-lisp (:use "LISP" "USER")
#+(and :SBCL :SB-THREAD) (:use "SB-THREAD")
#+(and :ECL :THREADS) (:use "MP")
#+(and :CLISP :MT) (:use "THREADS")
#+:gcl (:use "DEFPACKAGE")
#+:clozure (:import-from "CCL"
external-call %get-cstring
with-pointer-to-ivector with-cstrs)
#+:clozure (:export "CCL"
external-call %get-cstring
with-pointer-to-ivector with-cstrs)
(:export "%Thing"
"%Void"
"%Boolean"
"%String"
"%Symbol"
"%Short"
"%Bit"
"%Byte"
"%Char"
"%Bignum"
"%Integer"
"%Number"
"%IntegerSection"
"%DoubleFloat"
"%Atom"
"%Maybe"
"%Pair"
"%Node"
"%List"
"%Vector"
"%BitVector"
"%SimpleArray"
"%Table"
"makeTable"
"tableValue"
"tableLength"
"tableRemove!"
"ref"
"deref"
"$stdin"
"$stdout"
"$stdio"
"$InputStream"
"$OutputStream"
"$ErrorStream"
"directoryEntries"
"inputBinaryFile"
"outputBinaryFile"
"inputTextFile"
"outputTextFile"
"closeFile"
"closeStream"
"eof?"
"getFileCursor"
"setFileCursor"
"forkStreamByName"
"prettyPrint"
"readLine"
"readExpr"
"readIntegerIfCan"
"formatToString"
"formatToStream"
"formatToStdout"
"%Mode"
"%Sig"
"%Code"
"%Env"
"%Form"
"%Triple"
"%Shell"
"%FunctorData"
"%FunctorCoreData"
"%FunctorBytecode"
"%FunctorTemplate"
"%FunctorPredicateIndexTable"
"%FunctorOperatorDirectory"
"%FunctorCategoryTable"
"%FunctorAttributeTable"
"%FunctorDefaultTable"
"%FunctorLookupFunction"
"primitiveLoad"
"coreQuit"
"fatalError"
"internalError"
"coreError"
"errorCount"
"countError"
"resetErrorCount"
"warn"
"startCompileDuration"
"endCompileDuration"
"%ByteArray"
"makeByteArray"
"makeBitVector"
"makeString"
"mkVector"
"mkIntArray"
"listToString"
"maxIndex"
"%hasFeature"
"%systemOptions"
"%systemArguments"
"%sysInit"
"%basicSystemIsComplete"
"%algebraSystemIsComplete"
"%nothing"
"%nullStream"
"%nonNullStream"
"%escapeSequenceAverseHost?"
"%defaultReadAndLoadSettings"
"$hostPlatform"
"$buildPlatform"
"$targetPlatform"
"$faslType"
"$LispFileType"
"$delayedFFI"
"$useLLVM"
"$effectiveFaslType"
"$NativeModuleExt"
"$systemInstallationDirectory"
"$NativeTypeTable"
"$LispOptimizeOptions"
"$StandardLinking"
"$ECLVersionNumber"
"$FilesToRetain"
"$dynamicForeignFunctions"
"getOptionValue"
"getCommandLineArguments"
"$originalLispTopLevel"
"link"
"installDriver"
"associateRequestWithFileType"
"ensureTrailingSlash"
"getOutputPathname"
"loadPathname"
"loadFileIfPresent"
"compileLispFile"
"compileLispHandler"
"Option"
"systemRootDirectory"
"systemLibraryDirectory"
"userHomeDirectory"
"pathBasename"
"IMPORT-MODULE"
"bootImport"
"CONCAT"
"$EditorProgram"
"ident?"
"fixnum?"
"double"
"%fNaN?"
"integerAndFractionalParts"
))
(in-package "AxiomCore")
(deftype |%Void| () 't)
(deftype |%Thing| () 't)
(deftype |%Boolean| () 'boolean)
(deftype |%String| () 'string)
(deftype |%Symbol| () 'symbol)
(deftype |%Short| () 'fixnum)
(deftype |%Bit| () 'bit)
(deftype |%Byte| () '(unsigned-byte 8))
(deftype |%Char| () 'character)
(deftype |%Bignum| () 'bignum)
(deftype |%Integer| () 'integer)
(deftype |%IntegerSection| (n) `(integer ,n))
(deftype |%DoubleFloat| () 'double-float)
(deftype |%Number| () 'number)
(deftype |%Atom| () 'atom)
(deftype |%Maybe| (s) `(or null ,s))
(deftype |%Pair| (u v)
`(cons ,u ,v))
(deftype |%Node| (s)
`(cons ,s null))
(deftype |%List| (s)
`(or null (cons ,s)))
(deftype |%SimpleArray| (s) `(simple-array ,s))
(deftype |%Vector| (s) `(vector ,s))
(deftype |%BitVector| () '(simple-array bit))
(deftype |%Table| nil 'hash-table)
(deftype |%Shell| () 'simple-vector)
(deftype |%Mode| () '(or symbol string cons))
(deftype |%Sig| () '(or symbol cons))
(deftype |%Code| () '(or |%Form| |%Char|))
(deftype |%Env| () '(or null cons))
(deftype |%Form| () '(or number symbol string cons))
(deftype |%Triple| ()
'(cons |%Code| (cons |%Mode| (cons |%Env| null))))
(deftype |%FunctorTemplate| ()
'simple-vector)
(deftype |%FunctorOperatorDirectory| ()
'(simple-array (or symbol fixnum)))
(deftype |%FunctorAttributeTable| ()
'list)
(deftype |%FunctorLookupFunction| ()
'|%Symbol|)
(deftype |%FunctorPredicateIndexTable| ()
'(simple-array fixnum))
(deftype |%FunctorCategoryTable| ()
'(simple-array |%Form|))
(deftype |%FunctorDefaultTable| ()
'(simple-array (|%Maybe| |%Constructor|)))
(deftype |%FunctorBytecode| ()
'(simple-array fixnum))
(deftype |%FunctorCoreData| ()
'(cons |%FunctorPredicateIndexTable|
(cons |%FunctorDefaultTable|
(cons |%FunctorCategoryTable| |%FunctorBytecode|))))
(deftype |%FunctorData| ()
'(cons |%FunctorTemplate|
(cons |%FunctorOperatorDirectory|
(cons |%FunctorAttributeTable|
(cons |%Thing|
(cons |%FunctorLookupFunction| null))))))
(defconstant |$hostPlatform| "x86_64-unknown-linux-gnu")
(defconstant |$buildPlatform| "x86_64-unknown-linux-gnu")
(defconstant |$targetPlatform| "x86_64-unknown-linux-gnu")
(defconstant oa-cxx "g++")
(defconstant oa-ldflags "-m64")
(defconstant |$systemInstallationDirectory|
"/projects/77750c71-ec7b-4962-bf55-a49ff5065fb6/lib/open-axiom/x86_64-unknown-linux-gnu/1.5.0-2016-01-24/")
(defconstant |$FilesToRetain|
'())
(defparameter |$dynamicForeignFunctions| nil)
(defconstant |$LispOptimizeOptions|
'(speed))
(proclaim '(optimize speed))
(eval-when (:compile-toplevel :load-toplevel :execute)
(defconstant |$EnableLispProfiling| nil))
(eval-when (:compile-toplevel :load-toplevel :execute)
(progn #+(and :sbcl (not :win32)) (require :sb-sprof)))
(defun |%algebraSystemIsComplete| nil
(member :open-axiom-algebra-system *features*))
(defun |%basicSystemIsComplete| nil
(or (|%algebraSystemIsComplete|)
(member :open-axiom-basic-system *features*)))
(defun boot-completed-p nil
(or (|%basicSystemIsComplete|)
(member :open-axiom-boot *features*)))
(eval-when (:compile-toplevel :load-toplevel :execute)
(progn
(setq *read-default-float-format* 'double-float)
(setq *load-verbose* nil)))
(defconstant |$StandardLinking|
(eq 'no 'yes))
(defconstant |$useDynamicLink|
#+:ecl (member :dffi *features*)
#+:gcl nil
#-(or :ecl :gcl) t)
(defconstant |$delayedFFI|
(eq 'yes 'yes))
(defconstant |$useLLVM|
(eq 'yes 'yes))
(defconstant |$originalLispTopLevel|
#+:ecl #'si::top-level
#+:gcl #'si::top-level
#+:sbcl #'sb-impl::toplevel-init
#+clisp #'system::main-loop
#+:clozure nil
)
(defconstant |$LispFileType| "lisp")
(defconstant |$faslType|
(pathname-type (compile-file-pathname "foo.lisp")))
(defconstant |$effectiveFaslType|
#+:ecl (pathname-type (compile-file-pathname "foo.lisp" :system-p t))
#-:ecl |$faslType|)
(defconstant |$NativeModuleExt|
(cond (|$useDynamicLink| ".so")
(t ".a")))
(defun |%escapeSequenceAverseHost?| ()
(or (member :win32 *features*)
(member :windows *features*)))
(defmacro |%defaultReadAndLoadSettings| ()
`(eval-when (:compile-toplevel :load-toplevel :execute)
(progn
(setq *read-default-float-format* 'double-float)
(setq *load-verbose* nil))))
(defconstant |$EditorProgram| "/usr/bin/vi")
(defconstant |%nothing| :|OpenAxiomNoValue|)
(defconstant |%nullStream| :|OpenAxiomNullStream|)
(defconstant |%nonNullStream| :|OpenAxiomNonNullStream|)
(defconstant |$CoreLibName|
"open-axiom-core")
(defconstant |$ExtraRuntimeLibraries|
'("-lutil" "-lm"))
(defun extra-runtime-libs nil
(if (boot-completed-p)
(append
(list (concatenate 'string "-L" (|systemLibraryDirectory|))
(concatenate 'string "-l" |$CoreLibName|))
|$ExtraRuntimeLibraries|)
|$ExtraRuntimeLibraries|))
#+:clisp
(eval-when (:compile-toplevel :load-toplevel :execute)
(progn
(setf custom:*ansi* t)
(setf custom:*floating-point-contagion-ansi* t)
(setf custom:*warn-on-floating-point-contagion* t)
(setf custom:*trace-indent* t)
(setf custom:*foreign-encoding*
(ext:make-encoding :charset charset:iso-8859-1))))
(defconstant |$ECLVersionNumber|
#-:ecl -1
#+:ecl (let ((ver (find-symbol "+ECL-VERSION-NUMBER+" "EXT")))
(cond (ver (symbol-value ver))
(t -1))))
(defmacro |makeTable| (cmp)
`(make-hash-table :test ,cmp))
(defmacro |tableValue| (ht k)
`(gethash ,k ,ht))
(defmacro |tableRemove!| (ht k)
`(remhash ,k ,ht))
(defmacro |tableLength| (ht)
`(hash-table-count ,ht))
(defmacro |ref| (v)
`(cons ,v nil))
(defmacro |deref| (r)
`(car ,r))
(defparameter |$stdout| *standard-output*)
(defparameter |$stdin| *standard-input*)
(defparameter |$stdio| *terminal-io*)
(defparameter |$InputStream| (make-synonym-stream '*standard-input*))
(defparameter |$OutputStream| (make-synonym-stream '*standard-output*))
(defparameter |$ErrorStream| (make-synonym-stream '*standard-output*))
(defun |directoryEntries| (dir &optional (pattern nil))
(let ((dirname (namestring dir)))
(cond (pattern (directory (concatenate 'string dirname "/" pattern)))
(t
#+(or :clisp :clozure :gcl)
(directory (concatenate 'string dirname "/*"))
#-(or :clisp :clozure :gcl)
(nunion
(directory (concatenate 'string dirname "/*"))
(directory (concatenate 'string dirname "/*.*")))))))
(defun |inputBinaryFile| (f)
(open f
:direction :input
:element-type 'unsigned-byte
:if-does-not-exist nil))
(defun |outputBinaryFile| (f)
(open f
:direction :output
:element-type 'unsigned-byte
:if-exists :supersede))
(defun |inputTextFile| (f)
(open f
:direction :input
:if-does-not-exist nil))
(defun |outputTextFile| (f)
(open f
:direction :output
:if-exists :supersede))
(defun |closeFile| (f)
(close f))
(defmacro |closeStream| (s)
`(close ,s))
(defmacro |eof?| (s)
`(null (peek-char nil ,s nil nil nil)))
(defmacro |getFileCursor| (s)
`(file-position ,s))
(defmacro |setFileCursor| (s n)
`(file-position ,s ,n))
(defmacro |forkStreamByName| (s)
`(make-synonym-stream ,s))
(defmacro |readLine| (f)
`(read-line ,f nil |%nothing|))
(defmacro |readByte| (f)
`(read-byte ,f nil |%nothing|))
(defmacro |readExpr| (f)
`(read ,f nil |%nothing|))
(defun |readIntegerIfCan| (s)
(let ((r (multiple-value-call #'cons (parse-integer s :junk-allowed t))))
(cond ((eql (cdr r) (length s)) (car r))
(t nil))))
(defun |prettyPrint| (x &optional (s |$OutputStream|))
(let ((*print-pretty* t)
(*print-array* t)
(*print-circle* t)
(*print-length* nil)
(*print-level* nil))
(prin1 x s)))
(defmacro |formatToString| (&rest args)
`(format nil ,@args))
(defmacro |formatToStream| (&rest x)
`(format ,@x))
(defmacro |formatToStdout| (&rest args)
`(format |$stdout| ,@args))
(defconstant |$BootFileType| "boot")
(defconstant |$LibraryFileType| "spad")
(defconstant |$ScriptFileType| "input")
(defun |getFileType|(file)
(let ((file-type (pathname-type file)))
(cond ((or (equal "clisp" file-type)
(equal "lsp" file-type))
|$LispFileType|)
(t file-type))))
(defun |systemRootDirectory| nil
(let ((dir (assoc (|Option| "system") (|%systemOptions|))))
(if (not (null dir))
(|ensureTrailingSlash| (cdr dir))
|$systemInstallationDirectory|)))
(defun |systemLibraryDirectory| nil
(let ((dir (assoc (|Option| "syslib") (|%systemOptions|))))
(if (not (null dir))
(|ensureTrailingSlash| (cdr dir))
(concatenate 'string (|systemRootDirectory|) "lib/"))))
(defmacro |userHomeDirectory| nil
(user-homedir-pathname))
(defun linkset-from (dir)
(mapcar #'(lambda(f) (concatenate 'string dir f))
(with-open-file (stream (concatenate 'string dir "linkset"))
(read stream t))))
(defun system-subdirectory (subdir)
(concatenate 'string (|systemRootDirectory|) subdir))
(defun linkset-from-if (dir feature)
(if (member feature *features*)
(linkset-from (system-subdirectory dir))
nil))
(defun complete-fasl-list-for-link (fasls)
(append (linkset-from-if "lisp/" :open-axiom-base-lisp)
(linkset-from-if "boot/" :open-axiom-boot)
(map 'list #'|compileFilePathname| fasls)))
(defparameter |$driverTable|
(make-hash-table :test #'equal :size 10))
(defun |getDriver| (request)
(gethash request |$driverTable|))
(defun |installDriver| (request driver)
(when (|getDriver| request)
(|internalError| "attempt to override driver"))
(setf (gethash request |$driverTable|) driver))
(defun |useFileType?| (request)
(get request 'use-file-type))
(defun |associateRequestWithFileType| (request file-type driver)
(let ((key (cons request file-type)))
(unless (|useFileType?| request)
(setf (get request 'use-file-type) file-type))
(|installDriver| key driver)))
(defun |Option| (opt)
(intern (string opt) (find-package "AxiomCore")))
(defun translate-option-value (val)
(cond ((string= val "no") nil)
((string= val "yes") t)
(t (multiple-value-bind (ival idx)
(parse-integer val :junk-allowed t)
(cond ((null ival) val)
((eql idx (length val)) ival)
(t val))))))
(defun |parseOption| (option)
(setq option (subseq option 2))
(let ((p (position #\= option)))
(if p
(cons (|Option| (subseq option 0 p))
(translate-option-value (subseq option (1+ p))))
(|Option| option))))
(defun |getOptionValue| (opt &optional (options (|%systemOptions|)))
(let ((val (assoc (|Option| opt) options)))
(cond (val (cdr val))
(t nil))))
(defun |processCommandLine| (argv options-so-far args-so-far)
(cond ((null argv)
(values options-so-far (nreverse args-so-far)))
((equal "--" (car argv))
(values options-so-far (concatenate 'list
(nreverse args-so-far)
(cdr argv))))
((or (< (length (car argv)) 2)
(not (equal "--" (subseq (car argv) 0 2))))
(|processCommandLine| (cdr argv)
options-so-far
(cons (car argv) args-so-far)))
(t (let ((option (|parseOption| (car argv))))
(cond ((symbolp option)
(|processCommandLine| (cdr argv)
(cons (cons option t)
options-so-far)
args-so-far))
((consp option)
(|processCommandLine| (cdr argv)
(cons option options-so-far)
args-so-far))
(t (|internalError|
(format nil "processCommandLine: unknown option ~S"
option))))))))
(defun |getOutputPathname| (options)
(let ((output-option (assoc (|Option| "output") options)))
(when output-option
#+:sbcl (merge-pathnames (cdr output-option)
*default-pathname-defaults*)
#-:sbcl (cdr output-option))))
(defun |getMainEntryPoint| (options)
(|getOptionValue| (|Option| "main") options))
(defun |getPrologue| (options)
(let ((prologue (|getOptionValue| (|Option| "prologue") options)))
(if prologue (read-from-string prologue) nil)))
(defun unbind-foreign-function-symbols ()
(when |$delayedFFI|
(mapc #'(lambda (s)
(when (fboundp s)
(fmakunbound s)))
|$dynamicForeignFunctions|)))
(defun |saveCore| (core-image &optional (entry-point nil))
(when (consp entry-point)
(setq entry-point (apply (car entry-point)
(cdr entry-point))))
(unbind-foreign-function-symbols)
#+:sbcl (if (null entry-point)
(sb-ext::save-lisp-and-die core-image :executable t)
(sb-ext::save-lisp-and-die core-image
:toplevel entry-point
:executable t))
#+:gcl (progn
(when entry-point
(setq si::*top-level-hook* entry-point))
(system::save-system core-image))
#+:clisp (progn
(if entry-point
(ext::saveinitmem core-image
:init-function entry-point
:executable t
:norc t
:quiet t
)
(ext::saveinitmem core-image
:executable t
:norc t
))
(ext::quit))
#+:clozure (progn
(ccl:save-application core-image
:toplevel-function entry-point
:error-handler :quit
:prepend-kernel t)
(return-from |saveCore|))
(error "don't know how to save Lisp image"))
(defmacro |primitiveLoad| (f)
`(load ,f))
(defun |coreQuit| (&optional (status 0))
#+:sbcl (sb-ext:exit :code status)
#+:clisp (ext:quit status)
#+:gcl (si::bye status)
#+:ecl (ext:quit status)
#+:clozure (ccl:quit status)
#-(or :sbcl :clisp :gcl :ecl :clozure)
(error "`coreQuit' not implemented for this Lisp"))
(defun |diagnosticMessage|(prefix msg)
(let ((text (concatenate 'string prefix ": " msg)))
(write-line text *error-output*)))
(defparameter |$errorCount| 0)
(defun |errorCount| nil
|$errorCount|)
(defun |countError| nil
(setq |$errorCount| (1+ |$errorCount|)))
(defun |resetErrorCount| nil
(setq |$errorCount| 0))
(defun |catenateStrings| (&rest l)
#+ :gcl (apply #'si::string-concatenate l)
#- :gcl (apply #'concatenate 'string l))
(defun concat (a b &rest l)
(cond ((bit-vector-p a)
(apply #'concatenate 'bit-vector a b l))
(t
(apply #'|catenateStrings|
(string a)
(string b)
(mapcar #'string l)))))
(defun |fatalError| (msg)
(|countError|)
(|diagnosticMessage| "fatal error" msg)
(|coreQuit| 1))
(defun |internalError| (msg)
(|countError|)
(|diagnosticMessage| "internal error" msg)
(|coreQuit| 1))
(defun |coreError| (msg)
(|countError|)
(|diagnosticMessage| "error"
(cond ((consp msg)
(reduce #'(lambda (x y)
(concatenate 'string x y))
msg :initial-value ""))
(t msg)))
nil)
(defun |warn| (msg)
(|diagnosticMessage| "warning"
(cond ((consp msg)
(reduce #'(lambda (x y)
(concatenate 'string x y))
msg :initial-value ""))
(t msg))))
(defparameter |$sysOpts| nil)
(defparameter |$sysArgs| nil)
(defun |%systemOptions| ()
|$sysOpts|)
(defun |%systemArguments| ()
|$sysArgs|)
(defun |getCommandLineArguments| nil
#-(or :gcl :sbcl :clisp :ecl :clozure)
(|fatalError| "don't know how to get command line args")
(let* ((all-args
#+:clozure ccl:*command-line-argument-list*
#+:ecl (ext:command-args)
#+:gcl si::*command-args*
#+:sbcl sb-ext::*posix-argv*
#+:clisp (coerce (ext::argv) 'list))
(args (member "--" all-args :test #'equal)))
(cons (car all-args) (if args (cdr args) args))))
(defun |link| (core-image lisp-files
&optional (entry-point nil) (prologue nil))
(if (and entry-point (stringp entry-point))
(setq entry-point `(read-from-string ,entry-point)))
#-:ecl
(progn
(mapcar #'(lambda (p) (|loadOrElse| p)) lisp-files)
(eval prologue)
(|saveCore| core-image entry-point))
#+:ecl
(let* ((compiler::*ld* oa-cxx)
(compiler::*ld-flags* (concatenate 'string
compiler::*ld-flags*
" " oa-ldflags)))
(progn
(unless entry-point
(setq entry-point #'si::top-level))
(c:build-program core-image
:lisp-files
(complete-fasl-list-for-link lisp-files)
:ld-flags (extra-runtime-libs)
:epilogue-code
`(progn
(pushnew :open-axiom-base-lisp *features*)
,prologue
(funcall ,entry-point)))
(|coreQuit|))))
(defun |handleRequest| (prog-name request options args)
(let ((driver (|getDriver| request)))
(when (null driver)
(|fatalError| (format nil "invalid option `--~a'" (string request))))
(funcall driver prog-name options args)))
(defun |hasHandler?| (request)
(or (|getDriver| request)
(|useFileType?| request)))
(defun run-driver (prog-name action options args)
(cond ((|useFileType?| (car action))
(unless (not (null args))
(|coreError| "missing input files"))
(dolist (f args t)
(let* ((name (car action))
(file-type (or (|getFileType| f)
(|useFileType?| name)))
(request (cons name file-type)))
(unless (|handleRequest| prog-name request options f)
(return nil)))))
(t (|handleRequest| prog-name (car action) options args))))
(defun |handleCommandLine| (prog-name options args)
(when (or options args)
(let (action)
(dolist (opt options)
(cond ((stringp (cdr opt))
(when (|hasHandler?| (car opt))
(unless (|handleRequest| prog-name (car opt) options args)
(return nil))))
((|hasHandler?| (car opt))
(if (not (null action))
(|coreError| "multiple driver request")
(setq action opt)))))
(cond ((consp action)
(run-driver prog-name action options args))
(t nil)))))
(defun |printUsage| (prog-name)
(write-line "usage:")
(write-line
(concatenate 'string prog-name " -- [options] [files]"))
(write-line "option:")
(write-line " --help print this message")
(write-line " --system=<dir> set <dir> to the root directory of running system")
(write-line " --sysalg=<dir> set <dir> to the algebra directory of running system")
(write-line " --compile compile file")
(write-line " --output=<out> set output file to <out>")
(write-line " --load-directory=<dir> use <dir> as search path for modules")
(write-line " --make create an executable"))
(defun |helpHandler|(prog-name options args)
(declare (ignore options args))
(|printUsage| prog-name)
(|coreQuit|))
(|installDriver| (|Option| "help") #'|helpHandler|)
(defun |makeHandler| (prog-name options args)
(declare (ignore prog-name))
(unless (> (length args) 0)
(|fatalError| "--make requires at least one file"))
(|link| (or (|getOutputPathname| options) "a.out")
args
(|getMainEntryPoint| options)
(|getPrologue| options))
(|coreQuit|))
(|installDriver| (|Option| "make") #'|makeHandler|)
(defun |recordLoadDirectory| (prog-name options args)
(declare (ignore prog-name args)
(special |$LoadDirectories|))
(let ((load-option (assoc (|Option| "load-directory") options)))
(unless load-option
(|internalError| "`recordLoadDirectory' called without option"))
(unless (cdr load-option)
(|fatalError| "--load-directory option without value"))
(pushnew (cdr load-option) |$LoadDirectories| :test #'equal)
))
(|installDriver| (|Option| "load-directory") #'|recordLoadDirectory|)
(declaim (inline |compileFilePathname|))
(defun |compileFilePathname| (file)
#-:ecl (compile-file-pathname file)
#+:ecl (compile-file-pathname file :type :object))
(defun |currentDirectoryName| nil
(let* ((dir (namestring (truename "")))
(n (1- (length dir))))
(if (char= (char dir n) #\/)
(subseq dir 0 n)
dir)))
(defun |compileLispFile| (file out-file)
#+gcl (when (and (pathname-directory file)
(not (pathname-directory out-file)))
(setq out-file
(make-pathname :name (pathname-name out-file)
:type (pathname-type out-file)
:directory (list (|currentDirectoryName|)))))
(unwind-protect
(progn
(|startCompileDuration|)
(multiple-value-bind (result warning-p failure-p)
#-:ecl (compile-file file :output-file out-file)
#+:ecl (if |$EnableLispProfiling|
(compile-file file :output-file out-file :system-p t
:c-file t :h-file t)
(compile-file file :output-file out-file :system-p t))
#+:ecl
(let ((compiler::*ld* oa-cxx))
(if (and result (not failure-p)
(null (c::build-fasl (compile-file-pathname out-file)
:lisp-files `(,out-file)
:ld-flags (extra-runtime-libs))))
(setq result nil)))
(cond ((null result)
(|coreError| "compilation of Lisp code failed"))
(failure-p
(delete-file result)
(|coreError| "Lisp code contained errors"))
(warning-p
(|warn| "Lisp code contained warnings")))
result))
(|endCompileDuration|)))
(defun |compileLispHandler| (prog-name options in-file)
(declare (ignore prog-name))
(let ((out-file (|compileFilePathname| (or (|getOutputPathname| options)
in-file))))
(|compileLispFile| in-file out-file)))
(|associateRequestWithFileType| (|Option| "compile") |$LispFileType|
#'|compileLispHandler|)
(defun |topLevel|()
(let ((*package* (find-package "AxiomCore"))
(command-args (|getCommandLineArguments|)))
(when (null command-args)
(|internalError| "empty command line args"))
(multiple-value-bind
(options args) (|processCommandLine| (cdr command-args) nil nil)
(setq |$sysOpts| options)
(setq |$sysArgs| args)
(when (fboundp '|%sysInit|)
(funcall (symbol-function '|%sysInit|)))
(when (|handleCommandLine| (car command-args) options args)
(|coreQuit| (if (> (|errorCount|) 0) 1 0))))))
(defun |ensureTrailingSlash| (dir)
(let ((l (length dir)))
(unless (> l 0)
(|fatalError| "null directory name"))
(if (char= (char dir (- l 1)) #\/)
dir
(concatenate 'string dir "/"))))
(defun |pathBasename| (file)
(pathname-name file))
(defparameter |$LoadDirectories| nil)
(defparameter |$ImportedModules| nil)
(defun |getModuleInternalSymbol| (module)
(intern module (find-package "AxiomCore")))
(defun |alreadyLoaded?| (module)
(get (|getModuleInternalSymbol| (namestring module))
'|AxiomCore.loaded|))
(defun |noteUnitLoaded| (module)
(setf (get (|getModuleInternalSymbol| (namestring module))
'|AxiomCore.loaded|) t))
(defun |loadPathname| (module dir)
(setq dir (|ensureTrailingSlash| dir))
(make-pathname :directory (pathname-directory dir)
:name module
#-:ecl :type #-:ecl |$faslType|))
(defun |btxPthaname| (module dir)
(setq dir (|ensureTrailingSlash| dir))
(make-pathname :directory (pathname-directory dir)
:name module
:type "btx"))
(defun |loadFileIfPresent| (file)
(load file :if-does-not-exist nil))
(defun |loadIfPresent| (module)
(if (|alreadyLoaded?| module)
module
(when (|loadFileIfPresent| module)
(|noteUnitLoaded| module)
module)))
(defun |loadOrElse| (module)
(if (|alreadyLoaded?| module)
module
(when (load module :if-does-not-exist :error)
(|noteUnitLoaded| module)
module)))
(defun import-module-if-present (module dir)
(or (|loadIfPresent| (|btxPthaname| module dir))
(|loadIfPresent| (|loadPathname| module dir))))
(defun do-import-module (module directories)
(cond ((null directories)
(|fatalError|
(format nil
"module ~S not found in search path ~S"
module
|$LoadDirectories|)))
(t
(unless (import-module-if-present module (car directories))
(do-import-module module (cdr directories))))))
(defun |importModule| (module)
(do-import-module module |$LoadDirectories|))
(defmacro import-module (module)
`(progn (eval-when
#+:common-lisp (:compile-toplevel :load-toplevel :execute)
#-:common-lisp (compile load eval)
(if (compile-time-p)
(|importModule| ,module)))))
(defmacro |bootImport| (module)
`(|importModule| ,module))
(defun |%hasFeature| (f)
(member f *features* :test #'eq))
(defun |startCompileDuration| nil
(push :open-axiom-compile-time *features*))
(defun |endCompileDuration| nil
(delete :open-axiom-compile-time *features*))
(defun compile-time-p nil
(member :open-axiom-compile-time *features*))
#+(and :sbcl (not :win32))
(require "sb-posix")
#+ :sbcl
(defun shoe-provide-module(name)
(load name)
(provide name))
#+ :sbcl
(eval-when (:load-toplevel :execute)
(pushnew #'shoe-provide-module sb-ext:*module-provider-functions*))
(defun |ident?| (x)
(and (symbolp x)
(not (null x))))
(defmacro |fixnum?| (x)
`(typep ,x 'fixnum))
(defmacro |%fNaN?| (x)
#+:sbcl `(sb-ext:float-nan-p ,x)
#+:ecl `(ext:float-nan-p ,x)
#-(or :sbcl :ecl) `(/= ,x ,x))
(defmacro |double| (x)
`(float ,x 1.0d0))
(defmacro |integerAndFractionalParts| (x)
`(multiple-value-list (floor ,x)))
#-:gcl
(defmacro |maxIndex| (x)
`(1- (length ,x)))
#+:gcl
(defun |maxIndex| (x)
(1- (length x)))
(deftype |%ByteArray| ()
'(simple-array (unsigned-byte 8)))
(declaim (ftype (function (fixnum) |%ByteArray|) |makeByteArray|))
(defun |makeByteArray| (n)
(make-array n
:element-type '(unsigned-byte 8)
:initial-element 0))
(defmacro |makeBitVector| (n)
`(make-array ,n :element-type 'bit :initial-element 0))
(defun |makeString| (n &optional (c (code-char 0)))
(make-string n :initial-element c))
(defun |listToString| (l)
(let ((s (|makeString| (list-length l))))
(do ((i 0 (1+ i)))
((null l))
(setf (schar s i) (car l))
(setq l (cdr l)))
s))
(defmacro |mkVector| (n)
`(make-array ,n :initial-element nil))
(defmacro |mkIntArray| (n)
`(make-array ,n :initial-element 0))
(defconstant |$NativeTypeTable|
'((|void| . void)
(|char| . char)
(|int| . int)
(|float| . float)
(|double| . double)
(|string| . c-string)
(|address| . @pointer_type@)))