OSDN Git Service

8beb8b12a00b3eb76d55b237b1419ee61cca657e
[pf3gnuchains/gcc-fork.git] / libdecnumber / decNumberLocal.h
1 /* Local definitions for the decNumber C Library.
2    Copyright (C) 2007 Free Software Foundation, Inc.
3    Contributed by IBM Corporation.  Author Mike Cowlishaw.
4
5    This file is part of GCC.
6
7    GCC is free software; you can redistribute it and/or modify it under
8    the terms of the GNU General Public License as published by the Free
9    Software Foundation; either version 2, or (at your option) any later
10    version.
11
12    In addition to the permissions in the GNU General Public License,
13    the Free Software Foundation gives you unlimited permission to link
14    the compiled version of this file into combinations with other
15    programs, and to distribute those combinations without any
16    restriction coming from the use of this file.  (The General Public
17    License restrictions do apply in other respects; for example, they
18    cover modification of the file, and distribution when not linked
19    into a combine executable.)
20
21    GCC is distributed in the hope that it will be useful, but WITHOUT ANY
22    WARRANTY; without even the implied warranty of MERCHANTABILITY or
23    FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
24    for more details.
25
26    You should have received a copy of the GNU General Public License
27    along with GCC; see the file COPYING.  If not, write to the Free
28    Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA
29    02110-1301, USA.  */
30
31 /* ------------------------------------------------------------------ */
32 /* decNumber package local type, tuning, and macro definitions        */
33 /* ------------------------------------------------------------------ */
34 /* This header file is included by all modules in the decNumber       */
35 /* library, and contains local type definitions, tuning parameters,   */
36 /* etc.  It should not need to be used by application programs.       */
37 /* decNumber.h or one of decDouble (etc.) must be included first.     */
38 /* ------------------------------------------------------------------ */
39
40 #if !defined(DECNUMBERLOC)
41   #define DECNUMBERLOC
42   #define DECVERSION    "decNumber 3.61" /* Package Version [16 max.] */
43   #define DECNLAUTHOR   "Mike Cowlishaw"              /* Who to blame */
44
45   #include <stdlib.h>         /* for abs                              */
46   #include <string.h>         /* for memset, strcpy                   */
47   #include "dconfig.h"        /* for WORDS_BIGENDIAN                  */
48
49   /* Conditional code flag -- set this to match hardware platform     */
50   /* 1=little-endian, 0=big-endian                                   */
51   #if WORDS_BIGENDIAN
52   #define DECLITEND 0
53   #else
54   #define DECLITEND 1
55   #endif
56
57   #if !defined(DECLITEND)
58   #define DECLITEND 1         /* 1=little-endian, 0=big-endian        */
59   #endif
60
61   /* Conditional code flag -- set this to 1 for best performance      */
62   #if !defined(DECUSE64)
63   #define DECUSE64  1         /* 1=use int64s, 0=int32 & smaller only */
64   #endif
65
66   /* Conditional check flags -- set these to 0 for best performance   */
67   #if !defined(DECCHECK)
68   #define DECCHECK  0         /* 1 to enable robust checking          */
69   #endif
70   #if !defined(DECALLOC)
71   #define DECALLOC  0         /* 1 to enable memory accounting        */
72   #endif
73   #if !defined(DECTRACE)
74   #define DECTRACE  0         /* 1 to trace certain internals, etc.   */
75   #endif
76
77   /* Tuning parameter for decNumber (arbitrary precision) module      */
78   #if !defined(DECBUFFER)
79   #define DECBUFFER 36        /* Size basis for local buffers.  This  */
80                               /* should be a common maximum precision */
81                               /* rounded up to a multiple of 4; must  */
82                               /* be zero or positive.                 */
83   #endif
84
85   /* ---------------------------------------------------------------- */
86   /* Definitions for all modules (general-purpose)                    */
87   /* ---------------------------------------------------------------- */
88
89   /* Local names for common types -- for safety, decNumber modules do */
90   /* not use int or long directly.                                    */
91   #define Flag   uint8_t
92   #define Byte   int8_t
93   #define uByte  uint8_t
94   #define Short  int16_t
95   #define uShort uint16_t
96   #define Int    int32_t
97   #define uInt   uint32_t
98   #define Unit   decNumberUnit
99   #if DECUSE64
100   #define Long   int64_t
101   #define uLong  uint64_t
102   #endif
103
104   /* Development-use definitions                                      */
105   typedef long int LI;        /* for printf arguments only            */
106   #define DECNOINT  0         /* 1 to check no internal use of 'int'  */
107                               /*   or stdint types                    */
108   #if DECNOINT
109     /* if these interfere with your C includes, do not set DECNOINT   */
110     #define int     ?         /* enable to ensure that plain C 'int'  */
111     #define long    ??        /* .. or 'long' types are not used      */
112   #endif
113
114   /* Shared lookup tables                                             */
115   extern const uByte  DECSTICKYTAB[10]; /* re-round digits if sticky  */
116   extern const uInt   DECPOWERS[10];    /* powers of ten table        */
117   /* The following are included from decDPD.h                         */
118   #include "decDPDSymbols.h"
119   extern const uShort DPD2BIN[1024];    /* DPD -> 0-999               */
120   extern const uShort BIN2DPD[1000];    /* 0-999 -> DPD               */
121   extern const uInt   DPD2BINK[1024];   /* DPD -> 0-999000            */
122   extern const uInt   DPD2BINM[1024];   /* DPD -> 0-999000000         */
123   extern const uByte  DPD2BCD8[4096];   /* DPD -> ddd + len           */
124   extern const uByte  BIN2BCD8[4000];   /* 0-999 -> ddd + len         */
125   extern const uShort BCD2DPD[2458];    /* 0-0x999 -> DPD (0x999=2457)*/
126
127   /* LONGMUL32HI -- set w=(u*v)>>32, where w, u, and v are uInts      */
128   /* (that is, sets w to be the high-order word of the 64-bit result; */
129   /* the low-order word is simply u*v.)                               */
130   /* This version is derived from Knuth via Hacker's Delight;         */
131   /* it seems to optimize better than some others tried               */
132   #define LONGMUL32HI(w, u, v) {             \
133     uInt u0, u1, v0, v1, w0, w1, w2, t;      \
134     u0=u & 0xffff; u1=u>>16;                 \
135     v0=v & 0xffff; v1=v>>16;                 \
136     w0=u0*v0;                                \
137     t=u1*v0 + (w0>>16);                      \
138     w1=t & 0xffff; w2=t>>16;                 \
139     w1=u0*v1 + w1;                           \
140     (w)=u1*v1 + w2 + (w1>>16);}
141
142   /* ROUNDUP -- round an integer up to a multiple of n                */
143   #define ROUNDUP(i, n) ((((i)+(n)-1)/n)*n)
144   #define ROUNDUP4(i)   (((i)+3)&~3)    /* special for n=4            */
145
146   /* ROUNDDOWN -- round an integer down to a multiple of n            */
147   #define ROUNDDOWN(i, n) (((i)/n)*n)
148   #define ROUNDDOWN4(i)   ((i)&~3)      /* special for n=4            */
149
150   /* References to multi-byte sequences under different sizes; these  */
151   /* require locally declared variables, but do not violate strict    */
152   /* aliasing or alignment (as did the UINTAT simple cast to uInt).   */
153   /* Variables needed are uswork, uiwork, etc. [so do not use at same */
154   /* level in an expression, e.g., UBTOUI(x)==UBTOUI(y) may fail].    */
155
156   /* Return a uInt, etc., from bytes starting at a char* or uByte*    */
157   #define UBTOUS(b)  (memcpy((void *)&uswork, b, 2), uswork)
158   #define UBTOUI(b)  (memcpy((void *)&uiwork, b, 4), uiwork)
159
160   /* Store a uInt, etc., into bytes starting at a char* or uByte*.    */
161   /* Returns i, evaluated, for convenience; has to use uiwork because */
162   /* i may be an expression.                                          */
163   #define UBFROMUS(b, i)  (uswork=(i), memcpy(b, (void *)&uswork, 2), uswork)
164   #define UBFROMUI(b, i)  (uiwork=(i), memcpy(b, (void *)&uiwork, 4), uiwork)
165
166   /* X10 and X100 -- multiply integer i by 10 or 100                  */
167   /* [shifts are usually faster than multiply; could be conditional]  */
168   #define X10(i)  (((i)<<1)+((i)<<3))
169   #define X100(i) (((i)<<2)+((i)<<5)+((i)<<6))
170
171   /* MAXI and MINI -- general max & min (not in ANSI) for integers    */
172   #define MAXI(x,y) ((x)<(y)?(y):(x))
173   #define MINI(x,y) ((x)>(y)?(y):(x))
174
175   /* Useful constants                                                 */
176   #define BILLION      1000000000            /* 10**9                 */
177   /* CHARMASK: 0x30303030 for ASCII/UTF8; 0xF0F0F0F0 for EBCDIC       */
178   #define CHARMASK ((((((((uInt)'0')<<8)+'0')<<8)+'0')<<8)+'0')
179
180
181   /* ---------------------------------------------------------------- */
182   /* Definitions for arbitary-precision modules (only valid after     */
183   /* decNumber.h has been included)                                   */
184   /* ---------------------------------------------------------------- */
185
186   /* Limits and constants                                             */
187   #define DECNUMMAXP 999999999  /* maximum precision code can handle  */
188   #define DECNUMMAXE 999999999  /* maximum adjusted exponent ditto    */
189   #define DECNUMMINE -999999999 /* minimum adjusted exponent ditto    */
190   #if (DECNUMMAXP != DEC_MAX_DIGITS)
191     #error Maximum digits mismatch
192   #endif
193   #if (DECNUMMAXE != DEC_MAX_EMAX)
194     #error Maximum exponent mismatch
195   #endif
196   #if (DECNUMMINE != DEC_MIN_EMIN)
197     #error Minimum exponent mismatch
198   #endif
199
200   /* Set DECDPUNMAX -- the maximum integer that fits in DECDPUN       */
201   /* digits, and D2UTABLE -- the initializer for the D2U table        */
202   #if   DECDPUN==1
203     #define DECDPUNMAX 9
204     #define D2UTABLE {0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,  \
205                       18,19,20,21,22,23,24,25,26,27,28,29,30,31,32, \
206                       33,34,35,36,37,38,39,40,41,42,43,44,45,46,47, \
207                       48,49}
208   #elif DECDPUN==2
209     #define DECDPUNMAX 99
210     #define D2UTABLE {0,1,1,2,2,3,3,4,4,5,5,6,6,7,7,8,8,9,9,10,10,  \
211                       11,11,12,12,13,13,14,14,15,15,16,16,17,17,18, \
212                       18,19,19,20,20,21,21,22,22,23,23,24,24,25}
213   #elif DECDPUN==3
214     #define DECDPUNMAX 999
215     #define D2UTABLE {0,1,1,1,2,2,2,3,3,3,4,4,4,5,5,5,6,6,6,7,7,7,  \
216                       8,8,8,9,9,9,10,10,10,11,11,11,12,12,12,13,13, \
217                       13,14,14,14,15,15,15,16,16,16,17}
218   #elif DECDPUN==4
219     #define DECDPUNMAX 9999
220     #define D2UTABLE {0,1,1,1,1,2,2,2,2,3,3,3,3,4,4,4,4,5,5,5,5,6,  \
221                       6,6,6,7,7,7,7,8,8,8,8,9,9,9,9,10,10,10,10,11, \
222                       11,11,11,12,12,12,12,13}
223   #elif DECDPUN==5
224     #define DECDPUNMAX 99999
225     #define D2UTABLE {0,1,1,1,1,1,2,2,2,2,2,3,3,3,3,3,4,4,4,4,4,5,  \
226                       5,5,5,5,6,6,6,6,6,7,7,7,7,7,8,8,8,8,8,9,9,9,  \
227                       9,9,10,10,10,10}
228   #elif DECDPUN==6
229     #define DECDPUNMAX 999999
230     #define D2UTABLE {0,1,1,1,1,1,1,2,2,2,2,2,2,3,3,3,3,3,3,4,4,4,  \
231                       4,4,4,5,5,5,5,5,5,6,6,6,6,6,6,7,7,7,7,7,7,8,  \
232                       8,8,8,8,8,9}
233   #elif DECDPUN==7
234     #define DECDPUNMAX 9999999
235     #define D2UTABLE {0,1,1,1,1,1,1,1,2,2,2,2,2,2,2,3,3,3,3,3,3,3,  \
236                       4,4,4,4,4,4,4,5,5,5,5,5,5,5,6,6,6,6,6,6,6,7,  \
237                       7,7,7,7,7,7}
238   #elif DECDPUN==8
239     #define DECDPUNMAX 99999999
240     #define D2UTABLE {0,1,1,1,1,1,1,1,1,2,2,2,2,2,2,2,2,3,3,3,3,3,  \
241                       3,3,3,4,4,4,4,4,4,4,4,5,5,5,5,5,5,5,5,6,6,6,  \
242                       6,6,6,6,6,7}
243   #elif DECDPUN==9
244     #define DECDPUNMAX 999999999
245     #define D2UTABLE {0,1,1,1,1,1,1,1,1,1,2,2,2,2,2,2,2,2,2,3,3,3,  \
246                       3,3,3,3,3,3,4,4,4,4,4,4,4,4,4,5,5,5,5,5,5,5,  \
247                       5,5,6,6,6,6}
248   #elif defined(DECDPUN)
249     #error DECDPUN must be in the range 1-9
250   #endif
251
252   /* ----- Shared data (in decNumber.c) ----- */
253   /* Public lookup table used by the D2U macro (see below)            */
254   #define DECMAXD2U 49
255   extern const uByte d2utable[DECMAXD2U+1];
256
257   /* ----- Macros ----- */
258   /* ISZERO -- return true if decNumber dn is a zero                  */
259   /* [performance-critical in some situations]                        */
260   #define ISZERO(dn) decNumberIsZero(dn)     /* now just a local name */
261
262   /* D2U -- return the number of Units needed to hold d digits        */
263   /* (runtime version, with table lookaside for small d)              */
264   #if DECDPUN==8
265     #define D2U(d) ((unsigned)((d)<=DECMAXD2U?d2utable[d]:((d)+7)>>3))
266   #elif DECDPUN==4
267     #define D2U(d) ((unsigned)((d)<=DECMAXD2U?d2utable[d]:((d)+3)>>2))
268   #else
269     #define D2U(d) ((d)<=DECMAXD2U?d2utable[d]:((d)+DECDPUN-1)/DECDPUN)
270   #endif
271   /* SD2U -- static D2U macro (for compile-time calculation)          */
272   #define SD2U(d) (((d)+DECDPUN-1)/DECDPUN)
273
274   /* MSUDIGITS -- returns digits in msu, from digits, calculated      */
275   /* using D2U                                                        */
276   #define MSUDIGITS(d) ((d)-(D2U(d)-1)*DECDPUN)
277
278   /* D2N -- return the number of decNumber structs that would be      */
279   /* needed to contain that number of digits (and the initial         */
280   /* decNumber struct) safely.  Note that one Unit is included in the */
281   /* initial structure.  Used for allocating space that is aligned on */
282   /* a decNumber struct boundary. */
283   #define D2N(d) \
284     ((((SD2U(d)-1)*sizeof(Unit))+sizeof(decNumber)*2-1)/sizeof(decNumber))
285
286   /* TODIGIT -- macro to remove the leading digit from the unsigned   */
287   /* integer u at column cut (counting from the right, LSD=0) and     */
288   /* place it as an ASCII character into the character pointed to by  */
289   /* c.  Note that cut must be <= 9, and the maximum value for u is   */
290   /* 2,000,000,000 (as is needed for negative exponents of            */
291   /* subnormals).  The unsigned integer pow is used as a temporary    */
292   /* variable. */
293   #define TODIGIT(u, cut, c, pow) {       \
294     *(c)='0';                             \
295     pow=DECPOWERS[cut]*2;                 \
296     if ((u)>pow) {                        \
297       pow*=4;                             \
298       if ((u)>=pow) {(u)-=pow; *(c)+=8;}  \
299       pow/=2;                             \
300       if ((u)>=pow) {(u)-=pow; *(c)+=4;}  \
301       pow/=2;                             \
302       }                                   \
303     if ((u)>=pow) {(u)-=pow; *(c)+=2;}    \
304     pow/=2;                               \
305     if ((u)>=pow) {(u)-=pow; *(c)+=1;}    \
306     }
307
308   /* ---------------------------------------------------------------- */
309   /* Definitions for fixed-precision modules (only valid after        */
310   /* decSingle.h, decDouble.h, or decQuad.h has been included)        */
311   /* ---------------------------------------------------------------- */
312
313   /* bcdnum -- a structure describing a format-independent finite     */
314   /* number, whose coefficient is a string of bcd8 uBytes             */
315   typedef struct {
316     uByte   *msd;             /* -> most significant digit            */
317     uByte   *lsd;             /* -> least ditto                       */
318     uInt     sign;            /* 0=positive, DECFLOAT_Sign=negative   */
319     Int      exponent;        /* Unadjusted signed exponent (q), or   */
320                               /* DECFLOAT_NaN etc. for a special      */
321     } bcdnum;
322
323   /* Test if exponent or bcdnum exponent must be a special, etc.      */
324   #define EXPISSPECIAL(exp) ((exp)>=DECFLOAT_MinSp)
325   #define EXPISINF(exp) (exp==DECFLOAT_Inf)
326   #define EXPISNAN(exp) (exp==DECFLOAT_qNaN || exp==DECFLOAT_sNaN)
327   #define NUMISSPECIAL(num) (EXPISSPECIAL((num)->exponent))
328
329   /* Refer to a 32-bit word or byte in a decFloat (df) by big-endian  */
330   /* (array) notation (the 0 word or byte contains the sign bit),     */
331   /* automatically adjusting for endianness; similarly address a word */
332   /* in the next-wider format (decFloatWider, or dfw)                 */
333   #define DECWORDS  (DECBYTES/4)
334   #define DECWWORDS (DECWBYTES/4)
335   #if DECLITEND
336     #define DFBYTE(df, off)   ((df)->bytes[DECBYTES-1-(off)])
337     #define DFWORD(df, off)   ((df)->words[DECWORDS-1-(off)])
338     #define DFWWORD(dfw, off) ((dfw)->words[DECWWORDS-1-(off)])
339   #else
340     #define DFBYTE(df, off)   ((df)->bytes[off])
341     #define DFWORD(df, off)   ((df)->words[off])
342     #define DFWWORD(dfw, off) ((dfw)->words[off])
343   #endif
344
345   /* Tests for sign or specials, directly on DECFLOATs                */
346   #define DFISSIGNED(df)   (DFWORD(df, 0)&0x80000000)
347   #define DFISSPECIAL(df) ((DFWORD(df, 0)&0x78000000)==0x78000000)
348   #define DFISINF(df)     ((DFWORD(df, 0)&0x7c000000)==0x78000000)
349   #define DFISNAN(df)     ((DFWORD(df, 0)&0x7c000000)==0x7c000000)
350   #define DFISQNAN(df)    ((DFWORD(df, 0)&0x7e000000)==0x7c000000)
351   #define DFISSNAN(df)    ((DFWORD(df, 0)&0x7e000000)==0x7e000000)
352
353   /* Shared lookup tables                                             */
354 #include "decCommonSymbols.h"
355   extern const uInt   DECCOMBMSD[64];   /* Combination field -> MSD   */
356   extern const uInt   DECCOMBFROM[48];  /* exp+msd -> Combination     */
357
358   /* Private generic (utility) routine                                */
359   #if DECCHECK || DECTRACE
360     extern void decShowNum(const bcdnum *, const char *);
361   #endif
362
363   /* Format-dependent macros and constants                            */
364   #if defined(DECPMAX)
365
366     /* Useful constants                                               */
367     #define DECPMAX9  (ROUNDUP(DECPMAX, 9)/9)  /* 'Pmax' in 10**9s    */
368     /* Top words for a zero                                           */
369     #define SINGLEZERO   0x22500000
370     #define DOUBLEZERO   0x22380000
371     #define QUADZERO     0x22080000
372     /* [ZEROWORD is defined to be one of these in the DFISZERO macro] */
373
374     /* Format-dependent common tests:                                 */
375     /*   DFISZERO   -- test for (any) zero                            */
376     /*   DFISCCZERO -- test for coefficient continuation being zero   */
377     /*   DFISCC01   -- test for coefficient contains only 0s and 1s   */
378     /*   DFISINT    -- test for finite and exponent q=0               */
379     /*   DFISUINT01 -- test for sign=0, finite, exponent q=0, and     */
380     /*                 MSD=0 or 1                                     */
381     /*   ZEROWORD is also defined here.                               */
382     /* In DFISZERO the first test checks the least-significant word   */
383     /* (most likely to be non-zero); the penultimate tests MSD and    */
384     /* DPDs in the signword, and the final test excludes specials and */
385     /* MSD>7.  DFISINT similarly has to allow for the two forms of    */
386     /* MSD codes.  DFISUINT01 only has to allow for one form of MSD   */
387     /* code.                                                          */
388     #if DECPMAX==7
389       #define ZEROWORD SINGLEZERO
390       /* [test macros not needed except for Zero]                     */
391       #define DFISZERO(df)  ((DFWORD(df, 0)&0x1c0fffff)==0         \
392                           && (DFWORD(df, 0)&0x60000000)!=0x60000000)
393     #elif DECPMAX==16
394       #define ZEROWORD DOUBLEZERO
395       #define DFISZERO(df)  ((DFWORD(df, 1)==0                     \
396                           && (DFWORD(df, 0)&0x1c03ffff)==0         \
397                           && (DFWORD(df, 0)&0x60000000)!=0x60000000))
398       #define DFISINT(df) ((DFWORD(df, 0)&0x63fc0000)==0x22380000  \
399                          ||(DFWORD(df, 0)&0x7bfc0000)==0x6a380000)
400       #define DFISUINT01(df) ((DFWORD(df, 0)&0xfbfc0000)==0x22380000)
401       #define DFISCCZERO(df) (DFWORD(df, 1)==0                     \
402                           && (DFWORD(df, 0)&0x0003ffff)==0)
403       #define DFISCC01(df)  ((DFWORD(df, 0)&~0xfffc9124)==0        \
404                           && (DFWORD(df, 1)&~0x49124491)==0)
405     #elif DECPMAX==34
406       #define ZEROWORD QUADZERO
407       #define DFISZERO(df)  ((DFWORD(df, 3)==0                     \
408                           &&  DFWORD(df, 2)==0                     \
409                           &&  DFWORD(df, 1)==0                     \
410                           && (DFWORD(df, 0)&0x1c003fff)==0         \
411                           && (DFWORD(df, 0)&0x60000000)!=0x60000000))
412       #define DFISINT(df) ((DFWORD(df, 0)&0x63ffc000)==0x22080000  \
413                          ||(DFWORD(df, 0)&0x7bffc000)==0x6a080000)
414       #define DFISUINT01(df) ((DFWORD(df, 0)&0xfbffc000)==0x22080000)
415       #define DFISCCZERO(df) (DFWORD(df, 3)==0                     \
416                           &&  DFWORD(df, 2)==0                     \
417                           &&  DFWORD(df, 1)==0                     \
418                           && (DFWORD(df, 0)&0x00003fff)==0)
419
420       #define DFISCC01(df)   ((DFWORD(df, 0)&~0xffffc912)==0       \
421                           &&  (DFWORD(df, 1)&~0x44912449)==0       \
422                           &&  (DFWORD(df, 2)&~0x12449124)==0       \
423                           &&  (DFWORD(df, 3)&~0x49124491)==0)
424     #endif
425
426     /* Macros to test if a certain 10 bits of a uInt or pair of uInts */
427     /* are a canonical declet [higher or lower bits are ignored].     */
428     /* declet is at offset 0 (from the right) in a uInt:              */
429     #define CANONDPD(dpd) (((dpd)&0x300)==0 || ((dpd)&0x6e)!=0x6e)
430     /* declet is at offset k (a multiple of 2) in a uInt:             */
431     #define CANONDPDOFF(dpd, k) (((dpd)&(0x300<<(k)))==0            \
432       || ((dpd)&(((uInt)0x6e)<<(k)))!=(((uInt)0x6e)<<(k)))
433     /* declet is at offset k (a multiple of 2) in a pair of uInts:    */
434     /* [the top 2 bits will always be in the more-significant uInt]   */
435     #define CANONDPDTWO(hi, lo, k) (((hi)&(0x300>>(32-(k))))==0     \
436       || ((hi)&(0x6e>>(32-(k))))!=(0x6e>>(32-(k)))                  \
437       || ((lo)&(((uInt)0x6e)<<(k)))!=(((uInt)0x6e)<<(k)))
438
439     /* Macro to test whether a full-length (length DECPMAX) BCD8      */
440     /* coefficient, starting at uByte u, is all zeros                 */
441     /* Test just the LSWord first, then the remainder as a sequence   */
442     /* of tests in order to avoid same-level use of UBTOUI            */
443     #if DECPMAX==7
444       #define ISCOEFFZERO(u) (                                      \
445            UBTOUI((u)+DECPMAX-4)==0                                 \
446         && UBTOUS((u)+DECPMAX-6)==0                                 \
447         && *(u)==0)
448     #elif DECPMAX==16
449       #define ISCOEFFZERO(u) (                                      \
450            UBTOUI((u)+DECPMAX-4)==0                                 \
451         && UBTOUI((u)+DECPMAX-8)==0                                 \
452         && UBTOUI((u)+DECPMAX-12)==0                                \
453         && UBTOUI(u)==0)
454     #elif DECPMAX==34
455       #define ISCOEFFZERO(u) (                                      \
456            UBTOUI((u)+DECPMAX-4)==0                                 \
457         && UBTOUI((u)+DECPMAX-8)==0                                 \
458         && UBTOUI((u)+DECPMAX-12)==0                                \
459         && UBTOUI((u)+DECPMAX-16)==0                                \
460         && UBTOUI((u)+DECPMAX-20)==0                                \
461         && UBTOUI((u)+DECPMAX-24)==0                                \
462         && UBTOUI((u)+DECPMAX-28)==0                                \
463         && UBTOUI((u)+DECPMAX-32)==0                                \
464         && UBTOUS(u)==0)
465     #endif
466
467     /* Macros and masks for the exponent continuation field and MSD   */
468     /* Get the exponent continuation from a decFloat *df as an Int    */
469     #define GETECON(df) ((Int)((DFWORD((df), 0)&0x03ffffff)>>(32-6-DECECONL)))
470     /* Ditto, from the next-wider format                              */
471     #define GETWECON(df) ((Int)((DFWWORD((df), 0)&0x03ffffff)>>(32-6-DECWECONL)))
472     /* Get the biased exponent similarly                              */
473     #define GETEXP(df)  ((Int)(DECCOMBEXP[DFWORD((df), 0)>>26]+GETECON(df)))
474     /* Get the unbiased exponent similarly                            */
475     #define GETEXPUN(df) ((Int)GETEXP(df)-DECBIAS)
476     /* Get the MSD similarly (as uInt)                                */
477     #define GETMSD(df)   (DECCOMBMSD[DFWORD((df), 0)>>26])
478
479     /* Compile-time computes of the exponent continuation field masks */
480     /* full exponent continuation field:                              */
481     #define ECONMASK ((0x03ffffff>>(32-6-DECECONL))<<(32-6-DECECONL))
482     /* same, not including its first digit (the qNaN/sNaN selector):  */
483     #define ECONNANMASK ((0x01ffffff>>(32-6-DECECONL))<<(32-6-DECECONL))
484
485     /* Macros to decode the coefficient in a finite decFloat *df into */
486     /* a BCD string (uByte *bcdin) of length DECPMAX uBytes.          */
487
488     /* In-line sequence to convert least significant 10 bits of uInt  */
489     /* dpd to three BCD8 digits starting at uByte u.  Note that an    */
490     /* extra byte is written to the right of the three digits because */
491     /* four bytes are moved at a time for speed; the alternative      */
492     /* macro moves exactly three bytes (usually slower).              */
493     #define dpd2bcd8(u, dpd)  memcpy(u, &DPD2BCD8[((dpd)&0x3ff)*4], 4)
494     #define dpd2bcd83(u, dpd) memcpy(u, &DPD2BCD8[((dpd)&0x3ff)*4], 3)
495
496     /* Decode the declets.  After extracting each one, it is decoded  */
497     /* to BCD8 using a table lookup (also used for variable-length    */
498     /* decode).  Each DPD decode is 3 bytes BCD8 plus a one-byte      */
499     /* length which is not used, here).  Fixed-length 4-byte moves    */
500     /* are fast, however, almost everywhere, and so are used except   */
501     /* for the final three bytes (to avoid overrun).  The code below  */
502     /* is 36 instructions for Doubles and about 70 for Quads, even    */
503     /* on IA32.                                                       */
504
505     /* Two macros are defined for each format:                        */
506     /*   GETCOEFF extracts the coefficient of the current format      */
507     /*   GETWCOEFF extracts the coefficient of the next-wider format. */
508     /* The latter is a copy of the next-wider GETCOEFF using DFWWORD. */
509
510     #if DECPMAX==7
511     #define GETCOEFF(df, bcd) {                          \
512       uInt sourhi=DFWORD(df, 0);                         \
513       *(bcd)=(uByte)DECCOMBMSD[sourhi>>26];              \
514       dpd2bcd8(bcd+1, sourhi>>10);                       \
515       dpd2bcd83(bcd+4, sourhi);}
516     #define GETWCOEFF(df, bcd) {                         \
517       uInt sourhi=DFWWORD(df, 0);                        \
518       uInt sourlo=DFWWORD(df, 1);                        \
519       *(bcd)=(uByte)DECCOMBMSD[sourhi>>26];              \
520       dpd2bcd8(bcd+1, sourhi>>8);                        \
521       dpd2bcd8(bcd+4, (sourhi<<2) | (sourlo>>30));       \
522       dpd2bcd8(bcd+7, sourlo>>20);                       \
523       dpd2bcd8(bcd+10, sourlo>>10);                      \
524       dpd2bcd83(bcd+13, sourlo);}
525
526     #elif DECPMAX==16
527     #define GETCOEFF(df, bcd) {                          \
528       uInt sourhi=DFWORD(df, 0);                         \
529       uInt sourlo=DFWORD(df, 1);                         \
530       *(bcd)=(uByte)DECCOMBMSD[sourhi>>26];              \
531       dpd2bcd8(bcd+1, sourhi>>8);                        \
532       dpd2bcd8(bcd+4, (sourhi<<2) | (sourlo>>30));       \
533       dpd2bcd8(bcd+7, sourlo>>20);                       \
534       dpd2bcd8(bcd+10, sourlo>>10);                      \
535       dpd2bcd83(bcd+13, sourlo);}
536     #define GETWCOEFF(df, bcd) {                         \
537       uInt sourhi=DFWWORD(df, 0);                        \
538       uInt sourmh=DFWWORD(df, 1);                        \
539       uInt sourml=DFWWORD(df, 2);                        \
540       uInt sourlo=DFWWORD(df, 3);                        \
541       *(bcd)=(uByte)DECCOMBMSD[sourhi>>26];              \
542       dpd2bcd8(bcd+1, sourhi>>4);                        \
543       dpd2bcd8(bcd+4, ((sourhi)<<6) | (sourmh>>26));     \
544       dpd2bcd8(bcd+7, sourmh>>16);                       \
545       dpd2bcd8(bcd+10, sourmh>>6);                       \
546       dpd2bcd8(bcd+13, ((sourmh)<<4) | (sourml>>28));    \
547       dpd2bcd8(bcd+16, sourml>>18);                      \
548       dpd2bcd8(bcd+19, sourml>>8);                       \
549       dpd2bcd8(bcd+22, ((sourml)<<2) | (sourlo>>30));    \
550       dpd2bcd8(bcd+25, sourlo>>20);                      \
551       dpd2bcd8(bcd+28, sourlo>>10);                      \
552       dpd2bcd83(bcd+31, sourlo);}
553
554     #elif DECPMAX==34
555     #define GETCOEFF(df, bcd) {                          \
556       uInt sourhi=DFWORD(df, 0);                         \
557       uInt sourmh=DFWORD(df, 1);                         \
558       uInt sourml=DFWORD(df, 2);                         \
559       uInt sourlo=DFWORD(df, 3);                         \
560       *(bcd)=(uByte)DECCOMBMSD[sourhi>>26];              \
561       dpd2bcd8(bcd+1, sourhi>>4);                        \
562       dpd2bcd8(bcd+4, ((sourhi)<<6) | (sourmh>>26));     \
563       dpd2bcd8(bcd+7, sourmh>>16);                       \
564       dpd2bcd8(bcd+10, sourmh>>6);                       \
565       dpd2bcd8(bcd+13, ((sourmh)<<4) | (sourml>>28));    \
566       dpd2bcd8(bcd+16, sourml>>18);                      \
567       dpd2bcd8(bcd+19, sourml>>8);                       \
568       dpd2bcd8(bcd+22, ((sourml)<<2) | (sourlo>>30));    \
569       dpd2bcd8(bcd+25, sourlo>>20);                      \
570       dpd2bcd8(bcd+28, sourlo>>10);                      \
571       dpd2bcd83(bcd+31, sourlo);}
572
573       #define GETWCOEFF(df, bcd) {??} /* [should never be used]       */
574     #endif
575
576     /* Macros to decode the coefficient in a finite decFloat *df into */
577     /* a base-billion uInt array, with the least-significant          */
578     /* 0-999999999 'digit' at offset 0.                               */
579
580     /* Decode the declets.  After extracting each one, it is decoded  */
581     /* to binary using a table lookup.  Three tables are used; one    */
582     /* the usual DPD to binary, the other two pre-multiplied by 1000  */
583     /* and 1000000 to avoid multiplication during decode.  These      */
584     /* tables can also be used for multiplying up the MSD as the DPD  */
585     /* code for 0 through 9 is the identity.                          */
586     #define DPD2BIN0 DPD2BIN         /* for prettier code             */
587
588     #if DECPMAX==7
589     #define GETCOEFFBILL(df, buf) {                           \
590       uInt sourhi=DFWORD(df, 0);                              \
591       (buf)[0]=DPD2BIN0[sourhi&0x3ff]                         \
592               +DPD2BINK[(sourhi>>10)&0x3ff]                   \
593               +DPD2BINM[DECCOMBMSD[sourhi>>26]];}
594
595     #elif DECPMAX==16
596     #define GETCOEFFBILL(df, buf) {                           \
597       uInt sourhi, sourlo;                                    \
598       sourlo=DFWORD(df, 1);                                   \
599       (buf)[0]=DPD2BIN0[sourlo&0x3ff]                         \
600               +DPD2BINK[(sourlo>>10)&0x3ff]                   \
601               +DPD2BINM[(sourlo>>20)&0x3ff];                  \
602       sourhi=DFWORD(df, 0);                                   \
603       (buf)[1]=DPD2BIN0[((sourhi<<2) | (sourlo>>30))&0x3ff]   \
604               +DPD2BINK[(sourhi>>8)&0x3ff]                    \
605               +DPD2BINM[DECCOMBMSD[sourhi>>26]];}
606
607     #elif DECPMAX==34
608     #define GETCOEFFBILL(df, buf) {                           \
609       uInt sourhi, sourmh, sourml, sourlo;                    \
610       sourlo=DFWORD(df, 3);                                   \
611       (buf)[0]=DPD2BIN0[sourlo&0x3ff]                         \
612               +DPD2BINK[(sourlo>>10)&0x3ff]                   \
613               +DPD2BINM[(sourlo>>20)&0x3ff];                  \
614       sourml=DFWORD(df, 2);                                   \
615       (buf)[1]=DPD2BIN0[((sourml<<2) | (sourlo>>30))&0x3ff]   \
616               +DPD2BINK[(sourml>>8)&0x3ff]                    \
617               +DPD2BINM[(sourml>>18)&0x3ff];                  \
618       sourmh=DFWORD(df, 1);                                   \
619       (buf)[2]=DPD2BIN0[((sourmh<<4) | (sourml>>28))&0x3ff]   \
620               +DPD2BINK[(sourmh>>6)&0x3ff]                    \
621               +DPD2BINM[(sourmh>>16)&0x3ff];                  \
622       sourhi=DFWORD(df, 0);                                   \
623       (buf)[3]=DPD2BIN0[((sourhi<<6) | (sourmh>>26))&0x3ff]   \
624               +DPD2BINK[(sourhi>>4)&0x3ff]                    \
625               +DPD2BINM[DECCOMBMSD[sourhi>>26]];}
626
627     #endif
628
629     /* Macros to decode the coefficient in a finite decFloat *df into */
630     /* a base-thousand uInt array (of size DECLETS+1, to allow for    */
631     /* the MSD), with the least-significant 0-999 'digit' at offset 0.*/
632
633     /* Decode the declets.  After extracting each one, it is decoded  */
634     /* to binary using a table lookup.                                */
635     #if DECPMAX==7
636     #define GETCOEFFTHOU(df, buf) {                           \
637       uInt sourhi=DFWORD(df, 0);                              \
638       (buf)[0]=DPD2BIN[sourhi&0x3ff];                         \
639       (buf)[1]=DPD2BIN[(sourhi>>10)&0x3ff];                   \
640       (buf)[2]=DECCOMBMSD[sourhi>>26];}
641
642     #elif DECPMAX==16
643     #define GETCOEFFTHOU(df, buf) {                           \
644       uInt sourhi, sourlo;                                    \
645       sourlo=DFWORD(df, 1);                                   \
646       (buf)[0]=DPD2BIN[sourlo&0x3ff];                         \
647       (buf)[1]=DPD2BIN[(sourlo>>10)&0x3ff];                   \
648       (buf)[2]=DPD2BIN[(sourlo>>20)&0x3ff];                   \
649       sourhi=DFWORD(df, 0);                                   \
650       (buf)[3]=DPD2BIN[((sourhi<<2) | (sourlo>>30))&0x3ff];   \
651       (buf)[4]=DPD2BIN[(sourhi>>8)&0x3ff];                    \
652       (buf)[5]=DECCOMBMSD[sourhi>>26];}
653
654     #elif DECPMAX==34
655     #define GETCOEFFTHOU(df, buf) {                           \
656       uInt sourhi, sourmh, sourml, sourlo;                    \
657       sourlo=DFWORD(df, 3);                                   \
658       (buf)[0]=DPD2BIN[sourlo&0x3ff];                         \
659       (buf)[1]=DPD2BIN[(sourlo>>10)&0x3ff];                   \
660       (buf)[2]=DPD2BIN[(sourlo>>20)&0x3ff];                   \
661       sourml=DFWORD(df, 2);                                   \
662       (buf)[3]=DPD2BIN[((sourml<<2) | (sourlo>>30))&0x3ff];   \
663       (buf)[4]=DPD2BIN[(sourml>>8)&0x3ff];                    \
664       (buf)[5]=DPD2BIN[(sourml>>18)&0x3ff];                   \
665       sourmh=DFWORD(df, 1);                                   \
666       (buf)[6]=DPD2BIN[((sourmh<<4) | (sourml>>28))&0x3ff];   \
667       (buf)[7]=DPD2BIN[(sourmh>>6)&0x3ff];                    \
668       (buf)[8]=DPD2BIN[(sourmh>>16)&0x3ff];                   \
669       sourhi=DFWORD(df, 0);                                   \
670       (buf)[9]=DPD2BIN[((sourhi<<6) | (sourmh>>26))&0x3ff];   \
671       (buf)[10]=DPD2BIN[(sourhi>>4)&0x3ff];                   \
672       (buf)[11]=DECCOMBMSD[sourhi>>26];}
673     #endif
674
675
676     /* Macros to decode the coefficient in a finite decFloat *df and  */
677     /* add to a base-thousand uInt array (as for GETCOEFFTHOU).       */
678     /* After the addition then most significant 'digit' in the array  */
679     /* might have a value larger then 10 (with a maximum of 19).      */
680     #if DECPMAX==7
681     #define ADDCOEFFTHOU(df, buf) {                           \
682       uInt sourhi=DFWORD(df, 0);                              \
683       (buf)[0]+=DPD2BIN[sourhi&0x3ff];                        \
684       if (buf[0]>999) {buf[0]-=1000; buf[1]++;}               \
685       (buf)[1]+=DPD2BIN[(sourhi>>10)&0x3ff];                  \
686       if (buf[1]>999) {buf[1]-=1000; buf[2]++;}               \
687       (buf)[2]+=DECCOMBMSD[sourhi>>26];}
688
689     #elif DECPMAX==16
690     #define ADDCOEFFTHOU(df, buf) {                           \
691       uInt sourhi, sourlo;                                    \
692       sourlo=DFWORD(df, 1);                                   \
693       (buf)[0]+=DPD2BIN[sourlo&0x3ff];                        \
694       if (buf[0]>999) {buf[0]-=1000; buf[1]++;}               \
695       (buf)[1]+=DPD2BIN[(sourlo>>10)&0x3ff];                  \
696       if (buf[1]>999) {buf[1]-=1000; buf[2]++;}               \
697       (buf)[2]+=DPD2BIN[(sourlo>>20)&0x3ff];                  \
698       if (buf[2]>999) {buf[2]-=1000; buf[3]++;}               \
699       sourhi=DFWORD(df, 0);                                   \
700       (buf)[3]+=DPD2BIN[((sourhi<<2) | (sourlo>>30))&0x3ff];  \
701       if (buf[3]>999) {buf[3]-=1000; buf[4]++;}               \
702       (buf)[4]+=DPD2BIN[(sourhi>>8)&0x3ff];                   \
703       if (buf[4]>999) {buf[4]-=1000; buf[5]++;}               \
704       (buf)[5]+=DECCOMBMSD[sourhi>>26];}
705
706     #elif DECPMAX==34
707     #define ADDCOEFFTHOU(df, buf) {                           \
708       uInt sourhi, sourmh, sourml, sourlo;                    \
709       sourlo=DFWORD(df, 3);                                   \
710       (buf)[0]+=DPD2BIN[sourlo&0x3ff];                        \
711       if (buf[0]>999) {buf[0]-=1000; buf[1]++;}               \
712       (buf)[1]+=DPD2BIN[(sourlo>>10)&0x3ff];                  \
713       if (buf[1]>999) {buf[1]-=1000; buf[2]++;}               \
714       (buf)[2]+=DPD2BIN[(sourlo>>20)&0x3ff];                  \
715       if (buf[2]>999) {buf[2]-=1000; buf[3]++;}               \
716       sourml=DFWORD(df, 2);                                   \
717       (buf)[3]+=DPD2BIN[((sourml<<2) | (sourlo>>30))&0x3ff];  \
718       if (buf[3]>999) {buf[3]-=1000; buf[4]++;}               \
719       (buf)[4]+=DPD2BIN[(sourml>>8)&0x3ff];                   \
720       if (buf[4]>999) {buf[4]-=1000; buf[5]++;}               \
721       (buf)[5]+=DPD2BIN[(sourml>>18)&0x3ff];                  \
722       if (buf[5]>999) {buf[5]-=1000; buf[6]++;}               \
723       sourmh=DFWORD(df, 1);                                   \
724       (buf)[6]+=DPD2BIN[((sourmh<<4) | (sourml>>28))&0x3ff];  \
725       if (buf[6]>999) {buf[6]-=1000; buf[7]++;}               \
726       (buf)[7]+=DPD2BIN[(sourmh>>6)&0x3ff];                   \
727       if (buf[7]>999) {buf[7]-=1000; buf[8]++;}               \
728       (buf)[8]+=DPD2BIN[(sourmh>>16)&0x3ff];                  \
729       if (buf[8]>999) {buf[8]-=1000; buf[9]++;}               \
730       sourhi=DFWORD(df, 0);                                   \
731       (buf)[9]+=DPD2BIN[((sourhi<<6) | (sourmh>>26))&0x3ff];  \
732       if (buf[9]>999) {buf[9]-=1000; buf[10]++;}              \
733       (buf)[10]+=DPD2BIN[(sourhi>>4)&0x3ff];                  \
734       if (buf[10]>999) {buf[10]-=1000; buf[11]++;}            \
735       (buf)[11]+=DECCOMBMSD[sourhi>>26];}
736     #endif
737
738
739     /* Set a decFloat to the maximum positive finite number (Nmax)    */
740     #if DECPMAX==7
741     #define DFSETNMAX(df)            \
742       {DFWORD(df, 0)=0x77f3fcff;}
743     #elif DECPMAX==16
744     #define DFSETNMAX(df)            \
745       {DFWORD(df, 0)=0x77fcff3f;     \
746        DFWORD(df, 1)=0xcff3fcff;}
747     #elif DECPMAX==34
748     #define DFSETNMAX(df)            \
749       {DFWORD(df, 0)=0x77ffcff3;     \
750        DFWORD(df, 1)=0xfcff3fcf;     \
751        DFWORD(df, 2)=0xf3fcff3f;     \
752        DFWORD(df, 3)=0xcff3fcff;}
753     #endif
754
755   /* [end of format-dependent macros and constants]                   */
756   #endif
757
758 #else
759   #error decNumberLocal included more than once
760 #endif