malloc.h 36 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979
  1. /*
  2. This is a version (aka dlmalloc) of malloc/free/realloc written by
  3. Doug Lea and released to the public domain. Use, modify, and
  4. redistribute this code without permission or acknowledgement in any
  5. way you wish. Send questions, comments, complaints, performance
  6. data, etc to dl@cs.oswego.edu
  7. VERSION 2.7.2 Sat Aug 17 09:07:30 2002 Doug Lea (dl at gee)
  8. Note: There may be an updated version of this malloc obtainable at
  9. ftp://gee.cs.oswego.edu/pub/misc/malloc.c
  10. Check before installing!
  11. Hacked up for uClibc by Erik Andersen <andersen@codepoet.org>
  12. */
  13. #include <features.h>
  14. #include <stddef.h>
  15. #include <unistd.h>
  16. #include <errno.h>
  17. #include <string.h>
  18. #include <malloc.h>
  19. #include <stdlib.h>
  20. #include <sys/mman.h>
  21. #include <bits/uClibc_mutex.h>
  22. #include <bits/uClibc_page.h>
  23. __UCLIBC_MUTEX_EXTERN(__malloc_lock)
  24. #if defined __UCLIBC_HAS_THREADS__ && !defined __UCLIBC_HAS_LINUXTHREADS__
  25. attribute_hidden
  26. #endif
  27. ;
  28. #define __MALLOC_LOCK __UCLIBC_MUTEX_LOCK(__malloc_lock)
  29. #define __MALLOC_UNLOCK __UCLIBC_MUTEX_UNLOCK(__malloc_lock)
  30. /*
  31. MALLOC_ALIGNMENT is the minimum alignment for malloc'ed chunks.
  32. It must be a power of two at least 2 * (sizeof(size_t)), even on machines
  33. for which smaller alignments would suffice. It may be defined as
  34. larger than this though. Note however that code and data structures
  35. are optimized for the case of 8-byte alignment.
  36. */
  37. #ifndef MALLOC_ALIGNMENT
  38. #define MALLOC_ALIGNMENT (2 * (sizeof(size_t)))
  39. #endif
  40. /* The corresponding bit mask value */
  41. #define MALLOC_ALIGN_MASK (MALLOC_ALIGNMENT - 1)
  42. /*
  43. TRIM_FASTBINS controls whether free() of a very small chunk can
  44. immediately lead to trimming. Setting to true (1) can reduce memory
  45. footprint, but will almost always slow down programs that use a lot
  46. of small chunks.
  47. Define this only if you are willing to give up some speed to more
  48. aggressively reduce system-level memory footprint when releasing
  49. memory in programs that use many small chunks. You can get
  50. essentially the same effect by setting MXFAST to 0, but this can
  51. lead to even greater slowdowns in programs using many small chunks.
  52. TRIM_FASTBINS is an in-between compile-time option, that disables
  53. only those chunks bordering topmost memory from being placed in
  54. fastbins.
  55. */
  56. #ifndef TRIM_FASTBINS
  57. #define TRIM_FASTBINS 0
  58. #endif
  59. /*
  60. MORECORE-related declarations. By default, rely on sbrk
  61. */
  62. /*
  63. MORECORE is the name of the routine to call to obtain more memory
  64. from the system. See below for general guidance on writing
  65. alternative MORECORE functions, as well as a version for WIN32 and a
  66. sample version for pre-OSX macos.
  67. */
  68. #ifndef MORECORE
  69. #define MORECORE sbrk
  70. #endif
  71. /*
  72. MORECORE_FAILURE is the value returned upon failure of MORECORE
  73. as well as mmap. Since it cannot be an otherwise valid memory address,
  74. and must reflect values of standard sys calls, you probably ought not
  75. try to redefine it.
  76. */
  77. #ifndef MORECORE_FAILURE
  78. #define MORECORE_FAILURE (-1)
  79. #endif
  80. /*
  81. If MORECORE_CONTIGUOUS is true, take advantage of fact that
  82. consecutive calls to MORECORE with positive arguments always return
  83. contiguous increasing addresses. This is true of unix sbrk. Even
  84. if not defined, when regions happen to be contiguous, malloc will
  85. permit allocations spanning regions obtained from different
  86. calls. But defining this when applicable enables some stronger
  87. consistency checks and space efficiencies.
  88. */
  89. #ifndef MORECORE_CONTIGUOUS
  90. #define MORECORE_CONTIGUOUS 1
  91. #endif
  92. /*
  93. MMAP_AS_MORECORE_SIZE is the minimum mmap size argument to use if
  94. sbrk fails, and mmap is used as a backup (which is done only if
  95. HAVE_MMAP). The value must be a multiple of page size. This
  96. backup strategy generally applies only when systems have "holes" in
  97. address space, so sbrk cannot perform contiguous expansion, but
  98. there is still space available on system. On systems for which
  99. this is known to be useful (i.e. most linux kernels), this occurs
  100. only when programs allocate huge amounts of memory. Between this,
  101. and the fact that mmap regions tend to be limited, the size should
  102. be large, to avoid too many mmap calls and thus avoid running out
  103. of kernel resources.
  104. */
  105. #ifndef MMAP_AS_MORECORE_SIZE
  106. #define MMAP_AS_MORECORE_SIZE (1024 * 1024)
  107. #endif
  108. /*
  109. The system page size. To the extent possible, this malloc manages
  110. memory from the system in page-size units. Note that this value is
  111. cached during initialization into a field of malloc_state. So even
  112. if malloc_getpagesize is a function, it is only called once.
  113. The following mechanics for getpagesize were adapted from bsd/gnu
  114. getpagesize.h. If none of the system-probes here apply, a value of
  115. 4096 is used, which should be OK: If they don't apply, then using
  116. the actual value probably doesn't impact performance.
  117. */
  118. #ifndef malloc_getpagesize
  119. # include <unistd.h>
  120. # define malloc_getpagesize getpagesize()
  121. #else /* just guess */
  122. # define malloc_getpagesize (4096)
  123. #endif
  124. /* mallopt tuning options */
  125. /*
  126. M_MXFAST is the maximum request size used for "fastbins", special bins
  127. that hold returned chunks without consolidating their spaces. This
  128. enables future requests for chunks of the same size to be handled
  129. very quickly, but can increase fragmentation, and thus increase the
  130. overall memory footprint of a program.
  131. This malloc manages fastbins very conservatively yet still
  132. efficiently, so fragmentation is rarely a problem for values less
  133. than or equal to the default. The maximum supported value of MXFAST
  134. is 80. You wouldn't want it any higher than this anyway. Fastbins
  135. are designed especially for use with many small structs, objects or
  136. strings -- the default handles structs/objects/arrays with sizes up
  137. to 16 4byte fields, or small strings representing words, tokens,
  138. etc. Using fastbins for larger objects normally worsens
  139. fragmentation without improving speed.
  140. M_MXFAST is set in REQUEST size units. It is internally used in
  141. chunksize units, which adds padding and alignment. You can reduce
  142. M_MXFAST to 0 to disable all use of fastbins. This causes the malloc
  143. algorithm to be a closer approximation of fifo-best-fit in all cases,
  144. not just for larger requests, but will generally cause it to be
  145. slower.
  146. */
  147. /* M_MXFAST is a standard SVID/XPG tuning option, usually listed in malloc.h */
  148. #ifndef M_MXFAST
  149. #define M_MXFAST 1
  150. #endif
  151. #ifndef DEFAULT_MXFAST
  152. #define DEFAULT_MXFAST 64
  153. #endif
  154. /*
  155. M_TRIM_THRESHOLD is the maximum amount of unused top-most memory
  156. to keep before releasing via malloc_trim in free().
  157. Automatic trimming is mainly useful in long-lived programs.
  158. Because trimming via sbrk can be slow on some systems, and can
  159. sometimes be wasteful (in cases where programs immediately
  160. afterward allocate more large chunks) the value should be high
  161. enough so that your overall system performance would improve by
  162. releasing this much memory.
  163. The trim threshold and the mmap control parameters (see below)
  164. can be traded off with one another. Trimming and mmapping are
  165. two different ways of releasing unused memory back to the
  166. system. Between these two, it is often possible to keep
  167. system-level demands of a long-lived program down to a bare
  168. minimum. For example, in one test suite of sessions measuring
  169. the XF86 X server on Linux, using a trim threshold of 128K and a
  170. mmap threshold of 192K led to near-minimal long term resource
  171. consumption.
  172. If you are using this malloc in a long-lived program, it should
  173. pay to experiment with these values. As a rough guide, you
  174. might set to a value close to the average size of a process
  175. (program) running on your system. Releasing this much memory
  176. would allow such a process to run in memory. Generally, it's
  177. worth it to tune for trimming rather tham memory mapping when a
  178. program undergoes phases where several large chunks are
  179. allocated and released in ways that can reuse each other's
  180. storage, perhaps mixed with phases where there are no such
  181. chunks at all. And in well-behaved long-lived programs,
  182. controlling release of large blocks via trimming versus mapping
  183. is usually faster.
  184. However, in most programs, these parameters serve mainly as
  185. protection against the system-level effects of carrying around
  186. massive amounts of unneeded memory. Since frequent calls to
  187. sbrk, mmap, and munmap otherwise degrade performance, the default
  188. parameters are set to relatively high values that serve only as
  189. safeguards.
  190. The trim value must be greater than page size to have any useful
  191. effect. To disable trimming completely, you can set to
  192. (unsigned long)(-1)
  193. Trim settings interact with fastbin (MXFAST) settings: Unless
  194. TRIM_FASTBINS is defined, automatic trimming never takes place upon
  195. freeing a chunk with size less than or equal to MXFAST. Trimming is
  196. instead delayed until subsequent freeing of larger chunks. However,
  197. you can still force an attempted trim by calling malloc_trim.
  198. Also, trimming is not generally possible in cases where
  199. the main arena is obtained via mmap.
  200. Note that the trick some people use of mallocing a huge space and
  201. then freeing it at program startup, in an attempt to reserve system
  202. memory, doesn't have the intended effect under automatic trimming,
  203. since that memory will immediately be returned to the system.
  204. */
  205. #define M_TRIM_THRESHOLD -1
  206. #ifndef DEFAULT_TRIM_THRESHOLD
  207. #define DEFAULT_TRIM_THRESHOLD (256 * 1024)
  208. #endif
  209. /*
  210. M_TOP_PAD is the amount of extra `padding' space to allocate or
  211. retain whenever sbrk is called. It is used in two ways internally:
  212. * When sbrk is called to extend the top of the arena to satisfy
  213. a new malloc request, this much padding is added to the sbrk
  214. request.
  215. * When malloc_trim is called automatically from free(),
  216. it is used as the `pad' argument.
  217. In both cases, the actual amount of padding is rounded
  218. so that the end of the arena is always a system page boundary.
  219. The main reason for using padding is to avoid calling sbrk so
  220. often. Having even a small pad greatly reduces the likelihood
  221. that nearly every malloc request during program start-up (or
  222. after trimming) will invoke sbrk, which needlessly wastes
  223. time.
  224. Automatic rounding-up to page-size units is normally sufficient
  225. to avoid measurable overhead, so the default is 0. However, in
  226. systems where sbrk is relatively slow, it can pay to increase
  227. this value, at the expense of carrying around more memory than
  228. the program needs.
  229. */
  230. #define M_TOP_PAD -2
  231. #ifndef DEFAULT_TOP_PAD
  232. #define DEFAULT_TOP_PAD (0)
  233. #endif
  234. /*
  235. M_MMAP_THRESHOLD is the request size threshold for using mmap()
  236. to service a request. Requests of at least this size that cannot
  237. be allocated using already-existing space will be serviced via mmap.
  238. (If enough normal freed space already exists it is used instead.)
  239. Using mmap segregates relatively large chunks of memory so that
  240. they can be individually obtained and released from the host
  241. system. A request serviced through mmap is never reused by any
  242. other request (at least not directly; the system may just so
  243. happen to remap successive requests to the same locations).
  244. Segregating space in this way has the benefits that:
  245. 1. Mmapped space can ALWAYS be individually released back
  246. to the system, which helps keep the system level memory
  247. demands of a long-lived program low.
  248. 2. Mapped memory can never become `locked' between
  249. other chunks, as can happen with normally allocated chunks, which
  250. means that even trimming via malloc_trim would not release them.
  251. 3. On some systems with "holes" in address spaces, mmap can obtain
  252. memory that sbrk cannot.
  253. However, it has the disadvantages that:
  254. 1. The space cannot be reclaimed, consolidated, and then
  255. used to service later requests, as happens with normal chunks.
  256. 2. It can lead to more wastage because of mmap page alignment
  257. requirements
  258. 3. It causes malloc performance to be more dependent on host
  259. system memory management support routines which may vary in
  260. implementation quality and may impose arbitrary
  261. limitations. Generally, servicing a request via normal
  262. malloc steps is faster than going through a system's mmap.
  263. The advantages of mmap nearly always outweigh disadvantages for
  264. "large" chunks, but the value of "large" varies across systems. The
  265. default is an empirically derived value that works well in most
  266. systems.
  267. */
  268. #define M_MMAP_THRESHOLD -3
  269. #ifndef DEFAULT_MMAP_THRESHOLD
  270. #define DEFAULT_MMAP_THRESHOLD (256 * 1024)
  271. #endif
  272. /*
  273. M_MMAP_MAX is the maximum number of requests to simultaneously
  274. service using mmap. This parameter exists because
  275. . Some systems have a limited number of internal tables for
  276. use by mmap, and using more than a few of them may degrade
  277. performance.
  278. The default is set to a value that serves only as a safeguard.
  279. Setting to 0 disables use of mmap for servicing large requests. If
  280. HAVE_MMAP is not set, the default value is 0, and attempts to set it
  281. to non-zero values in mallopt will fail.
  282. */
  283. #define M_MMAP_MAX -4
  284. #ifndef DEFAULT_MMAP_MAX
  285. #define DEFAULT_MMAP_MAX (65536)
  286. #endif
  287. /* ------------------ MMAP support ------------------ */
  288. #include <fcntl.h>
  289. #include <sys/mman.h>
  290. #if !defined(MAP_ANONYMOUS) && defined(MAP_ANON)
  291. #define MAP_ANONYMOUS MAP_ANON
  292. #endif
  293. #ifdef __ARCH_USE_MMU__
  294. # define _MAP_UNINITIALIZED 0
  295. #else
  296. # define _MAP_UNINITIALIZED MAP_UNINITIALIZED
  297. #endif
  298. #define MMAP(addr, size, prot) \
  299. (mmap((addr), (size), (prot), MAP_PRIVATE|MAP_ANONYMOUS|_MAP_UNINITIALIZED, 0, 0))
  300. /* ----------------------- Chunk representations ----------------------- */
  301. /*
  302. This struct declaration is misleading (but accurate and necessary).
  303. It declares a "view" into memory allowing access to necessary
  304. fields at known offsets from a given base. See explanation below.
  305. */
  306. struct malloc_chunk {
  307. size_t prev_size; /* Size of previous chunk (if free). */
  308. size_t size; /* Size in bytes, including overhead. */
  309. struct malloc_chunk* fd; /* double links -- used only if free. */
  310. struct malloc_chunk* bk;
  311. };
  312. typedef struct malloc_chunk* mchunkptr;
  313. /*
  314. malloc_chunk details:
  315. (The following includes lightly edited explanations by Colin Plumb.)
  316. Chunks of memory are maintained using a `boundary tag' method as
  317. described in e.g., Knuth or Standish. (See the paper by Paul
  318. Wilson ftp://ftp.cs.utexas.edu/pub/garbage/allocsrv.ps for a
  319. survey of such techniques.) Sizes of free chunks are stored both
  320. in the front of each chunk and at the end. This makes
  321. consolidating fragmented chunks into bigger chunks very fast. The
  322. size fields also hold bits representing whether chunks are free or
  323. in use.
  324. An allocated chunk looks like this:
  325. chunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  326. | Size of previous chunk, if allocated | |
  327. +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  328. | Size of chunk, in bytes |P|
  329. mem-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  330. | User data starts here... .
  331. . .
  332. . (malloc_usable_space() bytes) .
  333. . |
  334. nextchunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  335. | Size of chunk |
  336. +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  337. Where "chunk" is the front of the chunk for the purpose of most of
  338. the malloc code, but "mem" is the pointer that is returned to the
  339. user. "Nextchunk" is the beginning of the next contiguous chunk.
  340. Chunks always begin on even word boundries, so the mem portion
  341. (which is returned to the user) is also on an even word boundary, and
  342. thus at least double-word aligned.
  343. Free chunks are stored in circular doubly-linked lists, and look like this:
  344. chunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  345. | Size of previous chunk |
  346. +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  347. `head:' | Size of chunk, in bytes |P|
  348. mem-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  349. | Forward pointer to next chunk in list |
  350. +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  351. | Back pointer to previous chunk in list |
  352. +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  353. | Unused space (may be 0 bytes long) .
  354. . .
  355. . |
  356. nextchunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  357. `foot:' | Size of chunk, in bytes |
  358. +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
  359. The P (PREV_INUSE) bit, stored in the unused low-order bit of the
  360. chunk size (which is always a multiple of two words), is an in-use
  361. bit for the *previous* chunk. If that bit is *clear*, then the
  362. word before the current chunk size contains the previous chunk
  363. size, and can be used to find the front of the previous chunk.
  364. The very first chunk allocated always has this bit set,
  365. preventing access to non-existent (or non-owned) memory. If
  366. prev_inuse is set for any given chunk, then you CANNOT determine
  367. the size of the previous chunk, and might even get a memory
  368. addressing fault when trying to do so.
  369. Note that the `foot' of the current chunk is actually represented
  370. as the prev_size of the NEXT chunk. This makes it easier to
  371. deal with alignments etc but can be very confusing when trying
  372. to extend or adapt this code.
  373. The two exceptions to all this are
  374. 1. The special chunk `top' doesn't bother using the
  375. trailing size field since there is no next contiguous chunk
  376. that would have to index off it. After initialization, `top'
  377. is forced to always exist. If it would become less than
  378. MINSIZE bytes long, it is replenished.
  379. 2. Chunks allocated via mmap, which have the second-lowest-order
  380. bit (IS_MMAPPED) set in their size fields. Because they are
  381. allocated one-by-one, each must contain its own trailing size field.
  382. */
  383. /*
  384. ---------- Size and alignment checks and conversions ----------
  385. */
  386. /* conversion from malloc headers to user pointers, and back */
  387. #define chunk2mem(p) ((void*)((char*)(p) + 2*(sizeof(size_t))))
  388. #define mem2chunk(mem) ((mchunkptr)((char*)(mem) - 2*(sizeof(size_t))))
  389. /* The smallest possible chunk */
  390. #define MIN_CHUNK_SIZE (sizeof(struct malloc_chunk))
  391. /* The smallest size we can malloc is an aligned minimal chunk */
  392. #define MINSIZE \
  393. (unsigned long)(((MIN_CHUNK_SIZE+MALLOC_ALIGN_MASK) & ~MALLOC_ALIGN_MASK))
  394. /* Check if m has acceptable alignment */
  395. #define aligned_OK(m) (((unsigned long)((m)) & (MALLOC_ALIGN_MASK)) == 0)
  396. /* Check if a request is so large that it would wrap around zero when
  397. padded and aligned. To simplify some other code, the bound is made
  398. low enough so that adding MINSIZE will also not wrap around sero.
  399. */
  400. #define REQUEST_OUT_OF_RANGE(req) \
  401. ((unsigned long)(req) >= \
  402. (unsigned long)(size_t)(-2 * MINSIZE))
  403. /* pad request bytes into a usable size -- internal version */
  404. #define request2size(req) \
  405. (((req) + (sizeof(size_t)) + MALLOC_ALIGN_MASK < MINSIZE) ? \
  406. MINSIZE : \
  407. ((req) + (sizeof(size_t)) + MALLOC_ALIGN_MASK) & ~MALLOC_ALIGN_MASK)
  408. /* Same, except also perform argument check */
  409. #define checked_request2size(req, sz) \
  410. if (REQUEST_OUT_OF_RANGE(req)) { \
  411. __set_errno(ENOMEM); \
  412. return 0; \
  413. } \
  414. (sz) = request2size(req);
  415. /*
  416. --------------- Physical chunk operations ---------------
  417. */
  418. /* size field is or'ed with PREV_INUSE when previous adjacent chunk in use */
  419. #define PREV_INUSE 0x1
  420. /* extract inuse bit of previous chunk */
  421. #define prev_inuse(p) ((p)->size & PREV_INUSE)
  422. /* size field is or'ed with IS_MMAPPED if the chunk was obtained with mmap() */
  423. #define IS_MMAPPED 0x2
  424. /* check for mmap()'ed chunk */
  425. #define chunk_is_mmapped(p) ((p)->size & IS_MMAPPED)
  426. /* Bits to mask off when extracting size
  427. Note: IS_MMAPPED is intentionally not masked off from size field in
  428. macros for which mmapped chunks should never be seen. This should
  429. cause helpful core dumps to occur if it is tried by accident by
  430. people extending or adapting this malloc.
  431. */
  432. #define SIZE_BITS (PREV_INUSE|IS_MMAPPED)
  433. /* Get size, ignoring use bits */
  434. #define chunksize(p) ((p)->size & ~(SIZE_BITS))
  435. /* Ptr to next physical malloc_chunk. */
  436. #define next_chunk(p) ((mchunkptr)( ((char*)(p)) + ((p)->size & ~PREV_INUSE) ))
  437. /* Ptr to previous physical malloc_chunk */
  438. #define prev_chunk(p) ((mchunkptr)( ((char*)(p)) - ((p)->prev_size) ))
  439. /* Treat space at ptr + offset as a chunk */
  440. #define chunk_at_offset(p, s) ((mchunkptr)(((char*)(p)) + (s)))
  441. /* extract p's inuse bit */
  442. #define inuse(p)\
  443. ((((mchunkptr)(((char*)(p))+((p)->size & ~PREV_INUSE)))->size) & PREV_INUSE)
  444. /* set/clear chunk as being inuse without otherwise disturbing */
  445. #define set_inuse(p)\
  446. ((mchunkptr)(((char*)(p)) + ((p)->size & ~PREV_INUSE)))->size |= PREV_INUSE
  447. #define clear_inuse(p)\
  448. ((mchunkptr)(((char*)(p)) + ((p)->size & ~PREV_INUSE)))->size &= ~(PREV_INUSE)
  449. /* check/set/clear inuse bits in known places */
  450. #define inuse_bit_at_offset(p, s)\
  451. (((mchunkptr)(((char*)(p)) + (s)))->size & PREV_INUSE)
  452. #define set_inuse_bit_at_offset(p, s)\
  453. (((mchunkptr)(((char*)(p)) + (s)))->size |= PREV_INUSE)
  454. #define clear_inuse_bit_at_offset(p, s)\
  455. (((mchunkptr)(((char*)(p)) + (s)))->size &= ~(PREV_INUSE))
  456. /* Set size at head, without disturbing its use bit */
  457. #define set_head_size(p, s) ((p)->size = (((p)->size & PREV_INUSE) | (s)))
  458. /* Set size/use field */
  459. #define set_head(p, s) ((p)->size = (s))
  460. /* Set size at footer (only when chunk is not in use) */
  461. #define set_foot(p, s) (((mchunkptr)((char*)(p) + (s)))->prev_size = (s))
  462. /* -------------------- Internal data structures -------------------- */
  463. /*
  464. Bins
  465. An array of bin headers for free chunks. Each bin is doubly
  466. linked. The bins are approximately proportionally (log) spaced.
  467. There are a lot of these bins (128). This may look excessive, but
  468. works very well in practice. Most bins hold sizes that are
  469. unusual as malloc request sizes, but are more usual for fragments
  470. and consolidated sets of chunks, which is what these bins hold, so
  471. they can be found quickly. All procedures maintain the invariant
  472. that no consolidated chunk physically borders another one, so each
  473. chunk in a list is known to be preceeded and followed by either
  474. inuse chunks or the ends of memory.
  475. Chunks in bins are kept in size order, with ties going to the
  476. approximately least recently used chunk. Ordering isn't needed
  477. for the small bins, which all contain the same-sized chunks, but
  478. facilitates best-fit allocation for larger chunks. These lists
  479. are just sequential. Keeping them in order almost never requires
  480. enough traversal to warrant using fancier ordered data
  481. structures.
  482. Chunks of the same size are linked with the most
  483. recently freed at the front, and allocations are taken from the
  484. back. This results in LRU (FIFO) allocation order, which tends
  485. to give each chunk an equal opportunity to be consolidated with
  486. adjacent freed chunks, resulting in larger free chunks and less
  487. fragmentation.
  488. To simplify use in double-linked lists, each bin header acts
  489. as a malloc_chunk. This avoids special-casing for headers.
  490. But to conserve space and improve locality, we allocate
  491. only the fd/bk pointers of bins, and then use repositioning tricks
  492. to treat these as the fields of a malloc_chunk*.
  493. */
  494. typedef struct malloc_chunk* mbinptr;
  495. /* addressing -- note that bin_at(0) does not exist */
  496. #define bin_at(m, i) ((mbinptr)((char*)&((m)->bins[(i)<<1]) - ((sizeof(size_t))<<1)))
  497. /* analog of ++bin */
  498. #define next_bin(b) ((mbinptr)((char*)(b) + (sizeof(mchunkptr)<<1)))
  499. /* Reminders about list directionality within bins */
  500. #define first(b) ((b)->fd)
  501. #define last(b) ((b)->bk)
  502. /* Take a chunk off a bin list */
  503. #define unlink(P, BK, FD) { \
  504. FD = P->fd; \
  505. BK = P->bk; \
  506. if (FD->bk != P || BK->fd != P) \
  507. abort(); \
  508. FD->bk = BK; \
  509. BK->fd = FD; \
  510. }
  511. /*
  512. Indexing
  513. Bins for sizes < 512 bytes contain chunks of all the same size, spaced
  514. 8 bytes apart. Larger bins are approximately logarithmically spaced:
  515. 64 bins of size 8
  516. 32 bins of size 64
  517. 16 bins of size 512
  518. 8 bins of size 4096
  519. 4 bins of size 32768
  520. 2 bins of size 262144
  521. 1 bin of size what's left
  522. The bins top out around 1MB because we expect to service large
  523. requests via mmap.
  524. */
  525. #define NBINS 96
  526. #define NSMALLBINS 32
  527. #define SMALLBIN_WIDTH 8
  528. #define MIN_LARGE_SIZE 256
  529. #define in_smallbin_range(sz) \
  530. ((unsigned long)(sz) < (unsigned long)MIN_LARGE_SIZE)
  531. #define smallbin_index(sz) (((unsigned)(sz)) >> 3)
  532. #define bin_index(sz) \
  533. ((in_smallbin_range(sz)) ? smallbin_index(sz) : __malloc_largebin_index(sz))
  534. /*
  535. FIRST_SORTED_BIN_SIZE is the chunk size corresponding to the
  536. first bin that is maintained in sorted order. This must
  537. be the smallest size corresponding to a given bin.
  538. Normally, this should be MIN_LARGE_SIZE. But you can weaken
  539. best fit guarantees to sometimes speed up malloc by increasing value.
  540. Doing this means that malloc may choose a chunk that is
  541. non-best-fitting by up to the width of the bin.
  542. Some useful cutoff values:
  543. 512 - all bins sorted
  544. 2560 - leaves bins <= 64 bytes wide unsorted
  545. 12288 - leaves bins <= 512 bytes wide unsorted
  546. 65536 - leaves bins <= 4096 bytes wide unsorted
  547. 262144 - leaves bins <= 32768 bytes wide unsorted
  548. -1 - no bins sorted (not recommended!)
  549. */
  550. #define FIRST_SORTED_BIN_SIZE MIN_LARGE_SIZE
  551. /* #define FIRST_SORTED_BIN_SIZE 65536 */
  552. /*
  553. Unsorted chunks
  554. All remainders from chunk splits, as well as all returned chunks,
  555. are first placed in the "unsorted" bin. They are then placed
  556. in regular bins after malloc gives them ONE chance to be used before
  557. binning. So, basically, the unsorted_chunks list acts as a queue,
  558. with chunks being placed on it in free (and __malloc_consolidate),
  559. and taken off (to be either used or placed in bins) in malloc.
  560. */
  561. /* The otherwise unindexable 1-bin is used to hold unsorted chunks. */
  562. #define unsorted_chunks(M) (bin_at(M, 1))
  563. /*
  564. Top
  565. The top-most available chunk (i.e., the one bordering the end of
  566. available memory) is treated specially. It is never included in
  567. any bin, is used only if no other chunk is available, and is
  568. released back to the system if it is very large (see
  569. M_TRIM_THRESHOLD). Because top initially
  570. points to its own bin with initial zero size, thus forcing
  571. extension on the first malloc request, we avoid having any special
  572. code in malloc to check whether it even exists yet. But we still
  573. need to do so when getting memory from system, so we make
  574. initial_top treat the bin as a legal but unusable chunk during the
  575. interval between initialization and the first call to
  576. __malloc_alloc. (This is somewhat delicate, since it relies on
  577. the 2 preceding words to be zero during this interval as well.)
  578. */
  579. /* Conveniently, the unsorted bin can be used as dummy top on first call */
  580. #define initial_top(M) (unsorted_chunks(M))
  581. /*
  582. Binmap
  583. To help compensate for the large number of bins, a one-level index
  584. structure is used for bin-by-bin searching. `binmap' is a
  585. bitvector recording whether bins are definitely empty so they can
  586. be skipped over during during traversals. The bits are NOT always
  587. cleared as soon as bins are empty, but instead only
  588. when they are noticed to be empty during traversal in malloc.
  589. */
  590. /* Conservatively use 32 bits per map word, even if on 64bit system */
  591. #define BINMAPSHIFT 5
  592. #define BITSPERMAP (1U << BINMAPSHIFT)
  593. #define BINMAPSIZE (NBINS / BITSPERMAP)
  594. #define idx2block(i) ((i) >> BINMAPSHIFT)
  595. #define idx2bit(i) ((1U << ((i) & ((1U << BINMAPSHIFT)-1))))
  596. #define mark_bin(m,i) ((m)->binmap[idx2block(i)] |= idx2bit(i))
  597. #define unmark_bin(m,i) ((m)->binmap[idx2block(i)] &= ~(idx2bit(i)))
  598. #define get_binmap(m,i) ((m)->binmap[idx2block(i)] & idx2bit(i))
  599. /*
  600. Fastbins
  601. An array of lists holding recently freed small chunks. Fastbins
  602. are not doubly linked. It is faster to single-link them, and
  603. since chunks are never removed from the middles of these lists,
  604. double linking is not necessary. Also, unlike regular bins, they
  605. are not even processed in FIFO order (they use faster LIFO) since
  606. ordering doesn't much matter in the transient contexts in which
  607. fastbins are normally used.
  608. Chunks in fastbins keep their inuse bit set, so they cannot
  609. be consolidated with other free chunks. __malloc_consolidate
  610. releases all chunks in fastbins and consolidates them with
  611. other free chunks.
  612. */
  613. typedef struct malloc_chunk* mfastbinptr;
  614. /* offset 2 to use otherwise unindexable first 2 bins */
  615. #define fastbin_index(sz) ((((unsigned int)(sz)) >> 3) - 2)
  616. /* The maximum fastbin request size we support */
  617. #define MAX_FAST_SIZE 80
  618. #define NFASTBINS (fastbin_index(request2size(MAX_FAST_SIZE))+1)
  619. /*
  620. FASTBIN_CONSOLIDATION_THRESHOLD is the size of a chunk in free()
  621. that triggers automatic consolidation of possibly-surrounding
  622. fastbin chunks. This is a heuristic, so the exact value should not
  623. matter too much. It is defined at half the default trim threshold as a
  624. compromise heuristic to only attempt consolidation if it is likely
  625. to lead to trimming. However, it is not dynamically tunable, since
  626. consolidation reduces fragmentation surrounding loarge chunks even
  627. if trimming is not used.
  628. */
  629. #define FASTBIN_CONSOLIDATION_THRESHOLD \
  630. ((unsigned long)(DEFAULT_TRIM_THRESHOLD) >> 1)
  631. /*
  632. Since the lowest 2 bits in max_fast don't matter in size comparisons,
  633. they are used as flags.
  634. */
  635. /*
  636. ANYCHUNKS_BIT held in max_fast indicates that there may be any
  637. freed chunks at all. It is set true when entering a chunk into any
  638. bin.
  639. */
  640. #define ANYCHUNKS_BIT (1U)
  641. #define have_anychunks(M) (((M)->max_fast & ANYCHUNKS_BIT))
  642. #define set_anychunks(M) ((M)->max_fast |= ANYCHUNKS_BIT)
  643. #define clear_anychunks(M) ((M)->max_fast &= ~ANYCHUNKS_BIT)
  644. /*
  645. FASTCHUNKS_BIT held in max_fast indicates that there are probably
  646. some fastbin chunks. It is set true on entering a chunk into any
  647. fastbin, and cleared only in __malloc_consolidate.
  648. */
  649. #define FASTCHUNKS_BIT (2U)
  650. #define have_fastchunks(M) (((M)->max_fast & FASTCHUNKS_BIT))
  651. #define set_fastchunks(M) ((M)->max_fast |= (FASTCHUNKS_BIT|ANYCHUNKS_BIT))
  652. #define clear_fastchunks(M) ((M)->max_fast &= ~(FASTCHUNKS_BIT))
  653. /* Set value of max_fast. Use impossibly small value if 0. */
  654. #define set_max_fast(M, s) \
  655. (M)->max_fast = (((s) == 0)? SMALLBIN_WIDTH: request2size(s)) | \
  656. ((M)->max_fast & (FASTCHUNKS_BIT|ANYCHUNKS_BIT))
  657. #define get_max_fast(M) \
  658. ((M)->max_fast & ~(FASTCHUNKS_BIT | ANYCHUNKS_BIT))
  659. /*
  660. Safe-Linking:
  661. Use randomness from ASLR (mmap_base) to protect single-linked lists
  662. of fastbins. Together with allocation alignment checks, this mechanism
  663. reduces the risk of pointer hijacking, as was done with Safe-Unlinking
  664. in the double-linked lists of smallbins.
  665. */
  666. #define PROTECT_PTR(pos, ptr) ((mchunkptr)((((size_t)pos) >> PAGE_SHIFT) ^ ((size_t)ptr)))
  667. #define REVEAL_PTR(pos, ptr) PROTECT_PTR(pos, ptr)
  668. #define PTR_FOR_ALIGNMENT_CHECK(P) \
  669. (MALLOC_ALIGNMENT == 2*(sizeof(size_t)) ? (P) : chunk2mem(P))
  670. #define CHECK_PTR(P) \
  671. if (!aligned_OK(PTR_FOR_ALIGNMENT_CHECK(P))) \
  672. abort();
  673. /*
  674. morecore_properties is a status word holding dynamically discovered
  675. or controlled properties of the morecore function
  676. */
  677. #define MORECORE_CONTIGUOUS_BIT (1U)
  678. #define contiguous(M) \
  679. (((M)->morecore_properties & MORECORE_CONTIGUOUS_BIT))
  680. #define noncontiguous(M) \
  681. (((M)->morecore_properties & MORECORE_CONTIGUOUS_BIT) == 0)
  682. #define set_contiguous(M) \
  683. ((M)->morecore_properties |= MORECORE_CONTIGUOUS_BIT)
  684. #define set_noncontiguous(M) \
  685. ((M)->morecore_properties &= ~MORECORE_CONTIGUOUS_BIT)
  686. /*
  687. ----------- Internal state representation and initialization -----------
  688. */
  689. struct malloc_state {
  690. /* The maximum chunk size to be eligible for fastbin */
  691. size_t max_fast; /* low 2 bits used as flags */
  692. /* Fastbins */
  693. mfastbinptr fastbins[NFASTBINS];
  694. /* Base of the topmost chunk -- not otherwise kept in a bin */
  695. mchunkptr top;
  696. /* The remainder from the most recent split of a small request */
  697. mchunkptr last_remainder;
  698. /* Normal bins packed as described above */
  699. mchunkptr bins[NBINS * 2];
  700. /* Bitmap of bins. Trailing zero map handles cases of largest binned size */
  701. unsigned int binmap[BINMAPSIZE+1];
  702. /* Tunable parameters */
  703. unsigned long trim_threshold;
  704. size_t top_pad;
  705. size_t mmap_threshold;
  706. /* Memory map support */
  707. int n_mmaps;
  708. int n_mmaps_max;
  709. int max_n_mmaps;
  710. /* Cache malloc_getpagesize */
  711. unsigned int pagesize;
  712. /* Track properties of MORECORE */
  713. unsigned int morecore_properties;
  714. /* Statistics */
  715. size_t mmapped_mem;
  716. size_t sbrked_mem;
  717. size_t max_sbrked_mem;
  718. size_t max_mmapped_mem;
  719. size_t max_total_mem;
  720. };
  721. typedef struct malloc_state *mstate;
  722. /*
  723. There is exactly one instance of this struct in this malloc.
  724. If you are adapting this malloc in a way that does NOT use a static
  725. malloc_state, you MUST explicitly zero-fill it before using. This
  726. malloc relies on the property that malloc_state is initialized to
  727. all zeroes (as is true of C statics).
  728. */
  729. extern struct malloc_state __malloc_state attribute_hidden; /* never directly referenced */
  730. /*
  731. All uses of av_ are via get_malloc_state().
  732. At most one "call" to get_malloc_state is made per invocation of
  733. the public versions of malloc and free, but other routines
  734. that in turn invoke malloc and/or free may call more then once.
  735. Also, it is called in check* routines if __UCLIBC_MALLOC_DEBUGGING__ is set.
  736. */
  737. #define get_malloc_state() (&(__malloc_state))
  738. /* External internal utilities operating on mstates */
  739. void __malloc_consolidate(mstate) attribute_hidden;
  740. /* Debugging support */
  741. #ifndef __UCLIBC_MALLOC_DEBUGGING__
  742. #define check_chunk(P)
  743. #define check_free_chunk(P)
  744. #define check_inuse_chunk(P)
  745. #define check_remalloced_chunk(P,N)
  746. #define check_malloced_chunk(P,N)
  747. #define check_malloc_state()
  748. #define assert(x) ((void)0)
  749. #else
  750. #define check_chunk(P) __do_check_chunk(P)
  751. #define check_free_chunk(P) __do_check_free_chunk(P)
  752. #define check_inuse_chunk(P) __do_check_inuse_chunk(P)
  753. #define check_remalloced_chunk(P,N) __do_check_remalloced_chunk(P,N)
  754. #define check_malloced_chunk(P,N) __do_check_malloced_chunk(P,N)
  755. #define check_malloc_state() __do_check_malloc_state()
  756. extern void __do_check_chunk(mchunkptr p) attribute_hidden;
  757. extern void __do_check_free_chunk(mchunkptr p) attribute_hidden;
  758. extern void __do_check_inuse_chunk(mchunkptr p) attribute_hidden;
  759. extern void __do_check_remalloced_chunk(mchunkptr p, size_t s) attribute_hidden;
  760. extern void __do_check_malloced_chunk(mchunkptr p, size_t s) attribute_hidden;
  761. extern void __do_check_malloc_state(void) attribute_hidden;
  762. #include <assert.h>
  763. #endif