-
Notifications
You must be signed in to change notification settings - Fork 71
/
sqWin32SpurAlloc.c
229 lines (192 loc) · 7.25 KB
/
sqWin32SpurAlloc.c
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
/****************************************************************************
* PROJECT: Squeak port for Win32 (NT / Win95)
* FILE: sqWin32SpurAlloc.c
* CONTENT: Virtual Memory Management For Spur
*
* AUTHOR: Eliot Miranda
* EMAIL: eliot.miranda@gmail.com
*
*****************************************************************************/
#include <windows.h>
#include <errno.h>
#include "sq.h"
#include "pharovm/debug.h"
/* Why does this have to be *here*?? eem 6/24/2014 */
#if !defined(NDEBUG)
/* in debug mode, let the system crash so that we can see where it happened */
#define EXCEPTION_WRONG_ACCESS EXCEPTION_CONTINUE_SEARCH
#else
/* in release mode, execute the exception handler notifying the user what happened */
#define EXCEPTION_WRONG_ACCESS EXCEPTION_EXECUTE_HANDLER
#endif
void *
sqAllocateMemorySegmentOfSizeAboveAllocatedSizeInto(sqInt size, void *minAddress, sqInt *allocatedSizePointer);
LONG CALLBACK sqExceptionFilter(LPEXCEPTION_POINTERS exp)
{
/* always wrong access - we handle memory differently now */
return EXCEPTION_WRONG_ACCESS;
}
static sqIntptr_t pageMask; /* bit mask for the start of a memory page */
static sqIntptr_t pageSize; /* size of a memory page */
static char *minAppAddr; /* SYSTEM_INFO lpMinimumApplicationAddress */
static char *maxAppAddr; /* SYSTEM_INFO lpMaximumApplicationAddress */
# define roundDownToPage(v) ((v)&pageMask)
# define roundUpToPage(v) (((v)+pageSize-1)&pageMask)
void* allocateJITMemory(usqInt desiredSize, usqInt desiredPosition){
char *address, *alloc;
usqIntptr_t alignment;
sqInt allocBytes;
SYSTEM_INFO sysInfo;
/* determine page boundaries & available address space */
GetSystemInfo(&sysInfo);
pageSize = sysInfo.dwPageSize;
pageMask = ~(pageSize - 1);
minAppAddr = sysInfo.lpMinimumApplicationAddress;
maxAppAddr = sysInfo.lpMaximumApplicationAddress;
alignment = max(pageSize,1024*1024);
address = (char *)(((usqInt)desiredPosition + alignment - 1) & ~(alignment - 1));
alloc = sqAllocateMemorySegmentOfSizeAboveAllocatedSizeInto(roundUpToPage(desiredSize), address, &allocBytes);
if (!alloc) {
logErrorFromErrno("Could not allocate JIT memory");
exit(1);
}
return alloc;
}
/************************************************************************/
/* sqAllocateMemory: Initialize virtual memory */
/************************************************************************/
usqInt
sqAllocateMemory(usqInt minHeapSize, usqInt desiredHeapSize, usqInt desiredBaseAddress)
{
char *address, *alloc;
usqIntptr_t alignment;
sqInt allocBytes;
SYSTEM_INFO sysInfo;
/* determine page boundaries & available address space */
GetSystemInfo(&sysInfo);
pageSize = sysInfo.dwPageSize;
pageMask = ~(pageSize - 1);
minAppAddr = sysInfo.lpMinimumApplicationAddress;
maxAppAddr = sysInfo.lpMaximumApplicationAddress;
alignment = max(pageSize,1024*1024);
address = (char *)(((usqInt)desiredBaseAddress + alignment - 1) & ~(alignment - 1));
alloc = sqAllocateMemorySegmentOfSizeAboveAllocatedSizeInto
(roundUpToPage(desiredHeapSize), address, &allocBytes);
return alloc;
}
#define roundDownToPage(v) ((v)&pageMask)
#define roundUpToPage(v) (((v)+pageSize-1)&pageMask)
/* Allocate a region of memory of at least size bytes, at or above minAddress.
* If the attempt fails, answer null. If the attempt succeeds, answer the
* start of the region and assign its size through allocatedSizePointer.
*
* This from the VirtualFree doc is rather scary:
dwSize [in]
The size of the region of memory to be freed, in bytes.
If the dwFreeType parameter is MEM_RELEASE, this parameter must be 0
(zero). The function frees the entire region that is reserved in the
initial allocation call to VirtualAlloc.
*
* So we rely on the SpurMemoryManager to free exactly the segments that were
* allocated.
*/
#define SizeForRelease(bytes) 0
static int
address_space_used(char *address, usqInt bytes)
{
MEMORY_BASIC_INFORMATION info;
int addressSpaceUnused;
if (address < minAppAddr || address > maxAppAddr)
return 1;
if (!VirtualQuery(address, &info, sizeof(info)))
sqMessageBox(MB_OK | MB_ICONSTOP, TEXT("VM Error:"),
TEXT("Unable to VirtualQuery range [%p, %p), Error: %u"),
address, (char *)address + bytes, GetLastError());
addressSpaceUnused = info.BaseAddress == address
&& info.RegionSize >= bytes
&& info.State == MEM_FREE;
return !addressSpaceUnused;
}
void *
sqAllocateMemorySegmentOfSizeAboveAllocatedSizeInto(sqInt size, void *minAddress, sqInt *allocatedSizePointer)
{
char *address, *alloc;
usqInt bytes, delta;
address = (char *)roundUpToPage((usqIntptr_t)minAddress);
bytes = roundUpToPage(size);
delta = max(pageSize,1024*1024);
# define printProbes 0
# define printMaps 0
while ((usqIntptr_t)(address + bytes) > (usqIntptr_t)address) {
if (printProbes)
logTrace("probing [%p,%p)\n", address, address + bytes);
if (address_space_used(address, bytes)) {
address += delta;
continue;
}
alloc = VirtualAlloc(address, bytes, MEM_COMMIT|MEM_RESERVE, PAGE_READWRITE);
/* For some reason (large page support?) we can ask for a page-aligned
* address such as 0xNNNNf000 but VirtualAlloc will answer 0xNNNN0000.
* So accept allocs above minAddress rather than allocs above address
*/
if (alloc >= (char *)minAddress && alloc <= address + delta) {
if (printMaps)
logWarn("VirtualAlloc [%p,%p) above %p)\n",
address, address+bytes, minAddress);
*allocatedSizePointer = bytes;
return alloc;
}
if (!alloc) {
logWarn("Unable to VirtualAlloc committed memory at desired address (%lld bytes requested at %p, above %p)", bytes, address, minAddress);
logErrorFromGetLastError("Unable to VirtualAlloc committed memory at desired address");
return 0;
}
/* VirtualAlloc answered a mapping well away from where Spur prefers.
* Discard the mapping and try again delta higher.
*/
if (alloc && !VirtualFree(alloc, SizeForRelease(bytes), MEM_RELEASE)){
logWarn("Unable to VirtualFree committed memory at desired address (%lld bytes requested at %p, above %p), Error: %lu\n",
bytes, address, minAddress, GetLastError());
}
address += delta;
}
logWarn("Unable to VirtualAlloc committed memory at desired address");
return 0;
}
/* Deallocate a region of memory previously allocated by
* sqAllocateMemorySegmentOfSizeAboveAllocatedSizeInto. Cannot fail.
*/
void
sqDeallocateMemorySegmentAtOfSize(void *addr, sqInt sz)
{
if (!VirtualFree(addr, SizeForRelease(sz), MEM_RELEASE))
sqMessageBox(MB_OK | MB_ICONSTOP, TEXT("VM Warning:"),
TEXT("Unable to VirtualFree committed memory (%") TEXT(PRIuSQINT) TEXT(" bytes requested), Error: %ul"),
sz, GetLastError());
}
# if COGVM
void
sqMakeMemoryExecutableFromTo(usqIntptr_t startAddr, usqIntptr_t endAddr)
{
DWORD previous;
SIZE_T size;
size = endAddr - startAddr;
if (!VirtualProtect((void *)startAddr,
size,
PAGE_EXECUTE_READWRITE,
&previous))
logErrorFromErrno("VirtualProtect(x,y,PAGE_EXECUTE_READWRITE)");
}
void
sqMakeMemoryNotExecutableFromTo(usqIntptr_t startAddr, usqIntptr_t endAddr)
{
DWORD previous;
SIZE_T size;
size = endAddr - startAddr;
if (!VirtualProtect((void *)startAddr,
size,
PAGE_READWRITE,
&previous))
logErrorFromErrno("VirtualProtect(x,y,PAGE_EXECUTE_READWRITE)");
}
# endif /* COGVM */