summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2002-06-03 14:21:50 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2002-06-03 14:21:50 +0000
commitc9c0e6d13c694dad2ff2fa3219491cd373256de7 (patch)
tree67bcb9189c0ec70008ee2bf41451a9fefe82ee92
parent685a839af651583941922c7aa87a9a13696e35ed (diff)
Nettoyage alloc_for_heap, free_for_heap. Prevoir d'utiliser mmap() au lieu de malloc() pour allouer le tas majeur (utile pour IA64/Linux)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4867 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--byterun/intern.c7
-rw-r--r--byterun/major_gc.c7
-rw-r--r--byterun/memory.c32
-rw-r--r--byterun/memory.h6
-rw-r--r--byterun/unix.c47
5 files changed, 78 insertions, 21 deletions
diff --git a/byterun/intern.c b/byterun/intern.c
index eaa6eb1e9..3128952f8 100644
--- a/byterun/intern.c
+++ b/byterun/intern.c
@@ -41,7 +41,7 @@ static int intern_input_malloced;
static header_t * intern_dest;
/* Writing pointer in destination block */
-static header_t * intern_extra_block;
+static char * intern_extra_block;
/* If non-NULL, point to new heap chunk allocated with alloc_for_heap. */
static asize_t obj_counter;
@@ -329,7 +329,7 @@ static void intern_alloc(mlsize_t whsize, mlsize_t num_objects)
intern_extra_block = alloc_for_heap(request);
if (intern_extra_block == NULL) raise_out_of_memory();
intern_color = allocation_color(intern_extra_block);
- intern_dest = intern_extra_block;
+ intern_dest = (header_t *) intern_extra_block;
} else {
/* this is a specialised version of alloc from alloc.c */
if (wosize == 0){
@@ -361,7 +361,8 @@ static void intern_add_to_heap(mlsize_t whsize)
/* If heap chunk not filled totally, build free block at end */
asize_t request =
((Bsize_wsize(whsize) + Page_size - 1) >> Page_log) << Page_log;
- header_t * end_extra_block = intern_extra_block + Wsize_bsize(request);
+ header_t * end_extra_block =
+ (header_t *) intern_extra_block + Wsize_bsize(request);
Assert(intern_dest <= end_extra_block);
if (intern_dest < end_extra_block)
*intern_dest =
diff --git a/byterun/major_gc.c b/byterun/major_gc.c
index 9d33ed7c0..3377bf7ca 100644
--- a/byterun/major_gc.c
+++ b/byterun/major_gc.c
@@ -406,15 +406,10 @@ void init_major_heap (asize_t heap_size)
stat_heap_size = clip_heap_chunk_size (heap_size);
stat_top_heap_size = stat_heap_size;
Assert (stat_heap_size % Page_size == 0);
- heap_start = aligned_malloc (stat_heap_size + sizeof (heap_chunk_head),
- sizeof (heap_chunk_head), &block);
+ heap_start = (char *) alloc_for_heap (stat_heap_size);
if (heap_start == NULL)
fatal_error ("Fatal error: not enough memory for the initial heap.\n");
- heap_start += sizeof (heap_chunk_head);
- Assert ((unsigned long) heap_start % Page_size == 0);
- Chunk_size (heap_start) = stat_heap_size;
Chunk_next (heap_start) = NULL;
- Chunk_block (heap_start) = block;
heap_end = heap_start + stat_heap_size;
Assert ((unsigned long) heap_end % Page_size == 0);
diff --git a/byterun/memory.c b/byterun/memory.c
index b503dc196..5587c1e45 100644
--- a/byterun/memory.c
+++ b/byterun/memory.c
@@ -26,6 +26,11 @@
#include "mlvalues.h"
#include "signals.h"
+#ifdef USE_MMAP_INSTEAD_OF_MALLOC
+extern char * aligned_mmap (asize_t size, int modulo, void ** block);
+extern void aligned_munmap (char * addr, asize_t size);
+#endif
+
/* Allocate a block of the requested size, to be passed to
[add_to_heap] later.
[request] must be a multiple of [Page_size].
@@ -33,26 +38,36 @@
The returned pointer is a hp, but the header must be initialized by
the caller.
*/
-header_t *alloc_for_heap (asize_t request)
+char *alloc_for_heap (asize_t request)
{
char *mem;
void *block;
Assert (request % Page_size == 0);
+#ifdef USE_MMAP_INSTEAD_OF_MALLOC
+ mem = aligned_mmap (request + sizeof (heap_chunk_head),
+ sizeof (heap_chunk_head), &block);
+#else
mem = aligned_malloc (request + sizeof (heap_chunk_head),
sizeof (heap_chunk_head), &block);
+#endif
if (mem == NULL) return NULL;
mem += sizeof (heap_chunk_head);
Chunk_size (mem) = request;
Chunk_block (mem) = block;
- return (header_t *) mem;
+ return mem;
}
/* Use this function to free a block allocated with [alloc_for_heap]
if you don't add it with [add_to_heap].
*/
-void free_for_heap (header_t *mem)
+void free_for_heap (char *mem)
{
+#ifdef USE_MMAP_INSTEAD_OF_MALLOC
+ aligned_munmap (Chunk_block (mem),
+ Chunk_size (mem) + sizeof (heap_chunk_head));
+#else
free (Chunk_block (mem));
+#endif
}
/* Take a chunk of memory as argument, which must be the result of a
@@ -64,10 +79,9 @@ void free_for_heap (header_t *mem)
The caller must update [allocated_words] if applicable.
Return value: 0 if no error; -1 in case of error.
*/
-int add_to_heap (header_t *mem)
+int add_to_heap (char *m)
{
asize_t i;
- char *m = (char *) mem;
Assert (Chunk_size (m) % Page_size == 0);
#ifdef DEBUG
/* Should check the contents of the block. */
@@ -149,7 +163,7 @@ int add_to_heap (header_t *mem)
*/
static char *expand_heap (mlsize_t request)
{
- header_t *mem;
+ char *mem;
asize_t malloc_request;
malloc_request = round_heap_chunk_size (Bhsize_wosize (request));
@@ -164,7 +178,7 @@ static char *expand_heap (mlsize_t request)
Hd_hp (mem) = Make_header (Wosize_bhsize (malloc_request), 0, Caml_blue);
if (add_to_heap (mem) != 0){
- free (mem);
+ free_for_heap (mem);
return NULL;
}
return Bp_hp (mem);
@@ -176,7 +190,7 @@ static char *expand_heap (mlsize_t request)
void shrink_heap (char *chunk)
{
char **cp;
- int i;
+ asize_t i;
/* Never deallocate the first block, because heap_start is both the
first block and the base address for page numbers, and we don't
@@ -211,7 +225,7 @@ void shrink_heap (char *chunk)
}
/* Free the [malloc] block that contains [chunk]. */
- free (Chunk_block (chunk));
+ free_for_heap (chunk);
}
color_t allocation_color (void *hp)
diff --git a/byterun/memory.h b/byterun/memory.h
index a5ffb6019..d97547e3c 100644
--- a/byterun/memory.h
+++ b/byterun/memory.h
@@ -36,9 +36,9 @@ CAMLextern value check_urgent_gc (value);
CAMLextern void * stat_alloc (asize_t); /* Size in bytes. */
CAMLextern void stat_free (void *);
CAMLextern void * stat_resize (void *, asize_t); /* Size in bytes. */
-header_t *alloc_for_heap (asize_t request); /* Size in bytes. */
-void free_for_heap (header_t *mem);
-int add_to_heap (header_t *mem);
+char *alloc_for_heap (asize_t request); /* Size in bytes. */
+void free_for_heap (char *mem);
+int add_to_heap (char *mem);
color_t allocation_color (void *hp);
/* void shrink_heap (char *); Only used in compact.c */
diff --git a/byterun/unix.c b/byterun/unix.c
index d1e29ec39..465b68409 100644
--- a/byterun/unix.c
+++ b/byterun/unix.c
@@ -207,3 +207,50 @@ char * caml_dlerror(void)
#endif
+#ifdef USE_MMAP_INSTEAD_OF_MALLOC
+
+/* The code below supports the use of mmap() rather than malloc()
+ for allocating the chunks composing the major heap.
+ This code is needed for the IA64 under Linux, where the native
+ malloc() implementation can return pointers several *exabytes* apart,
+ (some coming from mmap(), other from sbrk()); this makes the
+ page table *way* too large.
+ No other tested platform requires this hack so far. However, it could
+ be useful for other 64-bit platforms in the future. */
+
+#include <sys/mman.h>
+
+char *aligned_mmap (asize_t size, int modulo, void **block)
+{
+ char *raw_mem;
+ unsigned long aligned_mem;
+ Assert (modulo < Page_size);
+ raw_mem = (char *) mmap(NULL, size + Page_size, PROT_READ | PROT_WRITE,
+ MAP_PRIVATE | MAP_ANONYMOUS, -1, 0);
+ if (raw_mem == MAP_FAILED) return NULL;
+ *block = raw_mem;
+ raw_mem += modulo; /* Address to be aligned */
+ aligned_mem = (((unsigned long) raw_mem / Page_size + 1) * Page_size);
+#ifdef DEBUG
+ {
+ unsigned long *p;
+ unsigned long *p0 = (void *) *block,
+ *p1 = (void *) (aligned_mem - modulo),
+ *p2 = (void *) (aligned_mem - modulo + size),
+ *p3 = (void *) ((char *) *block + size + Page_size);
+
+ for (p = p0; p < p1; p++) *p = Debug_filler_align;
+ for (p = p1; p < p2; p++) *p = Debug_uninit_align;
+ for (p = p2; p < p3; p++) *p = Debug_filler_align;
+ }
+#endif
+ return (char *) (aligned_mem - modulo);
+}
+
+void aligned_munmap (char * addr, asize_t size)
+{
+ int retcode = munmap (addr, size + Page_size);
+ Assert(retcode == 0);
+}
+
+#endif