summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Makefile6
-rw-r--r--Makefile.config113
-rw-r--r--asmcomp/emit_sparc.mlp23
-rw-r--r--asmrun/Makefile4
-rw-r--r--asmrun/sparc.asm169
-rw-r--r--byterun/terminfo.c80
-rwxr-xr-xconfig/autoconf8
-rw-r--r--utils/config.mli5
-rw-r--r--utils/config.mlp4
9 files changed, 237 insertions, 175 deletions
diff --git a/Makefile b/Makefile
index 5afc2d5ae..4d80de8c6 100644
--- a/Makefile
+++ b/Makefile
@@ -80,6 +80,10 @@ all: runtime camlc camllex camlyacc library camltop
# The compilation of camltop will fail if the runtime has changed.
# Never mind, just do make bootstrap to reach fixpoint again.
+# Configure the system
+configure:
+ cd config; sh autoconf "$(BYTECC) $(CCLINKOPTS) $(CCLIBS)"
+
# Compile everything the first time
world: coldstart clean all
@@ -215,6 +219,8 @@ utils/config.ml: utils/config.mlp Makefile.config
-e 's|%%BYTECC%%|$(BYTECC) $(CCLINKFLAGS) $(LOWADDRESSES)|' \
-e 's|%%NATIVECC%%|$(NATIVECC) $(CCLINKFLAGS)|' \
-e 's|%%CCLIBS%%|$(CCLIBS)|' \
+ -e 's|%%ARCH%%|$(ARCH)|' \
+ -e 's|%%SYSTEM%%|$(SYSTEM)|' \
utils/config.mlp > utils/config.ml
@chmod -w utils/config.ml
diff --git a/Makefile.config b/Makefile.config
index f62781880..5125fb503 100644
--- a/Makefile.config
+++ b/Makefile.config
@@ -1,37 +1,36 @@
### Compile-time configuration
-### Name of architecture for the native-code compiler
-### Currently supported: alpha, sparc, i386
-### Set ARCH=none if your machine is not supported
-ARCH=alpha
-#ARCH=mips
-#ARCH=sparc
-#ARCH=i386
-#ARCH=none
+########## General configuration
+
+### Where to install the binaries
+BINDIR=/usr/local/bin
+
+### Where to install the standard library
+LIBDIR=/usr/local/lib/camlsl
+
+### Where to install the man pages
+MANDIR=/usr/local/man/man1
+MANEXT=1
+
+### Do #! scripts work on your system?
+SHARPBANGSCRIPTS=true
+#SHARPBANGSCRIPTS=false
+
+########## Configuration for the bytecode compiler
### Which C compiler to use for the bytecode interpreter.
### Performance of the bytecode interpreter is *much* improved
-### if Gnu CC 2 is used.
+### if Gnu CC version 2 is used.
BYTECC=gcc
# BYTECC=cc
### Additional compile-time options for $(BYTECC).
# If using gcc on Intel 386 or Motorola 68k:
-# BYTECCCOMPOPTS=-fno-defer-pop
+#BYTECCCOMPOPTS=-fno-defer-pop
# If using gcc and being superstitious:
BYTECCCOMPOPTS=-Wall
# Otherwise:
-# BYTECCCOMPOPTS=
-
-### Which C compiler to use for the native-code compiler.
-### cc is better than gcc on the Mips and Alpha.
-NATIVECC=cc
-#NATIVECC=gcc
-
-### Additional compile-time options for $(NATIVECC).
-# NATIVECCCOMPOPTS=
-# For the Alpha:
-NATIVECCCOMPOPTS=-std1
+#BYTECCCOMPOPTS=
### Additional link-time options
CCLINKOPTS=
@@ -39,37 +38,63 @@ CCLINKOPTS=
### If using GCC on a Dec Alpha under OSF1:
LOWADDRESSES=-Xlinker -taso
# Otherwise:
-# LOWADDRESSES=
-
-### Flags for the assembler
-# For the Sparc:
-# ASFLAGS=-P
-# For the Alpha or the Mips:
-ASFLAGS=-O2
-# Otherwise:
-# ASFLAGS=
+#LOWADDRESSES=
### Libraries needed
-CCLIBS=$(TERMINFOLIBS) -lm
+# On most platforms:
+CCLIBS=$(TERMCAPLIBS) -lm
+# For Solaris 2:
+#CCLIBS=$(TERMCAPLIBS) -lnsl -lsocket -lm
-### How to invoke ranlib (if needed)
+### How to invoke ranlib
# BSD-style:
RANLIB=ranlib
# System V-style:
-# RANLIB=ar -rs
+#RANLIB=ar -rs
# If ranlib is not needed at all:
-# RANLIB=true
+#RANLIB=true
-### Do #! scripts work on your system?
-SHARPBANGSCRIPTS=true
-# SHARPBANGSCRIPTS=false
+############# Configuration for the native-code compiler
-### Where to install the binaries
-BINDIR=/usr/local/bin
+### Name of architecture for the native-code compiler
+### Currently supported:
+###
+### alpha DecStation 3000 under OSF1
+### sparc Sun Sparcstation under SunOS 4.1 or Solaris 2
+### i386 Intel 386 / 486 / Pentium PCs under Linux
+### mips DecStation 3100 and 5000 under Ultrix 4
+###
+### Set ARCH=none if your machine is not supported
+ARCH=alpha
+#ARCH=sparc
+#ARCH=i386
+#ARCH=mips
+#ARCH=none
+
+### Name of operating system family for the native-code compiler
+### Currently needed only if ARCH=sparc to distinguish between
+### SunOS and Solaris.
+### Set SYSTEM=unknown in all other cases.
+#SYSTEM=sunos
+#SYSTEM=solaris
+SYSTEM=unknown
+
+### Which C compiler to use for the native-code compiler.
+### cc is better than gcc on the Mips and Alpha.
+NATIVECC=cc
+#NATIVECC=gcc
+
+### Additional compile-time options for $(NATIVECC).
+#NATIVECCCOMPOPTS=
+# For the Alpha:
+NATIVECCCOMPOPTS=-std1
+
+### Flags for the assembler
+# For the Alpha or the Mips:
+ASFLAGS=-O2
+# For the Sparc:
+#ASFLAGS=-P -DSYS_$(SYSTEM)
+# Otherwise:
+#ASFLAGS=
-### Where to install the standard library
-LIBDIR=/usr/local/lib/camlsl
-### Where to install the man pages
-MANDIR=/usr/local/man/man1
-MANEXT=1
diff --git a/asmcomp/emit_sparc.mlp b/asmcomp/emit_sparc.mlp
index be804cd74..d56649bb7 100644
--- a/asmcomp/emit_sparc.mlp
+++ b/asmcomp/emit_sparc.mlp
@@ -42,15 +42,25 @@ let next_in_pair = function
| {loc = Reg r; typ = Float} -> phys_reg (r + 15)
| _ -> fatal_error "Emit.next_in_pair"
-(* Symbols are prefixed with _ *)
+(* Symbols are prefixed with _ under SunOS but not under Solaris *)
+
+let symbol_prefix =
+ match Config.system with
+ "sunos" -> "_"
+ | "solaris" -> ""
let emit_symbol s =
- emit_string "_"; Emitaux.emit_symbol s
+ emit_string symbol_prefix; Emitaux.emit_symbol s
(* Output a label *)
+let label_prefix =
+ match Config.system with
+ "sunos" -> "L"
+ | "solaris" -> ".L"
+
let emit_label lbl =
- emit_string "L"; emit_int lbl
+ emit_string label_prefix; emit_int lbl
(* Output a pseudo-register *)
@@ -171,6 +181,7 @@ let float_constants = ref ([] : (int * string) list)
let emit_float_constant (lbl, cst) =
` .data\n`;
+ ` .align 8\n`;
`{emit_label lbl}: .double 0r{emit_string cst}\n`
(* Names of various instructions *)
@@ -291,7 +302,7 @@ let emit_instr i =
| Lop(Iextcall(s, alloc)) ->
if alloc then begin
` sethi %hi({emit_symbol s}), %g4\n`;
- `{record_frame i.live} call _caml_c_call\n`;
+ `{record_frame i.live} call {emit_symbol "caml_c_call"}\n`;
` or %g4, %lo({emit_symbol s}), %g4\n`
end else begin
` call {emit_symbol s}\n`;
@@ -335,12 +346,12 @@ let emit_instr i =
` cmp %g6, %g7\n`;
` bgeu {emit_label lbl_cont}\n`;
` add %g6, 4, {emit_reg i.res.(0)}\n`;
- `{record_frame i.live} call _caml_call_gc\n`;
+ `{record_frame i.live} call {emit_symbol "caml_call_gc"}\n`;
` mov {emit_int n}, %g4\n`;
` add %g6, 4, {emit_reg i.res.(0)}\n`;
`{emit_label lbl_cont}:\n`
end else begin
- `{record_frame i.live} call _caml_alloc\n`;
+ `{record_frame i.live} call {emit_symbol "caml_alloc"}\n`;
` mov {emit_int n}, %g4\n`;
` add %g6, 4, {emit_reg i.res.(0)}\n`
end
diff --git a/asmrun/Makefile b/asmrun/Makefile
index 3081392ee..3a0cdee63 100644
--- a/asmrun/Makefile
+++ b/asmrun/Makefile
@@ -2,8 +2,8 @@ include ../config/Makefile.h
include ../Makefile.config
CC=$(NATIVECC)
-CFLAGS=-I../byterun -DTARGET_$(ARCH) -O $(NATIVECCCOMPOPTS)
-DFLAGS=-I../byterun -DTARGET_$(ARCH) -g -DDEBUG $(NATIVECCCOMPOPTS)
+CFLAGS=-I../byterun -DTARGET_$(ARCH) -DSYS_$(SYSTEM) -O $(NATIVECCCOMPOPTS)
+DFLAGS=-I../byterun -DTARGET_$(ARCH) -DSYS_$(SYSTEM) -g -DDEBUG $(NATIVECCCOMPOPTS)
COBJS=main.o fail.o roots.o signals.o \
misc.o freelist.o major_gc.o minor_gc.o memory.o alloc.o compare.o ints.o \
diff --git a/asmrun/sparc.asm b/asmrun/sparc.asm
index 9ce01fca5..32fcebe68 100644
--- a/asmrun/sparc.asm
+++ b/asmrun/sparc.asm
@@ -1,15 +1,70 @@
/* Asm part of the runtime system for the Sparc processor. */
+/* Must be preprocessed by cpp */
- .common _young_start, 4, "data"
- .common _young_end, 4, "data"
- .common _young_ptr, 4, "data"
- .common _gc_entry_regs, 22 * 4, "data"
- .common _gc_entry_float_regs, 30 * 4, "data"
- .common _caml_top_of_stack, 4, "data"
- .common _caml_bottom_of_stack, 4, "data"
- .common _caml_last_return_address, 4, "data"
- .common _caml_exception_pointer, 4, "data"
- .common _caml_required_size, 4, "data"
+/* SunOS 4 prefixes identifiers with _, Solaris does not */
+
+#ifdef SYS_sunos
+
+ .common _young_start, 4, "bss"
+ .common _young_ptr, 4, "bss"
+ .common _gc_entry_regs, 22 * 4, "bss"
+ .common _gc_entry_float_regs, 30 * 4, "bss"
+ .common _caml_top_of_stack, 4, "bss"
+ .common _caml_bottom_of_stack, 4, "bss"
+ .common _caml_last_return_address, 4, "bss"
+ .common _caml_exception_pointer, 4, "bss"
+ .common _caml_required_size, 4, "bss"
+
+#define Young_start _young_start
+#define Young_ptr _young_ptr
+#define Gc_entry_regs _gc_entry_regs
+#define Gc_entry_float_regs _gc_entry_float_regs
+#define Caml_top_of_stack _caml_top_of_stack
+#define Caml_bottom_of_stack _caml_bottom_of_stack
+#define Caml_last_return_address _caml_last_return_address
+#define Caml_exception_pointer _caml_exception_pointer
+#define Caml_required_size _caml_required_size
+#define Caml_alloc _caml_alloc
+#define Caml_call_gc _caml_call_gc
+#define Minor_collection _minor_collection
+#define Caml_c_call _caml_c_call
+#define Caml_start_program _caml_start_program
+#define Caml_program _caml_program
+#define Raise_caml_exception _raise_caml_exception
+
+#endif
+
+#ifdef SYS_solaris
+
+ .common young_start, 4, 4
+ .common young_end, 4, 4
+ .common young_ptr, 4, 4
+ .common gc_entry_regs, 22 * 4, 4
+ .common gc_entry_float_regs, 30 * 4, 8
+ .common caml_top_of_stack, 4, 4
+ .common caml_bottom_of_stack, 4, 4
+ .common caml_last_return_address, 4, 4
+ .common caml_exception_pointer, 4, 4
+ .common caml_required_size, 4, 4
+
+#define Young_start young_start
+#define Young_ptr young_ptr
+#define Gc_entry_regs gc_entry_regs
+#define Gc_entry_float_regs gc_entry_float_regs
+#define Caml_top_of_stack caml_top_of_stack
+#define Caml_bottom_of_stack caml_bottom_of_stack
+#define Caml_last_return_address caml_last_return_address
+#define Caml_exception_pointer caml_exception_pointer
+#define Caml_required_size caml_required_size
+#define Caml_alloc caml_alloc
+#define Caml_call_gc caml_call_gc
+#define Minor_collection minor_collection
+#define Caml_c_call caml_c_call
+#define Caml_start_program caml_start_program
+#define Caml_program caml_program
+#define Raise_caml_exception raise_caml_exception
+
+#endif
/* libc functions appear to clobber %g2 ... %g7 */
/* Remember to save and restore %g5 %g6 %g7. */
@@ -20,33 +75,33 @@
/* Allocation functions */
.text
- .global _caml_alloc
- .global _caml_call_gc
+ .global Caml_alloc
+ .global Caml_call_gc
/* Required size in %g4 */
-_caml_alloc:
+Caml_alloc:
sub %g6, %g4, %g6
cmp %g6, %g7
- blu _caml_call_gc
+ blu Caml_call_gc
nop
retl
nop
/* Required size in %g4 */
-_caml_call_gc:
+Caml_call_gc:
/* Save %g4 (required size) */
- Store(%g4, _caml_required_size)
+ Store(%g4, Caml_required_size)
/* Save %g5 (exception pointer) */
- Store(%g5, _caml_exception_pointer)
+ Store(%g5, Caml_exception_pointer)
/* Save current allocation pointer for debugging purposes */
- Store(%g6, _young_ptr)
+ Store(%g6, Young_ptr)
/* Record lowest stack address */
- Store(%sp, _caml_bottom_of_stack)
+ Store(%sp, Caml_bottom_of_stack)
/* Record last return address */
- Store(%o7, _caml_last_return_address)
+ Store(%o7, Caml_last_return_address)
/* Save all regs used by the code generator */
- sethi %hi(_gc_entry_regs), %g1
- or %g1, %lo(_gc_entry_regs), %g1
+ sethi %hi(Gc_entry_regs), %g1
+ or %g1, %lo(Gc_entry_regs), %g1
std %l0, [%g1]
std %l2, [%g1 + 0x8]
std %l4, [%g1 + 0x10]
@@ -58,8 +113,8 @@ _caml_call_gc:
std %i2, [%g1 + 0x40]
std %i4, [%g1 + 0x48]
std %g2, [%g1 + 0x50]
- sethi %hi(_gc_entry_float_regs), %g1
- or %g1, %lo(_gc_entry_float_regs), %g1
+ sethi %hi(Gc_entry_float_regs), %g1
+ or %g1, %lo(Gc_entry_float_regs), %g1
std %f0, [%g1]
std %f2, [%g1 + 0x8]
std %f4, [%g1 + 0x10]
@@ -76,11 +131,11 @@ _caml_call_gc:
std %f26, [%g1 + 0x68]
std %f28, [%g1 + 0x70]
/* Call the garbage collector */
- call _minor_collection
+ call Minor_collection
nop
/* Restore all regs used by the code generator */
- sethi %hi(_gc_entry_regs), %g1
- or %g1, %lo(_gc_entry_regs), %g1
+ sethi %hi(Gc_entry_regs), %g1
+ or %g1, %lo(Gc_entry_regs), %g1
ldd [%g1], %l0
ldd [%g1 + 0x8], %l2
ldd [%g1 + 0x10], %l4
@@ -92,8 +147,8 @@ _caml_call_gc:
ldd [%g1 + 0x40], %i2
ldd [%g1 + 0x48], %i4
ldd [%g1 + 0x50], %g2
- sethi %hi(_gc_entry_float_regs), %g1
- or %g1, %lo(_gc_entry_float_regs), %g1
+ sethi %hi(Gc_entry_float_regs), %g1
+ or %g1, %lo(Gc_entry_float_regs), %g1
ldd [%g1], %f0
ldd [%g1 + 0x8], %f2
ldd [%g1 + 0x10], %f4
@@ -110,45 +165,45 @@ _caml_call_gc:
ldd [%g1 + 0x68], %f26
ldd [%g1 + 0x70], %f28
/* Reload %g5 - %g7 registers */
- Load(_caml_exception_pointer, %g5)
- Load(_young_ptr, %g6)
- Load(_young_start, %g7)
+ Load(Caml_exception_pointer, %g5)
+ Load(Young_ptr, %g6)
+ Load(Young_start, %g7)
/* Allocate space for block */
- Load(_caml_required_size, %g4)
+ Load(Caml_required_size, %g4)
sub %g6, %g4, %g6
/* Return to caller */
- Load(_caml_last_return_address, %o7)
+ Load(Caml_last_return_address, %o7)
retl
nop
/* Call a C function from Caml */
- .global _caml_c_call
+ .global Caml_c_call
/* Function to call is in %g4 */
-_caml_c_call:
+Caml_c_call:
/* Record lowest stack address and return address */
- Store(%sp, _caml_bottom_of_stack)
- Store(%o7, _caml_last_return_address)
+ Store(%sp, Caml_bottom_of_stack)
+ Store(%o7, Caml_last_return_address)
/* Save the exception handler and alloc pointer */
- Store(%g5, _caml_exception_pointer)
- sethi %hi(_young_ptr), %g1
+ Store(%g5, Caml_exception_pointer)
+ sethi %hi(Young_ptr), %g1
/* Call the C function */
call %g4
- st %g6, [%g1 + %lo(_young_ptr)] /* in delay slot */
+ st %g6, [%g1 + %lo(Young_ptr)] /* in delay slot */
/* Reload return address */
- Load(_caml_last_return_address, %o7)
+ Load(Caml_last_return_address, %o7)
/* Reload %g5 - %g7 */
- Load(_caml_exception_pointer, %g5)
- Load(_young_ptr, %g6)
- sethi %hi(_young_start), %g1
+ Load(Caml_exception_pointer, %g5)
+ Load(Young_ptr, %g6)
+ sethi %hi(Young_start), %g1
/* Return to caller */
retl
- ld [%g1 + %lo(_young_start)], %g7 /* in delay slot */
+ ld [%g1 + %lo(Young_start)], %g7 /* in delay slot */
/* Start the Caml program */
- .global _caml_start_program
-_caml_start_program:
+ .global Caml_start_program
+Caml_start_program:
/* Save all callee-save registers */
save %sp, -96, %sp
/* Build an exception handler */
@@ -160,12 +215,12 @@ L100: sub %sp, 8, %sp
st %o7, [%sp + 96]
mov %sp, %g5
/* Record highest stack address */
- Store(%sp, _caml_top_of_stack)
+ Store(%sp, Caml_top_of_stack)
/* Initialize allocation registers */
- Load(_young_ptr, %g6)
- Load(_young_start, %g7)
+ Load(Young_ptr, %g6)
+ Load(Young_start, %g7)
/* Go for it */
- call _caml_program
+ call Caml_program
nop
/* Pop handler */
add %sp, 8, %sp
@@ -176,12 +231,12 @@ L101: ret
/* Raise an exception from C */
- .global _raise_caml_exception
-_raise_caml_exception:
+ .global Raise_caml_exception
+Raise_caml_exception:
/* Reload %g5 - %g7 */
- Load(_caml_exception_pointer, %g5)
- Load(_young_ptr, %g6)
- Load(_young_start, %g7)
+ Load(Caml_exception_pointer, %g5)
+ Load(Young_ptr, %g6)
+ Load(Young_start, %g7)
/* Save exception bucket in a register outside the reg windows */
mov %o0, %g4
/* Pop some frames until the trap pointer is in the current frame. */
diff --git a/byterun/terminfo.c b/byterun/terminfo.c
index 214984892..968355b72 100644
--- a/byterun/terminfo.c
+++ b/byterun/terminfo.c
@@ -6,44 +6,13 @@
#include "io.h"
#include "mlvalues.h"
-#ifdef HAS_TERMINFO
-
-#undef getch
-#include <curses.h>
-#include <term.h>
-
-value terminfo_setup(unit) /* ML */
- value unit;
-{
- if (setupterm(NULL, 1, 1) != 1) failwith("Terminfo.setupterm");
- return Val_unit;
-}
-
-value terminfo_getstr(capa) /* ML */
- value capa;
-{
- char * res = (char *) tigetstr(String_val(capa));
- if (res == (char *)(-1)) raise_not_found();
- return copy_string(res);
-}
-
-value terminfo_getnum(capa) /* ML */
- value capa;
-{
- int res = tigetnum(String_val(capa));
- if (res == -2) raise_not_found();
- return Val_int(res);
-}
-
-#else
-
#ifdef HAS_TERMCAP
#define _BSD /* For DEC OSF1 */
#undef getch
#include <curses.h>
-value terminfo_setup(unit)
+value terminfo_setup(unit) /* ML */
value unit;
{
static buffer[1024];
@@ -51,7 +20,7 @@ value terminfo_setup(unit)
return Val_unit;
}
-value terminfo_getstr(capa)
+value terminfo_getstr(capa) /* ML */
value capa;
{
char buff[1024];
@@ -60,7 +29,7 @@ value terminfo_getstr(capa)
return copy_string(buff);
}
-value terminfo_getnum(capa)
+value terminfo_getnum(capa) /* ML */
value capa;
{
int res = tgetnum(String_val(capa));
@@ -68,6 +37,24 @@ value terminfo_getnum(capa)
return Val_int(res);
}
+static struct channel * terminfo_putc_channel;
+
+static int terminfo_putc(c)
+ int c;
+{
+ putch(terminfo_putc_channel, c);
+ return c;
+}
+
+value terminfo_puts(chan, str, count) /* ML */
+ struct channel * chan;
+ value str, count;
+{
+ terminfo_putc_channel = chan;
+ tputs(String_val(str), Int_val(count), terminfo_putc);
+ return Val_unit;
+}
+
#else
value terminfo_setup(unit)
@@ -91,31 +78,6 @@ value terminfo_getnum(capa)
return Val_unit;
}
-#endif
-#endif
-
-#if defined HAS_TERMINFO || defined HAS_TERMCAP
-
-static struct channel * terminfo_putc_channel;
-
-static int terminfo_putc(c)
- int c;
-{
- putch(terminfo_putc_channel, c);
- return c;
-}
-
-value terminfo_puts(chan, str, count) /* ML */
- struct channel * chan;
- value str, count;
-{
- terminfo_putc_channel = chan;
- tputs(String_val(str), Int_val(count), terminfo_putc);
- return Val_unit;
-}
-
-#else
-
value terminfo_puts(chan, str, count)
struct channel * chan;
value str, count;
diff --git a/config/autoconf b/config/autoconf
index c9f035c01..de80a0a5a 100755
--- a/config/autoconf
+++ b/config/autoconf
@@ -97,16 +97,10 @@ fi
# For the terminfo module
-if sh hasgot -lcurses setupterm tigetstr tigetnum tputs; then
- echo "terminfo functions found."
- echo "#define HAS_TERMINFO" >> s.h
- echo "TERMINFOLIBS=-lcurses" >> Makefile.h
-fi
-
if sh hasgot -lcurses -ltermcap tgetent tgetstr tgetnum tputs; then
echo "termcap functions found."
echo "#define HAS_TERMCAP" >> s.h
- echo "TERMINFOLIBS=-lcurses -ltermcap" >> Makefile.h
+ echo "TERMCAPLIBS=-lcurses -ltermcap" >> Makefile.h
fi
# For the Unix library
diff --git a/utils/config.mli b/utils/config.mli
index d552deda0..599f8cbde 100644
--- a/utils/config.mli
+++ b/utils/config.mli
@@ -31,3 +31,8 @@ val cmxa_magic_number: string
val max_tag: int
(* Biggest tag that can be stored in the header of a block. *)
+
+val architecture: string
+ (* Name of processor type for the native-code compiler *)
+val system: string
+ (* Name of operating system for the native-code compiler *)
diff --git a/utils/config.mlp b/utils/config.mlp
index 4eb854355..801c315b6 100644
--- a/utils/config.mlp
+++ b/utils/config.mlp
@@ -18,3 +18,7 @@ and cmxa_magic_number = "Caml1999Z001"
let load_path = ref ([] : string list)
let max_tag = 248
+
+let architecture = "%%ARCH%%"
+
+let system = "%%SYSTEM%%"