1/* Decimal number arithmetic module for the decNumber C Library.
2   Copyright (C) 2005-2015 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 3, or (at your option) any later
10   version.
11
12   GCC is distributed in the hope that it will be useful, but WITHOUT ANY
13   WARRANTY; without even the implied warranty of MERCHANTABILITY or
14   FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
15   for more details.
16
17Under Section 7 of GPL version 3, you are granted additional
18permissions described in the GCC Runtime Library Exception, version
193.1, as published by the Free Software Foundation.
20
21You should have received a copy of the GNU General Public License and
22a copy of the GCC Runtime Library Exception along with this program;
23see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see
24<http://www.gnu.org/licenses/>.  */
25
26/* ------------------------------------------------------------------ */
27/* Decimal Number arithmetic module				      */
28/* ------------------------------------------------------------------ */
29/* This module comprises the routines for arbitrary-precision General */
30/* Decimal Arithmetic as defined in the specification which may be    */
31/* found on the General Decimal Arithmetic pages.  It implements both */
32/* the full ('extended') arithmetic and the simpler ('subset')	      */
33/* arithmetic.							      */
34/*								      */
35/* Usage notes: 						      */
36/*								      */
37/* 1. This code is ANSI C89 except:				      */
38/*								      */
39/*    a) C99 line comments (double forward slash) are used.  (Most C  */
40/*	 compilers accept these.  If yours does not, a simple script  */
41/*	 can be used to convert them to ANSI C comments.)	      */
42/*								      */
43/*    b) Types from C99 stdint.h are used.  If you do not have this   */
44/*	 header file, see the User's Guide section of the decNumber   */
45/*	 documentation; this lists the necessary definitions.	      */
46/*								      */
47/*    c) If DECDPUN>4 or DECUSE64=1, the C99 64-bit int64_t and       */
48/*	 uint64_t types may be used.  To avoid these, set DECUSE64=0  */
49/*	 and DECDPUN<=4 (see documentation).			      */
50/*								      */
51/*    The code also conforms to C99 restrictions; in particular,      */
52/*    strict aliasing rules are observed.			      */
53/*								      */
54/* 2. The decNumber format which this library uses is optimized for   */
55/*    efficient processing of relatively short numbers; in particular */
56/*    it allows the use of fixed sized structures and minimizes copy  */
57/*    and move operations.  It does, however, support arbitrary       */
58/*    precision (up to 999,999,999 digits) and arbitrary exponent     */
59/*    range (Emax in the range 0 through 999,999,999 and Emin in the  */
60/*    range -999,999,999 through 0).  Mathematical functions (for     */
61/*    example decNumberExp) as identified below are restricted more   */
62/*    tightly: digits, emax, and -emin in the context must be <=      */
63/*    DEC_MAX_MATH (999999), and their operand(s) must be within      */
64/*    these bounds.						      */
65/*								      */
66/* 3. Logical functions are further restricted; their operands must   */
67/*    be finite, positive, have an exponent of zero, and all digits   */
68/*    must be either 0 or 1.  The result will only contain digits     */
69/*    which are 0 or 1 (and will have exponent=0 and a sign of 0).    */
70/*								      */
71/* 4. Operands to operator functions are never modified unless they   */
72/*    are also specified to be the result number (which is always     */
73/*    permitted).  Other than that case, operands must not overlap.   */
74/*								      */
75/* 5. Error handling: the type of the error is ORed into the status   */
76/*    flags in the current context (decContext structure).  The       */
77/*    SIGFPE signal is then raised if the corresponding trap-enabler  */
78/*    flag in the decContext is set (is 1).			      */
79/*								      */
80/*    It is the responsibility of the caller to clear the status      */
81/*    flags as required.					      */
82/*								      */
83/*    The result of any routine which returns a number will always    */
84/*    be a valid number (which may be a special value, such as an     */
85/*    Infinity or NaN). 					      */
86/*								      */
87/* 6. The decNumber format is not an exchangeable concrete	      */
88/*    representation as it comprises fields which may be machine-     */
89/*    dependent (packed or unpacked, or special length, for example). */
90/*    Canonical conversions to and from strings are provided; other   */
91/*    conversions are available in separate modules.		      */
92/*								      */
93/* 7. Normally, input operands are assumed to be valid.  Set DECCHECK */
94/*    to 1 for extended operand checking (including NULL operands).   */
95/*    Results are undefined if a badly-formed structure (or a NULL    */
96/*    pointer to a structure) is provided, though with DECCHECK       */
97/*    enabled the operator routines are protected against exceptions. */
98/*    (Except if the result pointer is NULL, which is unrecoverable.) */
99/*								      */
100/*    However, the routines will never cause exceptions if they are   */
101/*    given well-formed operands, even if the value of the operands   */
102/*    is inappropriate for the operation and DECCHECK is not set.     */
103/*    (Except for SIGFPE, as and where documented.)		      */
104/*								      */
105/* 8. Subset arithmetic is available only if DECSUBSET is set to 1.   */
106/* ------------------------------------------------------------------ */
107/* Implementation notes for maintenance of this module: 	      */
108/*								      */
109/* 1. Storage leak protection:	Routines which use malloc are not     */
110/*    permitted to use return for fastpath or error exits (i.e.,      */
111/*    they follow strict structured programming conventions).	      */
112/*    Instead they have a do{}while(0); construct surrounding the     */
113/*    code which is protected -- break may be used to exit this.      */
114/*    Other routines can safely use the return statement inline.      */
115/*								      */
116/*    Storage leak accounting can be enabled using DECALLOC.	      */
117/*								      */
118/* 2. All loops use the for(;;) construct.  Any do construct does     */
119/*    not loop; it is for allocation protection as just described.    */
120/*								      */
121/* 3. Setting status in the context must always be the very last      */
122/*    action in a routine, as non-0 status may raise a trap and hence */
123/*    the call to set status may not return (if the handler uses long */
124/*    jump).  Therefore all cleanup must be done first.  In general,  */
125/*    to achieve this status is accumulated and is only applied just  */
126/*    before return by calling decContextSetStatus (via decStatus).   */
127/*								      */
128/*    Routines which allocate storage cannot, in general, use the     */
129/*    'top level' routines which could cause a non-returning	      */
130/*    transfer of control.  The decXxxxOp routines are safe (do not   */
131/*    call decStatus even if traps are set in the context) and should */
132/*    be used instead (they are also a little faster).		      */
133/*								      */
134/* 4. Exponent checking is minimized by allowing the exponent to      */
135/*    grow outside its limits during calculations, provided that      */
136/*    the decFinalize function is called later.  Multiplication and   */
137/*    division, and intermediate calculations in exponentiation,      */
138/*    require more careful checks because of the risk of 31-bit       */
139/*    overflow (the most negative valid exponent is -1999999997, for  */
140/*    a 999999999-digit number with adjusted exponent of -999999999). */
141/*								      */
142/* 5. Rounding is deferred until finalization of results, with any    */
143/*    'off to the right' data being represented as a single digit     */
144/*    residue (in the range -1 through 9).  This avoids any double-   */
145/*    rounding when more than one shortening takes place (for	      */
146/*    example, when a result is subnormal).			      */
147/*								      */
148/* 6. The digits count is allowed to rise to a multiple of DECDPUN    */
149/*    during many operations, so whole Units are handled and exact    */
150/*    accounting of digits is not needed.  The correct digits value   */
151/*    is found by decGetDigits, which accounts for leading zeros.     */
152/*    This must be called before any rounding if the number of digits */
153/*    is not known exactly.					      */
154/*								      */
155/* 7. The multiply-by-reciprocal 'trick' is used for partitioning     */
156/*    numbers up to four digits, using appropriate constants.  This   */
157/*    is not useful for longer numbers because overflow of 32 bits    */
158/*    would lead to 4 multiplies, which is almost as expensive as     */
159/*    a divide (unless a floating-point or 64-bit multiply is	      */
160/*    assumed to be available). 				      */
161/*								      */
162/* 8. Unusual abbreviations that may be used in the commentary:       */
163/*	lhs -- left hand side (operand, of an operation)	      */
164/*	lsd -- least significant digit (of coefficient) 	      */
165/*	lsu -- least significant Unit (of coefficient)		      */
166/*	msd -- most significant digit (of coefficient)		      */
167/*	msi -- most significant item (in an array)		      */
168/*	msu -- most significant Unit (of coefficient)		      */
169/*	rhs -- right hand side (operand, of an operation)	      */
170/*	+ve -- positive 					      */
171/*	-ve -- negative 					      */
172/*	**  -- raise to the power				      */
173/* ------------------------------------------------------------------ */
174
175#include <stdlib.h>		   /* for malloc, free, etc. */
176#include <stdio.h>		   /* for printf [if needed] */
177#include <string.h>		   /* for strcpy */
178#include <ctype.h>		   /* for lower */
179#include "dconfig.h"		   /* for GCC definitions */
180#include "decNumber.h"		   /* base number library */
181#include "decNumberLocal.h"	   /* decNumber local types, etc. */
182
183/* Constants */
184/* Public lookup table used by the D2U macro */
185const uByte d2utable[DECMAXD2U+1]=D2UTABLE;
186
187#define DECVERB     1		   /* set to 1 for verbose DECCHECK */
188#define powers	    DECPOWERS	   /* old internal name */
189
190/* Local constants */
191#define DIVIDE	    0x80	   /* Divide operators */
192#define REMAINDER   0x40	   /* .. */
193#define DIVIDEINT   0x20	   /* .. */
194#define REMNEAR     0x10	   /* .. */
195#define COMPARE     0x01	   /* Compare operators */
196#define COMPMAX     0x02	   /* .. */
197#define COMPMIN     0x03	   /* .. */
198#define COMPTOTAL   0x04	   /* .. */
199#define COMPNAN     0x05	   /* .. [NaN processing] */
200#define COMPSIG     0x06	   /* .. [signaling COMPARE] */
201#define COMPMAXMAG  0x07	   /* .. */
202#define COMPMINMAG  0x08	   /* .. */
203
204#define DEC_sNaN     0x40000000    /* local status: sNaN signal */
205#define BADINT	(Int)0x80000000    /* most-negative Int; error indicator */
206/* Next two indicate an integer >= 10**6, and its parity (bottom bit) */
207#define BIGEVEN (Int)0x80000002
208#define BIGODD	(Int)0x80000003
209
210static Unit uarrone[1]={1};   /* Unit array of 1, used for incrementing */
211
212/* Granularity-dependent code */
213#if DECDPUN<=4
214  #define eInt	Int	      /* extended integer */
215  #define ueInt uInt	      /* unsigned extended integer */
216  /* Constant multipliers for divide-by-power-of five using reciprocal */
217  /* multiply, after removing powers of 2 by shifting, and final shift */
218  /* of 17 [we only need up to **4] */
219  static const uInt multies[]={131073, 26215, 5243, 1049, 210};
220  /* QUOT10 -- macro to return the quotient of unit u divided by 10**n */
221  #define QUOT10(u, n) ((((uInt)(u)>>(n))*multies[n])>>17)
222#else
223  /* For DECDPUN>4 non-ANSI-89 64-bit types are needed. */
224  #if !DECUSE64
225    #error decNumber.c: DECUSE64 must be 1 when DECDPUN>4
226  #endif
227  #define eInt	Long	      /* extended integer */
228  #define ueInt uLong	      /* unsigned extended integer */
229#endif
230
231/* Local routines */
232static decNumber * decAddOp(decNumber *, const decNumber *, const decNumber *,
233			      decContext *, uByte, uInt *);
234static Flag	   decBiStr(const char *, const char *, const char *);
235static uInt	   decCheckMath(const decNumber *, decContext *, uInt *);
236static void	   decApplyRound(decNumber *, decContext *, Int, uInt *);
237static Int	   decCompare(const decNumber *lhs, const decNumber *rhs, Flag);
238static decNumber * decCompareOp(decNumber *, const decNumber *,
239			      const decNumber *, decContext *,
240			      Flag, uInt *);
241static void	   decCopyFit(decNumber *, const decNumber *, decContext *,
242			      Int *, uInt *);
243static decNumber * decDecap(decNumber *, Int);
244static decNumber * decDivideOp(decNumber *, const decNumber *,
245			      const decNumber *, decContext *, Flag, uInt *);
246static decNumber * decExpOp(decNumber *, const decNumber *,
247			      decContext *, uInt *);
248static void	   decFinalize(decNumber *, decContext *, Int *, uInt *);
249static Int	   decGetDigits(Unit *, Int);
250static Int	   decGetInt(const decNumber *);
251static decNumber * decLnOp(decNumber *, const decNumber *,
252			      decContext *, uInt *);
253static decNumber * decMultiplyOp(decNumber *, const decNumber *,
254			      const decNumber *, decContext *,
255			      uInt *);
256static decNumber * decNaNs(decNumber *, const decNumber *,
257			      const decNumber *, decContext *, uInt *);
258static decNumber * decQuantizeOp(decNumber *, const decNumber *,
259			      const decNumber *, decContext *, Flag,
260			      uInt *);
261static void	   decReverse(Unit *, Unit *);
262static void	   decSetCoeff(decNumber *, decContext *, const Unit *,
263			      Int, Int *, uInt *);
264static void	   decSetMaxValue(decNumber *, decContext *);
265static void	   decSetOverflow(decNumber *, decContext *, uInt *);
266static void	   decSetSubnormal(decNumber *, decContext *, Int *, uInt *);
267static Int	   decShiftToLeast(Unit *, Int, Int);
268static Int	   decShiftToMost(Unit *, Int, Int);
269static void	   decStatus(decNumber *, uInt, decContext *);
270static void	   decToString(const decNumber *, char[], Flag);
271static decNumber * decTrim(decNumber *, decContext *, Flag, Flag, Int *);
272static Int	   decUnitAddSub(const Unit *, Int, const Unit *, Int, Int,
273			      Unit *, Int);
274static Int	   decUnitCompare(const Unit *, Int, const Unit *, Int, Int);
275
276#if !DECSUBSET
277/* decFinish == decFinalize when no subset arithmetic needed */
278#define decFinish(a,b,c,d) decFinalize(a,b,c,d)
279#else
280static void	   decFinish(decNumber *, decContext *, Int *, uInt *);
281static decNumber * decRoundOperand(const decNumber *, decContext *, uInt *);
282#endif
283
284/* Local macros */
285/* masked special-values bits */
286#define SPECIALARG  (rhs->bits & DECSPECIAL)
287#define SPECIALARGS ((lhs->bits | rhs->bits) & DECSPECIAL)
288
289/* Diagnostic macros, etc. */
290#if DECALLOC
291/* Handle malloc/free accounting.  If enabled, our accountable routines */
292/* are used; otherwise the code just goes straight to the system malloc */
293/* and free routines. */
294#define malloc(a) decMalloc(a)
295#define free(a) decFree(a)
296#define DECFENCE 0x5a		   /* corruption detector */
297/* 'Our' malloc and free: */
298static void *decMalloc(size_t);
299static void  decFree(void *);
300uInt decAllocBytes=0;		   /* count of bytes allocated */
301/* Note that DECALLOC code only checks for storage buffer overflow. */
302/* To check for memory leaks, the decAllocBytes variable must be */
303/* checked to be 0 at appropriate times (e.g., after the test */
304/* harness completes a set of tests).  This checking may be unreliable */
305/* if the testing is done in a multi-thread environment. */
306#endif
307
308#if DECCHECK
309/* Optional checking routines.	Enabling these means that decNumber */
310/* and decContext operands to operator routines are checked for */
311/* correctness.  This roughly doubles the execution time of the */
312/* fastest routines (and adds 600+ bytes), so should not normally be */
313/* used in 'production'. */
314/* decCheckInexact is used to check that inexact results have a full */
315/* complement of digits (where appropriate -- this is not the case */
316/* for Quantize, for example) */
317#define DECUNRESU ((decNumber *)(void *)0xffffffff)
318#define DECUNUSED ((const decNumber *)(void *)0xffffffff)
319#define DECUNCONT ((decContext *)(void *)(0xffffffff))
320static Flag decCheckOperands(decNumber *, const decNumber *,
321			     const decNumber *, decContext *);
322static Flag decCheckNumber(const decNumber *);
323static void decCheckInexact(const decNumber *, decContext *);
324#endif
325
326#if DECTRACE || DECCHECK
327/* Optional trace/debugging routines (may or may not be used) */
328void decNumberShow(const decNumber *);	/* displays the components of a number */
329static void decDumpAr(char, const Unit *, Int);
330#endif
331
332/* ================================================================== */
333/* Conversions							      */
334/* ================================================================== */
335
336/* ------------------------------------------------------------------ */
337/* from-int32 -- conversion from Int or uInt			      */
338/*								      */
339/*  dn is the decNumber to receive the integer			      */
340/*  in or uin is the integer to be converted			      */
341/*  returns dn							      */
342/*								      */
343/* No error is possible.					      */
344/* ------------------------------------------------------------------ */
345decNumber * decNumberFromInt32(decNumber *dn, Int in) {
346  uInt unsig;
347  if (in>=0) unsig=in;
348   else {				/* negative (possibly BADINT) */
349    if (in==BADINT) unsig=(uInt)1073741824*2; /* special case */
350     else unsig=-in;			/* invert */
351    }
352  /* in is now positive */
353  decNumberFromUInt32(dn, unsig);
354  if (in<0) dn->bits=DECNEG;		/* sign needed */
355  return dn;
356  } /* decNumberFromInt32 */
357
358decNumber * decNumberFromUInt32(decNumber *dn, uInt uin) {
359  Unit *up;				/* work pointer */
360  decNumberZero(dn);			/* clean */
361  if (uin==0) return dn;		/* [or decGetDigits bad call] */
362  for (up=dn->lsu; uin>0; up++) {
363    *up=(Unit)(uin%(DECDPUNMAX+1));
364    uin=uin/(DECDPUNMAX+1);
365    }
366  dn->digits=decGetDigits(dn->lsu, up-dn->lsu);
367  return dn;
368  } /* decNumberFromUInt32 */
369
370/* ------------------------------------------------------------------ */
371/* to-int32 -- conversion to Int or uInt			      */
372/*								      */
373/*  dn is the decNumber to convert				      */
374/*  set is the context for reporting errors			      */
375/*  returns the converted decNumber, or 0 if Invalid is set	      */
376/*								      */
377/* Invalid is set if the decNumber does not have exponent==0 or if    */
378/* it is a NaN, Infinite, or out-of-range.			      */
379/* ------------------------------------------------------------------ */
380Int decNumberToInt32(const decNumber *dn, decContext *set) {
381  #if DECCHECK
382  if (decCheckOperands(DECUNRESU, DECUNUSED, dn, set)) return 0;
383  #endif
384
385  /* special or too many digits, or bad exponent */
386  if (dn->bits&DECSPECIAL || dn->digits>10 || dn->exponent!=0) ; /* bad */
387   else { /* is a finite integer with 10 or fewer digits */
388    Int d;			   /* work */
389    const Unit *up;		   /* .. */
390    uInt hi=0, lo;		   /* .. */
391    up=dn->lsu; 		   /* -> lsu */
392    lo=*up;			   /* get 1 to 9 digits */
393    #if DECDPUN>1		   /* split to higher */
394      hi=lo/10;
395      lo=lo%10;
396    #endif
397    up++;
398    /* collect remaining Units, if any, into hi */
399    for (d=DECDPUN; d<dn->digits; up++, d+=DECDPUN) hi+=*up*powers[d-1];
400    /* now low has the lsd, hi the remainder */
401    if (hi>214748364 || (hi==214748364 && lo>7)) { /* out of range? */
402      /* most-negative is a reprieve */
403      if (dn->bits&DECNEG && hi==214748364 && lo==8) return 0x80000000;
404      /* bad -- drop through */
405      }
406     else { /* in-range always */
407      Int i=X10(hi)+lo;
408      if (dn->bits&DECNEG) return -i;
409      return i;
410      }
411    } /* integer */
412  decContextSetStatus(set, DEC_Invalid_operation); /* [may not return] */
413  return 0;
414  } /* decNumberToInt32 */
415
416uInt decNumberToUInt32(const decNumber *dn, decContext *set) {
417  #if DECCHECK
418  if (decCheckOperands(DECUNRESU, DECUNUSED, dn, set)) return 0;
419  #endif
420  /* special or too many digits, or bad exponent, or negative (<0) */
421  if (dn->bits&DECSPECIAL || dn->digits>10 || dn->exponent!=0
422    || (dn->bits&DECNEG && !ISZERO(dn)));		    /* bad */
423   else { /* is a finite integer with 10 or fewer digits */
424    Int d;			   /* work */
425    const Unit *up;		   /* .. */
426    uInt hi=0, lo;		   /* .. */
427    up=dn->lsu; 		   /* -> lsu */
428    lo=*up;			   /* get 1 to 9 digits */
429    #if DECDPUN>1		   /* split to higher */
430      hi=lo/10;
431      lo=lo%10;
432    #endif
433    up++;
434    /* collect remaining Units, if any, into hi */
435    for (d=DECDPUN; d<dn->digits; up++, d+=DECDPUN) hi+=*up*powers[d-1];
436
437    /* now low has the lsd, hi the remainder */
438    if (hi>429496729 || (hi==429496729 && lo>5)) ; /* no reprieve possible */
439     else return X10(hi)+lo;
440    } /* integer */
441  decContextSetStatus(set, DEC_Invalid_operation); /* [may not return] */
442  return 0;
443  } /* decNumberToUInt32 */
444
445/* ------------------------------------------------------------------ */
446/* to-scientific-string -- conversion to numeric string 	      */
447/* to-engineering-string -- conversion to numeric string	      */
448/*								      */
449/*   decNumberToString(dn, string);				      */
450/*   decNumberToEngString(dn, string);				      */
451/*								      */
452/*  dn is the decNumber to convert				      */
453/*  string is the string where the result will be laid out	      */
454/*								      */
455/*  string must be at least dn->digits+14 characters long	      */
456/*								      */
457/*  No error is possible, and no status can be set.		      */
458/* ------------------------------------------------------------------ */
459char * decNumberToString(const decNumber *dn, char *string){
460  decToString(dn, string, 0);
461  return string;
462  } /* DecNumberToString */
463
464char * decNumberToEngString(const decNumber *dn, char *string){
465  decToString(dn, string, 1);
466  return string;
467  } /* DecNumberToEngString */
468
469/* ------------------------------------------------------------------ */
470/* to-number -- conversion from numeric string			      */
471/*								      */
472/* decNumberFromString -- convert string to decNumber		      */
473/*   dn        -- the number structure to fill			      */
474/*   chars[]   -- the string to convert ('\0' terminated)	      */
475/*   set       -- the context used for processing any error,	      */
476/*		  determining the maximum precision available	      */
477/*		  (set.digits), determining the maximum and minimum   */
478/*		  exponent (set.emax and set.emin), determining if    */
479/*		  extended values are allowed, and checking the       */
480/*		  rounding mode if overflow occurs or rounding is     */
481/*		  needed.					      */
482/*								      */
483/* The length of the coefficient and the size of the exponent are     */
484/* checked by this routine, so the correct error (Underflow or	      */
485/* Overflow) can be reported or rounding applied, as necessary.       */
486/*								      */
487/* If bad syntax is detected, the result will be a quiet NaN.	      */
488/* ------------------------------------------------------------------ */
489decNumber * decNumberFromString(decNumber *dn, const char chars[],
490				decContext *set) {
491  Int	exponent=0;		   /* working exponent [assume 0] */
492  uByte bits=0; 		   /* working flags [assume +ve] */
493  Unit	*res;			   /* where result will be built */
494  Unit	resbuff[SD2U(DECBUFFER+9)];/* local buffer in case need temporary */
495				   /* [+9 allows for ln() constants] */
496  Unit	*allocres=NULL; 	   /* -> allocated result, iff allocated */
497  Int	d=0;			   /* count of digits found in decimal part */
498  const char *dotchar=NULL;	   /* where dot was found */
499  const char *cfirst=chars;	   /* -> first character of decimal part */
500  const char *last=NULL;	   /* -> last digit of decimal part */
501  const char *c;		   /* work */
502  Unit	*up;			   /* .. */
503  #if DECDPUN>1
504  Int	cut, out;		   /* .. */
505  #endif
506  Int	residue;		   /* rounding residue */
507  uInt	status=0;		   /* error code */
508
509  #if DECCHECK
510  if (decCheckOperands(DECUNRESU, DECUNUSED, DECUNUSED, set))
511    return decNumberZero(dn);
512  #endif
513
514  do {				   /* status & malloc protection */
515    for (c=chars;; c++) {	   /* -> input character */
516      if (*c>='0' && *c<='9') {    /* test for Arabic digit */
517	last=c;
518	d++;			   /* count of real digits */
519	continue;		   /* still in decimal part */
520	}
521      if (*c=='.' && dotchar==NULL) { /* first '.' */
522	dotchar=c;		   /* record offset into decimal part */
523	if (c==cfirst) cfirst++;   /* first digit must follow */
524	continue;}
525      if (c==chars) {		   /* first in string... */
526	if (*c=='-') {		   /* valid - sign */
527	  cfirst++;
528	  bits=DECNEG;
529	  continue;}
530	if (*c=='+') {		   /* valid + sign */
531	  cfirst++;
532	  continue;}
533	}
534      /* *c is not a digit, or a valid +, -, or '.' */
535      break;
536      } /* c */
537
538    if (last==NULL) {		   /* no digits yet */
539      status=DEC_Conversion_syntax;/* assume the worst */
540      if (*c=='\0') break;	   /* and no more to come... */
541      #if DECSUBSET
542      /* if subset then infinities and NaNs are not allowed */
543      if (!set->extended) break;   /* hopeless */
544      #endif
545      /* Infinities and NaNs are possible, here */
546      if (dotchar!=NULL) break;    /* .. unless had a dot */
547      decNumberZero(dn);	   /* be optimistic */
548      if (decBiStr(c, "infinity", "INFINITY")
549       || decBiStr(c, "inf", "INF")) {
550	dn->bits=bits | DECINF;
551	status=0;		   /* is OK */
552	break; /* all done */
553	}
554      /* a NaN expected */
555      /* 2003.09.10 NaNs are now permitted to have a sign */
556      dn->bits=bits | DECNAN;	   /* assume simple NaN */
557      if (*c=='s' || *c=='S') {    /* looks like an sNaN */
558	c++;
559	dn->bits=bits | DECSNAN;
560	}
561      if (*c!='n' && *c!='N') break;	/* check caseless "NaN" */
562      c++;
563      if (*c!='a' && *c!='A') break;	/* .. */
564      c++;
565      if (*c!='n' && *c!='N') break;	/* .. */
566      c++;
567      /* now either nothing, or nnnn payload, expected */
568      /* -> start of integer and skip leading 0s [including plain 0] */
569      for (cfirst=c; *cfirst=='0';) cfirst++;
570      if (*cfirst=='\0') {	   /* "NaN" or "sNaN", maybe with all 0s */
571	status=0;		   /* it's good */
572	break;			   /* .. */
573	}
574      /* something other than 0s; setup last and d as usual [no dots] */
575      for (c=cfirst;; c++, d++) {
576	if (*c<'0' || *c>'9') break; /* test for Arabic digit */
577	last=c;
578	}
579      if (*c!='\0') break;	   /* not all digits */
580      if (d>set->digits-1) {
581	/* [NB: payload in a decNumber can be full length unless */
582	/* clamped, in which case can only be digits-1] */
583	if (set->clamp) break;
584	if (d>set->digits) break;
585	} /* too many digits? */
586      /* good; drop through to convert the integer to coefficient */
587      status=0; 		   /* syntax is OK */
588      bits=dn->bits;		   /* for copy-back */
589      } /* last==NULL */
590
591     else if (*c!='\0') {	   /* more to process... */
592      /* had some digits; exponent is only valid sequence now */
593      Flag nege;		   /* 1=negative exponent */
594      const char *firstexp;	   /* -> first significant exponent digit */
595      status=DEC_Conversion_syntax;/* assume the worst */
596      if (*c!='e' && *c!='E') break;
597      /* Found 'e' or 'E' -- now process explicit exponent */
598      /* 1998.07.11: sign no longer required */
599      nege=0;
600      c++;			   /* to (possible) sign */
601      if (*c=='-') {nege=1; c++;}
602       else if (*c=='+') c++;
603      if (*c=='\0') break;
604
605      for (; *c=='0' && *(c+1)!='\0';) c++;  /* strip insignificant zeros */
606      firstexp=c;			     /* save exponent digit place */
607      for (; ;c++) {
608	if (*c<'0' || *c>'9') break;	     /* not a digit */
609	exponent=X10(exponent)+(Int)*c-(Int)'0';
610	} /* c */
611      /* if not now on a '\0', *c must not be a digit */
612      if (*c!='\0') break;
613
614      /* (this next test must be after the syntax checks) */
615      /* if it was too long the exponent may have wrapped, so check */
616      /* carefully and set it to a certain overflow if wrap possible */
617      if (c>=firstexp+9+1) {
618	if (c>firstexp+9+1 || *firstexp>'1') exponent=DECNUMMAXE*2;
619	/* [up to 1999999999 is OK, for example 1E-1000000998] */
620	}
621      if (nege) exponent=-exponent;	/* was negative */
622      status=0; 			/* is OK */
623      } /* stuff after digits */
624
625    /* Here when whole string has been inspected; syntax is good */
626    /* cfirst->first digit (never dot), last->last digit (ditto) */
627
628    /* strip leading zeros/dot [leave final 0 if all 0's] */
629    if (*cfirst=='0') { 		/* [cfirst has stepped over .] */
630      for (c=cfirst; c<last; c++, cfirst++) {
631	if (*c=='.') continue;		/* ignore dots */
632	if (*c!='0') break;		/* non-zero found */
633	d--;				/* 0 stripped */
634	} /* c */
635      #if DECSUBSET
636      /* make a rapid exit for easy zeros if !extended */
637      if (*cfirst=='0' && !set->extended) {
638	decNumberZero(dn);		/* clean result */
639	break;				/* [could be return] */
640	}
641      #endif
642      } /* at least one leading 0 */
643
644    /* Handle decimal point... */
645    if (dotchar!=NULL && dotchar<last)	/* non-trailing '.' found? */
646      exponent-=(last-dotchar); 	/* adjust exponent */
647    /* [we can now ignore the .] */
648
649    /* OK, the digits string is good.  Assemble in the decNumber, or in */
650    /* a temporary units array if rounding is needed */
651    if (d<=set->digits) res=dn->lsu;	/* fits into supplied decNumber */
652     else {				/* rounding needed */
653      Int needbytes=D2U(d)*sizeof(Unit);/* bytes needed */
654      res=resbuff;			/* assume use local buffer */
655      if (needbytes>(Int)sizeof(resbuff)) { /* too big for local */
656	allocres=(Unit *)malloc(needbytes);
657	if (allocres==NULL) {status|=DEC_Insufficient_storage; break;}
658	res=allocres;
659	}
660      }
661    /* res now -> number lsu, buffer, or allocated storage for Unit array */
662
663    /* Place the coefficient into the selected Unit array */
664    /* [this is often 70% of the cost of this function when DECDPUN>1] */
665    #if DECDPUN>1
666    out=0;			   /* accumulator */
667    up=res+D2U(d)-1;		   /* -> msu */
668    cut=d-(up-res)*DECDPUN;	   /* digits in top unit */
669    for (c=cfirst;; c++) {	   /* along the digits */
670      if (*c=='.') continue;	   /* ignore '.' [don't decrement cut] */
671      out=X10(out)+(Int)*c-(Int)'0';
672      if (c==last) break;	   /* done [never get to trailing '.'] */
673      cut--;
674      if (cut>0) continue;	   /* more for this unit */
675      *up=(Unit)out;		   /* write unit */
676      up--;			   /* prepare for unit below.. */
677      cut=DECDPUN;		   /* .. */
678      out=0;			   /* .. */
679      } /* c */
680    *up=(Unit)out;		   /* write lsu */
681
682    #else
683    /* DECDPUN==1 */
684    up=res;			   /* -> lsu */
685    for (c=last; c>=cfirst; c--) { /* over each character, from least */
686      if (*c=='.') continue;	   /* ignore . [don't step up] */
687      *up=(Unit)((Int)*c-(Int)'0');
688      up++;
689      } /* c */
690    #endif
691
692    dn->bits=bits;
693    dn->exponent=exponent;
694    dn->digits=d;
695
696    /* if not in number (too long) shorten into the number */
697    if (d>set->digits) {
698      residue=0;
699      decSetCoeff(dn, set, res, d, &residue, &status);
700      /* always check for overflow or subnormal and round as needed */
701      decFinalize(dn, set, &residue, &status);
702      }
703     else { /* no rounding, but may still have overflow or subnormal */
704      /* [these tests are just for performance; finalize repeats them] */
705      if ((dn->exponent-1<set->emin-dn->digits)
706       || (dn->exponent-1>set->emax-set->digits)) {
707	residue=0;
708	decFinalize(dn, set, &residue, &status);
709	}
710      }
711    /* decNumberShow(dn); */
712    } while(0); 			/* [for break] */
713
714  free(allocres);	/* drop any storage used */
715  if (status!=0) decStatus(dn, status, set);
716  return dn;
717  } /* decNumberFromString */
718
719/* ================================================================== */
720/* Operators							      */
721/* ================================================================== */
722
723/* ------------------------------------------------------------------ */
724/* decNumberAbs -- absolute value operator			      */
725/*								      */
726/*   This computes C = abs(A)					      */
727/*								      */
728/*   res is C, the result.  C may be A				      */
729/*   rhs is A							      */
730/*   set is the context 					      */
731/*								      */
732/* See also decNumberCopyAbs for a quiet bitwise version of this.     */
733/* C must have space for set->digits digits.			      */
734/* ------------------------------------------------------------------ */
735/* This has the same effect as decNumberPlus unless A is negative,    */
736/* in which case it has the same effect as decNumberMinus.	      */
737/* ------------------------------------------------------------------ */
738decNumber * decNumberAbs(decNumber *res, const decNumber *rhs,
739			 decContext *set) {
740  decNumber dzero;			/* for 0 */
741  uInt status=0;			/* accumulator */
742
743  #if DECCHECK
744  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
745  #endif
746
747  decNumberZero(&dzero);		/* set 0 */
748  dzero.exponent=rhs->exponent; 	/* [no coefficient expansion] */
749  decAddOp(res, &dzero, rhs, set, (uByte)(rhs->bits & DECNEG), &status);
750  if (status!=0) decStatus(res, status, set);
751  #if DECCHECK
752  decCheckInexact(res, set);
753  #endif
754  return res;
755  } /* decNumberAbs */
756
757/* ------------------------------------------------------------------ */
758/* decNumberAdd -- add two Numbers				      */
759/*								      */
760/*   This computes C = A + B					      */
761/*								      */
762/*   res is C, the result.  C may be A and/or B (e.g., X=X+X)	      */
763/*   lhs is A							      */
764/*   rhs is B							      */
765/*   set is the context 					      */
766/*								      */
767/* C must have space for set->digits digits.			      */
768/* ------------------------------------------------------------------ */
769/* This just calls the routine shared with Subtract		      */
770decNumber * decNumberAdd(decNumber *res, const decNumber *lhs,
771			 const decNumber *rhs, decContext *set) {
772  uInt status=0;			/* accumulator */
773  decAddOp(res, lhs, rhs, set, 0, &status);
774  if (status!=0) decStatus(res, status, set);
775  #if DECCHECK
776  decCheckInexact(res, set);
777  #endif
778  return res;
779  } /* decNumberAdd */
780
781/* ------------------------------------------------------------------ */
782/* decNumberAnd -- AND two Numbers, digitwise			      */
783/*								      */
784/*   This computes C = A & B					      */
785/*								      */
786/*   res is C, the result.  C may be A and/or B (e.g., X=X&X)	      */
787/*   lhs is A							      */
788/*   rhs is B							      */
789/*   set is the context (used for result length and error report)     */
790/*								      */
791/* C must have space for set->digits digits.			      */
792/*								      */
793/* Logical function restrictions apply (see above); a NaN is	      */
794/* returned with Invalid_operation if a restriction is violated.      */
795/* ------------------------------------------------------------------ */
796decNumber * decNumberAnd(decNumber *res, const decNumber *lhs,
797			 const decNumber *rhs, decContext *set) {
798  const Unit *ua, *ub;			/* -> operands */
799  const Unit *msua, *msub;		/* -> operand msus */
800  Unit *uc,  *msuc;			/* -> result and its msu */
801  Int	msudigs;			/* digits in res msu */
802  #if DECCHECK
803  if (decCheckOperands(res, lhs, rhs, set)) return res;
804  #endif
805
806  if (lhs->exponent!=0 || decNumberIsSpecial(lhs) || decNumberIsNegative(lhs)
807   || rhs->exponent!=0 || decNumberIsSpecial(rhs) || decNumberIsNegative(rhs)) {
808    decStatus(res, DEC_Invalid_operation, set);
809    return res;
810    }
811
812  /* operands are valid */
813  ua=lhs->lsu;				/* bottom-up */
814  ub=rhs->lsu;				/* .. */
815  uc=res->lsu;				/* .. */
816  msua=ua+D2U(lhs->digits)-1;		/* -> msu of lhs */
817  msub=ub+D2U(rhs->digits)-1;		/* -> msu of rhs */
818  msuc=uc+D2U(set->digits)-1;		/* -> msu of result */
819  msudigs=MSUDIGITS(set->digits);	/* [faster than remainder] */
820  for (; uc<=msuc; ua++, ub++, uc++) {	/* Unit loop */
821    Unit a, b;				/* extract units */
822    if (ua>msua) a=0;
823     else a=*ua;
824    if (ub>msub) b=0;
825     else b=*ub;
826    *uc=0;				/* can now write back */
827    if (a|b) {				/* maybe 1 bits to examine */
828      Int i, j;
829      *uc=0;				/* can now write back */
830      /* This loop could be unrolled and/or use BIN2BCD tables */
831      for (i=0; i<DECDPUN; i++) {
832	if (a&b&1) *uc=*uc+(Unit)powers[i];  /* effect AND */
833	j=a%10;
834	a=a/10;
835	j|=b%10;
836	b=b/10;
837	if (j>1) {
838	  decStatus(res, DEC_Invalid_operation, set);
839	  return res;
840	  }
841	if (uc==msuc && i==msudigs-1) break; /* just did final digit */
842	} /* each digit */
843      } /* both OK */
844    } /* each unit */
845  /* [here uc-1 is the msu of the result] */
846  res->digits=decGetDigits(res->lsu, uc-res->lsu);
847  res->exponent=0;			/* integer */
848  res->bits=0;				/* sign=0 */
849  return res;  /* [no status to set] */
850  } /* decNumberAnd */
851
852/* ------------------------------------------------------------------ */
853/* decNumberCompare -- compare two Numbers			      */
854/*								      */
855/*   This computes C = A ? B					      */
856/*								      */
857/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
858/*   lhs is A							      */
859/*   rhs is B							      */
860/*   set is the context 					      */
861/*								      */
862/* C must have space for one digit (or NaN).			      */
863/* ------------------------------------------------------------------ */
864decNumber * decNumberCompare(decNumber *res, const decNumber *lhs,
865			     const decNumber *rhs, decContext *set) {
866  uInt status=0;			/* accumulator */
867  decCompareOp(res, lhs, rhs, set, COMPARE, &status);
868  if (status!=0) decStatus(res, status, set);
869  return res;
870  } /* decNumberCompare */
871
872/* ------------------------------------------------------------------ */
873/* decNumberCompareSignal -- compare, signalling on all NaNs	      */
874/*								      */
875/*   This computes C = A ? B					      */
876/*								      */
877/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
878/*   lhs is A							      */
879/*   rhs is B							      */
880/*   set is the context 					      */
881/*								      */
882/* C must have space for one digit (or NaN).			      */
883/* ------------------------------------------------------------------ */
884decNumber * decNumberCompareSignal(decNumber *res, const decNumber *lhs,
885				   const decNumber *rhs, decContext *set) {
886  uInt status=0;			/* accumulator */
887  decCompareOp(res, lhs, rhs, set, COMPSIG, &status);
888  if (status!=0) decStatus(res, status, set);
889  return res;
890  } /* decNumberCompareSignal */
891
892/* ------------------------------------------------------------------ */
893/* decNumberCompareTotal -- compare two Numbers, using total ordering */
894/*								      */
895/*   This computes C = A ? B, under total ordering		      */
896/*								      */
897/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
898/*   lhs is A							      */
899/*   rhs is B							      */
900/*   set is the context 					      */
901/*								      */
902/* C must have space for one digit; the result will always be one of  */
903/* -1, 0, or 1. 						      */
904/* ------------------------------------------------------------------ */
905decNumber * decNumberCompareTotal(decNumber *res, const decNumber *lhs,
906				  const decNumber *rhs, decContext *set) {
907  uInt status=0;			/* accumulator */
908  decCompareOp(res, lhs, rhs, set, COMPTOTAL, &status);
909  if (status!=0) decStatus(res, status, set);
910  return res;
911  } /* decNumberCompareTotal */
912
913/* ------------------------------------------------------------------ */
914/* decNumberCompareTotalMag -- compare, total ordering of magnitudes  */
915/*								      */
916/*   This computes C = |A| ? |B|, under total ordering		      */
917/*								      */
918/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
919/*   lhs is A							      */
920/*   rhs is B							      */
921/*   set is the context 					      */
922/*								      */
923/* C must have space for one digit; the result will always be one of  */
924/* -1, 0, or 1. 						      */
925/* ------------------------------------------------------------------ */
926decNumber * decNumberCompareTotalMag(decNumber *res, const decNumber *lhs,
927				     const decNumber *rhs, decContext *set) {
928  uInt status=0;		   /* accumulator */
929  uInt needbytes;		   /* for space calculations */
930  decNumber bufa[D2N(DECBUFFER+1)];/* +1 in case DECBUFFER=0 */
931  decNumber *allocbufa=NULL;	   /* -> allocated bufa, iff allocated */
932  decNumber bufb[D2N(DECBUFFER+1)];
933  decNumber *allocbufb=NULL;	   /* -> allocated bufb, iff allocated */
934  decNumber *a, *b;		   /* temporary pointers */
935
936  #if DECCHECK
937  if (decCheckOperands(res, lhs, rhs, set)) return res;
938  #endif
939
940  do {					/* protect allocated storage */
941    /* if either is negative, take a copy and absolute */
942    if (decNumberIsNegative(lhs)) {	/* lhs<0 */
943      a=bufa;
944      needbytes=sizeof(decNumber)+(D2U(lhs->digits)-1)*sizeof(Unit);
945      if (needbytes>sizeof(bufa)) {	/* need malloc space */
946	allocbufa=(decNumber *)malloc(needbytes);
947	if (allocbufa==NULL) {		/* hopeless -- abandon */
948	  status|=DEC_Insufficient_storage;
949	  break;}
950	a=allocbufa;			/* use the allocated space */
951	}
952      decNumberCopy(a, lhs);		/* copy content */
953      a->bits&=~DECNEG; 		/* .. and clear the sign */
954      lhs=a;				/* use copy from here on */
955      }
956    if (decNumberIsNegative(rhs)) {	/* rhs<0 */
957      b=bufb;
958      needbytes=sizeof(decNumber)+(D2U(rhs->digits)-1)*sizeof(Unit);
959      if (needbytes>sizeof(bufb)) {	/* need malloc space */
960	allocbufb=(decNumber *)malloc(needbytes);
961	if (allocbufb==NULL) {		/* hopeless -- abandon */
962	  status|=DEC_Insufficient_storage;
963	  break;}
964	b=allocbufb;			/* use the allocated space */
965	}
966      decNumberCopy(b, rhs);		/* copy content */
967      b->bits&=~DECNEG; 		/* .. and clear the sign */
968      rhs=b;				/* use copy from here on */
969      }
970    decCompareOp(res, lhs, rhs, set, COMPTOTAL, &status);
971    } while(0); 			/* end protected */
972
973  free(allocbufa); /* drop any storage used */
974  free(allocbufb); /* .. */
975  if (status!=0) decStatus(res, status, set);
976  return res;
977  } /* decNumberCompareTotalMag */
978
979/* ------------------------------------------------------------------ */
980/* decNumberDivide -- divide one number by another		      */
981/*								      */
982/*   This computes C = A / B					      */
983/*								      */
984/*   res is C, the result.  C may be A and/or B (e.g., X=X/X)	      */
985/*   lhs is A							      */
986/*   rhs is B							      */
987/*   set is the context 					      */
988/*								      */
989/* C must have space for set->digits digits.			      */
990/* ------------------------------------------------------------------ */
991decNumber * decNumberDivide(decNumber *res, const decNumber *lhs,
992			    const decNumber *rhs, decContext *set) {
993  uInt status=0;			/* accumulator */
994  decDivideOp(res, lhs, rhs, set, DIVIDE, &status);
995  if (status!=0) decStatus(res, status, set);
996  #if DECCHECK
997  decCheckInexact(res, set);
998  #endif
999  return res;
1000  } /* decNumberDivide */
1001
1002/* ------------------------------------------------------------------ */
1003/* decNumberDivideInteger -- divide and return integer quotient       */
1004/*								      */
1005/*   This computes C = A # B, where # is the integer divide operator  */
1006/*								      */
1007/*   res is C, the result.  C may be A and/or B (e.g., X=X#X)	      */
1008/*   lhs is A							      */
1009/*   rhs is B							      */
1010/*   set is the context 					      */
1011/*								      */
1012/* C must have space for set->digits digits.			      */
1013/* ------------------------------------------------------------------ */
1014decNumber * decNumberDivideInteger(decNumber *res, const decNumber *lhs,
1015				   const decNumber *rhs, decContext *set) {
1016  uInt status=0;			/* accumulator */
1017  decDivideOp(res, lhs, rhs, set, DIVIDEINT, &status);
1018  if (status!=0) decStatus(res, status, set);
1019  return res;
1020  } /* decNumberDivideInteger */
1021
1022/* ------------------------------------------------------------------ */
1023/* decNumberExp -- exponentiation				      */
1024/*								      */
1025/*   This computes C = exp(A)					      */
1026/*								      */
1027/*   res is C, the result.  C may be A				      */
1028/*   rhs is A							      */
1029/*   set is the context; note that rounding mode has no effect	      */
1030/*								      */
1031/* C must have space for set->digits digits.			      */
1032/*								      */
1033/* Mathematical function restrictions apply (see above); a NaN is     */
1034/* returned with Invalid_operation if a restriction is violated.      */
1035/*								      */
1036/* Finite results will always be full precision and Inexact, except   */
1037/* when A is a zero or -Infinity (giving 1 or 0 respectively).	      */
1038/*								      */
1039/* An Inexact result is rounded using DEC_ROUND_HALF_EVEN; it will    */
1040/* almost always be correctly rounded, but may be up to 1 ulp in      */
1041/* error in rare cases. 					      */
1042/* ------------------------------------------------------------------ */
1043/* This is a wrapper for decExpOp which can handle the slightly wider */
1044/* (double) range needed by Ln (which has to be able to calculate     */
1045/* exp(-a) where a can be the tiniest number (Ntiny).		      */
1046/* ------------------------------------------------------------------ */
1047decNumber * decNumberExp(decNumber *res, const decNumber *rhs,
1048			 decContext *set) {
1049  uInt status=0;			/* accumulator */
1050  #if DECSUBSET
1051  decNumber *allocrhs=NULL;	   /* non-NULL if rounded rhs allocated */
1052  #endif
1053
1054  #if DECCHECK
1055  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1056  #endif
1057
1058  /* Check restrictions; these restrictions ensure that if h=8 (see */
1059  /* decExpOp) then the result will either overflow or underflow to 0. */
1060  /* Other math functions restrict the input range, too, for inverses. */
1061  /* If not violated then carry out the operation. */
1062  if (!decCheckMath(rhs, set, &status)) do { /* protect allocation */
1063    #if DECSUBSET
1064    if (!set->extended) {
1065      /* reduce operand and set lostDigits status, as needed */
1066      if (rhs->digits>set->digits) {
1067	allocrhs=decRoundOperand(rhs, set, &status);
1068	if (allocrhs==NULL) break;
1069	rhs=allocrhs;
1070	}
1071      }
1072    #endif
1073    decExpOp(res, rhs, set, &status);
1074    } while(0); 			/* end protected */
1075
1076  #if DECSUBSET
1077  free(allocrhs);	/* drop any storage used */
1078  #endif
1079  /* apply significant status */
1080  if (status!=0) decStatus(res, status, set);
1081  #if DECCHECK
1082  decCheckInexact(res, set);
1083  #endif
1084  return res;
1085  } /* decNumberExp */
1086
1087/* ------------------------------------------------------------------ */
1088/* decNumberFMA -- fused multiply add				      */
1089/*								      */
1090/*   This computes D = (A * B) + C with only one rounding	      */
1091/*								      */
1092/*   res is D, the result.  D may be A or B or C (e.g., X=FMA(X,X,X)) */
1093/*   lhs is A							      */
1094/*   rhs is B							      */
1095/*   fhs is C [far hand side]					      */
1096/*   set is the context 					      */
1097/*								      */
1098/* Mathematical function restrictions apply (see above); a NaN is     */
1099/* returned with Invalid_operation if a restriction is violated.      */
1100/*								      */
1101/* C must have space for set->digits digits.			      */
1102/* ------------------------------------------------------------------ */
1103decNumber * decNumberFMA(decNumber *res, const decNumber *lhs,
1104			 const decNumber *rhs, const decNumber *fhs,
1105			 decContext *set) {
1106  uInt status=0;		   /* accumulator */
1107  decContext dcmul;		   /* context for the multiplication */
1108  uInt needbytes;		   /* for space calculations */
1109  decNumber bufa[D2N(DECBUFFER*2+1)];
1110  decNumber *allocbufa=NULL;	   /* -> allocated bufa, iff allocated */
1111  decNumber *acc;		   /* accumulator pointer */
1112  decNumber dzero;		   /* work */
1113
1114  #if DECCHECK
1115  if (decCheckOperands(res, lhs, rhs, set)) return res;
1116  if (decCheckOperands(res, fhs, DECUNUSED, set)) return res;
1117  #endif
1118
1119  do {					/* protect allocated storage */
1120    #if DECSUBSET
1121    if (!set->extended) {		/* [undefined if subset] */
1122      status|=DEC_Invalid_operation;
1123      break;}
1124    #endif
1125    /* Check math restrictions [these ensure no overflow or underflow] */
1126    if ((!decNumberIsSpecial(lhs) && decCheckMath(lhs, set, &status))
1127     || (!decNumberIsSpecial(rhs) && decCheckMath(rhs, set, &status))
1128     || (!decNumberIsSpecial(fhs) && decCheckMath(fhs, set, &status))) break;
1129    /* set up context for multiply */
1130    dcmul=*set;
1131    dcmul.digits=lhs->digits+rhs->digits; /* just enough */
1132    /* [The above may be an over-estimate for subset arithmetic, but that's OK] */
1133    dcmul.emax=DEC_MAX_EMAX;		/* effectively unbounded .. */
1134    dcmul.emin=DEC_MIN_EMIN;		/* [thanks to Math restrictions] */
1135    /* set up decNumber space to receive the result of the multiply */
1136    acc=bufa;				/* may fit */
1137    needbytes=sizeof(decNumber)+(D2U(dcmul.digits)-1)*sizeof(Unit);
1138    if (needbytes>sizeof(bufa)) {	/* need malloc space */
1139      allocbufa=(decNumber *)malloc(needbytes);
1140      if (allocbufa==NULL) {		/* hopeless -- abandon */
1141	status|=DEC_Insufficient_storage;
1142	break;}
1143      acc=allocbufa;			/* use the allocated space */
1144      }
1145    /* multiply with extended range and necessary precision */
1146    /*printf("emin=%ld\n", dcmul.emin); */
1147    decMultiplyOp(acc, lhs, rhs, &dcmul, &status);
1148    /* Only Invalid operation (from sNaN or Inf * 0) is possible in */
1149    /* status; if either is seen than ignore fhs (in case it is */
1150    /* another sNaN) and set acc to NaN unless we had an sNaN */
1151    /* [decMultiplyOp leaves that to caller] */
1152    /* Note sNaN has to go through addOp to shorten payload if */
1153    /* necessary */
1154    if ((status&DEC_Invalid_operation)!=0) {
1155      if (!(status&DEC_sNaN)) { 	/* but be true invalid */
1156	decNumberZero(res);		/* acc not yet set */
1157	res->bits=DECNAN;
1158	break;
1159	}
1160      decNumberZero(&dzero);		/* make 0 (any non-NaN would do) */
1161      fhs=&dzero;			/* use that */
1162      }
1163    #if DECCHECK
1164     else { /* multiply was OK */
1165      if (status!=0) printf("Status=%08lx after FMA multiply\n", (LI)status);
1166      }
1167    #endif
1168    /* add the third operand and result -> res, and all is done */
1169    decAddOp(res, acc, fhs, set, 0, &status);
1170    } while(0); 			/* end protected */
1171
1172  free(allocbufa); /* drop any storage used */
1173  if (status!=0) decStatus(res, status, set);
1174  #if DECCHECK
1175  decCheckInexact(res, set);
1176  #endif
1177  return res;
1178  } /* decNumberFMA */
1179
1180/* ------------------------------------------------------------------ */
1181/* decNumberInvert -- invert a Number, digitwise		      */
1182/*								      */
1183/*   This computes C = ~A					      */
1184/*								      */
1185/*   res is C, the result.  C may be A (e.g., X=~X)		      */
1186/*   rhs is A							      */
1187/*   set is the context (used for result length and error report)     */
1188/*								      */
1189/* C must have space for set->digits digits.			      */
1190/*								      */
1191/* Logical function restrictions apply (see above); a NaN is	      */
1192/* returned with Invalid_operation if a restriction is violated.      */
1193/* ------------------------------------------------------------------ */
1194decNumber * decNumberInvert(decNumber *res, const decNumber *rhs,
1195			    decContext *set) {
1196  const Unit *ua, *msua;		/* -> operand and its msu */
1197  Unit	*uc, *msuc;			/* -> result and its msu */
1198  Int	msudigs;			/* digits in res msu */
1199  #if DECCHECK
1200  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1201  #endif
1202
1203  if (rhs->exponent!=0 || decNumberIsSpecial(rhs) || decNumberIsNegative(rhs)) {
1204    decStatus(res, DEC_Invalid_operation, set);
1205    return res;
1206    }
1207  /* operand is valid */
1208  ua=rhs->lsu;				/* bottom-up */
1209  uc=res->lsu;				/* .. */
1210  msua=ua+D2U(rhs->digits)-1;		/* -> msu of rhs */
1211  msuc=uc+D2U(set->digits)-1;		/* -> msu of result */
1212  msudigs=MSUDIGITS(set->digits);	/* [faster than remainder] */
1213  for (; uc<=msuc; ua++, uc++) {	/* Unit loop */
1214    Unit a;				/* extract unit */
1215    Int  i, j;				/* work */
1216    if (ua>msua) a=0;
1217     else a=*ua;
1218    *uc=0;				/* can now write back */
1219    /* always need to examine all bits in rhs */
1220    /* This loop could be unrolled and/or use BIN2BCD tables */
1221    for (i=0; i<DECDPUN; i++) {
1222      if ((~a)&1) *uc=*uc+(Unit)powers[i];   /* effect INVERT */
1223      j=a%10;
1224      a=a/10;
1225      if (j>1) {
1226	decStatus(res, DEC_Invalid_operation, set);
1227	return res;
1228	}
1229      if (uc==msuc && i==msudigs-1) break;   /* just did final digit */
1230      } /* each digit */
1231    } /* each unit */
1232  /* [here uc-1 is the msu of the result] */
1233  res->digits=decGetDigits(res->lsu, uc-res->lsu);
1234  res->exponent=0;			/* integer */
1235  res->bits=0;				/* sign=0 */
1236  return res;  /* [no status to set] */
1237  } /* decNumberInvert */
1238
1239/* ------------------------------------------------------------------ */
1240/* decNumberLn -- natural logarithm				      */
1241/*								      */
1242/*   This computes C = ln(A)					      */
1243/*								      */
1244/*   res is C, the result.  C may be A				      */
1245/*   rhs is A							      */
1246/*   set is the context; note that rounding mode has no effect	      */
1247/*								      */
1248/* C must have space for set->digits digits.			      */
1249/*								      */
1250/* Notable cases:						      */
1251/*   A<0 -> Invalid						      */
1252/*   A=0 -> -Infinity (Exact)					      */
1253/*   A=+Infinity -> +Infinity (Exact)				      */
1254/*   A=1 exactly -> 0 (Exact)					      */
1255/*								      */
1256/* Mathematical function restrictions apply (see above); a NaN is     */
1257/* returned with Invalid_operation if a restriction is violated.      */
1258/*								      */
1259/* An Inexact result is rounded using DEC_ROUND_HALF_EVEN; it will    */
1260/* almost always be correctly rounded, but may be up to 1 ulp in      */
1261/* error in rare cases. 					      */
1262/* ------------------------------------------------------------------ */
1263/* This is a wrapper for decLnOp which can handle the slightly wider  */
1264/* (+11) range needed by Ln, Log10, etc. (which may have to be able   */
1265/* to calculate at p+e+2).					      */
1266/* ------------------------------------------------------------------ */
1267decNumber * decNumberLn(decNumber *res, const decNumber *rhs,
1268			decContext *set) {
1269  uInt status=0;		   /* accumulator */
1270  #if DECSUBSET
1271  decNumber *allocrhs=NULL;	   /* non-NULL if rounded rhs allocated */
1272  #endif
1273
1274  #if DECCHECK
1275  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1276  #endif
1277
1278  /* Check restrictions; this is a math function; if not violated */
1279  /* then carry out the operation. */
1280  if (!decCheckMath(rhs, set, &status)) do { /* protect allocation */
1281    #if DECSUBSET
1282    if (!set->extended) {
1283      /* reduce operand and set lostDigits status, as needed */
1284      if (rhs->digits>set->digits) {
1285	allocrhs=decRoundOperand(rhs, set, &status);
1286	if (allocrhs==NULL) break;
1287	rhs=allocrhs;
1288	}
1289      /* special check in subset for rhs=0 */
1290      if (ISZERO(rhs)) {		/* +/- zeros -> error */
1291	status|=DEC_Invalid_operation;
1292	break;}
1293      } /* extended=0 */
1294    #endif
1295    decLnOp(res, rhs, set, &status);
1296    } while(0); 			/* end protected */
1297
1298  #if DECSUBSET
1299  free(allocrhs);	/* drop any storage used */
1300  #endif
1301  /* apply significant status */
1302  if (status!=0) decStatus(res, status, set);
1303  #if DECCHECK
1304  decCheckInexact(res, set);
1305  #endif
1306  return res;
1307  } /* decNumberLn */
1308
1309/* ------------------------------------------------------------------ */
1310/* decNumberLogB - get adjusted exponent, by 754 rules		      */
1311/*								      */
1312/*   This computes C = adjustedexponent(A)			      */
1313/*								      */
1314/*   res is C, the result.  C may be A				      */
1315/*   rhs is A							      */
1316/*   set is the context, used only for digits and status	      */
1317/*								      */
1318/* C must have space for 10 digits (A might have 10**9 digits and     */
1319/* an exponent of +999999999, or one digit and an exponent of	      */
1320/* -1999999999).						      */
1321/*								      */
1322/* This returns the adjusted exponent of A after (in theory) padding  */
1323/* with zeros on the right to set->digits digits while keeping the    */
1324/* same value.	The exponent is not limited by emin/emax.	      */
1325/*								      */
1326/* Notable cases:						      */
1327/*   A<0 -> Use |A|						      */
1328/*   A=0 -> -Infinity (Division by zero)			      */
1329/*   A=Infinite -> +Infinity (Exact)				      */
1330/*   A=1 exactly -> 0 (Exact)					      */
1331/*   NaNs are propagated as usual				      */
1332/* ------------------------------------------------------------------ */
1333decNumber * decNumberLogB(decNumber *res, const decNumber *rhs,
1334			  decContext *set) {
1335  uInt status=0;		   /* accumulator */
1336
1337  #if DECCHECK
1338  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1339  #endif
1340
1341  /* NaNs as usual; Infinities return +Infinity; 0->oops */
1342  if (decNumberIsNaN(rhs)) decNaNs(res, rhs, NULL, set, &status);
1343   else if (decNumberIsInfinite(rhs)) decNumberCopyAbs(res, rhs);
1344   else if (decNumberIsZero(rhs)) {
1345    decNumberZero(res); 		/* prepare for Infinity */
1346    res->bits=DECNEG|DECINF;		/* -Infinity */
1347    status|=DEC_Division_by_zero;	/* as per 754 */
1348    }
1349   else { /* finite non-zero */
1350    Int ae=rhs->exponent+rhs->digits-1; /* adjusted exponent */
1351    decNumberFromInt32(res, ae);	/* lay it out */
1352    }
1353
1354  if (status!=0) decStatus(res, status, set);
1355  return res;
1356  } /* decNumberLogB */
1357
1358/* ------------------------------------------------------------------ */
1359/* decNumberLog10 -- logarithm in base 10			      */
1360/*								      */
1361/*   This computes C = log10(A) 				      */
1362/*								      */
1363/*   res is C, the result.  C may be A				      */
1364/*   rhs is A							      */
1365/*   set is the context; note that rounding mode has no effect	      */
1366/*								      */
1367/* C must have space for set->digits digits.			      */
1368/*								      */
1369/* Notable cases:						      */
1370/*   A<0 -> Invalid						      */
1371/*   A=0 -> -Infinity (Exact)					      */
1372/*   A=+Infinity -> +Infinity (Exact)				      */
1373/*   A=10**n (if n is an integer) -> n (Exact)			      */
1374/*								      */
1375/* Mathematical function restrictions apply (see above); a NaN is     */
1376/* returned with Invalid_operation if a restriction is violated.      */
1377/*								      */
1378/* An Inexact result is rounded using DEC_ROUND_HALF_EVEN; it will    */
1379/* almost always be correctly rounded, but may be up to 1 ulp in      */
1380/* error in rare cases. 					      */
1381/* ------------------------------------------------------------------ */
1382/* This calculates ln(A)/ln(10) using appropriate precision.  For     */
1383/* ln(A) this is the max(p, rhs->digits + t) + 3, where p is the      */
1384/* requested digits and t is the number of digits in the exponent     */
1385/* (maximum 6).  For ln(10) it is p + 3; this is often handled by the */
1386/* fastpath in decLnOp.  The final division is done to the requested  */
1387/* precision.							      */
1388/* ------------------------------------------------------------------ */
1389decNumber * decNumberLog10(decNumber *res, const decNumber *rhs,
1390			  decContext *set) {
1391  uInt status=0, ignore=0;	   /* status accumulators */
1392  uInt needbytes;		   /* for space calculations */
1393  Int p;			   /* working precision */
1394  Int t;			   /* digits in exponent of A */
1395
1396  /* buffers for a and b working decimals */
1397  /* (adjustment calculator, same size) */
1398  decNumber bufa[D2N(DECBUFFER+2)];
1399  decNumber *allocbufa=NULL;	   /* -> allocated bufa, iff allocated */
1400  decNumber *a=bufa;		   /* temporary a */
1401  decNumber bufb[D2N(DECBUFFER+2)];
1402  decNumber *allocbufb=NULL;	   /* -> allocated bufb, iff allocated */
1403  decNumber *b=bufb;		   /* temporary b */
1404  decNumber bufw[D2N(10)];	   /* working 2-10 digit number */
1405  decNumber *w=bufw;		   /* .. */
1406  #if DECSUBSET
1407  decNumber *allocrhs=NULL;	   /* non-NULL if rounded rhs allocated */
1408  #endif
1409
1410  decContext aset;		   /* working context */
1411
1412  #if DECCHECK
1413  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1414  #endif
1415
1416  /* Check restrictions; this is a math function; if not violated */
1417  /* then carry out the operation. */
1418  if (!decCheckMath(rhs, set, &status)) do { /* protect malloc */
1419    #if DECSUBSET
1420    if (!set->extended) {
1421      /* reduce operand and set lostDigits status, as needed */
1422      if (rhs->digits>set->digits) {
1423	allocrhs=decRoundOperand(rhs, set, &status);
1424	if (allocrhs==NULL) break;
1425	rhs=allocrhs;
1426	}
1427      /* special check in subset for rhs=0 */
1428      if (ISZERO(rhs)) {		/* +/- zeros -> error */
1429	status|=DEC_Invalid_operation;
1430	break;}
1431      } /* extended=0 */
1432    #endif
1433
1434    decContextDefault(&aset, DEC_INIT_DECIMAL64); /* clean context */
1435
1436    /* handle exact powers of 10; only check if +ve finite */
1437    if (!(rhs->bits&(DECNEG|DECSPECIAL)) && !ISZERO(rhs)) {
1438      Int residue=0;		   /* (no residue) */
1439      uInt copystat=0;		   /* clean status */
1440
1441      /* round to a single digit... */
1442      aset.digits=1;
1443      decCopyFit(w, rhs, &aset, &residue, &copystat); /* copy & shorten */
1444      /* if exact and the digit is 1, rhs is a power of 10 */
1445      if (!(copystat&DEC_Inexact) && w->lsu[0]==1) {
1446	/* the exponent, conveniently, is the power of 10; making */
1447	/* this the result needs a little care as it might not fit, */
1448	/* so first convert it into the working number, and then move */
1449	/* to res */
1450	decNumberFromInt32(w, w->exponent);
1451	residue=0;
1452	decCopyFit(res, w, set, &residue, &status); /* copy & round */
1453	decFinish(res, set, &residue, &status);     /* cleanup/set flags */
1454	break;
1455	} /* not a power of 10 */
1456      } /* not a candidate for exact */
1457
1458    /* simplify the information-content calculation to use 'total */
1459    /* number of digits in a, including exponent' as compared to the */
1460    /* requested digits, as increasing this will only rarely cost an */
1461    /* iteration in ln(a) anyway */
1462    t=6;				/* it can never be >6 */
1463
1464    /* allocate space when needed... */
1465    p=(rhs->digits+t>set->digits?rhs->digits+t:set->digits)+3;
1466    needbytes=sizeof(decNumber)+(D2U(p)-1)*sizeof(Unit);
1467    if (needbytes>sizeof(bufa)) {	/* need malloc space */
1468      allocbufa=(decNumber *)malloc(needbytes);
1469      if (allocbufa==NULL) {		/* hopeless -- abandon */
1470	status|=DEC_Insufficient_storage;
1471	break;}
1472      a=allocbufa;			/* use the allocated space */
1473      }
1474    aset.digits=p;			/* as calculated */
1475    aset.emax=DEC_MAX_MATH;		/* usual bounds */
1476    aset.emin=-DEC_MAX_MATH;		/* .. */
1477    aset.clamp=0;			/* and no concrete format */
1478    decLnOp(a, rhs, &aset, &status);	/* a=ln(rhs) */
1479
1480    /* skip the division if the result so far is infinite, NaN, or */
1481    /* zero, or there was an error; note NaN from sNaN needs copy */
1482    if (status&DEC_NaNs && !(status&DEC_sNaN)) break;
1483    if (a->bits&DECSPECIAL || ISZERO(a)) {
1484      decNumberCopy(res, a);		/* [will fit] */
1485      break;}
1486
1487    /* for ln(10) an extra 3 digits of precision are needed */
1488    p=set->digits+3;
1489    needbytes=sizeof(decNumber)+(D2U(p)-1)*sizeof(Unit);
1490    if (needbytes>sizeof(bufb)) {	/* need malloc space */
1491      allocbufb=(decNumber *)malloc(needbytes);
1492      if (allocbufb==NULL) {		/* hopeless -- abandon */
1493	status|=DEC_Insufficient_storage;
1494	break;}
1495      b=allocbufb;			/* use the allocated space */
1496      }
1497    decNumberZero(w);			/* set up 10... */
1498    #if DECDPUN==1
1499    w->lsu[1]=1; w->lsu[0]=0;		/* .. */
1500    #else
1501    w->lsu[0]=10;			/* .. */
1502    #endif
1503    w->digits=2;			/* .. */
1504
1505    aset.digits=p;
1506    decLnOp(b, w, &aset, &ignore);	/* b=ln(10) */
1507
1508    aset.digits=set->digits;		/* for final divide */
1509    decDivideOp(res, a, b, &aset, DIVIDE, &status); /* into result */
1510    } while(0); 			/* [for break] */
1511
1512  free(allocbufa); /* drop any storage used */
1513  free(allocbufb); /* .. */
1514  #if DECSUBSET
1515  free(allocrhs);	/* .. */
1516  #endif
1517  /* apply significant status */
1518  if (status!=0) decStatus(res, status, set);
1519  #if DECCHECK
1520  decCheckInexact(res, set);
1521  #endif
1522  return res;
1523  } /* decNumberLog10 */
1524
1525/* ------------------------------------------------------------------ */
1526/* decNumberMax -- compare two Numbers and return the maximum	      */
1527/*								      */
1528/*   This computes C = A ? B, returning the maximum by 754 rules      */
1529/*								      */
1530/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
1531/*   lhs is A							      */
1532/*   rhs is B							      */
1533/*   set is the context 					      */
1534/*								      */
1535/* C must have space for set->digits digits.			      */
1536/* ------------------------------------------------------------------ */
1537decNumber * decNumberMax(decNumber *res, const decNumber *lhs,
1538			 const decNumber *rhs, decContext *set) {
1539  uInt status=0;			/* accumulator */
1540  decCompareOp(res, lhs, rhs, set, COMPMAX, &status);
1541  if (status!=0) decStatus(res, status, set);
1542  #if DECCHECK
1543  decCheckInexact(res, set);
1544  #endif
1545  return res;
1546  } /* decNumberMax */
1547
1548/* ------------------------------------------------------------------ */
1549/* decNumberMaxMag -- compare and return the maximum by magnitude     */
1550/*								      */
1551/*   This computes C = A ? B, returning the maximum by 754 rules      */
1552/*								      */
1553/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
1554/*   lhs is A							      */
1555/*   rhs is B							      */
1556/*   set is the context 					      */
1557/*								      */
1558/* C must have space for set->digits digits.			      */
1559/* ------------------------------------------------------------------ */
1560decNumber * decNumberMaxMag(decNumber *res, const decNumber *lhs,
1561			 const decNumber *rhs, decContext *set) {
1562  uInt status=0;			/* accumulator */
1563  decCompareOp(res, lhs, rhs, set, COMPMAXMAG, &status);
1564  if (status!=0) decStatus(res, status, set);
1565  #if DECCHECK
1566  decCheckInexact(res, set);
1567  #endif
1568  return res;
1569  } /* decNumberMaxMag */
1570
1571/* ------------------------------------------------------------------ */
1572/* decNumberMin -- compare two Numbers and return the minimum	      */
1573/*								      */
1574/*   This computes C = A ? B, returning the minimum by 754 rules      */
1575/*								      */
1576/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
1577/*   lhs is A							      */
1578/*   rhs is B							      */
1579/*   set is the context 					      */
1580/*								      */
1581/* C must have space for set->digits digits.			      */
1582/* ------------------------------------------------------------------ */
1583decNumber * decNumberMin(decNumber *res, const decNumber *lhs,
1584			 const decNumber *rhs, decContext *set) {
1585  uInt status=0;			/* accumulator */
1586  decCompareOp(res, lhs, rhs, set, COMPMIN, &status);
1587  if (status!=0) decStatus(res, status, set);
1588  #if DECCHECK
1589  decCheckInexact(res, set);
1590  #endif
1591  return res;
1592  } /* decNumberMin */
1593
1594/* ------------------------------------------------------------------ */
1595/* decNumberMinMag -- compare and return the minimum by magnitude     */
1596/*								      */
1597/*   This computes C = A ? B, returning the minimum by 754 rules      */
1598/*								      */
1599/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
1600/*   lhs is A							      */
1601/*   rhs is B							      */
1602/*   set is the context 					      */
1603/*								      */
1604/* C must have space for set->digits digits.			      */
1605/* ------------------------------------------------------------------ */
1606decNumber * decNumberMinMag(decNumber *res, const decNumber *lhs,
1607			 const decNumber *rhs, decContext *set) {
1608  uInt status=0;			/* accumulator */
1609  decCompareOp(res, lhs, rhs, set, COMPMINMAG, &status);
1610  if (status!=0) decStatus(res, status, set);
1611  #if DECCHECK
1612  decCheckInexact(res, set);
1613  #endif
1614  return res;
1615  } /* decNumberMinMag */
1616
1617/* ------------------------------------------------------------------ */
1618/* decNumberMinus -- prefix minus operator			      */
1619/*								      */
1620/*   This computes C = 0 - A					      */
1621/*								      */
1622/*   res is C, the result.  C may be A				      */
1623/*   rhs is A							      */
1624/*   set is the context 					      */
1625/*								      */
1626/* See also decNumberCopyNegate for a quiet bitwise version of this.  */
1627/* C must have space for set->digits digits.			      */
1628/* ------------------------------------------------------------------ */
1629/* Simply use AddOp for the subtract, which will do the necessary.    */
1630/* ------------------------------------------------------------------ */
1631decNumber * decNumberMinus(decNumber *res, const decNumber *rhs,
1632			   decContext *set) {
1633  decNumber dzero;
1634  uInt status=0;			/* accumulator */
1635
1636  #if DECCHECK
1637  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1638  #endif
1639
1640  decNumberZero(&dzero);		/* make 0 */
1641  dzero.exponent=rhs->exponent; 	/* [no coefficient expansion] */
1642  decAddOp(res, &dzero, rhs, set, DECNEG, &status);
1643  if (status!=0) decStatus(res, status, set);
1644  #if DECCHECK
1645  decCheckInexact(res, set);
1646  #endif
1647  return res;
1648  } /* decNumberMinus */
1649
1650/* ------------------------------------------------------------------ */
1651/* decNumberNextMinus -- next towards -Infinity 		      */
1652/*								      */
1653/*   This computes C = A - infinitesimal, rounded towards -Infinity   */
1654/*								      */
1655/*   res is C, the result.  C may be A				      */
1656/*   rhs is A							      */
1657/*   set is the context 					      */
1658/*								      */
1659/* This is a generalization of 754 NextDown.			      */
1660/* ------------------------------------------------------------------ */
1661decNumber * decNumberNextMinus(decNumber *res, const decNumber *rhs,
1662			       decContext *set) {
1663  decNumber dtiny;			     /* constant */
1664  decContext workset=*set;		     /* work */
1665  uInt status=0;			     /* accumulator */
1666  #if DECCHECK
1667  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1668  #endif
1669
1670  /* +Infinity is the special case */
1671  if ((rhs->bits&(DECINF|DECNEG))==DECINF) {
1672    decSetMaxValue(res, set);		     /* is +ve */
1673    /* there is no status to set */
1674    return res;
1675    }
1676  decNumberZero(&dtiny);		     /* start with 0 */
1677  dtiny.lsu[0]=1;			     /* make number that is .. */
1678  dtiny.exponent=DEC_MIN_EMIN-1;	     /* .. smaller than tiniest */
1679  workset.round=DEC_ROUND_FLOOR;
1680  decAddOp(res, rhs, &dtiny, &workset, DECNEG, &status);
1681  status&=DEC_Invalid_operation|DEC_sNaN;    /* only sNaN Invalid please */
1682  if (status!=0) decStatus(res, status, set);
1683  return res;
1684  } /* decNumberNextMinus */
1685
1686/* ------------------------------------------------------------------ */
1687/* decNumberNextPlus -- next towards +Infinity			      */
1688/*								      */
1689/*   This computes C = A + infinitesimal, rounded towards +Infinity   */
1690/*								      */
1691/*   res is C, the result.  C may be A				      */
1692/*   rhs is A							      */
1693/*   set is the context 					      */
1694/*								      */
1695/* This is a generalization of 754 NextUp.			      */
1696/* ------------------------------------------------------------------ */
1697decNumber * decNumberNextPlus(decNumber *res, const decNumber *rhs,
1698			      decContext *set) {
1699  decNumber dtiny;			     /* constant */
1700  decContext workset=*set;		     /* work */
1701  uInt status=0;			     /* accumulator */
1702  #if DECCHECK
1703  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1704  #endif
1705
1706  /* -Infinity is the special case */
1707  if ((rhs->bits&(DECINF|DECNEG))==(DECINF|DECNEG)) {
1708    decSetMaxValue(res, set);
1709    res->bits=DECNEG;			     /* negative */
1710    /* there is no status to set */
1711    return res;
1712    }
1713  decNumberZero(&dtiny);		     /* start with 0 */
1714  dtiny.lsu[0]=1;			     /* make number that is .. */
1715  dtiny.exponent=DEC_MIN_EMIN-1;	     /* .. smaller than tiniest */
1716  workset.round=DEC_ROUND_CEILING;
1717  decAddOp(res, rhs, &dtiny, &workset, 0, &status);
1718  status&=DEC_Invalid_operation|DEC_sNaN;    /* only sNaN Invalid please */
1719  if (status!=0) decStatus(res, status, set);
1720  return res;
1721  } /* decNumberNextPlus */
1722
1723/* ------------------------------------------------------------------ */
1724/* decNumberNextToward -- next towards rhs			      */
1725/*								      */
1726/*   This computes C = A +/- infinitesimal, rounded towards	      */
1727/*   +/-Infinity in the direction of B, as per 754-1985 nextafter     */
1728/*   modified during revision but dropped from 754-2008.	      */
1729/*								      */
1730/*   res is C, the result.  C may be A or B.			      */
1731/*   lhs is A							      */
1732/*   rhs is B							      */
1733/*   set is the context 					      */
1734/*								      */
1735/* This is a generalization of 754-1985 NextAfter.		      */
1736/* ------------------------------------------------------------------ */
1737decNumber * decNumberNextToward(decNumber *res, const decNumber *lhs,
1738				const decNumber *rhs, decContext *set) {
1739  decNumber dtiny;			     /* constant */
1740  decContext workset=*set;		     /* work */
1741  Int result;				     /* .. */
1742  uInt status=0;			     /* accumulator */
1743  #if DECCHECK
1744  if (decCheckOperands(res, lhs, rhs, set)) return res;
1745  #endif
1746
1747  if (decNumberIsNaN(lhs) || decNumberIsNaN(rhs)) {
1748    decNaNs(res, lhs, rhs, set, &status);
1749    }
1750   else { /* Is numeric, so no chance of sNaN Invalid, etc. */
1751    result=decCompare(lhs, rhs, 0);	/* sign matters */
1752    if (result==BADINT) status|=DEC_Insufficient_storage; /* rare */
1753     else { /* valid compare */
1754      if (result==0) decNumberCopySign(res, lhs, rhs); /* easy */
1755       else { /* differ: need NextPlus or NextMinus */
1756	uByte sub;			/* add or subtract */
1757	if (result<0) { 		/* lhs<rhs, do nextplus */
1758	  /* -Infinity is the special case */
1759	  if ((lhs->bits&(DECINF|DECNEG))==(DECINF|DECNEG)) {
1760	    decSetMaxValue(res, set);
1761	    res->bits=DECNEG;		/* negative */
1762	    return res; 		/* there is no status to set */
1763	    }
1764	  workset.round=DEC_ROUND_CEILING;
1765	  sub=0;			/* add, please */
1766	  } /* plus */
1767	 else { 			/* lhs>rhs, do nextminus */
1768	  /* +Infinity is the special case */
1769	  if ((lhs->bits&(DECINF|DECNEG))==DECINF) {
1770	    decSetMaxValue(res, set);
1771	    return res; 		/* there is no status to set */
1772	    }
1773	  workset.round=DEC_ROUND_FLOOR;
1774	  sub=DECNEG;			/* subtract, please */
1775	  } /* minus */
1776	decNumberZero(&dtiny);		/* start with 0 */
1777	dtiny.lsu[0]=1; 		/* make number that is .. */
1778	dtiny.exponent=DEC_MIN_EMIN-1;	/* .. smaller than tiniest */
1779	decAddOp(res, lhs, &dtiny, &workset, sub, &status); /* + or - */
1780	/* turn off exceptions if the result is a normal number */
1781	/* (including Nmin), otherwise let all status through */
1782	if (decNumberIsNormal(res, set)) status=0;
1783	} /* unequal */
1784      } /* compare OK */
1785    } /* numeric */
1786  if (status!=0) decStatus(res, status, set);
1787  return res;
1788  } /* decNumberNextToward */
1789
1790/* ------------------------------------------------------------------ */
1791/* decNumberOr -- OR two Numbers, digitwise			      */
1792/*								      */
1793/*   This computes C = A | B					      */
1794/*								      */
1795/*   res is C, the result.  C may be A and/or B (e.g., X=X|X)	      */
1796/*   lhs is A							      */
1797/*   rhs is B							      */
1798/*   set is the context (used for result length and error report)     */
1799/*								      */
1800/* C must have space for set->digits digits.			      */
1801/*								      */
1802/* Logical function restrictions apply (see above); a NaN is	      */
1803/* returned with Invalid_operation if a restriction is violated.      */
1804/* ------------------------------------------------------------------ */
1805decNumber * decNumberOr(decNumber *res, const decNumber *lhs,
1806			const decNumber *rhs, decContext *set) {
1807  const Unit *ua, *ub;			/* -> operands */
1808  const Unit *msua, *msub;		/* -> operand msus */
1809  Unit	*uc, *msuc;			/* -> result and its msu */
1810  Int	msudigs;			/* digits in res msu */
1811  #if DECCHECK
1812  if (decCheckOperands(res, lhs, rhs, set)) return res;
1813  #endif
1814
1815  if (lhs->exponent!=0 || decNumberIsSpecial(lhs) || decNumberIsNegative(lhs)
1816   || rhs->exponent!=0 || decNumberIsSpecial(rhs) || decNumberIsNegative(rhs)) {
1817    decStatus(res, DEC_Invalid_operation, set);
1818    return res;
1819    }
1820  /* operands are valid */
1821  ua=lhs->lsu;				/* bottom-up */
1822  ub=rhs->lsu;				/* .. */
1823  uc=res->lsu;				/* .. */
1824  msua=ua+D2U(lhs->digits)-1;		/* -> msu of lhs */
1825  msub=ub+D2U(rhs->digits)-1;		/* -> msu of rhs */
1826  msuc=uc+D2U(set->digits)-1;		/* -> msu of result */
1827  msudigs=MSUDIGITS(set->digits);	/* [faster than remainder] */
1828  for (; uc<=msuc; ua++, ub++, uc++) {	/* Unit loop */
1829    Unit a, b;				/* extract units */
1830    if (ua>msua) a=0;
1831     else a=*ua;
1832    if (ub>msub) b=0;
1833     else b=*ub;
1834    *uc=0;				/* can now write back */
1835    if (a|b) {				/* maybe 1 bits to examine */
1836      Int i, j;
1837      /* This loop could be unrolled and/or use BIN2BCD tables */
1838      for (i=0; i<DECDPUN; i++) {
1839	if ((a|b)&1) *uc=*uc+(Unit)powers[i];	  /* effect OR */
1840	j=a%10;
1841	a=a/10;
1842	j|=b%10;
1843	b=b/10;
1844	if (j>1) {
1845	  decStatus(res, DEC_Invalid_operation, set);
1846	  return res;
1847	  }
1848	if (uc==msuc && i==msudigs-1) break;	  /* just did final digit */
1849	} /* each digit */
1850      } /* non-zero */
1851    } /* each unit */
1852  /* [here uc-1 is the msu of the result] */
1853  res->digits=decGetDigits(res->lsu, uc-res->lsu);
1854  res->exponent=0;			/* integer */
1855  res->bits=0;				/* sign=0 */
1856  return res;  /* [no status to set] */
1857  } /* decNumberOr */
1858
1859/* ------------------------------------------------------------------ */
1860/* decNumberPlus -- prefix plus operator			      */
1861/*								      */
1862/*   This computes C = 0 + A					      */
1863/*								      */
1864/*   res is C, the result.  C may be A				      */
1865/*   rhs is A							      */
1866/*   set is the context 					      */
1867/*								      */
1868/* See also decNumberCopy for a quiet bitwise version of this.	      */
1869/* C must have space for set->digits digits.			      */
1870/* ------------------------------------------------------------------ */
1871/* This simply uses AddOp; Add will take fast path after preparing A. */
1872/* Performance is a concern here, as this routine is often used to    */
1873/* check operands and apply rounding and overflow/underflow testing.  */
1874/* ------------------------------------------------------------------ */
1875decNumber * decNumberPlus(decNumber *res, const decNumber *rhs,
1876			  decContext *set) {
1877  decNumber dzero;
1878  uInt status=0;			/* accumulator */
1879  #if DECCHECK
1880  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
1881  #endif
1882
1883  decNumberZero(&dzero);		/* make 0 */
1884  dzero.exponent=rhs->exponent; 	/* [no coefficient expansion] */
1885  decAddOp(res, &dzero, rhs, set, 0, &status);
1886  if (status!=0) decStatus(res, status, set);
1887  #if DECCHECK
1888  decCheckInexact(res, set);
1889  #endif
1890  return res;
1891  } /* decNumberPlus */
1892
1893/* ------------------------------------------------------------------ */
1894/* decNumberMultiply -- multiply two Numbers			      */
1895/*								      */
1896/*   This computes C = A x B					      */
1897/*								      */
1898/*   res is C, the result.  C may be A and/or B (e.g., X=X+X)	      */
1899/*   lhs is A							      */
1900/*   rhs is B							      */
1901/*   set is the context 					      */
1902/*								      */
1903/* C must have space for set->digits digits.			      */
1904/* ------------------------------------------------------------------ */
1905decNumber * decNumberMultiply(decNumber *res, const decNumber *lhs,
1906			      const decNumber *rhs, decContext *set) {
1907  uInt status=0;		   /* accumulator */
1908  decMultiplyOp(res, lhs, rhs, set, &status);
1909  if (status!=0) decStatus(res, status, set);
1910  #if DECCHECK
1911  decCheckInexact(res, set);
1912  #endif
1913  return res;
1914  } /* decNumberMultiply */
1915
1916/* ------------------------------------------------------------------ */
1917/* decNumberPower -- raise a number to a power			      */
1918/*								      */
1919/*   This computes C = A ** B					      */
1920/*								      */
1921/*   res is C, the result.  C may be A and/or B (e.g., X=X**X)	      */
1922/*   lhs is A							      */
1923/*   rhs is B							      */
1924/*   set is the context 					      */
1925/*								      */
1926/* C must have space for set->digits digits.			      */
1927/*								      */
1928/* Mathematical function restrictions apply (see above); a NaN is     */
1929/* returned with Invalid_operation if a restriction is violated.      */
1930/*								      */
1931/* However, if 1999999997<=B<=999999999 and B is an integer then the  */
1932/* restrictions on A and the context are relaxed to the usual bounds, */
1933/* for compatibility with the earlier (integer power only) version    */
1934/* of this function.						      */
1935/*								      */
1936/* When B is an integer, the result may be exact, even if rounded.    */
1937/*								      */
1938/* The final result is rounded according to the context; it will      */
1939/* almost always be correctly rounded, but may be up to 1 ulp in      */
1940/* error in rare cases. 					      */
1941/* ------------------------------------------------------------------ */
1942decNumber * decNumberPower(decNumber *res, const decNumber *lhs,
1943			   const decNumber *rhs, decContext *set) {
1944  #if DECSUBSET
1945  decNumber *alloclhs=NULL;	   /* non-NULL if rounded lhs allocated */
1946  decNumber *allocrhs=NULL;	   /* .., rhs */
1947  #endif
1948  decNumber *allocdac=NULL;	   /* -> allocated acc buffer, iff used */
1949  decNumber *allocinv=NULL;	   /* -> allocated 1/x buffer, iff used */
1950  Int	reqdigits=set->digits;	   /* requested DIGITS */
1951  Int	n;			   /* rhs in binary */
1952  Flag	rhsint=0;		   /* 1 if rhs is an integer */
1953  Flag	useint=0;		   /* 1 if can use integer calculation */
1954  Flag	isoddint=0;		   /* 1 if rhs is an integer and odd */
1955  Int	i;			   /* work */
1956  #if DECSUBSET
1957  Int	dropped;		   /* .. */
1958  #endif
1959  uInt	needbytes;		   /* buffer size needed */
1960  Flag	seenbit;		   /* seen a bit while powering */
1961  Int	residue=0;		   /* rounding residue */
1962  uInt	status=0;		   /* accumulators */
1963  uByte bits=0; 		   /* result sign if errors */
1964  decContext aset;		   /* working context */
1965  decNumber dnOne;		   /* work value 1... */
1966  /* local accumulator buffer [a decNumber, with digits+elength+1 digits] */
1967  decNumber dacbuff[D2N(DECBUFFER+9)];
1968  decNumber *dac=dacbuff;	   /* -> result accumulator */
1969  /* same again for possible 1/lhs calculation */
1970  decNumber invbuff[D2N(DECBUFFER+9)];
1971
1972  #if DECCHECK
1973  if (decCheckOperands(res, lhs, rhs, set)) return res;
1974  #endif
1975
1976  do {				   /* protect allocated storage */
1977    #if DECSUBSET
1978    if (!set->extended) { /* reduce operands and set status, as needed */
1979      if (lhs->digits>reqdigits) {
1980	alloclhs=decRoundOperand(lhs, set, &status);
1981	if (alloclhs==NULL) break;
1982	lhs=alloclhs;
1983	}
1984      if (rhs->digits>reqdigits) {
1985	allocrhs=decRoundOperand(rhs, set, &status);
1986	if (allocrhs==NULL) break;
1987	rhs=allocrhs;
1988	}
1989      }
1990    #endif
1991    /* [following code does not require input rounding] */
1992
1993    /* handle NaNs and rhs Infinity (lhs infinity is harder) */
1994    if (SPECIALARGS) {
1995      if (decNumberIsNaN(lhs) || decNumberIsNaN(rhs)) { /* NaNs */
1996	decNaNs(res, lhs, rhs, set, &status);
1997	break;}
1998      if (decNumberIsInfinite(rhs)) {	/* rhs Infinity */
1999	Flag rhsneg=rhs->bits&DECNEG;	/* save rhs sign */
2000	if (decNumberIsNegative(lhs)	/* lhs<0 */
2001	 && !decNumberIsZero(lhs))	/* .. */
2002	  status|=DEC_Invalid_operation;
2003	 else { 			/* lhs >=0 */
2004	  decNumberZero(&dnOne);	/* set up 1 */
2005	  dnOne.lsu[0]=1;
2006	  decNumberCompare(dac, lhs, &dnOne, set); /* lhs ? 1 */
2007	  decNumberZero(res);		/* prepare for 0/1/Infinity */
2008	  if (decNumberIsNegative(dac)) {    /* lhs<1 */
2009	    if (rhsneg) res->bits|=DECINF;   /* +Infinity [else is +0] */
2010	    }
2011	   else if (dac->lsu[0]==0) {	     /* lhs=1 */
2012	    /* 1**Infinity is inexact, so return fully-padded 1.0000 */
2013	    Int shift=set->digits-1;
2014	    *res->lsu=1;		     /* was 0, make int 1 */
2015	    res->digits=decShiftToMost(res->lsu, 1, shift);
2016	    res->exponent=-shift;	     /* make 1.0000... */
2017	    status|=DEC_Inexact|DEC_Rounded; /* deemed inexact */
2018	    }
2019	   else {			     /* lhs>1 */
2020	    if (!rhsneg) res->bits|=DECINF;  /* +Infinity [else is +0] */
2021	    }
2022	  } /* lhs>=0 */
2023	break;}
2024      /* [lhs infinity drops through] */
2025      } /* specials */
2026
2027    /* Original rhs may be an integer that fits and is in range */
2028    n=decGetInt(rhs);
2029    if (n!=BADINT) {			/* it is an integer */
2030      rhsint=1; 			/* record the fact for 1**n */
2031      isoddint=(Flag)n&1;		/* [works even if big] */
2032      if (n!=BIGEVEN && n!=BIGODD)	/* can use integer path? */
2033	useint=1;			/* looks good */
2034      }
2035
2036    if (decNumberIsNegative(lhs)	/* -x .. */
2037      && isoddint) bits=DECNEG; 	/* .. to an odd power */
2038
2039    /* handle LHS infinity */
2040    if (decNumberIsInfinite(lhs)) {	/* [NaNs already handled] */
2041      uByte rbits=rhs->bits;		/* save */
2042      decNumberZero(res);		/* prepare */
2043      if (n==0) *res->lsu=1;		/* [-]Inf**0 => 1 */
2044       else {
2045	/* -Inf**nonint -> error */
2046	if (!rhsint && decNumberIsNegative(lhs)) {
2047	  status|=DEC_Invalid_operation;     /* -Inf**nonint is error */
2048	  break;}
2049	if (!(rbits & DECNEG)) bits|=DECINF; /* was not a **-n */
2050	/* [otherwise will be 0 or -0] */
2051	res->bits=bits;
2052	}
2053      break;}
2054
2055    /* similarly handle LHS zero */
2056    if (decNumberIsZero(lhs)) {
2057      if (n==0) {			     /* 0**0 => Error */
2058	#if DECSUBSET
2059	if (!set->extended) {		     /* [unless subset] */
2060	  decNumberZero(res);
2061	  *res->lsu=1;			     /* return 1 */
2062	  break;}
2063	#endif
2064	status|=DEC_Invalid_operation;
2065	}
2066       else {				     /* 0**x */
2067	uByte rbits=rhs->bits;		     /* save */
2068	if (rbits & DECNEG) {		     /* was a 0**(-n) */
2069	  #if DECSUBSET
2070	  if (!set->extended) { 	     /* [bad if subset] */
2071	    status|=DEC_Invalid_operation;
2072	    break;}
2073	  #endif
2074	  bits|=DECINF;
2075	  }
2076	decNumberZero(res);		     /* prepare */
2077	/* [otherwise will be 0 or -0] */
2078	res->bits=bits;
2079	}
2080      break;}
2081
2082    /* here both lhs and rhs are finite; rhs==0 is handled in the */
2083    /* integer path.  Next handle the non-integer cases */
2084    if (!useint) {			/* non-integral rhs */
2085      /* any -ve lhs is bad, as is either operand or context out of */
2086      /* bounds */
2087      if (decNumberIsNegative(lhs)) {
2088	status|=DEC_Invalid_operation;
2089	break;}
2090      if (decCheckMath(lhs, set, &status)
2091       || decCheckMath(rhs, set, &status)) break; /* variable status */
2092
2093      decContextDefault(&aset, DEC_INIT_DECIMAL64); /* clean context */
2094      aset.emax=DEC_MAX_MATH;		/* usual bounds */
2095      aset.emin=-DEC_MAX_MATH;		/* .. */
2096      aset.clamp=0;			/* and no concrete format */
2097
2098      /* calculate the result using exp(ln(lhs)*rhs), which can */
2099      /* all be done into the accumulator, dac.  The precision needed */
2100      /* is enough to contain the full information in the lhs (which */
2101      /* is the total digits, including exponent), or the requested */
2102      /* precision, if larger, + 4; 6 is used for the exponent */
2103      /* maximum length, and this is also used when it is shorter */
2104      /* than the requested digits as it greatly reduces the >0.5 ulp */
2105      /* cases at little cost (because Ln doubles digits each */
2106      /* iteration so a few extra digits rarely causes an extra */
2107      /* iteration) */
2108      aset.digits=MAXI(lhs->digits, set->digits)+6+4;
2109      } /* non-integer rhs */
2110
2111     else { /* rhs is in-range integer */
2112      if (n==0) {			/* x**0 = 1 */
2113	/* (0**0 was handled above) */
2114	decNumberZero(res);		/* result=1 */
2115	*res->lsu=1;			/* .. */
2116	break;}
2117      /* rhs is a non-zero integer */
2118      if (n<0) n=-n;			/* use abs(n) */
2119
2120      aset=*set;			/* clone the context */
2121      aset.round=DEC_ROUND_HALF_EVEN;	/* internally use balanced */
2122      /* calculate the working DIGITS */
2123      aset.digits=reqdigits+(rhs->digits+rhs->exponent)+2;
2124      #if DECSUBSET
2125      if (!set->extended) aset.digits--;     /* use classic precision */
2126      #endif
2127      /* it's an error if this is more than can be handled */
2128      if (aset.digits>DECNUMMAXP) {status|=DEC_Invalid_operation; break;}
2129      } /* integer path */
2130
2131    /* aset.digits is the count of digits for the accumulator needed */
2132    /* if accumulator is too long for local storage, then allocate */
2133    needbytes=sizeof(decNumber)+(D2U(aset.digits)-1)*sizeof(Unit);
2134    /* [needbytes also used below if 1/lhs needed] */
2135    if (needbytes>sizeof(dacbuff)) {
2136      allocdac=(decNumber *)malloc(needbytes);
2137      if (allocdac==NULL) {   /* hopeless -- abandon */
2138	status|=DEC_Insufficient_storage;
2139	break;}
2140      dac=allocdac;	      /* use the allocated space */
2141      }
2142    /* here, aset is set up and accumulator is ready for use */
2143
2144    if (!useint) {			     /* non-integral rhs */
2145      /* x ** y; special-case x=1 here as it will otherwise always */
2146      /* reduce to integer 1; decLnOp has a fastpath which detects */
2147      /* the case of x=1 */
2148      decLnOp(dac, lhs, &aset, &status);     /* dac=ln(lhs) */
2149      /* [no error possible, as lhs 0 already handled] */
2150      if (ISZERO(dac)) {		     /* x==1, 1.0, etc. */
2151	/* need to return fully-padded 1.0000 etc., but rhsint->1 */
2152	*dac->lsu=1;			     /* was 0, make int 1 */
2153	if (!rhsint) {			     /* add padding */
2154	  Int shift=set->digits-1;
2155	  dac->digits=decShiftToMost(dac->lsu, 1, shift);
2156	  dac->exponent=-shift; 	     /* make 1.0000... */
2157	  status|=DEC_Inexact|DEC_Rounded;   /* deemed inexact */
2158	  }
2159	}
2160       else {
2161	decMultiplyOp(dac, dac, rhs, &aset, &status);  /* dac=dac*rhs */
2162	decExpOp(dac, dac, &aset, &status);	       /* dac=exp(dac) */
2163	}
2164      /* and drop through for final rounding */
2165      } /* non-integer rhs */
2166
2167     else {				/* carry on with integer */
2168      decNumberZero(dac);		/* acc=1 */
2169      *dac->lsu=1;			/* .. */
2170
2171      /* if a negative power the constant 1 is needed, and if not subset */
2172      /* invert the lhs now rather than inverting the result later */
2173      if (decNumberIsNegative(rhs)) {	/* was a **-n [hence digits>0] */
2174	decNumber *inv=invbuff; 	/* asssume use fixed buffer */
2175	decNumberCopy(&dnOne, dac);	/* dnOne=1;  [needed now or later] */
2176	#if DECSUBSET
2177	if (set->extended) {		/* need to calculate 1/lhs */
2178	#endif
2179	  /* divide lhs into 1, putting result in dac [dac=1/dac] */
2180	  decDivideOp(dac, &dnOne, lhs, &aset, DIVIDE, &status);
2181	  /* now locate or allocate space for the inverted lhs */
2182	  if (needbytes>sizeof(invbuff)) {
2183	    allocinv=(decNumber *)malloc(needbytes);
2184	    if (allocinv==NULL) {	/* hopeless -- abandon */
2185	      status|=DEC_Insufficient_storage;
2186	      break;}
2187	    inv=allocinv;		/* use the allocated space */
2188	    }
2189	  /* [inv now points to big-enough buffer or allocated storage] */
2190	  decNumberCopy(inv, dac);	/* copy the 1/lhs */
2191	  decNumberCopy(dac, &dnOne);	/* restore acc=1 */
2192	  lhs=inv;			/* .. and go forward with new lhs */
2193	#if DECSUBSET
2194	  }
2195	#endif
2196	}
2197
2198      /* Raise-to-the-power loop... */
2199      seenbit=0;		   /* set once a 1-bit is encountered */
2200      for (i=1;;i++){		   /* for each bit [top bit ignored] */
2201	/* abandon if had overflow or terminal underflow */
2202	if (status & (DEC_Overflow|DEC_Underflow)) { /* interesting? */
2203	  if (status&DEC_Overflow || ISZERO(dac)) break;
2204	  }
2205	/* [the following two lines revealed an optimizer bug in a C++ */
2206	/* compiler, with symptom: 5**3 -> 25, when n=n+n was used] */
2207	n=n<<1; 		   /* move next bit to testable position */
2208	if (n<0) {		   /* top bit is set */
2209	  seenbit=1;		   /* OK, significant bit seen */
2210	  decMultiplyOp(dac, dac, lhs, &aset, &status); /* dac=dac*x */
2211	  }
2212	if (i==31) break;	   /* that was the last bit */
2213	if (!seenbit) continue;    /* no need to square 1 */
2214	decMultiplyOp(dac, dac, dac, &aset, &status); /* dac=dac*dac [square] */
2215	} /*i*/ /* 32 bits */
2216
2217      /* complete internal overflow or underflow processing */
2218      if (status & (DEC_Overflow|DEC_Underflow)) {
2219	#if DECSUBSET
2220	/* If subset, and power was negative, reverse the kind of -erflow */
2221	/* [1/x not yet done] */
2222	if (!set->extended && decNumberIsNegative(rhs)) {
2223	  if (status & DEC_Overflow)
2224	    status^=DEC_Overflow | DEC_Underflow | DEC_Subnormal;
2225	   else { /* trickier -- Underflow may or may not be set */
2226	    status&=~(DEC_Underflow | DEC_Subnormal); /* [one or both] */
2227	    status|=DEC_Overflow;
2228	    }
2229	  }
2230	#endif
2231	dac->bits=(dac->bits & ~DECNEG) | bits; /* force correct sign */
2232	/* round subnormals [to set.digits rather than aset.digits] */
2233	/* or set overflow result similarly as required */
2234	decFinalize(dac, set, &residue, &status);
2235	decNumberCopy(res, dac);   /* copy to result (is now OK length) */
2236	break;
2237	}
2238
2239      #if DECSUBSET
2240      if (!set->extended &&		     /* subset math */
2241	  decNumberIsNegative(rhs)) {	     /* was a **-n [hence digits>0] */
2242	/* so divide result into 1 [dac=1/dac] */
2243	decDivideOp(dac, &dnOne, dac, &aset, DIVIDE, &status);
2244	}
2245      #endif
2246      } /* rhs integer path */
2247
2248    /* reduce result to the requested length and copy to result */
2249    decCopyFit(res, dac, set, &residue, &status);
2250    decFinish(res, set, &residue, &status);  /* final cleanup */
2251    #if DECSUBSET
2252    if (!set->extended) decTrim(res, set, 0, 1, &dropped); /* trailing zeros */
2253    #endif
2254    } while(0); 			/* end protected */
2255
2256  free(allocdac);	/* drop any storage used */
2257  free(allocinv);	/* .. */
2258  #if DECSUBSET
2259  free(alloclhs);	/* .. */
2260  free(allocrhs);	/* .. */
2261  #endif
2262  if (status!=0) decStatus(res, status, set);
2263  #if DECCHECK
2264  decCheckInexact(res, set);
2265  #endif
2266  return res;
2267  } /* decNumberPower */
2268
2269/* ------------------------------------------------------------------ */
2270/* decNumberQuantize -- force exponent to requested value	      */
2271/*								      */
2272/*   This computes C = op(A, B), where op adjusts the coefficient     */
2273/*   of C (by rounding or shifting) such that the exponent (-scale)   */
2274/*   of C has exponent of B.  The numerical value of C will equal A,  */
2275/*   except for the effects of any rounding that occurred.	      */
2276/*								      */
2277/*   res is C, the result.  C may be A or B			      */
2278/*   lhs is A, the number to adjust				      */
2279/*   rhs is B, the number with exponent to match		      */
2280/*   set is the context 					      */
2281/*								      */
2282/* C must have space for set->digits digits.			      */
2283/*								      */
2284/* Unless there is an error or the result is infinite, the exponent   */
2285/* after the operation is guaranteed to be equal to that of B.	      */
2286/* ------------------------------------------------------------------ */
2287decNumber * decNumberQuantize(decNumber *res, const decNumber *lhs,
2288			      const decNumber *rhs, decContext *set) {
2289  uInt status=0;			/* accumulator */
2290  decQuantizeOp(res, lhs, rhs, set, 1, &status);
2291  if (status!=0) decStatus(res, status, set);
2292  return res;
2293  } /* decNumberQuantize */
2294
2295/* ------------------------------------------------------------------ */
2296/* decNumberReduce -- remove trailing zeros			      */
2297/*								      */
2298/*   This computes C = 0 + A, and normalizes the result 	      */
2299/*								      */
2300/*   res is C, the result.  C may be A				      */
2301/*   rhs is A							      */
2302/*   set is the context 					      */
2303/*								      */
2304/* C must have space for set->digits digits.			      */
2305/* ------------------------------------------------------------------ */
2306/* Previously known as Normalize */
2307decNumber * decNumberNormalize(decNumber *res, const decNumber *rhs,
2308			       decContext *set) {
2309  return decNumberReduce(res, rhs, set);
2310  } /* decNumberNormalize */
2311
2312decNumber * decNumberReduce(decNumber *res, const decNumber *rhs,
2313			    decContext *set) {
2314  #if DECSUBSET
2315  decNumber *allocrhs=NULL;	   /* non-NULL if rounded rhs allocated */
2316  #endif
2317  uInt status=0;		   /* as usual */
2318  Int  residue=0;		   /* as usual */
2319  Int  dropped; 		   /* work */
2320
2321  #if DECCHECK
2322  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
2323  #endif
2324
2325  do {				   /* protect allocated storage */
2326    #if DECSUBSET
2327    if (!set->extended) {
2328      /* reduce operand and set lostDigits status, as needed */
2329      if (rhs->digits>set->digits) {
2330	allocrhs=decRoundOperand(rhs, set, &status);
2331	if (allocrhs==NULL) break;
2332	rhs=allocrhs;
2333	}
2334      }
2335    #endif
2336    /* [following code does not require input rounding] */
2337
2338    /* Infinities copy through; NaNs need usual treatment */
2339    if (decNumberIsNaN(rhs)) {
2340      decNaNs(res, rhs, NULL, set, &status);
2341      break;
2342      }
2343
2344    /* reduce result to the requested length and copy to result */
2345    decCopyFit(res, rhs, set, &residue, &status); /* copy & round */
2346    decFinish(res, set, &residue, &status);	  /* cleanup/set flags */
2347    decTrim(res, set, 1, 0, &dropped);		  /* normalize in place */
2348						  /* [may clamp] */
2349    } while(0); 			     /* end protected */
2350
2351  #if DECSUBSET
2352  free(allocrhs);	     /* .. */
2353  #endif
2354  if (status!=0) decStatus(res, status, set);/* then report status */
2355  return res;
2356  } /* decNumberReduce */
2357
2358/* ------------------------------------------------------------------ */
2359/* decNumberRescale -- force exponent to requested value	      */
2360/*								      */
2361/*   This computes C = op(A, B), where op adjusts the coefficient     */
2362/*   of C (by rounding or shifting) such that the exponent (-scale)   */
2363/*   of C has the value B.  The numerical value of C will equal A,    */
2364/*   except for the effects of any rounding that occurred.	      */
2365/*								      */
2366/*   res is C, the result.  C may be A or B			      */
2367/*   lhs is A, the number to adjust				      */
2368/*   rhs is B, the requested exponent				      */
2369/*   set is the context 					      */
2370/*								      */
2371/* C must have space for set->digits digits.			      */
2372/*								      */
2373/* Unless there is an error or the result is infinite, the exponent   */
2374/* after the operation is guaranteed to be equal to B.		      */
2375/* ------------------------------------------------------------------ */
2376decNumber * decNumberRescale(decNumber *res, const decNumber *lhs,
2377			     const decNumber *rhs, decContext *set) {
2378  uInt status=0;			/* accumulator */
2379  decQuantizeOp(res, lhs, rhs, set, 0, &status);
2380  if (status!=0) decStatus(res, status, set);
2381  return res;
2382  } /* decNumberRescale */
2383
2384/* ------------------------------------------------------------------ */
2385/* decNumberRemainder -- divide and return remainder		      */
2386/*								      */
2387/*   This computes C = A % B					      */
2388/*								      */
2389/*   res is C, the result.  C may be A and/or B (e.g., X=X%X)	      */
2390/*   lhs is A							      */
2391/*   rhs is B							      */
2392/*   set is the context 					      */
2393/*								      */
2394/* C must have space for set->digits digits.			      */
2395/* ------------------------------------------------------------------ */
2396decNumber * decNumberRemainder(decNumber *res, const decNumber *lhs,
2397			       const decNumber *rhs, decContext *set) {
2398  uInt status=0;			/* accumulator */
2399  decDivideOp(res, lhs, rhs, set, REMAINDER, &status);
2400  if (status!=0) decStatus(res, status, set);
2401  #if DECCHECK
2402  decCheckInexact(res, set);
2403  #endif
2404  return res;
2405  } /* decNumberRemainder */
2406
2407/* ------------------------------------------------------------------ */
2408/* decNumberRemainderNear -- divide and return remainder from nearest */
2409/*								      */
2410/*   This computes C = A % B, where % is the IEEE remainder operator  */
2411/*								      */
2412/*   res is C, the result.  C may be A and/or B (e.g., X=X%X)	      */
2413/*   lhs is A							      */
2414/*   rhs is B							      */
2415/*   set is the context 					      */
2416/*								      */
2417/* C must have space for set->digits digits.			      */
2418/* ------------------------------------------------------------------ */
2419decNumber * decNumberRemainderNear(decNumber *res, const decNumber *lhs,
2420				   const decNumber *rhs, decContext *set) {
2421  uInt status=0;			/* accumulator */
2422  decDivideOp(res, lhs, rhs, set, REMNEAR, &status);
2423  if (status!=0) decStatus(res, status, set);
2424  #if DECCHECK
2425  decCheckInexact(res, set);
2426  #endif
2427  return res;
2428  } /* decNumberRemainderNear */
2429
2430/* ------------------------------------------------------------------ */
2431/* decNumberRotate -- rotate the coefficient of a Number left/right   */
2432/*								      */
2433/*   This computes C = A rot B	(in base ten and rotating set->digits */
2434/*   digits).							      */
2435/*								      */
2436/*   res is C, the result.  C may be A and/or B (e.g., X=XrotX)       */
2437/*   lhs is A							      */
2438/*   rhs is B, the number of digits to rotate (-ve to right)	      */
2439/*   set is the context 					      */
2440/*								      */
2441/* The digits of the coefficient of A are rotated to the left (if B   */
2442/* is positive) or to the right (if B is negative) without adjusting  */
2443/* the exponent or the sign of A.  If lhs->digits is less than	      */
2444/* set->digits the coefficient is padded with zeros on the left       */
2445/* before the rotate.  Any leading zeros in the result are removed    */
2446/* as usual.							      */
2447/*								      */
2448/* B must be an integer (q=0) and in the range -set->digits through   */
2449/* +set->digits.						      */
2450/* C must have space for set->digits digits.			      */
2451/* NaNs are propagated as usual.  Infinities are unaffected (but      */
2452/* B must be valid).  No status is set unless B is invalid or an      */
2453/* operand is an sNaN.						      */
2454/* ------------------------------------------------------------------ */
2455decNumber * decNumberRotate(decNumber *res, const decNumber *lhs,
2456			   const decNumber *rhs, decContext *set) {
2457  uInt status=0;	      /* accumulator */
2458  Int  rotate;		      /* rhs as an Int */
2459
2460  #if DECCHECK
2461  if (decCheckOperands(res, lhs, rhs, set)) return res;
2462  #endif
2463
2464  /* NaNs propagate as normal */
2465  if (decNumberIsNaN(lhs) || decNumberIsNaN(rhs))
2466    decNaNs(res, lhs, rhs, set, &status);
2467   /* rhs must be an integer */
2468   else if (decNumberIsInfinite(rhs) || rhs->exponent!=0)
2469    status=DEC_Invalid_operation;
2470   else { /* both numeric, rhs is an integer */
2471    rotate=decGetInt(rhs);		     /* [cannot fail] */
2472    if (rotate==BADINT			     /* something bad .. */
2473     || rotate==BIGODD || rotate==BIGEVEN    /* .. very big .. */
2474     || abs(rotate)>set->digits)	     /* .. or out of range */
2475      status=DEC_Invalid_operation;
2476     else {				     /* rhs is OK */
2477      decNumberCopy(res, lhs);
2478      /* convert -ve rotate to equivalent positive rotation */
2479      if (rotate<0) rotate=set->digits+rotate;
2480      if (rotate!=0 && rotate!=set->digits   /* zero or full rotation */
2481       && !decNumberIsInfinite(res)) {	     /* lhs was infinite */
2482	/* left-rotate to do; 0 < rotate < set->digits */
2483	uInt units, shift;		     /* work */
2484	uInt msudigits; 		     /* digits in result msu */
2485	Unit *msu=res->lsu+D2U(res->digits)-1;	  /* current msu */
2486	Unit *msumax=res->lsu+D2U(set->digits)-1; /* rotation msu */
2487	for (msu++; msu<=msumax; msu++) *msu=0;   /* ensure high units=0 */
2488	res->digits=set->digits;		  /* now full-length */
2489	msudigits=MSUDIGITS(res->digits);	  /* actual digits in msu */
2490
2491	/* rotation here is done in-place, in three steps */
2492	/* 1. shift all to least up to one unit to unit-align final */
2493	/*    lsd [any digits shifted out are rotated to the left, */
2494	/*    abutted to the original msd (which may require split)] */
2495	/* */
2496	/*    [if there are no whole units left to rotate, the */
2497	/*    rotation is now complete] */
2498	/* */
2499	/* 2. shift to least, from below the split point only, so that */
2500	/*    the final msd is in the right place in its Unit [any */
2501	/*    digits shifted out will fit exactly in the current msu, */
2502	/*    left aligned, no split required] */
2503	/* */
2504	/* 3. rotate all the units by reversing left part, right */
2505	/*    part, and then whole */
2506	/* */
2507	/* example: rotate right 8 digits (2 units + 2), DECDPUN=3. */
2508	/* */
2509	/*   start: 00a bcd efg hij klm npq */
2510	/* */
2511	/*	1a  000 0ab cde fgh|ijk lmn [pq saved] */
2512	/*	1b  00p qab cde fgh|ijk lmn */
2513	/* */
2514	/*	2a  00p qab cde fgh|00i jkl [mn saved] */
2515	/*	2b  mnp qab cde fgh|00i jkl */
2516	/* */
2517	/*	3a  fgh cde qab mnp|00i jkl */
2518	/*	3b  fgh cde qab mnp|jkl 00i */
2519	/*	3c  00i jkl mnp qab cde fgh */
2520
2521	/* Step 1: amount to shift is the partial right-rotate count */
2522	rotate=set->digits-rotate;	/* make it right-rotate */
2523	units=rotate/DECDPUN;		/* whole units to rotate */
2524	shift=rotate%DECDPUN;		/* left-over digits count */
2525	if (shift>0) {			/* not an exact number of units */
2526	  uInt save=res->lsu[0]%powers[shift];	  /* save low digit(s) */
2527	  decShiftToLeast(res->lsu, D2U(res->digits), shift);
2528	  if (shift>msudigits) {	/* msumax-1 needs >0 digits */
2529	    uInt rem=save%powers[shift-msudigits];/* split save */
2530	    *msumax=(Unit)(save/powers[shift-msudigits]); /* and insert */
2531	    *(msumax-1)=*(msumax-1)
2532		       +(Unit)(rem*powers[DECDPUN-(shift-msudigits)]); /* .. */
2533	    }
2534	   else { /* all fits in msumax */
2535	    *msumax=*msumax+(Unit)(save*powers[msudigits-shift]); /* [maybe *1] */
2536	    }
2537	  } /* digits shift needed */
2538
2539	/* If whole units to rotate... */
2540	if (units>0) {			/* some to do */
2541	  /* Step 2: the units to touch are the whole ones in rotate, */
2542	  /*   if any, and the shift is DECDPUN-msudigits (which may be */
2543	  /*   0, again) */
2544	  shift=DECDPUN-msudigits;
2545	  if (shift>0) {		/* not an exact number of units */
2546	    uInt save=res->lsu[0]%powers[shift];  /* save low digit(s) */
2547	    decShiftToLeast(res->lsu, units, shift);
2548	    *msumax=*msumax+(Unit)(save*powers[msudigits]);
2549	    } /* partial shift needed */
2550
2551	  /* Step 3: rotate the units array using triple reverse */
2552	  /* (reversing is easy and fast) */
2553	  decReverse(res->lsu+units, msumax);	  /* left part */
2554	  decReverse(res->lsu, res->lsu+units-1); /* right part */
2555	  decReverse(res->lsu, msumax); 	  /* whole */
2556	  } /* whole units to rotate */
2557	/* the rotation may have left an undetermined number of zeros */
2558	/* on the left, so true length needs to be calculated */
2559	res->digits=decGetDigits(res->lsu, msumax-res->lsu+1);
2560	} /* rotate needed */
2561      } /* rhs OK */
2562    } /* numerics */
2563  if (status!=0) decStatus(res, status, set);
2564  return res;
2565  } /* decNumberRotate */
2566
2567/* ------------------------------------------------------------------ */
2568/* decNumberSameQuantum -- test for equal exponents		      */
2569/*								      */
2570/*   res is the result number, which will contain either 0 or 1       */
2571/*   lhs is a number to test					      */
2572/*   rhs is the second (usually a pattern)			      */
2573/*								      */
2574/* No errors are possible and no context is needed.		      */
2575/* ------------------------------------------------------------------ */
2576decNumber * decNumberSameQuantum(decNumber *res, const decNumber *lhs,
2577				 const decNumber *rhs) {
2578  Unit ret=0;			   /* return value */
2579
2580  #if DECCHECK
2581  if (decCheckOperands(res, lhs, rhs, DECUNCONT)) return res;
2582  #endif
2583
2584  if (SPECIALARGS) {
2585    if (decNumberIsNaN(lhs) && decNumberIsNaN(rhs)) ret=1;
2586     else if (decNumberIsInfinite(lhs) && decNumberIsInfinite(rhs)) ret=1;
2587     /* [anything else with a special gives 0] */
2588    }
2589   else if (lhs->exponent==rhs->exponent) ret=1;
2590
2591  decNumberZero(res);		   /* OK to overwrite an operand now */
2592  *res->lsu=ret;
2593  return res;
2594  } /* decNumberSameQuantum */
2595
2596/* ------------------------------------------------------------------ */
2597/* decNumberScaleB -- multiply by a power of 10 		      */
2598/*								      */
2599/* This computes C = A x 10**B where B is an integer (q=0) with       */
2600/* maximum magnitude 2*(emax+digits)				      */
2601/*								      */
2602/*   res is C, the result.  C may be A or B			      */
2603/*   lhs is A, the number to adjust				      */
2604/*   rhs is B, the requested power of ten to use		      */
2605/*   set is the context 					      */
2606/*								      */
2607/* C must have space for set->digits digits.			      */
2608/*								      */
2609/* The result may underflow or overflow.			      */
2610/* ------------------------------------------------------------------ */
2611decNumber * decNumberScaleB(decNumber *res, const decNumber *lhs,
2612			    const decNumber *rhs, decContext *set) {
2613  Int  reqexp;		      /* requested exponent change [B] */
2614  uInt status=0;	      /* accumulator */
2615  Int  residue; 	      /* work */
2616
2617  #if DECCHECK
2618  if (decCheckOperands(res, lhs, rhs, set)) return res;
2619  #endif
2620
2621  /* Handle special values except lhs infinite */
2622  if (decNumberIsNaN(lhs) || decNumberIsNaN(rhs))
2623    decNaNs(res, lhs, rhs, set, &status);
2624    /* rhs must be an integer */
2625   else if (decNumberIsInfinite(rhs) || rhs->exponent!=0)
2626    status=DEC_Invalid_operation;
2627   else {
2628    /* lhs is a number; rhs is a finite with q==0 */
2629    reqexp=decGetInt(rhs);		     /* [cannot fail] */
2630    if (reqexp==BADINT			     /* something bad .. */
2631     || reqexp==BIGODD || reqexp==BIGEVEN    /* .. very big .. */
2632     || abs(reqexp)>(2*(set->digits+set->emax))) /* .. or out of range */
2633      status=DEC_Invalid_operation;
2634     else {				     /* rhs is OK */
2635      decNumberCopy(res, lhs);		     /* all done if infinite lhs */
2636      if (!decNumberIsInfinite(res)) {	     /* prepare to scale */
2637	res->exponent+=reqexp;		     /* adjust the exponent */
2638	residue=0;
2639	decFinalize(res, set, &residue, &status); /* .. and check */
2640	} /* finite LHS */
2641      } /* rhs OK */
2642    } /* rhs finite */
2643  if (status!=0) decStatus(res, status, set);
2644  return res;
2645  } /* decNumberScaleB */
2646
2647/* ------------------------------------------------------------------ */
2648/* decNumberShift -- shift the coefficient of a Number left or right  */
2649/*								      */
2650/*   This computes C = A << B or C = A >> -B  (in base ten).	      */
2651/*								      */
2652/*   res is C, the result.  C may be A and/or B (e.g., X=X<<X)	      */
2653/*   lhs is A							      */
2654/*   rhs is B, the number of digits to shift (-ve to right)	      */
2655/*   set is the context 					      */
2656/*								      */
2657/* The digits of the coefficient of A are shifted to the left (if B   */
2658/* is positive) or to the right (if B is negative) without adjusting  */
2659/* the exponent or the sign of A.				      */
2660/*								      */
2661/* B must be an integer (q=0) and in the range -set->digits through   */
2662/* +set->digits.						      */
2663/* C must have space for set->digits digits.			      */
2664/* NaNs are propagated as usual.  Infinities are unaffected (but      */
2665/* B must be valid).  No status is set unless B is invalid or an      */
2666/* operand is an sNaN.						      */
2667/* ------------------------------------------------------------------ */
2668decNumber * decNumberShift(decNumber *res, const decNumber *lhs,
2669			   const decNumber *rhs, decContext *set) {
2670  uInt status=0;	      /* accumulator */
2671  Int  shift;		      /* rhs as an Int */
2672
2673  #if DECCHECK
2674  if (decCheckOperands(res, lhs, rhs, set)) return res;
2675  #endif
2676
2677  /* NaNs propagate as normal */
2678  if (decNumberIsNaN(lhs) || decNumberIsNaN(rhs))
2679    decNaNs(res, lhs, rhs, set, &status);
2680   /* rhs must be an integer */
2681   else if (decNumberIsInfinite(rhs) || rhs->exponent!=0)
2682    status=DEC_Invalid_operation;
2683   else { /* both numeric, rhs is an integer */
2684    shift=decGetInt(rhs);		     /* [cannot fail] */
2685    if (shift==BADINT			     /* something bad .. */
2686     || shift==BIGODD || shift==BIGEVEN      /* .. very big .. */
2687     || abs(shift)>set->digits) 	     /* .. or out of range */
2688      status=DEC_Invalid_operation;
2689     else {				     /* rhs is OK */
2690      decNumberCopy(res, lhs);
2691      if (shift!=0 && !decNumberIsInfinite(res)) { /* something to do */
2692	if (shift>0) {			     /* to left */
2693	  if (shift==set->digits) {	     /* removing all */
2694	    *res->lsu=0;		     /* so place 0 */
2695	    res->digits=1;		     /* .. */
2696	    }
2697	   else {			     /* */
2698	    /* first remove leading digits if necessary */
2699	    if (res->digits+shift>set->digits) {
2700	      decDecap(res, res->digits+shift-set->digits);
2701	      /* that updated res->digits; may have gone to 1 (for a */
2702	      /* single digit or for zero */
2703	      }
2704	    if (res->digits>1 || *res->lsu)  /* if non-zero.. */
2705	      res->digits=decShiftToMost(res->lsu, res->digits, shift);
2706	    } /* partial left */
2707	  } /* left */
2708	 else { /* to right */
2709	  if (-shift>=res->digits) {	     /* discarding all */
2710	    *res->lsu=0;		     /* so place 0 */
2711	    res->digits=1;		     /* .. */
2712	    }
2713	   else {
2714	    decShiftToLeast(res->lsu, D2U(res->digits), -shift);
2715	    res->digits-=(-shift);
2716	    }
2717	  } /* to right */
2718	} /* non-0 non-Inf shift */
2719      } /* rhs OK */
2720    } /* numerics */
2721  if (status!=0) decStatus(res, status, set);
2722  return res;
2723  } /* decNumberShift */
2724
2725/* ------------------------------------------------------------------ */
2726/* decNumberSquareRoot -- square root operator			      */
2727/*								      */
2728/*   This computes C = squareroot(A)				      */
2729/*								      */
2730/*   res is C, the result.  C may be A				      */
2731/*   rhs is A							      */
2732/*   set is the context; note that rounding mode has no effect	      */
2733/*								      */
2734/* C must have space for set->digits digits.			      */
2735/* ------------------------------------------------------------------ */
2736/* This uses the following varying-precision algorithm in:	      */
2737/*								      */
2738/*   Properly Rounded Variable Precision Square Root, T. E. Hull and  */
2739/*   A. Abrham, ACM Transactions on Mathematical Software, Vol 11 #3, */
2740/*   pp229-237, ACM, September 1985.				      */
2741/*								      */
2742/* The square-root is calculated using Newton's method, after which   */
2743/* a check is made to ensure the result is correctly rounded.	      */
2744/*								      */
2745/* % [Reformatted original Numerical Turing source code follows.]     */
2746/* function sqrt(x : real) : real				      */
2747/* % sqrt(x) returns the properly rounded approximation to the square */
2748/* % root of x, in the precision of the calling environment, or it    */
2749/* % fails if x < 0.						      */
2750/* % t e hull and a abrham, august, 1984			      */
2751/* if x <= 0 then						      */
2752/*   if x < 0 then						      */
2753/*     assert false						      */
2754/*   else							      */
2755/*     result 0 						      */
2756/*   end if							      */
2757/* end if							      */
2758/* var f := setexp(x, 0)  % fraction part of x	 [0.1 <= x < 1]       */
2759/* var e := getexp(x)	  % exponent part of x			      */
2760/* var approx : real						      */
2761/* if e mod 2 = 0  then 					      */
2762/*   approx := .259 + .819 * f	 % approx to root of f		      */
2763/* else 							      */
2764/*   f := f/l0			 % adjustments			      */
2765/*   e := e + 1 		 %   for odd			      */
2766/*   approx := .0819 + 2.59 * f  %   exponent			      */
2767/* end if							      */
2768/*								      */
2769/* var p:= 3							      */
2770/* const maxp := currentprecision + 2				      */
2771/* loop 							      */
2772/*   p := min(2*p - 2, maxp)	 % p = 4,6,10, . . . , maxp	      */
2773/*   precision p						      */
2774/*   approx := .5 * (approx + f/approx) 			      */
2775/*   exit when p = maxp 					      */
2776/* end loop							      */
2777/*								      */
2778/* % approx is now within 1 ulp of the properly rounded square root   */
2779/* % of f; to ensure proper rounding, compare squares of (approx -    */
2780/* % l/2 ulp) and (approx + l/2 ulp) with f.			      */
2781/* p := currentprecision					      */
2782/* begin							      */
2783/*   precision p + 2						      */
2784/*   const approxsubhalf := approx - setexp(.5, -p)		      */
2785/*   if mulru(approxsubhalf, approxsubhalf) > f then		      */
2786/*     approx := approx - setexp(.l, -p + 1)			      */
2787/*   else							      */
2788/*     const approxaddhalf := approx + setexp(.5, -p)		      */
2789/*     if mulrd(approxaddhalf, approxaddhalf) < f then		      */
2790/*	 approx := approx + setexp(.l, -p + 1)			      */
2791/*     end if							      */
2792/*   end if							      */
2793/* end								      */
2794/* result setexp(approx, e div 2)  % fix exponent		      */
2795/* end sqrt							      */
2796/* ------------------------------------------------------------------ */
2797decNumber * decNumberSquareRoot(decNumber *res, const decNumber *rhs,
2798				decContext *set) {
2799  decContext workset, approxset;   /* work contexts */
2800  decNumber dzero;		   /* used for constant zero */
2801  Int  maxp;			   /* largest working precision */
2802  Int  workp;			   /* working precision */
2803  Int  residue=0;		   /* rounding residue */
2804  uInt status=0, ignore=0;	   /* status accumulators */
2805  uInt rstatus; 		   /* .. */
2806  Int  exp;			   /* working exponent */
2807  Int  ideal;			   /* ideal (preferred) exponent */
2808  Int  needbytes;		   /* work */
2809  Int  dropped; 		   /* .. */
2810
2811  #if DECSUBSET
2812  decNumber *allocrhs=NULL;	   /* non-NULL if rounded rhs allocated */
2813  #endif
2814  /* buffer for f [needs +1 in case DECBUFFER 0] */
2815  decNumber buff[D2N(DECBUFFER+1)];
2816  /* buffer for a [needs +2 to match likely maxp] */
2817  decNumber bufa[D2N(DECBUFFER+2)];
2818  /* buffer for temporary, b [must be same size as a] */
2819  decNumber bufb[D2N(DECBUFFER+2)];
2820  decNumber *allocbuff=NULL;	   /* -> allocated buff, iff allocated */
2821  decNumber *allocbufa=NULL;	   /* -> allocated bufa, iff allocated */
2822  decNumber *allocbufb=NULL;	   /* -> allocated bufb, iff allocated */
2823  decNumber *f=buff;		   /* reduced fraction */
2824  decNumber *a=bufa;		   /* approximation to result */
2825  decNumber *b=bufb;		   /* intermediate result */
2826  /* buffer for temporary variable, up to 3 digits */
2827  decNumber buft[D2N(3)];
2828  decNumber *t=buft;		   /* up-to-3-digit constant or work */
2829
2830  #if DECCHECK
2831  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
2832  #endif
2833
2834  do {				   /* protect allocated storage */
2835    #if DECSUBSET
2836    if (!set->extended) {
2837      /* reduce operand and set lostDigits status, as needed */
2838      if (rhs->digits>set->digits) {
2839	allocrhs=decRoundOperand(rhs, set, &status);
2840	if (allocrhs==NULL) break;
2841	/* [Note: 'f' allocation below could reuse this buffer if */
2842	/* used, but as this is rare they are kept separate for clarity.] */
2843	rhs=allocrhs;
2844	}
2845      }
2846    #endif
2847    /* [following code does not require input rounding] */
2848
2849    /* handle infinities and NaNs */
2850    if (SPECIALARG) {
2851      if (decNumberIsInfinite(rhs)) {	      /* an infinity */
2852	if (decNumberIsNegative(rhs)) status|=DEC_Invalid_operation;
2853	 else decNumberCopy(res, rhs);	      /* +Infinity */
2854	}
2855       else decNaNs(res, rhs, NULL, set, &status); /* a NaN */
2856      break;
2857      }
2858
2859    /* calculate the ideal (preferred) exponent [floor(exp/2)] */
2860    /* [It would be nicer to write: ideal=rhs->exponent>>1, but this */
2861    /* generates a compiler warning.  Generated code is the same.] */
2862    ideal=(rhs->exponent&~1)/2; 	/* target */
2863
2864    /* handle zeros */
2865    if (ISZERO(rhs)) {
2866      decNumberCopy(res, rhs);		/* could be 0 or -0 */
2867      res->exponent=ideal;		/* use the ideal [safe] */
2868      /* use decFinish to clamp any out-of-range exponent, etc. */
2869      decFinish(res, set, &residue, &status);
2870      break;
2871      }
2872
2873    /* any other -x is an oops */
2874    if (decNumberIsNegative(rhs)) {
2875      status|=DEC_Invalid_operation;
2876      break;
2877      }
2878
2879    /* space is needed for three working variables */
2880    /*	 f -- the same precision as the RHS, reduced to 0.01->0.99... */
2881    /*	 a -- Hull's approximation -- precision, when assigned, is */
2882    /*	      currentprecision+1 or the input argument precision, */
2883    /*	      whichever is larger (+2 for use as temporary) */
2884    /*	 b -- intermediate temporary result (same size as a) */
2885    /* if any is too long for local storage, then allocate */
2886    workp=MAXI(set->digits+1, rhs->digits);  /* actual rounding precision */
2887    workp=MAXI(workp, 7);		     /* at least 7 for low cases */
2888    maxp=workp+2;			     /* largest working precision */
2889
2890    needbytes=sizeof(decNumber)+(D2U(rhs->digits)-1)*sizeof(Unit);
2891    if (needbytes>(Int)sizeof(buff)) {
2892      allocbuff=(decNumber *)malloc(needbytes);
2893      if (allocbuff==NULL) {  /* hopeless -- abandon */
2894	status|=DEC_Insufficient_storage;
2895	break;}
2896      f=allocbuff;	      /* use the allocated space */
2897      }
2898    /* a and b both need to be able to hold a maxp-length number */
2899    needbytes=sizeof(decNumber)+(D2U(maxp)-1)*sizeof(Unit);
2900    if (needbytes>(Int)sizeof(bufa)) {		  /* [same applies to b] */
2901      allocbufa=(decNumber *)malloc(needbytes);
2902      allocbufb=(decNumber *)malloc(needbytes);
2903      if (allocbufa==NULL || allocbufb==NULL) {   /* hopeless */
2904	status|=DEC_Insufficient_storage;
2905	break;}
2906      a=allocbufa;	      /* use the allocated spaces */
2907      b=allocbufb;	      /* .. */
2908      }
2909
2910    /* copy rhs -> f, save exponent, and reduce so 0.1 <= f < 1 */
2911    decNumberCopy(f, rhs);
2912    exp=f->exponent+f->digits;		     /* adjusted to Hull rules */
2913    f->exponent=-(f->digits);		     /* to range */
2914
2915    /* set up working context */
2916    decContextDefault(&workset, DEC_INIT_DECIMAL64);
2917    workset.emax=DEC_MAX_EMAX;
2918    workset.emin=DEC_MIN_EMIN;
2919
2920    /* [Until further notice, no error is possible and status bits */
2921    /* (Rounded, etc.) should be ignored, not accumulated.] */
2922
2923    /* Calculate initial approximation, and allow for odd exponent */
2924    workset.digits=workp;		     /* p for initial calculation */
2925    t->bits=0; t->digits=3;
2926    a->bits=0; a->digits=3;
2927    if ((exp & 1)==0) { 		     /* even exponent */
2928      /* Set t=0.259, a=0.819 */
2929      t->exponent=-3;
2930      a->exponent=-3;
2931      #if DECDPUN>=3
2932	t->lsu[0]=259;
2933	a->lsu[0]=819;
2934      #elif DECDPUN==2
2935	t->lsu[0]=59; t->lsu[1]=2;
2936	a->lsu[0]=19; a->lsu[1]=8;
2937      #else
2938	t->lsu[0]=9; t->lsu[1]=5; t->lsu[2]=2;
2939	a->lsu[0]=9; a->lsu[1]=1; a->lsu[2]=8;
2940      #endif
2941      }
2942     else {				     /* odd exponent */
2943      /* Set t=0.0819, a=2.59 */
2944      f->exponent--;			     /* f=f/10 */
2945      exp++;				     /* e=e+1 */
2946      t->exponent=-4;
2947      a->exponent=-2;
2948      #if DECDPUN>=3
2949	t->lsu[0]=819;
2950	a->lsu[0]=259;
2951      #elif DECDPUN==2
2952	t->lsu[0]=19; t->lsu[1]=8;
2953	a->lsu[0]=59; a->lsu[1]=2;
2954      #else
2955	t->lsu[0]=9; t->lsu[1]=1; t->lsu[2]=8;
2956	a->lsu[0]=9; a->lsu[1]=5; a->lsu[2]=2;
2957      #endif
2958      }
2959
2960    decMultiplyOp(a, a, f, &workset, &ignore);	  /* a=a*f */
2961    decAddOp(a, a, t, &workset, 0, &ignore);	  /* ..+t */
2962    /* [a is now the initial approximation for sqrt(f), calculated with */
2963    /* currentprecision, which is also a's precision.] */
2964
2965    /* the main calculation loop */
2966    decNumberZero(&dzero);		     /* make 0 */
2967    decNumberZero(t);			     /* set t = 0.5 */
2968    t->lsu[0]=5;			     /* .. */
2969    t->exponent=-1;			     /* .. */
2970    workset.digits=3;			     /* initial p */
2971    for (; workset.digits<maxp;) {
2972      /* set p to min(2*p - 2, maxp)  [hence 3; or: 4, 6, 10, ... , maxp] */
2973      workset.digits=MINI(workset.digits*2-2, maxp);
2974      /* a = 0.5 * (a + f/a) */
2975      /* [calculated at p then rounded to currentprecision] */
2976      decDivideOp(b, f, a, &workset, DIVIDE, &ignore); /* b=f/a */
2977      decAddOp(b, b, a, &workset, 0, &ignore);	       /* b=b+a */
2978      decMultiplyOp(a, b, t, &workset, &ignore);       /* a=b*0.5 */
2979      } /* loop */
2980
2981    /* Here, 0.1 <= a < 1 [Hull], and a has maxp digits */
2982    /* now reduce to length, etc.; this needs to be done with a */
2983    /* having the correct exponent so as to handle subnormals */
2984    /* correctly */
2985    approxset=*set;			     /* get emin, emax, etc. */
2986    approxset.round=DEC_ROUND_HALF_EVEN;
2987    a->exponent+=exp/2; 		     /* set correct exponent */
2988    rstatus=0;				     /* clear status */
2989    residue=0;				     /* .. and accumulator */
2990    decCopyFit(a, a, &approxset, &residue, &rstatus);  /* reduce (if needed) */
2991    decFinish(a, &approxset, &residue, &rstatus);      /* clean and finalize */
2992
2993    /* Overflow was possible if the input exponent was out-of-range, */
2994    /* in which case quit */
2995    if (rstatus&DEC_Overflow) {
2996      status=rstatus;			     /* use the status as-is */
2997      decNumberCopy(res, a);		     /* copy to result */
2998      break;
2999      }
3000
3001    /* Preserve status except Inexact/Rounded */
3002    status|=(rstatus & ~(DEC_Rounded|DEC_Inexact));
3003
3004    /* Carry out the Hull correction */
3005    a->exponent-=exp/2; 		     /* back to 0.1->1 */
3006
3007    /* a is now at final precision and within 1 ulp of the properly */
3008    /* rounded square root of f; to ensure proper rounding, compare */
3009    /* squares of (a - l/2 ulp) and (a + l/2 ulp) with f. */
3010    /* Here workset.digits=maxp and t=0.5, and a->digits determines */
3011    /* the ulp */
3012    workset.digits--;				  /* maxp-1 is OK now */
3013    t->exponent=-a->digits-1;			  /* make 0.5 ulp */
3014    decAddOp(b, a, t, &workset, DECNEG, &ignore); /* b = a - 0.5 ulp */
3015    workset.round=DEC_ROUND_UP;
3016    decMultiplyOp(b, b, b, &workset, &ignore);	  /* b = mulru(b, b) */
3017    decCompareOp(b, f, b, &workset, COMPARE, &ignore); /* b ? f, reversed */
3018    if (decNumberIsNegative(b)) {		  /* f < b [i.e., b > f] */
3019      /* this is the more common adjustment, though both are rare */
3020      t->exponent++;				  /* make 1.0 ulp */
3021      t->lsu[0]=1;				  /* .. */
3022      decAddOp(a, a, t, &workset, DECNEG, &ignore); /* a = a - 1 ulp */
3023      /* assign to approx [round to length] */
3024      approxset.emin-=exp/2;			  /* adjust to match a */
3025      approxset.emax-=exp/2;
3026      decAddOp(a, &dzero, a, &approxset, 0, &ignore);
3027      }
3028     else {
3029      decAddOp(b, a, t, &workset, 0, &ignore);	  /* b = a + 0.5 ulp */
3030      workset.round=DEC_ROUND_DOWN;
3031      decMultiplyOp(b, b, b, &workset, &ignore);  /* b = mulrd(b, b) */
3032      decCompareOp(b, b, f, &workset, COMPARE, &ignore);   /* b ? f */
3033      if (decNumberIsNegative(b)) {		  /* b < f */
3034	t->exponent++;				  /* make 1.0 ulp */
3035	t->lsu[0]=1;				  /* .. */
3036	decAddOp(a, a, t, &workset, 0, &ignore);  /* a = a + 1 ulp */
3037	/* assign to approx [round to length] */
3038	approxset.emin-=exp/2;			  /* adjust to match a */
3039	approxset.emax-=exp/2;
3040	decAddOp(a, &dzero, a, &approxset, 0, &ignore);
3041	}
3042      }
3043    /* [no errors are possible in the above, and rounding/inexact during */
3044    /* estimation are irrelevant, so status was not accumulated] */
3045
3046    /* Here, 0.1 <= a < 1  (still), so adjust back */
3047    a->exponent+=exp/2; 		     /* set correct exponent */
3048
3049    /* count droppable zeros [after any subnormal rounding] by */
3050    /* trimming a copy */
3051    decNumberCopy(b, a);
3052    decTrim(b, set, 1, 1, &dropped);	     /* [drops trailing zeros] */
3053
3054    /* Set Inexact and Rounded.  The answer can only be exact if */
3055    /* it is short enough so that squaring it could fit in workp */
3056    /* digits, so this is the only (relatively rare) condition that */
3057    /* a careful check is needed */
3058    if (b->digits*2-1 > workp) {	     /* cannot fit */
3059      status|=DEC_Inexact|DEC_Rounded;
3060      }
3061     else {				     /* could be exact/unrounded */
3062      uInt mstatus=0;			     /* local status */
3063      decMultiplyOp(b, b, b, &workset, &mstatus); /* try the multiply */
3064      if (mstatus&DEC_Overflow) {	     /* result just won't fit */
3065	status|=DEC_Inexact|DEC_Rounded;
3066	}
3067       else {				     /* plausible */
3068	decCompareOp(t, b, rhs, &workset, COMPARE, &mstatus); /* b ? rhs */
3069	if (!ISZERO(t)) status|=DEC_Inexact|DEC_Rounded; /* not equal */
3070	 else { 			     /* is Exact */
3071	  /* here, dropped is the count of trailing zeros in 'a' */
3072	  /* use closest exponent to ideal... */
3073	  Int todrop=ideal-a->exponent;      /* most that can be dropped */
3074	  if (todrop<0) status|=DEC_Rounded; /* ideally would add 0s */
3075	   else {			     /* unrounded */
3076	    /* there are some to drop, but emax may not allow all */
3077	    Int maxexp=set->emax-set->digits+1;
3078	    Int maxdrop=maxexp-a->exponent;
3079	    if (todrop>maxdrop && set->clamp) { /* apply clamping */
3080	      todrop=maxdrop;
3081	      status|=DEC_Clamped;
3082	      }
3083	    if (dropped<todrop) {	     /* clamp to those available */
3084	      todrop=dropped;
3085	      status|=DEC_Clamped;
3086	      }
3087	    if (todrop>0) {		     /* have some to drop */
3088	      decShiftToLeast(a->lsu, D2U(a->digits), todrop);
3089	      a->exponent+=todrop;	     /* maintain numerical value */
3090	      a->digits-=todrop;	     /* new length */
3091	      }
3092	    }
3093	  }
3094	}
3095      }
3096
3097    /* double-check Underflow, as perhaps the result could not have */
3098    /* been subnormal (initial argument too big), or it is now Exact */
3099    if (status&DEC_Underflow) {
3100      Int ae=rhs->exponent+rhs->digits-1;    /* adjusted exponent */
3101      /* check if truly subnormal */
3102      #if DECEXTFLAG			     /* DEC_Subnormal too */
3103	if (ae>=set->emin*2) status&=~(DEC_Subnormal|DEC_Underflow);
3104      #else
3105	if (ae>=set->emin*2) status&=~DEC_Underflow;
3106      #endif
3107      /* check if truly inexact */
3108      if (!(status&DEC_Inexact)) status&=~DEC_Underflow;
3109      }
3110
3111    decNumberCopy(res, a);		     /* a is now the result */
3112    } while(0); 			     /* end protected */
3113
3114  free(allocbuff);      /* drop any storage used */
3115  free(allocbufa);      /* .. */
3116  free(allocbufb);      /* .. */
3117  #if DECSUBSET
3118  free(allocrhs);	     /* .. */
3119  #endif
3120  if (status!=0) decStatus(res, status, set);/* then report status */
3121  #if DECCHECK
3122  decCheckInexact(res, set);
3123  #endif
3124  return res;
3125  } /* decNumberSquareRoot */
3126
3127/* ------------------------------------------------------------------ */
3128/* decNumberSubtract -- subtract two Numbers			      */
3129/*								      */
3130/*   This computes C = A - B					      */
3131/*								      */
3132/*   res is C, the result.  C may be A and/or B (e.g., X=X-X)	      */
3133/*   lhs is A							      */
3134/*   rhs is B							      */
3135/*   set is the context 					      */
3136/*								      */
3137/* C must have space for set->digits digits.			      */
3138/* ------------------------------------------------------------------ */
3139decNumber * decNumberSubtract(decNumber *res, const decNumber *lhs,
3140			      const decNumber *rhs, decContext *set) {
3141  uInt status=0;			/* accumulator */
3142
3143  decAddOp(res, lhs, rhs, set, DECNEG, &status);
3144  if (status!=0) decStatus(res, status, set);
3145  #if DECCHECK
3146  decCheckInexact(res, set);
3147  #endif
3148  return res;
3149  } /* decNumberSubtract */
3150
3151/* ------------------------------------------------------------------ */
3152/* decNumberToIntegralExact -- round-to-integral-value with InExact   */
3153/* decNumberToIntegralValue -- round-to-integral-value		      */
3154/*								      */
3155/*   res is the result						      */
3156/*   rhs is input number					      */
3157/*   set is the context 					      */
3158/*								      */
3159/* res must have space for any value of rhs.			      */
3160/*								      */
3161/* This implements the IEEE special operators and therefore treats    */
3162/* special values as valid.  For finite numbers it returns	      */
3163/* rescale(rhs, 0) if rhs->exponent is <0.			      */
3164/* Otherwise the result is rhs (so no error is possible, except for   */
3165/* sNaN).							      */
3166/*								      */
3167/* The context is used for rounding mode and status after sNaN, but   */
3168/* the digits setting is ignored.  The Exact version will signal      */
3169/* Inexact if the result differs numerically from rhs; the other      */
3170/* never signals Inexact.					      */
3171/* ------------------------------------------------------------------ */
3172decNumber * decNumberToIntegralExact(decNumber *res, const decNumber *rhs,
3173				     decContext *set) {
3174  decNumber dn;
3175  decContext workset;		   /* working context */
3176  uInt status=0;		   /* accumulator */
3177
3178  #if DECCHECK
3179  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
3180  #endif
3181
3182  /* handle infinities and NaNs */
3183  if (SPECIALARG) {
3184    if (decNumberIsInfinite(rhs)) decNumberCopy(res, rhs); /* an Infinity */
3185     else decNaNs(res, rhs, NULL, set, &status); /* a NaN */
3186    }
3187   else { /* finite */
3188    /* have a finite number; no error possible (res must be big enough) */
3189    if (rhs->exponent>=0) return decNumberCopy(res, rhs);
3190    /* that was easy, but if negative exponent there is work to do... */
3191    workset=*set;		   /* clone rounding, etc. */
3192    workset.digits=rhs->digits;    /* no length rounding */
3193    workset.traps=0;		   /* no traps */
3194    decNumberZero(&dn); 	   /* make a number with exponent 0 */
3195    decNumberQuantize(res, rhs, &dn, &workset);
3196    status|=workset.status;
3197    }
3198  if (status!=0) decStatus(res, status, set);
3199  return res;
3200  } /* decNumberToIntegralExact */
3201
3202decNumber * decNumberToIntegralValue(decNumber *res, const decNumber *rhs,
3203				     decContext *set) {
3204  decContext workset=*set;	   /* working context */
3205  workset.traps=0;		   /* no traps */
3206  decNumberToIntegralExact(res, rhs, &workset);
3207  /* this never affects set, except for sNaNs; NaN will have been set */
3208  /* or propagated already, so no need to call decStatus */
3209  set->status|=workset.status&DEC_Invalid_operation;
3210  return res;
3211  } /* decNumberToIntegralValue */
3212
3213/* ------------------------------------------------------------------ */
3214/* decNumberXor -- XOR two Numbers, digitwise			      */
3215/*								      */
3216/*   This computes C = A ^ B					      */
3217/*								      */
3218/*   res is C, the result.  C may be A and/or B (e.g., X=X^X)	      */
3219/*   lhs is A							      */
3220/*   rhs is B							      */
3221/*   set is the context (used for result length and error report)     */
3222/*								      */
3223/* C must have space for set->digits digits.			      */
3224/*								      */
3225/* Logical function restrictions apply (see above); a NaN is	      */
3226/* returned with Invalid_operation if a restriction is violated.      */
3227/* ------------------------------------------------------------------ */
3228decNumber * decNumberXor(decNumber *res, const decNumber *lhs,
3229			 const decNumber *rhs, decContext *set) {
3230  const Unit *ua, *ub;			/* -> operands */
3231  const Unit *msua, *msub;		/* -> operand msus */
3232  Unit	*uc, *msuc;			/* -> result and its msu */
3233  Int	msudigs;			/* digits in res msu */
3234  #if DECCHECK
3235  if (decCheckOperands(res, lhs, rhs, set)) return res;
3236  #endif
3237
3238  if (lhs->exponent!=0 || decNumberIsSpecial(lhs) || decNumberIsNegative(lhs)
3239   || rhs->exponent!=0 || decNumberIsSpecial(rhs) || decNumberIsNegative(rhs)) {
3240    decStatus(res, DEC_Invalid_operation, set);
3241    return res;
3242    }
3243  /* operands are valid */
3244  ua=lhs->lsu;				/* bottom-up */
3245  ub=rhs->lsu;				/* .. */
3246  uc=res->lsu;				/* .. */
3247  msua=ua+D2U(lhs->digits)-1;		/* -> msu of lhs */
3248  msub=ub+D2U(rhs->digits)-1;		/* -> msu of rhs */
3249  msuc=uc+D2U(set->digits)-1;		/* -> msu of result */
3250  msudigs=MSUDIGITS(set->digits);	/* [faster than remainder] */
3251  for (; uc<=msuc; ua++, ub++, uc++) {	/* Unit loop */
3252    Unit a, b;				/* extract units */
3253    if (ua>msua) a=0;
3254     else a=*ua;
3255    if (ub>msub) b=0;
3256     else b=*ub;
3257    *uc=0;				/* can now write back */
3258    if (a|b) {				/* maybe 1 bits to examine */
3259      Int i, j;
3260      /* This loop could be unrolled and/or use BIN2BCD tables */
3261      for (i=0; i<DECDPUN; i++) {
3262	if ((a^b)&1) *uc=*uc+(Unit)powers[i];	  /* effect XOR */
3263	j=a%10;
3264	a=a/10;
3265	j|=b%10;
3266	b=b/10;
3267	if (j>1) {
3268	  decStatus(res, DEC_Invalid_operation, set);
3269	  return res;
3270	  }
3271	if (uc==msuc && i==msudigs-1) break;	  /* just did final digit */
3272	} /* each digit */
3273      } /* non-zero */
3274    } /* each unit */
3275  /* [here uc-1 is the msu of the result] */
3276  res->digits=decGetDigits(res->lsu, uc-res->lsu);
3277  res->exponent=0;			/* integer */
3278  res->bits=0;				/* sign=0 */
3279  return res;  /* [no status to set] */
3280  } /* decNumberXor */
3281
3282
3283/* ================================================================== */
3284/* Utility routines						      */
3285/* ================================================================== */
3286
3287/* ------------------------------------------------------------------ */
3288/* decNumberClass -- return the decClass of a decNumber 	      */
3289/*   dn -- the decNumber to test				      */
3290/*   set -- the context to use for Emin 			      */
3291/*   returns the decClass enum					      */
3292/* ------------------------------------------------------------------ */
3293enum decClass decNumberClass(const decNumber *dn, decContext *set) {
3294  if (decNumberIsSpecial(dn)) {
3295    if (decNumberIsQNaN(dn)) return DEC_CLASS_QNAN;
3296    if (decNumberIsSNaN(dn)) return DEC_CLASS_SNAN;
3297    /* must be an infinity */
3298    if (decNumberIsNegative(dn)) return DEC_CLASS_NEG_INF;
3299    return DEC_CLASS_POS_INF;
3300    }
3301  /* is finite */
3302  if (decNumberIsNormal(dn, set)) { /* most common */
3303    if (decNumberIsNegative(dn)) return DEC_CLASS_NEG_NORMAL;
3304    return DEC_CLASS_POS_NORMAL;
3305    }
3306  /* is subnormal or zero */
3307  if (decNumberIsZero(dn)) {	/* most common */
3308    if (decNumberIsNegative(dn)) return DEC_CLASS_NEG_ZERO;
3309    return DEC_CLASS_POS_ZERO;
3310    }
3311  if (decNumberIsNegative(dn)) return DEC_CLASS_NEG_SUBNORMAL;
3312  return DEC_CLASS_POS_SUBNORMAL;
3313  } /* decNumberClass */
3314
3315/* ------------------------------------------------------------------ */
3316/* decNumberClassToString -- convert decClass to a string	      */
3317/*								      */
3318/*  eclass is a valid decClass					      */
3319/*  returns a constant string describing the class (max 13+1 chars)   */
3320/* ------------------------------------------------------------------ */
3321const char *decNumberClassToString(enum decClass eclass) {
3322  if (eclass==DEC_CLASS_POS_NORMAL)    return DEC_ClassString_PN;
3323  if (eclass==DEC_CLASS_NEG_NORMAL)    return DEC_ClassString_NN;
3324  if (eclass==DEC_CLASS_POS_ZERO)      return DEC_ClassString_PZ;
3325  if (eclass==DEC_CLASS_NEG_ZERO)      return DEC_ClassString_NZ;
3326  if (eclass==DEC_CLASS_POS_SUBNORMAL) return DEC_ClassString_PS;
3327  if (eclass==DEC_CLASS_NEG_SUBNORMAL) return DEC_ClassString_NS;
3328  if (eclass==DEC_CLASS_POS_INF)       return DEC_ClassString_PI;
3329  if (eclass==DEC_CLASS_NEG_INF)       return DEC_ClassString_NI;
3330  if (eclass==DEC_CLASS_QNAN)	       return DEC_ClassString_QN;
3331  if (eclass==DEC_CLASS_SNAN)	       return DEC_ClassString_SN;
3332  return DEC_ClassString_UN;	       /* Unknown */
3333  } /* decNumberClassToString */
3334
3335/* ------------------------------------------------------------------ */
3336/* decNumberCopy -- copy a number				      */
3337/*								      */
3338/*   dest is the target decNumber				      */
3339/*   src  is the source decNumber				      */
3340/*   returns dest						      */
3341/*								      */
3342/* (dest==src is allowed and is a no-op)			      */
3343/* All fields are updated as required.	This is a utility operation,  */
3344/* so special values are unchanged and no error is possible.	      */
3345/* ------------------------------------------------------------------ */
3346decNumber * decNumberCopy(decNumber *dest, const decNumber *src) {
3347
3348  #if DECCHECK
3349  if (src==NULL) return decNumberZero(dest);
3350  #endif
3351
3352  if (dest==src) return dest;		     /* no copy required */
3353
3354  /* Use explicit assignments here as structure assignment could copy */
3355  /* more than just the lsu (for small DECDPUN).  This would not affect */
3356  /* the value of the results, but could disturb test harness spill */
3357  /* checking. */
3358  dest->bits=src->bits;
3359  dest->exponent=src->exponent;
3360  dest->digits=src->digits;
3361  dest->lsu[0]=src->lsu[0];
3362  if (src->digits>DECDPUN) {		     /* more Units to come */
3363    const Unit *smsup, *s;		     /* work */
3364    Unit  *d;				     /* .. */
3365    /* memcpy for the remaining Units would be safe as they cannot */
3366    /* overlap.  However, this explicit loop is faster in short cases. */
3367    d=dest->lsu+1;			     /* -> first destination */
3368    smsup=src->lsu+D2U(src->digits);	     /* -> source msu+1 */
3369    for (s=src->lsu+1; s<smsup; s++, d++) *d=*s;
3370    }
3371  return dest;
3372  } /* decNumberCopy */
3373
3374/* ------------------------------------------------------------------ */
3375/* decNumberCopyAbs -- quiet absolute value operator		      */
3376/*								      */
3377/*   This sets C = abs(A)					      */
3378/*								      */
3379/*   res is C, the result.  C may be A				      */
3380/*   rhs is A							      */
3381/*								      */
3382/* C must have space for set->digits digits.			      */
3383/* No exception or error can occur; this is a quiet bitwise operation.*/
3384/* See also decNumberAbs for a checking version of this.	      */
3385/* ------------------------------------------------------------------ */
3386decNumber * decNumberCopyAbs(decNumber *res, const decNumber *rhs) {
3387  #if DECCHECK
3388  if (decCheckOperands(res, DECUNUSED, rhs, DECUNCONT)) return res;
3389  #endif
3390  decNumberCopy(res, rhs);
3391  res->bits&=~DECNEG;			/* turn off sign */
3392  return res;
3393  } /* decNumberCopyAbs */
3394
3395/* ------------------------------------------------------------------ */
3396/* decNumberCopyNegate -- quiet negate value operator		      */
3397/*								      */
3398/*   This sets C = negate(A)					      */
3399/*								      */
3400/*   res is C, the result.  C may be A				      */
3401/*   rhs is A							      */
3402/*								      */
3403/* C must have space for set->digits digits.			      */
3404/* No exception or error can occur; this is a quiet bitwise operation.*/
3405/* See also decNumberMinus for a checking version of this.	      */
3406/* ------------------------------------------------------------------ */
3407decNumber * decNumberCopyNegate(decNumber *res, const decNumber *rhs) {
3408  #if DECCHECK
3409  if (decCheckOperands(res, DECUNUSED, rhs, DECUNCONT)) return res;
3410  #endif
3411  decNumberCopy(res, rhs);
3412  res->bits^=DECNEG;			/* invert the sign */
3413  return res;
3414  } /* decNumberCopyNegate */
3415
3416/* ------------------------------------------------------------------ */
3417/* decNumberCopySign -- quiet copy and set sign operator	      */
3418/*								      */
3419/*   This sets C = A with the sign of B 			      */
3420/*								      */
3421/*   res is C, the result.  C may be A				      */
3422/*   lhs is A							      */
3423/*   rhs is B							      */
3424/*								      */
3425/* C must have space for set->digits digits.			      */
3426/* No exception or error can occur; this is a quiet bitwise operation.*/
3427/* ------------------------------------------------------------------ */
3428decNumber * decNumberCopySign(decNumber *res, const decNumber *lhs,
3429			      const decNumber *rhs) {
3430  uByte sign;				/* rhs sign */
3431  #if DECCHECK
3432  if (decCheckOperands(res, DECUNUSED, rhs, DECUNCONT)) return res;
3433  #endif
3434  sign=rhs->bits & DECNEG;		/* save sign bit */
3435  decNumberCopy(res, lhs);
3436  res->bits&=~DECNEG;			/* clear the sign */
3437  res->bits|=sign;			/* set from rhs */
3438  return res;
3439  } /* decNumberCopySign */
3440
3441/* ------------------------------------------------------------------ */
3442/* decNumberGetBCD -- get the coefficient in BCD8		      */
3443/*   dn is the source decNumber 				      */
3444/*   bcd is the uInt array that will receive dn->digits BCD bytes,    */
3445/*     most-significant at offset 0				      */
3446/*   returns bcd						      */
3447/*								      */
3448/* bcd must have at least dn->digits bytes.  No error is possible; if */
3449/* dn is a NaN or Infinite, digits must be 1 and the coefficient 0.   */
3450/* ------------------------------------------------------------------ */
3451uByte * decNumberGetBCD(const decNumber *dn, uByte *bcd) {
3452  uByte *ub=bcd+dn->digits-1;	   /* -> lsd */
3453  const Unit *up=dn->lsu;	   /* Unit pointer, -> lsu */
3454
3455  #if DECDPUN==1		   /* trivial simple copy */
3456    for (; ub>=bcd; ub--, up++) *ub=*up;
3457  #else 			   /* chopping needed */
3458    uInt u=*up; 		   /* work */
3459    uInt cut=DECDPUN;		   /* downcounter through unit */
3460    for (; ub>=bcd; ub--) {
3461      *ub=(uByte)(u%10);	   /* [*6554 trick inhibits, here] */
3462      u=u/10;
3463      cut--;
3464      if (cut>0) continue;	   /* more in this unit */
3465      up++;
3466      u=*up;
3467      cut=DECDPUN;
3468      }
3469  #endif
3470  return bcd;
3471  } /* decNumberGetBCD */
3472
3473/* ------------------------------------------------------------------ */
3474/* decNumberSetBCD -- set (replace) the coefficient from BCD8	      */
3475/*   dn is the target decNumber 				      */
3476/*   bcd is the uInt array that will source n BCD bytes, most-	      */
3477/*     significant at offset 0					      */
3478/*   n is the number of digits in the source BCD array (bcd)	      */
3479/*   returns dn 						      */
3480/*								      */
3481/* dn must have space for at least n digits.  No error is possible;   */
3482/* if dn is a NaN, or Infinite, or is to become a zero, n must be 1   */
3483/* and bcd[0] zero.						      */
3484/* ------------------------------------------------------------------ */
3485decNumber * decNumberSetBCD(decNumber *dn, const uByte *bcd, uInt n) {
3486  Unit *up=dn->lsu+D2U(dn->digits)-1;	/* -> msu [target pointer] */
3487  const uByte *ub=bcd;			/* -> source msd */
3488
3489  #if DECDPUN==1			/* trivial simple copy */
3490    for (; ub<bcd+n; ub++, up--) *up=*ub;
3491  #else 				/* some assembly needed */
3492    /* calculate how many digits in msu, and hence first cut */
3493    Int cut=MSUDIGITS(n);		/* [faster than remainder] */
3494    for (;up>=dn->lsu; up--) {		/* each Unit from msu */
3495      *up=0;				/* will take <=DECDPUN digits */
3496      for (; cut>0; ub++, cut--) *up=X10(*up)+*ub;
3497      cut=DECDPUN;			/* next Unit has all digits */
3498      }
3499  #endif
3500  dn->digits=n; 			/* set digit count */
3501  return dn;
3502  } /* decNumberSetBCD */
3503
3504/* ------------------------------------------------------------------ */
3505/* decNumberIsNormal -- test normality of a decNumber		      */
3506/*   dn is the decNumber to test				      */
3507/*   set is the context to use for Emin 			      */
3508/*   returns 1 if |dn| is finite and >=Nmin, 0 otherwise	      */
3509/* ------------------------------------------------------------------ */
3510Int decNumberIsNormal(const decNumber *dn, decContext *set) {
3511  Int ae;				/* adjusted exponent */
3512  #if DECCHECK
3513  if (decCheckOperands(DECUNRESU, DECUNUSED, dn, set)) return 0;
3514  #endif
3515
3516  if (decNumberIsSpecial(dn)) return 0; /* not finite */
3517  if (decNumberIsZero(dn)) return 0;	/* not non-zero */
3518
3519  ae=dn->exponent+dn->digits-1; 	/* adjusted exponent */
3520  if (ae<set->emin) return 0;		/* is subnormal */
3521  return 1;
3522  } /* decNumberIsNormal */
3523
3524/* ------------------------------------------------------------------ */
3525/* decNumberIsSubnormal -- test subnormality of a decNumber	      */
3526/*   dn is the decNumber to test				      */
3527/*   set is the context to use for Emin 			      */
3528/*   returns 1 if |dn| is finite, non-zero, and <Nmin, 0 otherwise    */
3529/* ------------------------------------------------------------------ */
3530Int decNumberIsSubnormal(const decNumber *dn, decContext *set) {
3531  Int ae;				/* adjusted exponent */
3532  #if DECCHECK
3533  if (decCheckOperands(DECUNRESU, DECUNUSED, dn, set)) return 0;
3534  #endif
3535
3536  if (decNumberIsSpecial(dn)) return 0; /* not finite */
3537  if (decNumberIsZero(dn)) return 0;	/* not non-zero */
3538
3539  ae=dn->exponent+dn->digits-1; 	/* adjusted exponent */
3540  if (ae<set->emin) return 1;		/* is subnormal */
3541  return 0;
3542  } /* decNumberIsSubnormal */
3543
3544/* ------------------------------------------------------------------ */
3545/* decNumberTrim -- remove insignificant zeros			      */
3546/*								      */
3547/*   dn is the number to trim					      */
3548/*   returns dn 						      */
3549/*								      */
3550/* All fields are updated as required.	This is a utility operation,  */
3551/* so special values are unchanged and no error is possible.  The     */
3552/* zeros are removed unconditionally.				      */
3553/* ------------------------------------------------------------------ */
3554decNumber * decNumberTrim(decNumber *dn) {
3555  Int  dropped; 		   /* work */
3556  decContext set;		   /* .. */
3557  #if DECCHECK
3558  if (decCheckOperands(DECUNRESU, DECUNUSED, dn, DECUNCONT)) return dn;
3559  #endif
3560  decContextDefault(&set, DEC_INIT_BASE);    /* clamp=0 */
3561  return decTrim(dn, &set, 0, 1, &dropped);
3562  } /* decNumberTrim */
3563
3564/* ------------------------------------------------------------------ */
3565/* decNumberVersion -- return the name and version of this module     */
3566/*								      */
3567/* No error is possible.					      */
3568/* ------------------------------------------------------------------ */
3569const char * decNumberVersion(void) {
3570  return DECVERSION;
3571  } /* decNumberVersion */
3572
3573/* ------------------------------------------------------------------ */
3574/* decNumberZero -- set a number to 0				      */
3575/*								      */
3576/*   dn is the number to set, with space for one digit		      */
3577/*   returns dn 						      */
3578/*								      */
3579/* No error is possible.					      */
3580/* ------------------------------------------------------------------ */
3581/* Memset is not used as it is much slower in some environments. */
3582decNumber * decNumberZero(decNumber *dn) {
3583
3584  #if DECCHECK
3585  if (decCheckOperands(dn, DECUNUSED, DECUNUSED, DECUNCONT)) return dn;
3586  #endif
3587
3588  dn->bits=0;
3589  dn->exponent=0;
3590  dn->digits=1;
3591  dn->lsu[0]=0;
3592  return dn;
3593  } /* decNumberZero */
3594
3595/* ================================================================== */
3596/* Local routines						      */
3597/* ================================================================== */
3598
3599/* ------------------------------------------------------------------ */
3600/* decToString -- lay out a number into a string		      */
3601/*								      */
3602/*   dn     is the number to lay out				      */
3603/*   string is where to lay out the number			      */
3604/*   eng    is 1 if Engineering, 0 if Scientific		      */
3605/*								      */
3606/* string must be at least dn->digits+14 characters long	      */
3607/* No error is possible.					      */
3608/*								      */
3609/* Note that this routine can generate a -0 or 0.000.  These are      */
3610/* never generated in subset to-number or arithmetic, but can occur   */
3611/* in non-subset arithmetic (e.g., -1*0 or 1.234-1.234).	      */
3612/* ------------------------------------------------------------------ */
3613/* If DECCHECK is enabled the string "?" is returned if a number is */
3614/* invalid. */
3615static void decToString(const decNumber *dn, char *string, Flag eng) {
3616  Int exp=dn->exponent;       /* local copy */
3617  Int e;		      /* E-part value */
3618  Int pre;		      /* digits before the '.' */
3619  Int cut;		      /* for counting digits in a Unit */
3620  char *c=string;	      /* work [output pointer] */
3621  const Unit *up=dn->lsu+D2U(dn->digits)-1; /* -> msu [input pointer] */
3622  uInt u, pow;		      /* work */
3623
3624  #if DECCHECK
3625  if (decCheckOperands(DECUNRESU, dn, DECUNUSED, DECUNCONT)) {
3626    strcpy(string, "?");
3627    return;}
3628  #endif
3629
3630  if (decNumberIsNegative(dn)) {   /* Negatives get a minus */
3631    *c='-';
3632    c++;
3633    }
3634  if (dn->bits&DECSPECIAL) {	   /* Is a special value */
3635    if (decNumberIsInfinite(dn)) {
3636      strcpy(c,   "Inf");
3637      strcpy(c+3, "inity");
3638      return;}
3639    /* a NaN */
3640    if (dn->bits&DECSNAN) {	   /* signalling NaN */
3641      *c='s';
3642      c++;
3643      }
3644    strcpy(c, "NaN");
3645    c+=3;			   /* step past */
3646    /* if not a clean non-zero coefficient, that's all there is in a */
3647    /* NaN string */
3648    if (exp!=0 || (*dn->lsu==0 && dn->digits==1)) return;
3649    /* [drop through to add integer] */
3650    }
3651
3652  /* calculate how many digits in msu, and hence first cut */
3653  cut=MSUDIGITS(dn->digits);	   /* [faster than remainder] */
3654  cut--;			   /* power of ten for digit */
3655
3656  if (exp==0) { 		   /* simple integer [common fastpath] */
3657    for (;up>=dn->lsu; up--) {	   /* each Unit from msu */
3658      u=*up;			   /* contains DECDPUN digits to lay out */
3659      for (; cut>=0; c++, cut--) TODIGIT(u, cut, c, pow);
3660      cut=DECDPUN-1;		   /* next Unit has all digits */
3661      }
3662    *c='\0';			   /* terminate the string */
3663    return;}
3664
3665  /* non-0 exponent -- assume plain form */
3666  pre=dn->digits+exp;		   /* digits before '.' */
3667  e=0;				   /* no E */
3668  if ((exp>0) || (pre<-5)) {	   /* need exponential form */
3669    e=exp+dn->digits-1; 	   /* calculate E value */
3670    pre=1;			   /* assume one digit before '.' */
3671    if (eng && (e!=0)) {	   /* engineering: may need to adjust */
3672      Int adj;			   /* adjustment */
3673      /* The C remainder operator is undefined for negative numbers, so */
3674      /* a positive remainder calculation must be used here */
3675      if (e<0) {
3676	adj=(-e)%3;
3677	if (adj!=0) adj=3-adj;
3678	}
3679       else { /* e>0 */
3680	adj=e%3;
3681	}
3682      e=e-adj;
3683      /* if dealing with zero still produce an exponent which is a */
3684      /* multiple of three, as expected, but there will only be the */
3685      /* one zero before the E, still.	Otherwise note the padding. */
3686      if (!ISZERO(dn)) pre+=adj;
3687       else {  /* is zero */
3688	if (adj!=0) {		   /* 0.00Esnn needed */
3689	  e=e+3;
3690	  pre=-(2-adj);
3691	  }
3692	} /* zero */
3693      } /* eng */
3694    } /* need exponent */
3695
3696  /* lay out the digits of the coefficient, adding 0s and . as needed */
3697  u=*up;
3698  if (pre>0) {			   /* xxx.xxx or xx00 (engineering) form */
3699    Int n=pre;
3700    for (; pre>0; pre--, c++, cut--) {
3701      if (cut<0) {		   /* need new Unit */
3702	if (up==dn->lsu) break;    /* out of input digits (pre>digits) */
3703	up--;
3704	cut=DECDPUN-1;
3705	u=*up;
3706	}
3707      TODIGIT(u, cut, c, pow);
3708      }
3709    if (n<dn->digits) { 	   /* more to come, after '.' */
3710      *c='.'; c++;
3711      for (;; c++, cut--) {
3712	if (cut<0) {		   /* need new Unit */
3713	  if (up==dn->lsu) break;  /* out of input digits */
3714	  up--;
3715	  cut=DECDPUN-1;
3716	  u=*up;
3717	  }
3718	TODIGIT(u, cut, c, pow);
3719	}
3720      }
3721     else for (; pre>0; pre--, c++) *c='0'; /* 0 padding (for engineering) needed */
3722    }
3723   else {			   /* 0.xxx or 0.000xxx form */
3724    *c='0'; c++;
3725    *c='.'; c++;
3726    for (; pre<0; pre++, c++) *c='0';	/* add any 0's after '.' */
3727    for (; ; c++, cut--) {
3728      if (cut<0) {		   /* need new Unit */
3729	if (up==dn->lsu) break;    /* out of input digits */
3730	up--;
3731	cut=DECDPUN-1;
3732	u=*up;
3733	}
3734      TODIGIT(u, cut, c, pow);
3735      }
3736    }
3737
3738  /* Finally add the E-part, if needed.  It will never be 0, has a
3739     base maximum and minimum of +999999999 through -999999999, but
3740     could range down to -1999999998 for anormal numbers */
3741  if (e!=0) {
3742    Flag had=0; 	      /* 1=had non-zero */
3743    *c='E'; c++;
3744    *c='+'; c++;	      /* assume positive */
3745    u=e;		      /* .. */
3746    if (e<0) {
3747      *(c-1)='-';	      /* oops, need - */
3748      u=-e;		      /* uInt, please */
3749      }
3750    /* lay out the exponent [_itoa or equivalent is not ANSI C] */
3751    for (cut=9; cut>=0; cut--) {
3752      TODIGIT(u, cut, c, pow);
3753      if (*c=='0' && !had) continue;	/* skip leading zeros */
3754      had=1;				/* had non-0 */
3755      c++;				/* step for next */
3756      } /* cut */
3757    }
3758  *c='\0';	    /* terminate the string (all paths) */
3759  return;
3760  } /* decToString */
3761
3762/* ------------------------------------------------------------------ */
3763/* decAddOp -- add/subtract operation				      */
3764/*								      */
3765/*   This computes C = A + B					      */
3766/*								      */
3767/*   res is C, the result.  C may be A and/or B (e.g., X=X+X)	      */
3768/*   lhs is A							      */
3769/*   rhs is B							      */
3770/*   set is the context 					      */
3771/*   negate is DECNEG if rhs should be negated, or 0 otherwise	      */
3772/*   status accumulates status for the caller			      */
3773/*								      */
3774/* C must have space for set->digits digits.			      */
3775/* Inexact in status must be 0 for correct Exact zero sign in result  */
3776/* ------------------------------------------------------------------ */
3777/* If possible, the coefficient is calculated directly into C.	      */
3778/* However, if: 						      */
3779/*   -- a digits+1 calculation is needed because the numbers are      */
3780/*	unaligned and span more than set->digits digits 	      */
3781/*   -- a carry to digits+1 digits looks possible		      */
3782/*   -- C is the same as A or B, and the result would destructively   */
3783/*	overlap the A or B coefficient				      */
3784/* then the result must be calculated into a temporary buffer.	In    */
3785/* this case a local (stack) buffer is used if possible, and only if  */
3786/* too long for that does malloc become the final resort.	      */
3787/*								      */
3788/* Misalignment is handled as follows:				      */
3789/*   Apad: (AExp>BExp) Swap operands and proceed as for BExp>AExp.    */
3790/*   BPad: Apply the padding by a combination of shifting (whole      */
3791/*	   units) and multiplication (part units).		      */
3792/*								      */
3793/* Addition, especially x=x+1, is speed-critical.		      */
3794/* The static buffer is larger than might be expected to allow for    */
3795/* calls from higher-level funtions (notable exp).		      */
3796/* ------------------------------------------------------------------ */
3797static decNumber * decAddOp(decNumber *res, const decNumber *lhs,
3798			    const decNumber *rhs, decContext *set,
3799			    uByte negate, uInt *status) {
3800  #if DECSUBSET
3801  decNumber *alloclhs=NULL;	   /* non-NULL if rounded lhs allocated */
3802  decNumber *allocrhs=NULL;	   /* .., rhs */
3803  #endif
3804  Int	rhsshift;		   /* working shift (in Units) */
3805  Int	maxdigits;		   /* longest logical length */
3806  Int	mult;			   /* multiplier */
3807  Int	residue;		   /* rounding accumulator */
3808  uByte bits;			   /* result bits */
3809  Flag	diffsign;		   /* non-0 if arguments have different sign */
3810  Unit	*acc;			   /* accumulator for result */
3811  Unit	accbuff[SD2U(DECBUFFER*2+20)]; /* local buffer [*2+20 reduces many */
3812				   /* allocations when called from */
3813				   /* other operations, notable exp] */
3814  Unit	*allocacc=NULL; 	   /* -> allocated acc buffer, iff allocated */
3815  Int	reqdigits=set->digits;	   /* local copy; requested DIGITS */
3816  Int	padding;		   /* work */
3817
3818  #if DECCHECK
3819  if (decCheckOperands(res, lhs, rhs, set)) return res;
3820  #endif
3821
3822  do {				   /* protect allocated storage */
3823    #if DECSUBSET
3824    if (!set->extended) {
3825      /* reduce operands and set lostDigits status, as needed */
3826      if (lhs->digits>reqdigits) {
3827	alloclhs=decRoundOperand(lhs, set, status);
3828	if (alloclhs==NULL) break;
3829	lhs=alloclhs;
3830	}
3831      if (rhs->digits>reqdigits) {
3832	allocrhs=decRoundOperand(rhs, set, status);
3833	if (allocrhs==NULL) break;
3834	rhs=allocrhs;
3835	}
3836      }
3837    #endif
3838    /* [following code does not require input rounding] */
3839
3840    /* note whether signs differ [used all paths] */
3841    diffsign=(Flag)((lhs->bits^rhs->bits^negate)&DECNEG);
3842
3843    /* handle infinities and NaNs */
3844    if (SPECIALARGS) {			/* a special bit set */
3845      if (SPECIALARGS & (DECSNAN | DECNAN))  /* a NaN */
3846	decNaNs(res, lhs, rhs, set, status);
3847       else { /* one or two infinities */
3848	if (decNumberIsInfinite(lhs)) { /* LHS is infinity */
3849	  /* two infinities with different signs is invalid */
3850	  if (decNumberIsInfinite(rhs) && diffsign) {
3851	    *status|=DEC_Invalid_operation;
3852	    break;
3853	    }
3854	  bits=lhs->bits & DECNEG;	/* get sign from LHS */
3855	  }
3856	 else bits=(rhs->bits^negate) & DECNEG;/* RHS must be Infinity */
3857	bits|=DECINF;
3858	decNumberZero(res);
3859	res->bits=bits; 		/* set +/- infinity */
3860	} /* an infinity */
3861      break;
3862      }
3863
3864    /* Quick exit for add 0s; return the non-0, modified as need be */
3865    if (ISZERO(lhs)) {
3866      Int adjust;			/* work */
3867      Int lexp=lhs->exponent;		/* save in case LHS==RES */
3868      bits=lhs->bits;			/* .. */
3869      residue=0;			/* clear accumulator */
3870      decCopyFit(res, rhs, set, &residue, status); /* copy (as needed) */
3871      res->bits^=negate;		/* flip if rhs was negated */
3872      #if DECSUBSET
3873      if (set->extended) {		/* exponents on zeros count */
3874      #endif
3875	/* exponent will be the lower of the two */
3876	adjust=lexp-res->exponent;	/* adjustment needed [if -ve] */
3877	if (ISZERO(res)) {		/* both 0: special IEEE 754 rules */
3878	  if (adjust<0) res->exponent=lexp;  /* set exponent */
3879	  /* 0-0 gives +0 unless rounding to -infinity, and -0-0 gives -0 */
3880	  if (diffsign) {
3881	    if (set->round!=DEC_ROUND_FLOOR) res->bits=0;
3882	     else res->bits=DECNEG;	/* preserve 0 sign */
3883	    }
3884	  }
3885	 else { /* non-0 res */
3886	  if (adjust<0) {     /* 0-padding needed */
3887	    if ((res->digits-adjust)>set->digits) {
3888	      adjust=res->digits-set->digits;	  /* to fit exactly */
3889	      *status|=DEC_Rounded;		  /* [but exact] */
3890	      }
3891	    res->digits=decShiftToMost(res->lsu, res->digits, -adjust);
3892	    res->exponent+=adjust;		  /* set the exponent. */
3893	    }
3894	  } /* non-0 res */
3895      #if DECSUBSET
3896	} /* extended */
3897      #endif
3898      decFinish(res, set, &residue, status);	  /* clean and finalize */
3899      break;}
3900
3901    if (ISZERO(rhs)) {			/* [lhs is non-zero] */
3902      Int adjust;			/* work */
3903      Int rexp=rhs->exponent;		/* save in case RHS==RES */
3904      bits=rhs->bits;			/* be clean */
3905      residue=0;			/* clear accumulator */
3906      decCopyFit(res, lhs, set, &residue, status); /* copy (as needed) */
3907      #if DECSUBSET
3908      if (set->extended) {		/* exponents on zeros count */
3909      #endif
3910	/* exponent will be the lower of the two */
3911	/* [0-0 case handled above] */
3912	adjust=rexp-res->exponent;	/* adjustment needed [if -ve] */
3913	if (adjust<0) {     /* 0-padding needed */
3914	  if ((res->digits-adjust)>set->digits) {
3915	    adjust=res->digits-set->digits;	/* to fit exactly */
3916	    *status|=DEC_Rounded;		/* [but exact] */
3917	    }
3918	  res->digits=decShiftToMost(res->lsu, res->digits, -adjust);
3919	  res->exponent+=adjust;		/* set the exponent. */
3920	  }
3921      #if DECSUBSET
3922	} /* extended */
3923      #endif
3924      decFinish(res, set, &residue, status);	  /* clean and finalize */
3925      break;}
3926
3927    /* [NB: both fastpath and mainpath code below assume these cases */
3928    /* (notably 0-0) have already been handled] */
3929
3930    /* calculate the padding needed to align the operands */
3931    padding=rhs->exponent-lhs->exponent;
3932
3933    /* Fastpath cases where the numbers are aligned and normal, the RHS */
3934    /* is all in one unit, no operand rounding is needed, and no carry, */
3935    /* lengthening, or borrow is needed */
3936    if (padding==0
3937	&& rhs->digits<=DECDPUN
3938	&& rhs->exponent>=set->emin	/* [some normals drop through] */
3939	&& rhs->exponent<=set->emax-set->digits+1 /* [could clamp] */
3940	&& rhs->digits<=reqdigits
3941	&& lhs->digits<=reqdigits) {
3942      Int partial=*lhs->lsu;
3943      if (!diffsign) {			/* adding */
3944	partial+=*rhs->lsu;
3945	if ((partial<=DECDPUNMAX)	/* result fits in unit */
3946	 && (lhs->digits>=DECDPUN ||	/* .. and no digits-count change */
3947	     partial<(Int)powers[lhs->digits])) { /* .. */
3948	  if (res!=lhs) decNumberCopy(res, lhs);  /* not in place */
3949	  *res->lsu=(Unit)partial;	/* [copy could have overwritten RHS] */
3950	  break;
3951	  }
3952	/* else drop out for careful add */
3953	}
3954       else {				/* signs differ */
3955	partial-=*rhs->lsu;
3956	if (partial>0) { /* no borrow needed, and non-0 result */
3957	  if (res!=lhs) decNumberCopy(res, lhs);  /* not in place */
3958	  *res->lsu=(Unit)partial;
3959	  /* this could have reduced digits [but result>0] */
3960	  res->digits=decGetDigits(res->lsu, D2U(res->digits));
3961	  break;
3962	  }
3963	/* else drop out for careful subtract */
3964	}
3965      }
3966
3967    /* Now align (pad) the lhs or rhs so they can be added or */
3968    /* subtracted, as necessary.  If one number is much larger than */
3969    /* the other (that is, if in plain form there is a least one */
3970    /* digit between the lowest digit of one and the highest of the */
3971    /* other) padding with up to DIGITS-1 trailing zeros may be */
3972    /* needed; then apply rounding (as exotic rounding modes may be */
3973    /* affected by the residue). */
3974    rhsshift=0; 	      /* rhs shift to left (padding) in Units */
3975    bits=lhs->bits;	      /* assume sign is that of LHS */
3976    mult=1;		      /* likely multiplier */
3977
3978    /* [if padding==0 the operands are aligned; no padding is needed] */
3979    if (padding!=0) {
3980      /* some padding needed; always pad the RHS, as any required */
3981      /* padding can then be effected by a simple combination of */
3982      /* shifts and a multiply */
3983      Flag swapped=0;
3984      if (padding<0) {			/* LHS needs the padding */
3985	const decNumber *t;
3986	padding=-padding;		/* will be +ve */
3987	bits=(uByte)(rhs->bits^negate); /* assumed sign is now that of RHS */
3988	t=lhs; lhs=rhs; rhs=t;
3989	swapped=1;
3990	}
3991
3992      /* If, after pad, rhs would be longer than lhs by digits+1 or */
3993      /* more then lhs cannot affect the answer, except as a residue, */
3994      /* so only need to pad up to a length of DIGITS+1. */
3995      if (rhs->digits+padding > lhs->digits+reqdigits+1) {
3996	/* The RHS is sufficient */
3997	/* for residue use the relative sign indication... */
3998	Int shift=reqdigits-rhs->digits;     /* left shift needed */
3999	residue=1;			     /* residue for rounding */
4000	if (diffsign) residue=-residue;      /* signs differ */
4001	/* copy, shortening if necessary */
4002	decCopyFit(res, rhs, set, &residue, status);
4003	/* if it was already shorter, then need to pad with zeros */
4004	if (shift>0) {
4005	  res->digits=decShiftToMost(res->lsu, res->digits, shift);
4006	  res->exponent-=shift; 	     /* adjust the exponent. */
4007	  }
4008	/* flip the result sign if unswapped and rhs was negated */
4009	if (!swapped) res->bits^=negate;
4010	decFinish(res, set, &residue, status);	  /* done */
4011	break;}
4012
4013      /* LHS digits may affect result */
4014      rhsshift=D2U(padding+1)-1;	/* this much by Unit shift .. */
4015      mult=powers[padding-(rhsshift*DECDPUN)]; /* .. this by multiplication */
4016      } /* padding needed */
4017
4018    if (diffsign) mult=-mult;		/* signs differ */
4019
4020    /* determine the longer operand */
4021    maxdigits=rhs->digits+padding;	/* virtual length of RHS */
4022    if (lhs->digits>maxdigits) maxdigits=lhs->digits;
4023
4024    /* Decide on the result buffer to use; if possible place directly */
4025    /* into result. */
4026    acc=res->lsu;			/* assume add direct to result */
4027    /* If destructive overlap, or the number is too long, or a carry or */
4028    /* borrow to DIGITS+1 might be possible, a buffer must be used. */
4029    /* [Might be worth more sophisticated tests when maxdigits==reqdigits] */
4030    if ((maxdigits>=reqdigits)		/* is, or could be, too large */
4031     || (res==rhs && rhsshift>0)) {	/* destructive overlap */
4032      /* buffer needed, choose it; units for maxdigits digits will be */
4033      /* needed, +1 Unit for carry or borrow */
4034      Int need=D2U(maxdigits)+1;
4035      acc=accbuff;			/* assume use local buffer */
4036      if (need*sizeof(Unit)>sizeof(accbuff)) {
4037	/* printf("malloc add %ld %ld\n", need, sizeof(accbuff)); */
4038	allocacc=(Unit *)malloc(need*sizeof(Unit));
4039	if (allocacc==NULL) {		/* hopeless -- abandon */
4040	  *status|=DEC_Insufficient_storage;
4041	  break;}
4042	acc=allocacc;
4043	}
4044      }
4045
4046    res->bits=(uByte)(bits&DECNEG);	/* it's now safe to overwrite.. */
4047    res->exponent=lhs->exponent;	/* .. operands (even if aliased) */
4048
4049    #if DECTRACE
4050      decDumpAr('A', lhs->lsu, D2U(lhs->digits));
4051      decDumpAr('B', rhs->lsu, D2U(rhs->digits));
4052      printf("	:h: %ld %ld\n", rhsshift, mult);
4053    #endif
4054
4055    /* add [A+B*m] or subtract [A+B*(-m)] */
4056    res->digits=decUnitAddSub(lhs->lsu, D2U(lhs->digits),
4057			      rhs->lsu, D2U(rhs->digits),
4058			      rhsshift, acc, mult)
4059	       *DECDPUN;	   /* [units -> digits] */
4060    if (res->digits<0) {	   /* borrowed... */
4061      res->digits=-res->digits;
4062      res->bits^=DECNEG;	   /* flip the sign */
4063      }
4064    #if DECTRACE
4065      decDumpAr('+', acc, D2U(res->digits));
4066    #endif
4067
4068    /* If a buffer was used the result must be copied back, possibly */
4069    /* shortening.  (If no buffer was used then the result must have */
4070    /* fit, so can't need rounding and residue must be 0.) */
4071    residue=0;			   /* clear accumulator */
4072    if (acc!=res->lsu) {
4073      #if DECSUBSET
4074      if (set->extended) {	   /* round from first significant digit */
4075      #endif
4076	/* remove leading zeros that were added due to rounding up to */
4077	/* integral Units -- before the test for rounding. */
4078	if (res->digits>reqdigits)
4079	  res->digits=decGetDigits(acc, D2U(res->digits));
4080	decSetCoeff(res, set, acc, res->digits, &residue, status);
4081      #if DECSUBSET
4082	}
4083       else { /* subset arithmetic rounds from original significant digit */
4084	/* May have an underestimate.  This only occurs when both */
4085	/* numbers fit in DECDPUN digits and are padding with a */
4086	/* negative multiple (-10, -100...) and the top digit(s) become */
4087	/* 0.  (This only matters when using X3.274 rules where the */
4088	/* leading zero could be included in the rounding.) */
4089	if (res->digits<maxdigits) {
4090	  *(acc+D2U(res->digits))=0; /* ensure leading 0 is there */
4091	  res->digits=maxdigits;
4092	  }
4093	 else {
4094	  /* remove leading zeros that added due to rounding up to */
4095	  /* integral Units (but only those in excess of the original */
4096	  /* maxdigits length, unless extended) before test for rounding. */
4097	  if (res->digits>reqdigits) {
4098	    res->digits=decGetDigits(acc, D2U(res->digits));
4099	    if (res->digits<maxdigits) res->digits=maxdigits;
4100	    }
4101	  }
4102	decSetCoeff(res, set, acc, res->digits, &residue, status);
4103	/* Now apply rounding if needed before removing leading zeros. */
4104	/* This is safe because subnormals are not a possibility */
4105	if (residue!=0) {
4106	  decApplyRound(res, set, residue, status);
4107	  residue=0;		     /* did what needed to be done */
4108	  }
4109	} /* subset */
4110      #endif
4111      } /* used buffer */
4112
4113    /* strip leading zeros [these were left on in case of subset subtract] */
4114    res->digits=decGetDigits(res->lsu, D2U(res->digits));
4115
4116    /* apply checks and rounding */
4117    decFinish(res, set, &residue, status);
4118
4119    /* "When the sum of two operands with opposite signs is exactly */
4120    /* zero, the sign of that sum shall be '+' in all rounding modes */
4121    /* except round toward -Infinity, in which mode that sign shall be */
4122    /* '-'."  [Subset zeros also never have '-', set by decFinish.] */
4123    if (ISZERO(res) && diffsign
4124     #if DECSUBSET
4125     && set->extended
4126     #endif
4127     && (*status&DEC_Inexact)==0) {
4128      if (set->round==DEC_ROUND_FLOOR) res->bits|=DECNEG;   /* sign - */
4129				  else res->bits&=~DECNEG;  /* sign + */
4130      }
4131    } while(0); 			     /* end protected */
4132
4133  free(allocacc);	     /* drop any storage used */
4134  #if DECSUBSET
4135  free(allocrhs);	     /* .. */
4136  free(alloclhs);	     /* .. */
4137  #endif
4138  return res;
4139  } /* decAddOp */
4140
4141/* ------------------------------------------------------------------ */
4142/* decDivideOp -- division operation				      */
4143/*								      */
4144/*  This routine performs the calculations for all four division      */
4145/*  operators (divide, divideInteger, remainder, remainderNear).      */
4146/*								      */
4147/*  C=A op B							      */
4148/*								      */
4149/*   res is C, the result.  C may be A and/or B (e.g., X=X/X)	      */
4150/*   lhs is A							      */
4151/*   rhs is B							      */
4152/*   set is the context 					      */
4153/*   op  is DIVIDE, DIVIDEINT, REMAINDER, or REMNEAR respectively.    */
4154/*   status is the usual accumulator				      */
4155/*								      */
4156/* C must have space for set->digits digits.			      */
4157/*								      */
4158/* ------------------------------------------------------------------ */
4159/*   The underlying algorithm of this routine is the same as in the   */
4160/*   1981 S/370 implementation, that is, non-restoring long division  */
4161/*   with bi-unit (rather than bi-digit) estimation for each unit     */
4162/*   multiplier.  In this pseudocode overview, complications for the  */
4163/*   Remainder operators and division residues for exact rounding are */
4164/*   omitted for clarity.					      */
4165/*								      */
4166/*     Prepare operands and handle special values		      */
4167/*     Test for x/0 and then 0/x				      */
4168/*     Exp =Exp1 - Exp2 					      */
4169/*     Exp =Exp +len(var1) -len(var2)				      */
4170/*     Sign=Sign1 * Sign2					      */
4171/*     Pad accumulator (Var1) to double-length with 0's (pad1)	      */
4172/*     Pad Var2 to same length as Var1				      */
4173/*     msu2pair/plus=1st 2 or 1 units of var2, +1 to allow for round  */
4174/*     have=0							      */
4175/*     Do until (have=digits+1 OR residue=0)			      */
4176/*	 if exp<0 then if integer divide/residue then leave	      */
4177/*	 this_unit=0						      */
4178/*	 Do forever						      */
4179/*	    compare numbers					      */
4180/*	    if <0 then leave inner_loop 			      */
4181/*	    if =0 then (* quick exit without subtract *) do	      */
4182/*	       this_unit=this_unit+1; output this_unit		      */
4183/*	       leave outer_loop; end				      */
4184/*	    Compare lengths of numbers (mantissae):		      */
4185/*	    If same then tops2=msu2pair -- {units 1&2 of var2}	      */
4186/*		    else tops2=msu2plus -- {0, unit 1 of var2}	      */
4187/*	    tops1=first_unit_of_Var1*10**DECDPUN +second_unit_of_var1 */
4188/*	    mult=tops1/tops2  -- Good and safe guess at divisor       */
4189/*	    if mult=0 then mult=1				      */
4190/*	    this_unit=this_unit+mult				      */
4191/*	    subtract						      */
4192/*	    end inner_loop					      */
4193/*	  if have\=0 | this_unit\=0 then do			      */
4194/*	    output this_unit					      */
4195/*	    have=have+1; end					      */
4196/*	  var2=var2/10						      */
4197/*	  exp=exp-1						      */
4198/*	  end outer_loop					      */
4199/*     exp=exp+1   -- set the proper exponent			      */
4200/*     if have=0 then generate answer=0 			      */
4201/*     Return (Result is defined by Var1)			      */
4202/*								      */
4203/* ------------------------------------------------------------------ */
4204/* Two working buffers are needed during the division; one (digits+   */
4205/* 1) to accumulate the result, and the other (up to 2*digits+1) for  */
4206/* long subtractions.  These are acc and var1 respectively.	      */
4207/* var1 is a copy of the lhs coefficient, var2 is the rhs coefficient.*/
4208/* The static buffers may be larger than might be expected to allow   */
4209/* for calls from higher-level funtions (notable exp).		      */
4210/* ------------------------------------------------------------------ */
4211static decNumber * decDivideOp(decNumber *res,
4212			       const decNumber *lhs, const decNumber *rhs,
4213			       decContext *set, Flag op, uInt *status) {
4214  #if DECSUBSET
4215  decNumber *alloclhs=NULL;	   /* non-NULL if rounded lhs allocated */
4216  decNumber *allocrhs=NULL;	   /* .., rhs */
4217  #endif
4218  Unit	accbuff[SD2U(DECBUFFER+DECDPUN+10)]; /* local buffer */
4219  Unit	*acc=accbuff;		   /* -> accumulator array for result */
4220  Unit	*allocacc=NULL; 	   /* -> allocated buffer, iff allocated */
4221  Unit	*accnext;		   /* -> where next digit will go */
4222  Int	acclength;		   /* length of acc needed [Units] */
4223  Int	accunits;		   /* count of units accumulated */
4224  Int	accdigits;		   /* count of digits accumulated */
4225
4226  Unit	varbuff[SD2U(DECBUFFER*2+DECDPUN)];  /* buffer for var1 */
4227  Unit	*var1=varbuff;		   /* -> var1 array for long subtraction */
4228  Unit	*varalloc=NULL; 	   /* -> allocated buffer, iff used */
4229  Unit	*msu1;			   /* -> msu of var1 */
4230
4231  const Unit *var2;		   /* -> var2 array */
4232  const Unit *msu2;		   /* -> msu of var2 */
4233  Int	msu2plus;		   /* msu2 plus one [does not vary] */
4234  eInt	msu2pair;		   /* msu2 pair plus one [does not vary] */
4235
4236  Int	var1units, var2units;	   /* actual lengths */
4237  Int	var2ulen;		   /* logical length (units) */
4238  Int	var1initpad=0;		   /* var1 initial padding (digits) */
4239  Int	maxdigits;		   /* longest LHS or required acc length */
4240  Int	mult;			   /* multiplier for subtraction */
4241  Unit	thisunit;		   /* current unit being accumulated */
4242  Int	residue;		   /* for rounding */
4243  Int	reqdigits=set->digits;	   /* requested DIGITS */
4244  Int	exponent;		   /* working exponent */
4245  Int	maxexponent=0;		   /* DIVIDE maximum exponent if unrounded */
4246  uByte bits;			   /* working sign */
4247  Unit	*target;		   /* work */
4248  const Unit *source;		   /* .. */
4249  uInt	const *pow;		   /* .. */
4250  Int	shift, cut;		   /* .. */
4251  #if DECSUBSET
4252  Int	dropped;		   /* work */
4253  #endif
4254
4255  #if DECCHECK
4256  if (decCheckOperands(res, lhs, rhs, set)) return res;
4257  #endif
4258
4259  do {				   /* protect allocated storage */
4260    #if DECSUBSET
4261    if (!set->extended) {
4262      /* reduce operands and set lostDigits status, as needed */
4263      if (lhs->digits>reqdigits) {
4264	alloclhs=decRoundOperand(lhs, set, status);
4265	if (alloclhs==NULL) break;
4266	lhs=alloclhs;
4267	}
4268      if (rhs->digits>reqdigits) {
4269	allocrhs=decRoundOperand(rhs, set, status);
4270	if (allocrhs==NULL) break;
4271	rhs=allocrhs;
4272	}
4273      }
4274    #endif
4275    /* [following code does not require input rounding] */
4276
4277    bits=(lhs->bits^rhs->bits)&DECNEG;	/* assumed sign for divisions */
4278
4279    /* handle infinities and NaNs */
4280    if (SPECIALARGS) {			/* a special bit set */
4281      if (SPECIALARGS & (DECSNAN | DECNAN)) { /* one or two NaNs */
4282	decNaNs(res, lhs, rhs, set, status);
4283	break;
4284	}
4285      /* one or two infinities */
4286      if (decNumberIsInfinite(lhs)) {	/* LHS (dividend) is infinite */
4287	if (decNumberIsInfinite(rhs) || /* two infinities are invalid .. */
4288	    op & (REMAINDER | REMNEAR)) { /* as is remainder of infinity */
4289	  *status|=DEC_Invalid_operation;
4290	  break;
4291	  }
4292	/* [Note that infinity/0 raises no exceptions] */
4293	decNumberZero(res);
4294	res->bits=bits|DECINF;		/* set +/- infinity */
4295	break;
4296	}
4297       else {				/* RHS (divisor) is infinite */
4298	residue=0;
4299	if (op&(REMAINDER|REMNEAR)) {
4300	  /* result is [finished clone of] lhs */
4301	  decCopyFit(res, lhs, set, &residue, status);
4302	  }
4303	 else {  /* a division */
4304	  decNumberZero(res);
4305	  res->bits=bits;		/* set +/- zero */
4306	  /* for DIVIDEINT the exponent is always 0.  For DIVIDE, result */
4307	  /* is a 0 with infinitely negative exponent, clamped to minimum */
4308	  if (op&DIVIDE) {
4309	    res->exponent=set->emin-set->digits+1;
4310	    *status|=DEC_Clamped;
4311	    }
4312	  }
4313	decFinish(res, set, &residue, status);
4314	break;
4315	}
4316      }
4317
4318    /* handle 0 rhs (x/0) */
4319    if (ISZERO(rhs)) {			/* x/0 is always exceptional */
4320      if (ISZERO(lhs)) {
4321	decNumberZero(res);		/* [after lhs test] */
4322	*status|=DEC_Division_undefined;/* 0/0 will become NaN */
4323	}
4324       else {
4325	decNumberZero(res);
4326	if (op&(REMAINDER|REMNEAR)) *status|=DEC_Invalid_operation;
4327	 else {
4328	  *status|=DEC_Division_by_zero; /* x/0 */
4329	  res->bits=bits|DECINF;	 /* .. is +/- Infinity */
4330	  }
4331	}
4332      break;}
4333
4334    /* handle 0 lhs (0/x) */
4335    if (ISZERO(lhs)) {			/* 0/x [x!=0] */
4336      #if DECSUBSET
4337      if (!set->extended) decNumberZero(res);
4338       else {
4339      #endif
4340	if (op&DIVIDE) {
4341	  residue=0;
4342	  exponent=lhs->exponent-rhs->exponent; /* ideal exponent */
4343	  decNumberCopy(res, lhs);	/* [zeros always fit] */
4344	  res->bits=bits;		/* sign as computed */
4345	  res->exponent=exponent;	/* exponent, too */
4346	  decFinalize(res, set, &residue, status);   /* check exponent */
4347	  }
4348	 else if (op&DIVIDEINT) {
4349	  decNumberZero(res);		/* integer 0 */
4350	  res->bits=bits;		/* sign as computed */
4351	  }
4352	 else { 			/* a remainder */
4353	  exponent=rhs->exponent;	/* [save in case overwrite] */
4354	  decNumberCopy(res, lhs);	/* [zeros always fit] */
4355	  if (exponent<res->exponent) res->exponent=exponent; /* use lower */
4356	  }
4357      #if DECSUBSET
4358	}
4359      #endif
4360      break;}
4361
4362    /* Precalculate exponent.  This starts off adjusted (and hence fits */
4363    /* in 31 bits) and becomes the usual unadjusted exponent as the */
4364    /* division proceeds.  The order of evaluation is important, here, */
4365    /* to avoid wrap. */
4366    exponent=(lhs->exponent+lhs->digits)-(rhs->exponent+rhs->digits);
4367
4368    /* If the working exponent is -ve, then some quick exits are */
4369    /* possible because the quotient is known to be <1 */
4370    /* [for REMNEAR, it needs to be < -1, as -0.5 could need work] */
4371    if (exponent<0 && !(op==DIVIDE)) {
4372      if (op&DIVIDEINT) {
4373	decNumberZero(res);		     /* integer part is 0 */
4374	#if DECSUBSET
4375	if (set->extended)
4376	#endif
4377	  res->bits=bits;		     /* set +/- zero */
4378	break;}
4379      /* fastpath remainders so long as the lhs has the smaller */
4380      /* (or equal) exponent */
4381      if (lhs->exponent<=rhs->exponent) {
4382	if (op&REMAINDER || exponent<-1) {
4383	  /* It is REMAINDER or safe REMNEAR; result is [finished */
4384	  /* clone of] lhs  (r = x - 0*y) */
4385	  residue=0;
4386	  decCopyFit(res, lhs, set, &residue, status);
4387	  decFinish(res, set, &residue, status);
4388	  break;
4389	  }
4390	/* [unsafe REMNEAR drops through] */
4391	}
4392      } /* fastpaths */
4393
4394    /* Long (slow) division is needed; roll up the sleeves... */
4395
4396    /* The accumulator will hold the quotient of the division. */
4397    /* If it needs to be too long for stack storage, then allocate. */
4398    acclength=D2U(reqdigits+DECDPUN);	/* in Units */
4399    if (acclength*sizeof(Unit)>sizeof(accbuff)) {
4400      /* printf("malloc dvacc %ld units\n", acclength); */
4401      allocacc=(Unit *)malloc(acclength*sizeof(Unit));
4402      if (allocacc==NULL) {		/* hopeless -- abandon */
4403	*status|=DEC_Insufficient_storage;
4404	break;}
4405      acc=allocacc;			/* use the allocated space */
4406      }
4407
4408    /* var1 is the padded LHS ready for subtractions. */
4409    /* If it needs to be too long for stack storage, then allocate. */
4410    /* The maximum units needed for var1 (long subtraction) is: */
4411    /* Enough for */
4412    /*	   (rhs->digits+reqdigits-1) -- to allow full slide to right */
4413    /* or  (lhs->digits)	     -- to allow for long lhs */
4414    /* whichever is larger */
4415    /*	 +1		   -- for rounding of slide to right */
4416    /*	 +1		   -- for leading 0s */
4417    /*	 +1		   -- for pre-adjust if a remainder or DIVIDEINT */
4418    /* [Note: unused units do not participate in decUnitAddSub data] */
4419    maxdigits=rhs->digits+reqdigits-1;
4420    if (lhs->digits>maxdigits) maxdigits=lhs->digits;
4421    var1units=D2U(maxdigits)+2;
4422    /* allocate a guard unit above msu1 for REMAINDERNEAR */
4423    if (!(op&DIVIDE)) var1units++;
4424    if ((var1units+1)*sizeof(Unit)>sizeof(varbuff)) {
4425      /* printf("malloc dvvar %ld units\n", var1units+1); */
4426      varalloc=(Unit *)malloc((var1units+1)*sizeof(Unit));
4427      if (varalloc==NULL) {		/* hopeless -- abandon */
4428	*status|=DEC_Insufficient_storage;
4429	break;}
4430      var1=varalloc;			/* use the allocated space */
4431      }
4432
4433    /* Extend the lhs and rhs to full long subtraction length.	The lhs */
4434    /* is truly extended into the var1 buffer, with 0 padding, so a */
4435    /* subtract in place is always possible.  The rhs (var2) has */
4436    /* virtual padding (implemented by decUnitAddSub). */
4437    /* One guard unit was allocated above msu1 for rem=rem+rem in */
4438    /* REMAINDERNEAR. */
4439    msu1=var1+var1units-1;		/* msu of var1 */
4440    source=lhs->lsu+D2U(lhs->digits)-1; /* msu of input array */
4441    for (target=msu1; source>=lhs->lsu; source--, target--) *target=*source;
4442    for (; target>=var1; target--) *target=0;
4443
4444    /* rhs (var2) is left-aligned with var1 at the start */
4445    var2ulen=var1units; 		/* rhs logical length (units) */
4446    var2units=D2U(rhs->digits); 	/* rhs actual length (units) */
4447    var2=rhs->lsu;			/* -> rhs array */
4448    msu2=var2+var2units-1;		/* -> msu of var2 [never changes] */
4449    /* now set up the variables which will be used for estimating the */
4450    /* multiplication factor.  If these variables are not exact, add */
4451    /* 1 to make sure that the multiplier is never overestimated. */
4452    msu2plus=*msu2;			/* it's value .. */
4453    if (var2units>1) msu2plus++;	/* .. +1 if any more */
4454    msu2pair=(eInt)*msu2*(DECDPUNMAX+1);/* top two pair .. */
4455    if (var2units>1) {			/* .. [else treat 2nd as 0] */
4456      msu2pair+=*(msu2-1);		/* .. */
4457      if (var2units>2) msu2pair++;	/* .. +1 if any more */
4458      }
4459
4460    /* The calculation is working in units, which may have leading zeros, */
4461    /* but the exponent was calculated on the assumption that they are */
4462    /* both left-aligned.  Adjust the exponent to compensate: add the */
4463    /* number of leading zeros in var1 msu and subtract those in var2 msu. */
4464    /* [This is actually done by counting the digits and negating, as */
4465    /* lead1=DECDPUN-digits1, and similarly for lead2.] */
4466    for (pow=&powers[1]; *msu1>=*pow; pow++) exponent--;
4467    for (pow=&powers[1]; *msu2>=*pow; pow++) exponent++;
4468
4469    /* Now, if doing an integer divide or remainder, ensure that */
4470    /* the result will be Unit-aligned.  To do this, shift the var1 */
4471    /* accumulator towards least if need be.  (It's much easier to */
4472    /* do this now than to reassemble the residue afterwards, if */
4473    /* doing a remainder.)  Also ensure the exponent is not negative. */
4474    if (!(op&DIVIDE)) {
4475      Unit *u;				/* work */
4476      /* save the initial 'false' padding of var1, in digits */
4477      var1initpad=(var1units-D2U(lhs->digits))*DECDPUN;
4478      /* Determine the shift to do. */
4479      if (exponent<0) cut=-exponent;
4480       else cut=DECDPUN-exponent%DECDPUN;
4481      decShiftToLeast(var1, var1units, cut);
4482      exponent+=cut;			/* maintain numerical value */
4483      var1initpad-=cut; 		/* .. and reduce padding */
4484      /* clean any most-significant units which were just emptied */
4485      for (u=msu1; cut>=DECDPUN; cut-=DECDPUN, u--) *u=0;
4486      } /* align */
4487     else { /* is DIVIDE */
4488      maxexponent=lhs->exponent-rhs->exponent;	  /* save */
4489      /* optimization: if the first iteration will just produce 0, */
4490      /* preadjust to skip it [valid for DIVIDE only] */
4491      if (*msu1<*msu2) {
4492	var2ulen--;			/* shift down */
4493	exponent-=DECDPUN;		/* update the exponent */
4494	}
4495      }
4496
4497    /* ---- start the long-division loops ------------------------------ */
4498    accunits=0; 			/* no units accumulated yet */
4499    accdigits=0;			/* .. or digits */
4500    accnext=acc+acclength-1;		/* -> msu of acc [NB: allows digits+1] */
4501    for (;;) {				/* outer forever loop */
4502      thisunit=0;			/* current unit assumed 0 */
4503      /* find the next unit */
4504      for (;;) {			/* inner forever loop */
4505	/* strip leading zero units [from either pre-adjust or from */
4506	/* subtract last time around].	Leave at least one unit. */
4507	for (; *msu1==0 && msu1>var1; msu1--) var1units--;
4508
4509	if (var1units<var2ulen) break;	     /* var1 too low for subtract */
4510	if (var1units==var2ulen) {	     /* unit-by-unit compare needed */
4511	  /* compare the two numbers, from msu */
4512	  const Unit *pv1, *pv2;
4513	  Unit v2;			     /* units to compare */
4514	  pv2=msu2;			     /* -> msu */
4515	  for (pv1=msu1; ; pv1--, pv2--) {
4516	    /* v1=*pv1 -- always OK */
4517	    v2=0;			     /* assume in padding */
4518	    if (pv2>=var2) v2=*pv2;	     /* in range */
4519	    if (*pv1!=v2) break;	     /* no longer the same */
4520	    if (pv1==var1) break;	     /* done; leave pv1 as is */
4521	    }
4522	  /* here when all inspected or a difference seen */
4523	  if (*pv1<v2) break;		     /* var1 too low to subtract */
4524	  if (*pv1==v2) {		     /* var1 == var2 */
4525	    /* reach here if var1 and var2 are identical; subtraction */
4526	    /* would increase digit by one, and the residue will be 0 so */
4527	    /* the calculation is done; leave the loop with residue=0. */
4528	    thisunit++; 		     /* as though subtracted */
4529	    *var1=0;			     /* set var1 to 0 */
4530	    var1units=1;		     /* .. */
4531	    break;  /* from inner */
4532	    } /* var1 == var2 */
4533	  /* *pv1>v2.  Prepare for real subtraction; the lengths are equal */
4534	  /* Estimate the multiplier (there's always a msu1-1)... */
4535	  /* Bring in two units of var2 to provide a good estimate. */
4536	  mult=(Int)(((eInt)*msu1*(DECDPUNMAX+1)+*(msu1-1))/msu2pair);
4537	  } /* lengths the same */
4538	 else { /* var1units > var2ulen, so subtraction is safe */
4539	  /* The var2 msu is one unit towards the lsu of the var1 msu, */
4540	  /* so only one unit for var2 can be used. */
4541	  mult=(Int)(((eInt)*msu1*(DECDPUNMAX+1)+*(msu1-1))/msu2plus);
4542	  }
4543	if (mult==0) mult=1;		     /* must always be at least 1 */
4544	/* subtraction needed; var1 is > var2 */
4545	thisunit=(Unit)(thisunit+mult);      /* accumulate */
4546	/* subtract var1-var2, into var1; only the overlap needs */
4547	/* processing, as this is an in-place calculation */
4548	shift=var2ulen-var2units;
4549	#if DECTRACE
4550	  decDumpAr('1', &var1[shift], var1units-shift);
4551	  decDumpAr('2', var2, var2units);
4552	  printf("m=%ld\n", -mult);
4553	#endif
4554	decUnitAddSub(&var1[shift], var1units-shift,
4555		      var2, var2units, 0,
4556		      &var1[shift], -mult);
4557	#if DECTRACE
4558	  decDumpAr('#', &var1[shift], var1units-shift);
4559	#endif
4560	/* var1 now probably has leading zeros; these are removed at the */
4561	/* top of the inner loop. */
4562	} /* inner loop */
4563
4564      /* The next unit has been calculated in full; unless it's a */
4565      /* leading zero, add to acc */
4566      if (accunits!=0 || thisunit!=0) {      /* is first or non-zero */
4567	*accnext=thisunit;		     /* store in accumulator */
4568	/* account exactly for the new digits */
4569	if (accunits==0) {
4570	  accdigits++;			     /* at least one */
4571	  for (pow=&powers[1]; thisunit>=*pow; pow++) accdigits++;
4572	  }
4573	 else accdigits+=DECDPUN;
4574	accunits++;			     /* update count */
4575	accnext--;			     /* ready for next */
4576	if (accdigits>reqdigits) break;      /* have enough digits */
4577	}
4578
4579      /* if the residue is zero, the operation is done (unless divide */
4580      /* or divideInteger and still not enough digits yet) */
4581      if (*var1==0 && var1units==1) {	     /* residue is 0 */
4582	if (op&(REMAINDER|REMNEAR)) break;
4583	if ((op&DIVIDE) && (exponent<=maxexponent)) break;
4584	/* [drop through if divideInteger] */
4585	}
4586      /* also done enough if calculating remainder or integer */
4587      /* divide and just did the last ('units') unit */
4588      if (exponent==0 && !(op&DIVIDE)) break;
4589
4590      /* to get here, var1 is less than var2, so divide var2 by the per- */
4591      /* Unit power of ten and go for the next digit */
4592      var2ulen--;			     /* shift down */
4593      exponent-=DECDPUN;		     /* update the exponent */
4594      } /* outer loop */
4595
4596    /* ---- division is complete --------------------------------------- */
4597    /* here: acc      has at least reqdigits+1 of good results (or fewer */
4598    /*		      if early stop), starting at accnext+1 (its lsu) */
4599    /*	     var1     has any residue at the stopping point */
4600    /*	     accunits is the number of digits collected in acc */
4601    if (accunits==0) {		   /* acc is 0 */
4602      accunits=1;		   /* show have a unit .. */
4603      accdigits=1;		   /* .. */
4604      *accnext=0;		   /* .. whose value is 0 */
4605      }
4606     else accnext++;		   /* back to last placed */
4607    /* accnext now -> lowest unit of result */
4608
4609    residue=0;			   /* assume no residue */
4610    if (op&DIVIDE) {
4611      /* record the presence of any residue, for rounding */
4612      if (*var1!=0 || var1units>1) residue=1;
4613       else { /* no residue */
4614	/* Had an exact division; clean up spurious trailing 0s. */
4615	/* There will be at most DECDPUN-1, from the final multiply, */
4616	/* and then only if the result is non-0 (and even) and the */
4617	/* exponent is 'loose'. */
4618	#if DECDPUN>1
4619	Unit lsu=*accnext;
4620	if (!(lsu&0x01) && (lsu!=0)) {
4621	  /* count the trailing zeros */
4622	  Int drop=0;
4623	  for (;; drop++) {    /* [will terminate because lsu!=0] */
4624	    if (exponent>=maxexponent) break;	  /* don't chop real 0s */
4625	    #if DECDPUN<=4
4626	      if ((lsu-QUOT10(lsu, drop+1)
4627		  *powers[drop+1])!=0) break;	  /* found non-0 digit */
4628	    #else
4629	      if (lsu%powers[drop+1]!=0) break;   /* found non-0 digit */
4630	    #endif
4631	    exponent++;
4632	    }
4633	  if (drop>0) {
4634	    accunits=decShiftToLeast(accnext, accunits, drop);
4635	    accdigits=decGetDigits(accnext, accunits);
4636	    accunits=D2U(accdigits);
4637	    /* [exponent was adjusted in the loop] */
4638	    }
4639	  } /* neither odd nor 0 */
4640	#endif
4641	} /* exact divide */
4642      } /* divide */
4643     else /* op!=DIVIDE */ {
4644      /* check for coefficient overflow */
4645      if (accdigits+exponent>reqdigits) {
4646	*status|=DEC_Division_impossible;
4647	break;
4648	}
4649      if (op & (REMAINDER|REMNEAR)) {
4650	/* [Here, the exponent will be 0, because var1 was adjusted */
4651	/* appropriately.] */
4652	Int postshift;			     /* work */
4653	Flag wasodd=0;			     /* integer was odd */
4654	Unit *quotlsu;			     /* for save */
4655	Int  quotdigits;		     /* .. */
4656
4657	bits=lhs->bits; 		     /* remainder sign is always as lhs */
4658
4659	/* Fastpath when residue is truly 0 is worthwhile [and */
4660	/* simplifies the code below] */
4661	if (*var1==0 && var1units==1) {      /* residue is 0 */
4662	  Int exp=lhs->exponent;	     /* save min(exponents) */
4663	  if (rhs->exponent<exp) exp=rhs->exponent;
4664	  decNumberZero(res);		     /* 0 coefficient */
4665	  #if DECSUBSET
4666	  if (set->extended)
4667	  #endif
4668	  res->exponent=exp;		     /* .. with proper exponent */
4669	  res->bits=(uByte)(bits&DECNEG);	   /* [cleaned] */
4670	  decFinish(res, set, &residue, status);   /* might clamp */
4671	  break;
4672	  }
4673	/* note if the quotient was odd */
4674	if (*accnext & 0x01) wasodd=1;	     /* acc is odd */
4675	quotlsu=accnext;		     /* save in case need to reinspect */
4676	quotdigits=accdigits;		     /* .. */
4677
4678	/* treat the residue, in var1, as the value to return, via acc */
4679	/* calculate the unused zero digits.  This is the smaller of: */
4680	/*   var1 initial padding (saved above) */
4681	/*   var2 residual padding, which happens to be given by: */
4682	postshift=var1initpad+exponent-lhs->exponent+rhs->exponent;
4683	/* [the 'exponent' term accounts for the shifts during divide] */
4684	if (var1initpad<postshift) postshift=var1initpad;
4685
4686	/* shift var1 the requested amount, and adjust its digits */
4687	var1units=decShiftToLeast(var1, var1units, postshift);
4688	accnext=var1;
4689	accdigits=decGetDigits(var1, var1units);
4690	accunits=D2U(accdigits);
4691
4692	exponent=lhs->exponent; 	/* exponent is smaller of lhs & rhs */
4693	if (rhs->exponent<exponent) exponent=rhs->exponent;
4694
4695	/* Now correct the result if doing remainderNear; if it */
4696	/* (looking just at coefficients) is > rhs/2, or == rhs/2 and */
4697	/* the integer was odd then the result should be rem-rhs. */
4698	if (op&REMNEAR) {
4699	  Int compare, tarunits;	/* work */
4700	  Unit *up;			/* .. */
4701	  /* calculate remainder*2 into the var1 buffer (which has */
4702	  /* 'headroom' of an extra unit and hence enough space) */
4703	  /* [a dedicated 'double' loop would be faster, here] */
4704	  tarunits=decUnitAddSub(accnext, accunits, accnext, accunits,
4705				 0, accnext, 1);
4706	  /* decDumpAr('r', accnext, tarunits); */
4707
4708	  /* Here, accnext (var1) holds tarunits Units with twice the */
4709	  /* remainder's coefficient, which must now be compared to the */
4710	  /* RHS.  The remainder's exponent may be smaller than the RHS's. */
4711	  compare=decUnitCompare(accnext, tarunits, rhs->lsu, D2U(rhs->digits),
4712				 rhs->exponent-exponent);
4713	  if (compare==BADINT) {	     /* deep trouble */
4714	    *status|=DEC_Insufficient_storage;
4715	    break;}
4716
4717	  /* now restore the remainder by dividing by two; the lsu */
4718	  /* is known to be even. */
4719	  for (up=accnext; up<accnext+tarunits; up++) {
4720	    Int half;		   /* half to add to lower unit */
4721	    half=*up & 0x01;
4722	    *up/=2;		   /* [shift] */
4723	    if (!half) continue;
4724	    *(up-1)+=(DECDPUNMAX+1)/2;
4725	    }
4726	  /* [accunits still describes the original remainder length] */
4727
4728	  if (compare>0 || (compare==0 && wasodd)) { /* adjustment needed */
4729	    Int exp, expunits, exprem;	     /* work */
4730	    /* This is effectively causing round-up of the quotient, */
4731	    /* so if it was the rare case where it was full and all */
4732	    /* nines, it would overflow and hence division-impossible */
4733	    /* should be raised */
4734	    Flag allnines=0;		     /* 1 if quotient all nines */
4735	    if (quotdigits==reqdigits) {     /* could be borderline */
4736	      for (up=quotlsu; ; up++) {
4737		if (quotdigits>DECDPUN) {
4738		  if (*up!=DECDPUNMAX) break;/* non-nines */
4739		  }
4740		 else { 		     /* this is the last Unit */
4741		  if (*up==powers[quotdigits]-1) allnines=1;
4742		  break;
4743		  }
4744		quotdigits-=DECDPUN;	     /* checked those digits */
4745		} /* up */
4746	      } /* borderline check */
4747	    if (allnines) {
4748	      *status|=DEC_Division_impossible;
4749	      break;}
4750
4751	    /* rem-rhs is needed; the sign will invert.  Again, var1 */
4752	    /* can safely be used for the working Units array. */
4753	    exp=rhs->exponent-exponent;      /* RHS padding needed */
4754	    /* Calculate units and remainder from exponent. */
4755	    expunits=exp/DECDPUN;
4756	    exprem=exp%DECDPUN;
4757	    /* subtract [A+B*(-m)]; the result will always be negative */
4758	    accunits=-decUnitAddSub(accnext, accunits,
4759				    rhs->lsu, D2U(rhs->digits),
4760				    expunits, accnext, -(Int)powers[exprem]);
4761	    accdigits=decGetDigits(accnext, accunits); /* count digits exactly */
4762	    accunits=D2U(accdigits);	/* and recalculate the units for copy */
4763	    /* [exponent is as for original remainder] */
4764	    bits^=DECNEG;		/* flip the sign */
4765	    }
4766	  } /* REMNEAR */
4767	} /* REMAINDER or REMNEAR */
4768      } /* not DIVIDE */
4769
4770    /* Set exponent and bits */
4771    res->exponent=exponent;
4772    res->bits=(uByte)(bits&DECNEG);	     /* [cleaned] */
4773
4774    /* Now the coefficient. */
4775    decSetCoeff(res, set, accnext, accdigits, &residue, status);
4776
4777    decFinish(res, set, &residue, status);   /* final cleanup */
4778
4779    #if DECSUBSET
4780    /* If a divide then strip trailing zeros if subset [after round] */
4781    if (!set->extended && (op==DIVIDE)) decTrim(res, set, 0, 1, &dropped);
4782    #endif
4783    } while(0); 			     /* end protected */
4784
4785  free(varalloc);	/* drop any storage used */
4786  free(allocacc);	/* .. */
4787  #if DECSUBSET
4788  free(allocrhs);	/* .. */
4789  free(alloclhs);	/* .. */
4790  #endif
4791  return res;
4792  } /* decDivideOp */
4793
4794/* ------------------------------------------------------------------ */
4795/* decMultiplyOp -- multiplication operation			      */
4796/*								      */
4797/*  This routine performs the multiplication C=A x B.		      */
4798/*								      */
4799/*   res is C, the result.  C may be A and/or B (e.g., X=X*X)	      */
4800/*   lhs is A							      */
4801/*   rhs is B							      */
4802/*   set is the context 					      */
4803/*   status is the usual accumulator				      */
4804/*								      */
4805/* C must have space for set->digits digits.			      */
4806/*								      */
4807/* ------------------------------------------------------------------ */
4808/* 'Classic' multiplication is used rather than Karatsuba, as the     */
4809/* latter would give only a minor improvement for the short numbers   */
4810/* expected to be handled most (and uses much more memory).	      */
4811/*								      */
4812/* There are two major paths here: the general-purpose ('old code')   */
4813/* path which handles all DECDPUN values, and a fastpath version      */
4814/* which is used if 64-bit ints are available, DECDPUN<=4, and more   */
4815/* than two calls to decUnitAddSub would be made.		      */
4816/*								      */
4817/* The fastpath version lumps units together into 8-digit or 9-digit  */
4818/* chunks, and also uses a lazy carry strategy to minimise expensive  */
4819/* 64-bit divisions.  The chunks are then broken apart again into     */
4820/* units for continuing processing.  Despite this overhead, the       */
4821/* fastpath can speed up some 16-digit operations by 10x (and much    */
4822/* more for higher-precision calculations).			      */
4823/*								      */
4824/* A buffer always has to be used for the accumulator; in the	      */
4825/* fastpath, buffers are also always needed for the chunked copies of */
4826/* of the operand coefficients. 				      */
4827/* Static buffers are larger than needed just for multiply, to allow  */
4828/* for calls from other operations (notably exp).		      */
4829/* ------------------------------------------------------------------ */
4830#define FASTMUL (DECUSE64 && DECDPUN<5)
4831static decNumber * decMultiplyOp(decNumber *res, const decNumber *lhs,
4832				 const decNumber *rhs, decContext *set,
4833				 uInt *status) {
4834  Int	 accunits;		   /* Units of accumulator in use */
4835  Int	 exponent;		   /* work */
4836  Int	 residue=0;		   /* rounding residue */
4837  uByte  bits;			   /* result sign */
4838  Unit	*acc;			   /* -> accumulator Unit array */
4839  Int	 needbytes;		   /* size calculator */
4840  void	*allocacc=NULL; 	   /* -> allocated accumulator, iff allocated */
4841  Unit	accbuff[SD2U(DECBUFFER*4+1)]; /* buffer (+1 for DECBUFFER==0, */
4842				   /* *4 for calls from other operations) */
4843  const Unit *mer, *mermsup;	   /* work */
4844  Int	madlength;		   /* Units in multiplicand */
4845  Int	shift;			   /* Units to shift multiplicand by */
4846
4847  #if FASTMUL
4848    /* if DECDPUN is 1 or 3 work in base 10**9, otherwise */
4849    /* (DECDPUN is 2 or 4) then work in base 10**8 */
4850    #if DECDPUN & 1		   /* odd */
4851      #define FASTBASE 1000000000  /* base */
4852      #define FASTDIGS		9  /* digits in base */
4853      #define FASTLAZY	       18  /* carry resolution point [1->18] */
4854    #else
4855      #define FASTBASE	100000000
4856      #define FASTDIGS		8
4857      #define FASTLAZY	     1844  /* carry resolution point [1->1844] */
4858    #endif
4859    /* three buffers are used, two for chunked copies of the operands */
4860    /* (base 10**8 or base 10**9) and one base 2**64 accumulator with */
4861    /* lazy carry evaluation */
4862    uInt   zlhibuff[(DECBUFFER*2+1)/8+1]; /* buffer (+1 for DECBUFFER==0) */
4863    uInt  *zlhi=zlhibuff;		  /* -> lhs array */
4864    uInt  *alloclhi=NULL;		  /* -> allocated buffer, iff allocated */
4865    uInt   zrhibuff[(DECBUFFER*2+1)/8+1]; /* buffer (+1 for DECBUFFER==0) */
4866    uInt  *zrhi=zrhibuff;		  /* -> rhs array */
4867    uInt  *allocrhi=NULL;		  /* -> allocated buffer, iff allocated */
4868    uLong  zaccbuff[(DECBUFFER*2+1)/4+2]; /* buffer (+1 for DECBUFFER==0) */
4869    /* [allocacc is shared for both paths, as only one will run] */
4870    uLong *zacc=zaccbuff;	   /* -> accumulator array for exact result */
4871    #if DECDPUN==1
4872    Int    zoff;		   /* accumulator offset */
4873    #endif
4874    uInt  *lip, *rip;		   /* item pointers */
4875    uInt  *lmsi, *rmsi; 	   /* most significant items */
4876    Int    ilhs, irhs, iacc;	   /* item counts in the arrays */
4877    Int    lazy;		   /* lazy carry counter */
4878    uLong  lcarry;		   /* uLong carry */
4879    uInt   carry;		   /* carry (NB not uLong) */
4880    Int    count;		   /* work */
4881    const  Unit *cup;		   /* .. */
4882    Unit  *up;			   /* .. */
4883    uLong *lp;			   /* .. */
4884    Int    p;			   /* .. */
4885  #endif
4886
4887  #if DECSUBSET
4888    decNumber *alloclhs=NULL;	   /* -> allocated buffer, iff allocated */
4889    decNumber *allocrhs=NULL;	   /* -> allocated buffer, iff allocated */
4890  #endif
4891
4892  #if DECCHECK
4893  if (decCheckOperands(res, lhs, rhs, set)) return res;
4894  #endif
4895
4896  /* precalculate result sign */
4897  bits=(uByte)((lhs->bits^rhs->bits)&DECNEG);
4898
4899  /* handle infinities and NaNs */
4900  if (SPECIALARGS) {		   /* a special bit set */
4901    if (SPECIALARGS & (DECSNAN | DECNAN)) { /* one or two NaNs */
4902      decNaNs(res, lhs, rhs, set, status);
4903      return res;}
4904    /* one or two infinities; Infinity * 0 is invalid */
4905    if (((lhs->bits & DECINF)==0 && ISZERO(lhs))
4906      ||((rhs->bits & DECINF)==0 && ISZERO(rhs))) {
4907      *status|=DEC_Invalid_operation;
4908      return res;}
4909    decNumberZero(res);
4910    res->bits=bits|DECINF;	   /* infinity */
4911    return res;}
4912
4913  /* For best speed, as in DMSRCN [the original Rexx numerics */
4914  /* module], use the shorter number as the multiplier (rhs) and */
4915  /* the longer as the multiplicand (lhs) to minimise the number of */
4916  /* adds (partial products) */
4917  if (lhs->digits<rhs->digits) {   /* swap... */
4918    const decNumber *hold=lhs;
4919    lhs=rhs;
4920    rhs=hold;
4921    }
4922
4923  do {				   /* protect allocated storage */
4924    #if DECSUBSET
4925    if (!set->extended) {
4926      /* reduce operands and set lostDigits status, as needed */
4927      if (lhs->digits>set->digits) {
4928	alloclhs=decRoundOperand(lhs, set, status);
4929	if (alloclhs==NULL) break;
4930	lhs=alloclhs;
4931	}
4932      if (rhs->digits>set->digits) {
4933	allocrhs=decRoundOperand(rhs, set, status);
4934	if (allocrhs==NULL) break;
4935	rhs=allocrhs;
4936	}
4937      }
4938    #endif
4939    /* [following code does not require input rounding] */
4940
4941    #if FASTMUL 		   /* fastpath can be used */
4942    /* use the fast path if there are enough digits in the shorter */
4943    /* operand to make the setup and takedown worthwhile */
4944    #define NEEDTWO (DECDPUN*2)    /* within two decUnitAddSub calls */
4945    if (rhs->digits>NEEDTWO) {	   /* use fastpath... */
4946      /* calculate the number of elements in each array */
4947      ilhs=(lhs->digits+FASTDIGS-1)/FASTDIGS; /* [ceiling] */
4948      irhs=(rhs->digits+FASTDIGS-1)/FASTDIGS; /* .. */
4949      iacc=ilhs+irhs;
4950
4951      /* allocate buffers if required, as usual */
4952      needbytes=ilhs*sizeof(uInt);
4953      if (needbytes>(Int)sizeof(zlhibuff)) {
4954	alloclhi=(uInt *)malloc(needbytes);
4955	zlhi=alloclhi;}
4956      needbytes=irhs*sizeof(uInt);
4957      if (needbytes>(Int)sizeof(zrhibuff)) {
4958	allocrhi=(uInt *)malloc(needbytes);
4959	zrhi=allocrhi;}
4960
4961      /* Allocating the accumulator space needs a special case when */
4962      /* DECDPUN=1 because when converting the accumulator to Units */
4963      /* after the multiplication each 8-byte item becomes 9 1-byte */
4964      /* units.  Therefore iacc extra bytes are needed at the front */
4965      /* (rounded up to a multiple of 8 bytes), and the uLong */
4966      /* accumulator starts offset the appropriate number of units */
4967      /* to the right to avoid overwrite during the unchunking. */
4968      needbytes=iacc*sizeof(uLong);
4969      #if DECDPUN==1
4970      zoff=(iacc+7)/8;	      /* items to offset by */
4971      needbytes+=zoff*8;
4972      #endif
4973      if (needbytes>(Int)sizeof(zaccbuff)) {
4974	allocacc=(uLong *)malloc(needbytes);
4975	zacc=(uLong *)allocacc;}
4976      if (zlhi==NULL||zrhi==NULL||zacc==NULL) {
4977	*status|=DEC_Insufficient_storage;
4978	break;}
4979
4980      acc=(Unit *)zacc;       /* -> target Unit array */
4981      #if DECDPUN==1
4982      zacc+=zoff;	      /* start uLong accumulator to right */
4983      #endif
4984
4985      /* assemble the chunked copies of the left and right sides */
4986      for (count=lhs->digits, cup=lhs->lsu, lip=zlhi; count>0; lip++)
4987	for (p=0, *lip=0; p<FASTDIGS && count>0;
4988	     p+=DECDPUN, cup++, count-=DECDPUN)
4989	  *lip+=*cup*powers[p];
4990      lmsi=lip-1;     /* save -> msi */
4991      for (count=rhs->digits, cup=rhs->lsu, rip=zrhi; count>0; rip++)
4992	for (p=0, *rip=0; p<FASTDIGS && count>0;
4993	     p+=DECDPUN, cup++, count-=DECDPUN)
4994	  *rip+=*cup*powers[p];
4995      rmsi=rip-1;     /* save -> msi */
4996
4997      /* zero the accumulator */
4998      for (lp=zacc; lp<zacc+iacc; lp++) *lp=0;
4999
5000      /* Start the multiplication */
5001      /* Resolving carries can dominate the cost of accumulating the */
5002      /* partial products, so this is only done when necessary. */
5003      /* Each uLong item in the accumulator can hold values up to */
5004      /* 2**64-1, and each partial product can be as large as */
5005      /* (10**FASTDIGS-1)**2.  When FASTDIGS=9, this can be added to */
5006      /* itself 18.4 times in a uLong without overflowing, so during */
5007      /* the main calculation resolution is carried out every 18th */
5008      /* add -- every 162 digits.  Similarly, when FASTDIGS=8, the */
5009      /* partial products can be added to themselves 1844.6 times in */
5010      /* a uLong without overflowing, so intermediate carry */
5011      /* resolution occurs only every 14752 digits.  Hence for common */
5012      /* short numbers usually only the one final carry resolution */
5013      /* occurs. */
5014      /* (The count is set via FASTLAZY to simplify experiments to */
5015      /* measure the value of this approach: a 35% improvement on a */
5016      /* [34x34] multiply.) */
5017      lazy=FASTLAZY;			     /* carry delay count */
5018      for (rip=zrhi; rip<=rmsi; rip++) {     /* over each item in rhs */
5019	lp=zacc+(rip-zrhi);		     /* where to add the lhs */
5020	for (lip=zlhi; lip<=lmsi; lip++, lp++) { /* over each item in lhs */
5021	  *lp+=(uLong)(*lip)*(*rip);	     /* [this should in-line] */
5022	  } /* lip loop */
5023	lazy--;
5024	if (lazy>0 && rip!=rmsi) continue;
5025	lazy=FASTLAZY;			     /* reset delay count */
5026	/* spin up the accumulator resolving overflows */
5027	for (lp=zacc; lp<zacc+iacc; lp++) {
5028	  if (*lp<FASTBASE) continue;	     /* it fits */
5029	  lcarry=*lp/FASTBASE;		     /* top part [slow divide] */
5030	  /* lcarry can exceed 2**32-1, so check again; this check */
5031	  /* and occasional extra divide (slow) is well worth it, as */
5032	  /* it allows FASTLAZY to be increased to 18 rather than 4 */
5033	  /* in the FASTDIGS=9 case */
5034	  if (lcarry<FASTBASE) carry=(uInt)lcarry;  /* [usual] */
5035	   else { /* two-place carry [fairly rare] */
5036	    uInt carry2=(uInt)(lcarry/FASTBASE);    /* top top part */
5037	    *(lp+2)+=carry2;			    /* add to item+2 */
5038	    *lp-=((uLong)FASTBASE*FASTBASE*carry2); /* [slow] */
5039	    carry=(uInt)(lcarry-((uLong)FASTBASE*carry2)); /* [inline] */
5040	    }
5041	  *(lp+1)+=carry;		     /* add to item above [inline] */
5042	  *lp-=((uLong)FASTBASE*carry);      /* [inline] */
5043	  } /* carry resolution */
5044	} /* rip loop */
5045
5046      /* The multiplication is complete; time to convert back into */
5047      /* units.  This can be done in-place in the accumulator and in */
5048      /* 32-bit operations, because carries were resolved after the */
5049      /* final add.  This needs N-1 divides and multiplies for */
5050      /* each item in the accumulator (which will become up to N */
5051      /* units, where 2<=N<=9). */
5052      for (lp=zacc, up=acc; lp<zacc+iacc; lp++) {
5053	uInt item=(uInt)*lp;		     /* decapitate to uInt */
5054	for (p=0; p<FASTDIGS-DECDPUN; p+=DECDPUN, up++) {
5055	  uInt part=item/(DECDPUNMAX+1);
5056	  *up=(Unit)(item-(part*(DECDPUNMAX+1)));
5057	  item=part;
5058	  } /* p */
5059	*up=(Unit)item; up++;		     /* [final needs no division] */
5060	} /* lp */
5061      accunits=up-acc;			     /* count of units */
5062      }
5063     else { /* here to use units directly, without chunking ['old code'] */
5064    #endif
5065
5066      /* if accumulator will be too long for local storage, then allocate */
5067      acc=accbuff;		   /* -> assume buffer for accumulator */
5068      needbytes=(D2U(lhs->digits)+D2U(rhs->digits))*sizeof(Unit);
5069      if (needbytes>(Int)sizeof(accbuff)) {
5070	allocacc=(Unit *)malloc(needbytes);
5071	if (allocacc==NULL) {*status|=DEC_Insufficient_storage; break;}
5072	acc=(Unit *)allocacc;		     /* use the allocated space */
5073	}
5074
5075      /* Now the main long multiplication loop */
5076      /* Unlike the equivalent in the IBM Java implementation, there */
5077      /* is no advantage in calculating from msu to lsu.  So, do it */
5078      /* by the book, as it were. */
5079      /* Each iteration calculates ACC=ACC+MULTAND*MULT */
5080      accunits=1;		   /* accumulator starts at '0' */
5081      *acc=0;			   /* .. (lsu=0) */
5082      shift=0;			   /* no multiplicand shift at first */
5083      madlength=D2U(lhs->digits);  /* this won't change */
5084      mermsup=rhs->lsu+D2U(rhs->digits); /* -> msu+1 of multiplier */
5085
5086      for (mer=rhs->lsu; mer<mermsup; mer++) {
5087	/* Here, *mer is the next Unit in the multiplier to use */
5088	/* If non-zero [optimization] add it... */
5089	if (*mer!=0) accunits=decUnitAddSub(&acc[shift], accunits-shift,
5090					    lhs->lsu, madlength, 0,
5091					    &acc[shift], *mer)
5092					    + shift;
5093	 else { /* extend acc with a 0; it will be used shortly */
5094	  *(acc+accunits)=0;	   /* [this avoids length of <=0 later] */
5095	  accunits++;
5096	  }
5097	/* multiply multiplicand by 10**DECDPUN for next Unit to left */
5098	shift++;		   /* add this for 'logical length' */
5099	} /* n */
5100    #if FASTMUL
5101      } /* unchunked units */
5102    #endif
5103    /* common end-path */
5104    #if DECTRACE
5105      decDumpAr('*', acc, accunits);	     /* Show exact result */
5106    #endif
5107
5108    /* acc now contains the exact result of the multiplication, */
5109    /* possibly with a leading zero unit; build the decNumber from */
5110    /* it, noting if any residue */
5111    res->bits=bits;			     /* set sign */
5112    res->digits=decGetDigits(acc, accunits); /* count digits exactly */
5113
5114    /* There can be a 31-bit wrap in calculating the exponent. */
5115    /* This can only happen if both input exponents are negative and */
5116    /* both their magnitudes are large.  If there was a wrap, set a */
5117    /* safe very negative exponent, from which decFinalize() will */
5118    /* raise a hard underflow shortly. */
5119    exponent=lhs->exponent+rhs->exponent;    /* calculate exponent */
5120    if (lhs->exponent<0 && rhs->exponent<0 && exponent>0)
5121      exponent=-2*DECNUMMAXE;		     /* force underflow */
5122    res->exponent=exponent;		     /* OK to overwrite now */
5123
5124
5125    /* Set the coefficient.  If any rounding, residue records */
5126    decSetCoeff(res, set, acc, res->digits, &residue, status);
5127    decFinish(res, set, &residue, status);   /* final cleanup */
5128    } while(0); 			/* end protected */
5129
5130  free(allocacc);	/* drop any storage used */
5131  #if DECSUBSET
5132  free(allocrhs);	/* .. */
5133  free(alloclhs);	/* .. */
5134  #endif
5135  #if FASTMUL
5136  free(allocrhi);	/* .. */
5137  free(alloclhi);	/* .. */
5138  #endif
5139  return res;
5140  } /* decMultiplyOp */
5141
5142/* ------------------------------------------------------------------ */
5143/* decExpOp -- effect exponentiation				      */
5144/*								      */
5145/*   This computes C = exp(A)					      */
5146/*								      */
5147/*   res is C, the result.  C may be A				      */
5148/*   rhs is A							      */
5149/*   set is the context; note that rounding mode has no effect	      */
5150/*								      */
5151/* C must have space for set->digits digits. status is updated but    */
5152/* not set.							      */
5153/*								      */
5154/* Restrictions:						      */
5155/*								      */
5156/*   digits, emax, and -emin in the context must be less than	      */
5157/*   2*DEC_MAX_MATH (1999998), and the rhs must be within these       */
5158/*   bounds or a zero.	This is an internal routine, so these	      */
5159/*   restrictions are contractual and not enforced.		      */
5160/*								      */
5161/* A finite result is rounded using DEC_ROUND_HALF_EVEN; it will      */
5162/* almost always be correctly rounded, but may be up to 1 ulp in      */
5163/* error in rare cases. 					      */
5164/*								      */
5165/* Finite results will always be full precision and Inexact, except   */
5166/* when A is a zero or -Infinity (giving 1 or 0 respectively).	      */
5167/* ------------------------------------------------------------------ */
5168/* This approach used here is similar to the algorithm described in   */
5169/*								      */
5170/*   Variable Precision Exponential Function, T. E. Hull and	      */
5171/*   A. Abrham, ACM Transactions on Mathematical Software, Vol 12 #2, */
5172/*   pp79-91, ACM, June 1986.					      */
5173/*								      */
5174/* with the main difference being that the iterations in the series   */
5175/* evaluation are terminated dynamically (which does not require the  */
5176/* extra variable-precision variables which are expensive in this     */
5177/* context).							      */
5178/*								      */
5179/* The error analysis in Hull & Abrham's paper applies except for the */
5180/* round-off error accumulation during the series evaluation.  This   */
5181/* code does not precalculate the number of iterations and so cannot  */
5182/* use Horner's scheme.  Instead, the accumulation is done at double- */
5183/* precision, which ensures that the additions of the terms are exact */
5184/* and do not accumulate round-off (and any round-off errors in the   */
5185/* terms themselves move 'to the right' faster than they can	      */
5186/* accumulate).  This code also extends the calculation by allowing,  */
5187/* in the spirit of other decNumber operators, the input to be more   */
5188/* precise than the result (the precision used is based on the more   */
5189/* precise of the input or requested result).			      */
5190/*								      */
5191/* Implementation notes:					      */
5192/*								      */
5193/* 1. This is separated out as decExpOp so it can be called from      */
5194/*    other Mathematical functions (notably Ln) with a wider range    */
5195/*    than normal.  In particular, it can handle the slightly wider   */
5196/*    (double) range needed by Ln (which has to be able to calculate  */
5197/*    exp(-x) where x can be the tiniest number (Ntiny).	      */
5198/*								      */
5199/* 2. Normalizing x to be <=0.1 (instead of <=1) reduces loop	      */
5200/*    iterations by appoximately a third with additional (although    */
5201/*    diminishing) returns as the range is reduced to even smaller    */
5202/*    fractions.  However, h (the power of 10 used to correct the     */
5203/*    result at the end, see below) must be kept <=8 as otherwise     */
5204/*    the final result cannot be computed.  Hence the leverage is a   */
5205/*    sliding value (8-h), where potentially the range is reduced     */
5206/*    more for smaller values.					      */
5207/*								      */
5208/*    The leverage that can be applied in this way is severely	      */
5209/*    limited by the cost of the raise-to-the power at the end,       */
5210/*    which dominates when the number of iterations is small (less    */
5211/*    than ten) or when rhs is short.  As an example, the adjustment  */
5212/*    x**10,000,000 needs 31 multiplications, all but one full-width. */
5213/*								      */
5214/* 3. The restrictions (especially precision) could be raised with    */
5215/*    care, but the full decNumber range seems very hard within the   */
5216/*    32-bit limits.						      */
5217/*								      */
5218/* 4. The working precisions for the static buffers are twice the     */
5219/*    obvious size to allow for calls from decNumberPower.	      */
5220/* ------------------------------------------------------------------ */
5221decNumber * decExpOp(decNumber *res, const decNumber *rhs,
5222			 decContext *set, uInt *status) {
5223  uInt ignore=0;		   /* working status */
5224  Int h;			   /* adjusted exponent for 0.xxxx */
5225  Int p;			   /* working precision */
5226  Int residue;			   /* rounding residue */
5227  uInt needbytes;		   /* for space calculations */
5228  const decNumber *x=rhs;	   /* (may point to safe copy later) */
5229  decContext aset, tset, dset;	   /* working contexts */
5230  Int comp;			   /* work */
5231
5232  /* the argument is often copied to normalize it, so (unusually) it */
5233  /* is treated like other buffers, using DECBUFFER, +1 in case */
5234  /* DECBUFFER is 0 */
5235  decNumber bufr[D2N(DECBUFFER*2+1)];
5236  decNumber *allocrhs=NULL;	   /* non-NULL if rhs buffer allocated */
5237
5238  /* the working precision will be no more than set->digits+8+1 */
5239  /* so for on-stack buffers DECBUFFER+9 is used, +1 in case DECBUFFER */
5240  /* is 0 (and twice that for the accumulator) */
5241
5242  /* buffer for t, term (working precision plus) */
5243  decNumber buft[D2N(DECBUFFER*2+9+1)];
5244  decNumber *allocbuft=NULL;	   /* -> allocated buft, iff allocated */
5245  decNumber *t=buft;		   /* term */
5246  /* buffer for a, accumulator (working precision * 2), at least 9 */
5247  decNumber bufa[D2N(DECBUFFER*4+18+1)];
5248  decNumber *allocbufa=NULL;	   /* -> allocated bufa, iff allocated */
5249  decNumber *a=bufa;		   /* accumulator */
5250  /* decNumber for the divisor term; this needs at most 9 digits */
5251  /* and so can be fixed size [16 so can use standard context] */
5252  decNumber bufd[D2N(16)];
5253  decNumber *d=bufd;		   /* divisor */
5254  decNumber numone;		   /* constant 1 */
5255
5256  #if DECCHECK
5257  Int iterations=0;		   /* for later sanity check */
5258  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
5259  #endif
5260
5261  do {					/* protect allocated storage */
5262    if (SPECIALARG) {			/* handle infinities and NaNs */
5263      if (decNumberIsInfinite(rhs)) {	/* an infinity */
5264	if (decNumberIsNegative(rhs))	/* -Infinity -> +0 */
5265	  decNumberZero(res);
5266	 else decNumberCopy(res, rhs);	/* +Infinity -> self */
5267	}
5268       else decNaNs(res, rhs, NULL, set, status); /* a NaN */
5269      break;}
5270
5271    if (ISZERO(rhs)) {			/* zeros -> exact 1 */
5272      decNumberZero(res);		/* make clean 1 */
5273      *res->lsu=1;			/* .. */
5274      break;}				/* [no status to set] */
5275
5276    /* e**x when 0 < x < 0.66 is < 1+3x/2, hence can fast-path */
5277    /* positive and negative tiny cases which will result in inexact */
5278    /* 1.  This also allows the later add-accumulate to always be */
5279    /* exact (because its length will never be more than twice the */
5280    /* working precision). */
5281    /* The comparator (tiny) needs just one digit, so use the */
5282    /* decNumber d for it (reused as the divisor, etc., below); its */
5283    /* exponent is such that if x is positive it will have */
5284    /* set->digits-1 zeros between the decimal point and the digit, */
5285    /* which is 4, and if x is negative one more zero there as the */
5286    /* more precise result will be of the form 0.9999999 rather than */
5287    /* 1.0000001.  Hence, tiny will be 0.0000004  if digits=7 and x>0 */
5288    /* or 0.00000004 if digits=7 and x<0.  If RHS not larger than */
5289    /* this then the result will be 1.000000 */
5290    decNumberZero(d);			/* clean */
5291    *d->lsu=4;				/* set 4 .. */
5292    d->exponent=-set->digits;		/* * 10**(-d) */
5293    if (decNumberIsNegative(rhs)) d->exponent--;  /* negative case */
5294    comp=decCompare(d, rhs, 1); 	/* signless compare */
5295    if (comp==BADINT) {
5296      *status|=DEC_Insufficient_storage;
5297      break;}
5298    if (comp>=0) {			/* rhs < d */
5299      Int shift=set->digits-1;
5300      decNumberZero(res);		/* set 1 */
5301      *res->lsu=1;			/* .. */
5302      res->digits=decShiftToMost(res->lsu, 1, shift);
5303      res->exponent=-shift;		     /* make 1.0000... */
5304      *status|=DEC_Inexact | DEC_Rounded;    /* .. inexactly */
5305      break;} /* tiny */
5306
5307    /* set up the context to be used for calculating a, as this is */
5308    /* used on both paths below */
5309    decContextDefault(&aset, DEC_INIT_DECIMAL64);
5310    /* accumulator bounds are as requested (could underflow) */
5311    aset.emax=set->emax;		/* usual bounds */
5312    aset.emin=set->emin;		/* .. */
5313    aset.clamp=0;			/* and no concrete format */
5314
5315    /* calculate the adjusted (Hull & Abrham) exponent (where the */
5316    /* decimal point is just to the left of the coefficient msd) */
5317    h=rhs->exponent+rhs->digits;
5318    /* if h>8 then 10**h cannot be calculated safely; however, when */
5319    /* h=8 then exp(|rhs|) will be at least exp(1E+7) which is at */
5320    /* least 6.59E+4342944, so (due to the restriction on Emax/Emin) */
5321    /* overflow (or underflow to 0) is guaranteed -- so this case can */
5322    /* be handled by simply forcing the appropriate excess */
5323    if (h>8) {				/* overflow/underflow */
5324      /* set up here so Power call below will over or underflow to */
5325      /* zero; set accumulator to either 2 or 0.02 */
5326      /* [stack buffer for a is always big enough for this] */
5327      decNumberZero(a);
5328      *a->lsu=2;			/* not 1 but < exp(1) */
5329      if (decNumberIsNegative(rhs)) a->exponent=-2; /* make 0.02 */
5330      h=8;				/* clamp so 10**h computable */
5331      p=9;				/* set a working precision */
5332      }
5333     else {				/* h<=8 */
5334      Int maxlever=(rhs->digits>8?1:0);
5335      /* [could/should increase this for precisions >40 or so, too] */
5336
5337      /* if h is 8, cannot normalize to a lower upper limit because */
5338      /* the final result will not be computable (see notes above), */
5339      /* but leverage can be applied whenever h is less than 8. */
5340      /* Apply as much as possible, up to a MAXLEVER digits, which */
5341      /* sets the tradeoff against the cost of the later a**(10**h). */
5342      /* As h is increased, the working precision below also */
5343      /* increases to compensate for the "constant digits at the */
5344      /* front" effect. */
5345      Int lever=MINI(8-h, maxlever);	/* leverage attainable */
5346      Int use=-rhs->digits-lever;	/* exponent to use for RHS */
5347      h+=lever; 			/* apply leverage selected */
5348      if (h<0) {			/* clamp */
5349	use+=h; 			/* [may end up subnormal] */
5350	h=0;
5351	}
5352      /* Take a copy of RHS if it needs normalization (true whenever x>=1) */
5353      if (rhs->exponent!=use) {
5354	decNumber *newrhs=bufr; 	/* assume will fit on stack */
5355	needbytes=sizeof(decNumber)+(D2U(rhs->digits)-1)*sizeof(Unit);
5356	if (needbytes>sizeof(bufr)) {	/* need malloc space */
5357	  allocrhs=(decNumber *)malloc(needbytes);
5358	  if (allocrhs==NULL) { 	/* hopeless -- abandon */
5359	    *status|=DEC_Insufficient_storage;
5360	    break;}
5361	  newrhs=allocrhs;		/* use the allocated space */
5362	  }
5363	decNumberCopy(newrhs, rhs);	/* copy to safe space */
5364	newrhs->exponent=use;		/* normalize; now <1 */
5365	x=newrhs;			/* ready for use */
5366	/* decNumberShow(x); */
5367	}
5368
5369      /* Now use the usual power series to evaluate exp(x).  The */
5370      /* series starts as 1 + x + x^2/2 ... so prime ready for the */
5371      /* third term by setting the term variable t=x, the accumulator */
5372      /* a=1, and the divisor d=2. */
5373
5374      /* First determine the working precision.  From Hull & Abrham */
5375      /* this is set->digits+h+2.  However, if x is 'over-precise' we */
5376      /* need to allow for all its digits to potentially participate */
5377      /* (consider an x where all the excess digits are 9s) so in */
5378      /* this case use x->digits+h+2 */
5379      p=MAXI(x->digits, set->digits)+h+2;    /* [h<=8] */
5380
5381      /* a and t are variable precision, and depend on p, so space */
5382      /* must be allocated for them if necessary */
5383
5384      /* the accumulator needs to be able to hold 2p digits so that */
5385      /* the additions on the second and subsequent iterations are */
5386      /* sufficiently exact. */
5387      needbytes=sizeof(decNumber)+(D2U(p*2)-1)*sizeof(Unit);
5388      if (needbytes>sizeof(bufa)) {	/* need malloc space */
5389	allocbufa=(decNumber *)malloc(needbytes);
5390	if (allocbufa==NULL) {		/* hopeless -- abandon */
5391	  *status|=DEC_Insufficient_storage;
5392	  break;}
5393	a=allocbufa;			/* use the allocated space */
5394	}
5395      /* the term needs to be able to hold p digits (which is */
5396      /* guaranteed to be larger than x->digits, so the initial copy */
5397      /* is safe); it may also be used for the raise-to-power */
5398      /* calculation below, which needs an extra two digits */
5399      needbytes=sizeof(decNumber)+(D2U(p+2)-1)*sizeof(Unit);
5400      if (needbytes>sizeof(buft)) {	/* need malloc space */
5401	allocbuft=(decNumber *)malloc(needbytes);
5402	if (allocbuft==NULL) {		/* hopeless -- abandon */
5403	  *status|=DEC_Insufficient_storage;
5404	  break;}
5405	t=allocbuft;			/* use the allocated space */
5406	}
5407
5408      decNumberCopy(t, x);		/* term=x */
5409      decNumberZero(a); *a->lsu=1;	/* accumulator=1 */
5410      decNumberZero(d); *d->lsu=2;	/* divisor=2 */
5411      decNumberZero(&numone); *numone.lsu=1; /* constant 1 for increment */
5412
5413      /* set up the contexts for calculating a, t, and d */
5414      decContextDefault(&tset, DEC_INIT_DECIMAL64);
5415      dset=tset;
5416      /* accumulator bounds are set above, set precision now */
5417      aset.digits=p*2;			/* double */
5418      /* term bounds avoid any underflow or overflow */
5419      tset.digits=p;
5420      tset.emin=DEC_MIN_EMIN;		/* [emax is plenty] */
5421      /* [dset.digits=16, etc., are sufficient] */
5422
5423      /* finally ready to roll */
5424      for (;;) {
5425	#if DECCHECK
5426	iterations++;
5427	#endif
5428	/* only the status from the accumulation is interesting */
5429	/* [but it should remain unchanged after first add] */
5430	decAddOp(a, a, t, &aset, 0, status);	       /* a=a+t */
5431	decMultiplyOp(t, t, x, &tset, &ignore);        /* t=t*x */
5432	decDivideOp(t, t, d, &tset, DIVIDE, &ignore);  /* t=t/d */
5433	/* the iteration ends when the term cannot affect the result, */
5434	/* if rounded to p digits, which is when its value is smaller */
5435	/* than the accumulator by p+1 digits.	There must also be */
5436	/* full precision in a. */
5437	if (((a->digits+a->exponent)>=(t->digits+t->exponent+p+1))
5438	    && (a->digits>=p)) break;
5439	decAddOp(d, d, &numone, &dset, 0, &ignore);    /* d=d+1 */
5440	} /* iterate */
5441
5442      #if DECCHECK
5443      /* just a sanity check; comment out test to show always */
5444      if (iterations>p+3)
5445	printf("Exp iterations=%ld, status=%08lx, p=%ld, d=%ld\n",
5446	       (LI)iterations, (LI)*status, (LI)p, (LI)x->digits);
5447      #endif
5448      } /* h<=8 */
5449
5450    /* apply postconditioning: a=a**(10**h) -- this is calculated */
5451    /* at a slightly higher precision than Hull & Abrham suggest */
5452    if (h>0) {
5453      Int seenbit=0;		   /* set once a 1-bit is seen */
5454      Int i;			   /* counter */
5455      Int n=powers[h];		   /* always positive */
5456      aset.digits=p+2;		   /* sufficient precision */
5457      /* avoid the overhead and many extra digits of decNumberPower */
5458      /* as all that is needed is the short 'multipliers' loop; here */
5459      /* accumulate the answer into t */
5460      decNumberZero(t); *t->lsu=1; /* acc=1 */
5461      for (i=1;;i++){		   /* for each bit [top bit ignored] */
5462	/* abandon if have had overflow or terminal underflow */
5463	if (*status & (DEC_Overflow|DEC_Underflow)) { /* interesting? */
5464	  if (*status&DEC_Overflow || ISZERO(t)) break;}
5465	n=n<<1; 		   /* move next bit to testable position */
5466	if (n<0) {		   /* top bit is set */
5467	  seenbit=1;		   /* OK, have a significant bit */
5468	  decMultiplyOp(t, t, a, &aset, status); /* acc=acc*x */
5469	  }
5470	if (i==31) break;	   /* that was the last bit */
5471	if (!seenbit) continue;    /* no need to square 1 */
5472	decMultiplyOp(t, t, t, &aset, status); /* acc=acc*acc [square] */
5473	} /*i*/ /* 32 bits */
5474      /* decNumberShow(t); */
5475      a=t;			   /* and carry on using t instead of a */
5476      }
5477
5478    /* Copy and round the result to res */
5479    residue=1;				/* indicate dirt to right .. */
5480    if (ISZERO(a)) residue=0;		/* .. unless underflowed to 0 */
5481    aset.digits=set->digits;		/* [use default rounding] */
5482    decCopyFit(res, a, &aset, &residue, status); /* copy & shorten */
5483    decFinish(res, set, &residue, status);	 /* cleanup/set flags */
5484    } while(0); 			/* end protected */
5485
5486  free(allocrhs);	/* drop any storage used */
5487  free(allocbufa); /* .. */
5488  free(allocbuft); /* .. */
5489  /* [status is handled by caller] */
5490  return res;
5491  } /* decExpOp */
5492
5493/* ------------------------------------------------------------------ */
5494/* Initial-estimate natural logarithm table			      */
5495/*								      */
5496/*   LNnn -- 90-entry 16-bit table for values from .10 through .99.   */
5497/*	     The result is a 4-digit encode of the coefficient (c=the */
5498/*	     top 14 bits encoding 0-9999) and a 2-digit encode of the */
5499/*	     exponent (e=the bottom 2 bits encoding 0-3)	      */
5500/*								      */
5501/*	     The resulting value is given by:			      */
5502/*								      */
5503/*	       v = -c * 10**(-e-3)				      */
5504/*								      */
5505/*	     where e and c are extracted from entry k = LNnn[x-10]    */
5506/*	     where x is truncated (NB) into the range 10 through 99,  */
5507/*	     and then c = k>>2 and e = k&3.			      */
5508/* ------------------------------------------------------------------ */
5509const uShort LNnn[90]={9016,  8652,  8316,  8008,  7724,  7456,  7208,
5510  6972,  6748,	6540,  6340,  6148,  5968,  5792,  5628,  5464,  5312,
5511  5164,  5020,	4884,  4748,  4620,  4496,  4376,  4256,  4144,  4032,
5512 39233, 38181, 37157, 36157, 35181, 34229, 33297, 32389, 31501, 30629,
5513 29777, 28945, 28129, 27329, 26545, 25777, 25021, 24281, 23553, 22837,
5514 22137, 21445, 20769, 20101, 19445, 18801, 18165, 17541, 16925, 16321,
5515 15721, 15133, 14553, 13985, 13421, 12865, 12317, 11777, 11241, 10717,
5516 10197,  9685,	9177,  8677,  8185,  7697,  7213,  6737,  6269,  5801,
5517  5341,  4889,	4437, 39930, 35534, 31186, 26886, 22630, 18418, 14254,
5518 10130,  6046, 20055};
5519
5520/* ------------------------------------------------------------------ */
5521/* decLnOp -- effect natural logarithm				      */
5522/*								      */
5523/*   This computes C = ln(A)					      */
5524/*								      */
5525/*   res is C, the result.  C may be A				      */
5526/*   rhs is A							      */
5527/*   set is the context; note that rounding mode has no effect	      */
5528/*								      */
5529/* C must have space for set->digits digits.			      */
5530/*								      */
5531/* Notable cases:						      */
5532/*   A<0 -> Invalid						      */
5533/*   A=0 -> -Infinity (Exact)					      */
5534/*   A=+Infinity -> +Infinity (Exact)				      */
5535/*   A=1 exactly -> 0 (Exact)					      */
5536/*								      */
5537/* Restrictions (as for Exp):					      */
5538/*								      */
5539/*   digits, emax, and -emin in the context must be less than	      */
5540/*   DEC_MAX_MATH+11 (1000010), and the rhs must be within these      */
5541/*   bounds or a zero.	This is an internal routine, so these	      */
5542/*   restrictions are contractual and not enforced.		      */
5543/*								      */
5544/* A finite result is rounded using DEC_ROUND_HALF_EVEN; it will      */
5545/* almost always be correctly rounded, but may be up to 1 ulp in      */
5546/* error in rare cases. 					      */
5547/* ------------------------------------------------------------------ */
5548/* The result is calculated using Newton's method, with each	      */
5549/* iteration calculating a' = a + x * exp(-a) - 1.  See, for example, */
5550/* Epperson 1989.						      */
5551/*								      */
5552/* The iteration ends when the adjustment x*exp(-a)-1 is tiny enough. */
5553/* This has to be calculated at the sum of the precision of x and the */
5554/* working precision.						      */
5555/*								      */
5556/* Implementation notes:					      */
5557/*								      */
5558/* 1. This is separated out as decLnOp so it can be called from       */
5559/*    other Mathematical functions (e.g., Log 10) with a wider range  */
5560/*    than normal.  In particular, it can handle the slightly wider   */
5561/*    (+9+2) range needed by a power function.			      */
5562/*								      */
5563/* 2. The speed of this function is about 10x slower than exp, as     */
5564/*    it typically needs 4-6 iterations for short numbers, and the    */
5565/*    extra precision needed adds a squaring effect, twice.	      */
5566/*								      */
5567/* 3. Fastpaths are included for ln(10) and ln(2), up to length 40,   */
5568/*    as these are common requests.  ln(10) is used by log10(x).      */
5569/*								      */
5570/* 4. An iteration might be saved by widening the LNnn table, and     */
5571/*    would certainly save at least one if it were made ten times     */
5572/*    bigger, too (for truncated fractions 0.100 through 0.999).      */
5573/*    However, for most practical evaluations, at least four or five  */
5574/*    iterations will be neede -- so this would only speed up by      */
5575/*    20-25% and that probably does not justify increasing the table  */
5576/*    size.							      */
5577/*								      */
5578/* 5. The static buffers are larger than might be expected to allow   */
5579/*    for calls from decNumberPower.				      */
5580/* ------------------------------------------------------------------ */
5581decNumber * decLnOp(decNumber *res, const decNumber *rhs,
5582		    decContext *set, uInt *status) {
5583  uInt ignore=0;		   /* working status accumulator */
5584  uInt needbytes;		   /* for space calculations */
5585  Int residue;			   /* rounding residue */
5586  Int r;			   /* rhs=f*10**r [see below] */
5587  Int p;			   /* working precision */
5588  Int pp;			   /* precision for iteration */
5589  Int t;			   /* work */
5590
5591  /* buffers for a (accumulator, typically precision+2) and b */
5592  /* (adjustment calculator, same size) */
5593  decNumber bufa[D2N(DECBUFFER+12)];
5594  decNumber *allocbufa=NULL;	   /* -> allocated bufa, iff allocated */
5595  decNumber *a=bufa;		   /* accumulator/work */
5596  decNumber bufb[D2N(DECBUFFER*2+2)];
5597  decNumber *allocbufb=NULL;	   /* -> allocated bufa, iff allocated */
5598  decNumber *b=bufb;		   /* adjustment/work */
5599
5600  decNumber  numone;		   /* constant 1 */
5601  decNumber  cmp;		   /* work */
5602  decContext aset, bset;	   /* working contexts */
5603
5604  #if DECCHECK
5605  Int iterations=0;		   /* for later sanity check */
5606  if (decCheckOperands(res, DECUNUSED, rhs, set)) return res;
5607  #endif
5608
5609  do {					/* protect allocated storage */
5610    if (SPECIALARG) {			/* handle infinities and NaNs */
5611      if (decNumberIsInfinite(rhs)) {	/* an infinity */
5612	if (decNumberIsNegative(rhs))	/* -Infinity -> error */
5613	  *status|=DEC_Invalid_operation;
5614	 else decNumberCopy(res, rhs);	/* +Infinity -> self */
5615	}
5616       else decNaNs(res, rhs, NULL, set, status); /* a NaN */
5617      break;}
5618
5619    if (ISZERO(rhs)) {			/* +/- zeros -> -Infinity */
5620      decNumberZero(res);		/* make clean */
5621      res->bits=DECINF|DECNEG;		/* set - infinity */
5622      break;}				/* [no status to set] */
5623
5624    /* Non-zero negatives are bad... */
5625    if (decNumberIsNegative(rhs)) {	/* -x -> error */
5626      *status|=DEC_Invalid_operation;
5627      break;}
5628
5629    /* Here, rhs is positive, finite, and in range */
5630
5631    /* lookaside fastpath code for ln(2) and ln(10) at common lengths */
5632    if (rhs->exponent==0 && set->digits<=40) {
5633      #if DECDPUN==1
5634      if (rhs->lsu[0]==0 && rhs->lsu[1]==1 && rhs->digits==2) { /* ln(10) */
5635      #else
5636      if (rhs->lsu[0]==10 && rhs->digits==2) {			/* ln(10) */
5637      #endif
5638	aset=*set; aset.round=DEC_ROUND_HALF_EVEN;
5639	#define LN10 "2.302585092994045684017991454684364207601"
5640	decNumberFromString(res, LN10, &aset);
5641	*status|=(DEC_Inexact | DEC_Rounded); /* is inexact */
5642	break;}
5643      if (rhs->lsu[0]==2 && rhs->digits==1) { /* ln(2) */
5644	aset=*set; aset.round=DEC_ROUND_HALF_EVEN;
5645	#define LN2 "0.6931471805599453094172321214581765680755"
5646	decNumberFromString(res, LN2, &aset);
5647	*status|=(DEC_Inexact | DEC_Rounded);
5648	break;}
5649      } /* integer and short */
5650
5651    /* Determine the working precision.  This is normally the */
5652    /* requested precision + 2, with a minimum of 9.  However, if */
5653    /* the rhs is 'over-precise' then allow for all its digits to */
5654    /* potentially participate (consider an rhs where all the excess */
5655    /* digits are 9s) so in this case use rhs->digits+2. */
5656    p=MAXI(rhs->digits, MAXI(set->digits, 7))+2;
5657
5658    /* Allocate space for the accumulator and the high-precision */
5659    /* adjustment calculator, if necessary.  The accumulator must */
5660    /* be able to hold p digits, and the adjustment up to */
5661    /* rhs->digits+p digits.  They are also made big enough for 16 */
5662    /* digits so that they can be used for calculating the initial */
5663    /* estimate. */
5664    needbytes=sizeof(decNumber)+(D2U(MAXI(p,16))-1)*sizeof(Unit);
5665    if (needbytes>sizeof(bufa)) {     /* need malloc space */
5666      allocbufa=(decNumber *)malloc(needbytes);
5667      if (allocbufa==NULL) {	      /* hopeless -- abandon */
5668	*status|=DEC_Insufficient_storage;
5669	break;}
5670      a=allocbufa;		      /* use the allocated space */
5671      }
5672    pp=p+rhs->digits;
5673    needbytes=sizeof(decNumber)+(D2U(MAXI(pp,16))-1)*sizeof(Unit);
5674    if (needbytes>sizeof(bufb)) {     /* need malloc space */
5675      allocbufb=(decNumber *)malloc(needbytes);
5676      if (allocbufb==NULL) {	      /* hopeless -- abandon */
5677	*status|=DEC_Insufficient_storage;
5678	break;}
5679      b=allocbufb;		      /* use the allocated space */
5680      }
5681
5682    /* Prepare an initial estimate in acc. Calculate this by */
5683    /* considering the coefficient of x to be a normalized fraction, */
5684    /* f, with the decimal point at far left and multiplied by */
5685    /* 10**r.  Then, rhs=f*10**r and 0.1<=f<1, and */
5686    /*	 ln(x) = ln(f) + ln(10)*r */
5687    /* Get the initial estimate for ln(f) from a small lookup */
5688    /* table (see above) indexed by the first two digits of f, */
5689    /* truncated. */
5690
5691    decContextDefault(&aset, DEC_INIT_DECIMAL64); /* 16-digit extended */
5692    r=rhs->exponent+rhs->digits;	/* 'normalised' exponent */
5693    decNumberFromInt32(a, r);		/* a=r */
5694    decNumberFromInt32(b, 2302585);	/* b=ln(10) (2.302585) */
5695    b->exponent=-6;			/*  .. */
5696    decMultiplyOp(a, a, b, &aset, &ignore);  /* a=a*b */
5697    /* now get top two digits of rhs into b by simple truncate and */
5698    /* force to integer */
5699    residue=0;				/* (no residue) */
5700    aset.digits=2; aset.round=DEC_ROUND_DOWN;
5701    decCopyFit(b, rhs, &aset, &residue, &ignore); /* copy & shorten */
5702    b->exponent=0;			/* make integer */
5703    t=decGetInt(b);			/* [cannot fail] */
5704    if (t<10) t=X10(t); 		/* adjust single-digit b */
5705    t=LNnn[t-10];			/* look up ln(b) */
5706    decNumberFromInt32(b, t>>2);	/* b=ln(b) coefficient */
5707    b->exponent=-(t&3)-3;		/* set exponent */
5708    b->bits=DECNEG;			/* ln(0.10)->ln(0.99) always -ve */
5709    aset.digits=16; aset.round=DEC_ROUND_HALF_EVEN; /* restore */
5710    decAddOp(a, a, b, &aset, 0, &ignore); /* acc=a+b */
5711    /* the initial estimate is now in a, with up to 4 digits correct. */
5712    /* When rhs is at or near Nmax the estimate will be low, so we */
5713    /* will approach it from below, avoiding overflow when calling exp. */
5714
5715    decNumberZero(&numone); *numone.lsu=1;   /* constant 1 for adjustment */
5716
5717    /* accumulator bounds are as requested (could underflow, but */
5718    /* cannot overflow) */
5719    aset.emax=set->emax;
5720    aset.emin=set->emin;
5721    aset.clamp=0;			/* no concrete format */
5722    /* set up a context to be used for the multiply and subtract */
5723    bset=aset;
5724    bset.emax=DEC_MAX_MATH*2;		/* use double bounds for the */
5725    bset.emin=-DEC_MAX_MATH*2;		/* adjustment calculation */
5726					/* [see decExpOp call below] */
5727    /* for each iteration double the number of digits to calculate, */
5728    /* up to a maximum of p */
5729    pp=9;				/* initial precision */
5730    /* [initially 9 as then the sequence starts 7+2, 16+2, and */
5731    /* 34+2, which is ideal for standard-sized numbers] */
5732    aset.digits=pp;			/* working context */
5733    bset.digits=pp+rhs->digits; 	/* wider context */
5734    for (;;) {				/* iterate */
5735      #if DECCHECK
5736      iterations++;
5737      if (iterations>24) break; 	/* consider 9 * 2**24 */
5738      #endif
5739      /* calculate the adjustment (exp(-a)*x-1) into b.  This is a */
5740      /* catastrophic subtraction but it really is the difference */
5741      /* from 1 that is of interest. */
5742      /* Use the internal entry point to Exp as it allows the double */
5743      /* range for calculating exp(-a) when a is the tiniest subnormal. */
5744      a->bits^=DECNEG;			/* make -a */
5745      decExpOp(b, a, &bset, &ignore);	/* b=exp(-a) */
5746      a->bits^=DECNEG;			/* restore sign of a */
5747      /* now multiply by rhs and subtract 1, at the wider precision */
5748      decMultiplyOp(b, b, rhs, &bset, &ignore);        /* b=b*rhs */
5749      decAddOp(b, b, &numone, &bset, DECNEG, &ignore); /* b=b-1 */
5750
5751      /* the iteration ends when the adjustment cannot affect the */
5752      /* result by >=0.5 ulp (at the requested digits), which */
5753      /* is when its value is smaller than the accumulator by */
5754      /* set->digits+1 digits (or it is zero) -- this is a looser */
5755      /* requirement than for Exp because all that happens to the */
5756      /* accumulator after this is the final rounding (but note that */
5757      /* there must also be full precision in a, or a=0). */
5758
5759      if (decNumberIsZero(b) ||
5760	  (a->digits+a->exponent)>=(b->digits+b->exponent+set->digits+1)) {
5761	if (a->digits==p) break;
5762	if (decNumberIsZero(a)) {
5763	  decCompareOp(&cmp, rhs, &numone, &aset, COMPARE, &ignore); /* rhs=1 ? */
5764	  if (cmp.lsu[0]==0) a->exponent=0;	       /* yes, exact 0 */
5765	   else *status|=(DEC_Inexact | DEC_Rounded);  /* no, inexact */
5766	  break;
5767	  }
5768	/* force padding if adjustment has gone to 0 before full length */
5769	if (decNumberIsZero(b)) b->exponent=a->exponent-p;
5770	}
5771
5772      /* not done yet ... */
5773      decAddOp(a, a, b, &aset, 0, &ignore);  /* a=a+b for next estimate */
5774      if (pp==p) continue;		     /* precision is at maximum */
5775      /* lengthen the next calculation */
5776      pp=pp*2;				     /* double precision */
5777      if (pp>p) pp=p;			     /* clamp to maximum */
5778      aset.digits=pp;			     /* working context */
5779      bset.digits=pp+rhs->digits;	     /* wider context */
5780      } /* Newton's iteration */
5781
5782    #if DECCHECK
5783    /* just a sanity check; remove the test to show always */
5784    if (iterations>24)
5785      printf("Ln iterations=%ld, status=%08lx, p=%ld, d=%ld\n",
5786	    (LI)iterations, (LI)*status, (LI)p, (LI)rhs->digits);
5787    #endif
5788
5789    /* Copy and round the result to res */
5790    residue=1;				/* indicate dirt to right */
5791    if (ISZERO(a)) residue=0;		/* .. unless underflowed to 0 */
5792    aset.digits=set->digits;		/* [use default rounding] */
5793    decCopyFit(res, a, &aset, &residue, status); /* copy & shorten */
5794    decFinish(res, set, &residue, status);	 /* cleanup/set flags */
5795    } while(0); 			/* end protected */
5796
5797  free(allocbufa); /* drop any storage used */
5798  free(allocbufb); /* .. */
5799  /* [status is handled by caller] */
5800  return res;
5801  } /* decLnOp */
5802
5803/* ------------------------------------------------------------------ */
5804/* decQuantizeOp  -- force exponent to requested value		      */
5805/*								      */
5806/*   This computes C = op(A, B), where op adjusts the coefficient     */
5807/*   of C (by rounding or shifting) such that the exponent (-scale)   */
5808/*   of C has the value B or matches the exponent of B. 	      */
5809/*   The numerical value of C will equal A, except for the effects of */
5810/*   any rounding that occurred.				      */
5811/*								      */
5812/*   res is C, the result.  C may be A or B			      */
5813/*   lhs is A, the number to adjust				      */
5814/*   rhs is B, the requested exponent				      */
5815/*   set is the context 					      */
5816/*   quant is 1 for quantize or 0 for rescale			      */
5817/*   status is the status accumulator (this can be called without     */
5818/*	    risk of control loss)				      */
5819/*								      */
5820/* C must have space for set->digits digits.			      */
5821/*								      */
5822/* Unless there is an error or the result is infinite, the exponent   */
5823/* after the operation is guaranteed to be that requested.	      */
5824/* ------------------------------------------------------------------ */
5825static decNumber * decQuantizeOp(decNumber *res, const decNumber *lhs,
5826				 const decNumber *rhs, decContext *set,
5827				 Flag quant, uInt *status) {
5828  #if DECSUBSET
5829  decNumber *alloclhs=NULL;	   /* non-NULL if rounded lhs allocated */
5830  decNumber *allocrhs=NULL;	   /* .., rhs */
5831  #endif
5832  const decNumber *inrhs=rhs;	   /* save original rhs */
5833  Int	reqdigits=set->digits;	   /* requested DIGITS */
5834  Int	reqexp; 		   /* requested exponent [-scale] */
5835  Int	residue=0;		   /* rounding residue */
5836  Int	etiny=set->emin-(reqdigits-1);
5837
5838  #if DECCHECK
5839  if (decCheckOperands(res, lhs, rhs, set)) return res;
5840  #endif
5841
5842  do {				   /* protect allocated storage */
5843    #if DECSUBSET
5844    if (!set->extended) {
5845      /* reduce operands and set lostDigits status, as needed */
5846      if (lhs->digits>reqdigits) {
5847	alloclhs=decRoundOperand(lhs, set, status);
5848	if (alloclhs==NULL) break;
5849	lhs=alloclhs;
5850	}
5851      if (rhs->digits>reqdigits) { /* [this only checks lostDigits] */
5852	allocrhs=decRoundOperand(rhs, set, status);
5853	if (allocrhs==NULL) break;
5854	rhs=allocrhs;
5855	}
5856      }
5857    #endif
5858    /* [following code does not require input rounding] */
5859
5860    /* Handle special values */
5861    if (SPECIALARGS) {
5862      /* NaNs get usual processing */
5863      if (SPECIALARGS & (DECSNAN | DECNAN))
5864	decNaNs(res, lhs, rhs, set, status);
5865      /* one infinity but not both is bad */
5866      else if ((lhs->bits ^ rhs->bits) & DECINF)
5867	*status|=DEC_Invalid_operation;
5868      /* both infinity: return lhs */
5869      else decNumberCopy(res, lhs);	     /* [nop if in place] */
5870      break;
5871      }
5872
5873    /* set requested exponent */
5874    if (quant) reqexp=inrhs->exponent;	/* quantize -- match exponents */
5875     else {				/* rescale -- use value of rhs */
5876      /* Original rhs must be an integer that fits and is in range, */
5877      /* which could be from -1999999997 to +999999999, thanks to */
5878      /* subnormals */
5879      reqexp=decGetInt(inrhs);		     /* [cannot fail] */
5880      }
5881
5882    #if DECSUBSET
5883    if (!set->extended) etiny=set->emin;     /* no subnormals */
5884    #endif
5885
5886    if (reqexp==BADINT			     /* bad (rescale only) or .. */
5887     || reqexp==BIGODD || reqexp==BIGEVEN    /* very big (ditto) or .. */
5888     || (reqexp<etiny)			     /* < lowest */
5889     || (reqexp>set->emax)) {		     /* > emax */
5890      *status|=DEC_Invalid_operation;
5891      break;}
5892
5893    /* the RHS has been processed, so it can be overwritten now if necessary */
5894    if (ISZERO(lhs)) {			     /* zero coefficient unchanged */
5895      decNumberCopy(res, lhs);		     /* [nop if in place] */
5896      res->exponent=reqexp;		     /* .. just set exponent */
5897      #if DECSUBSET
5898      if (!set->extended) res->bits=0;	     /* subset specification; no -0 */
5899      #endif
5900      }
5901     else {				     /* non-zero lhs */
5902      Int adjust=reqexp-lhs->exponent;	     /* digit adjustment needed */
5903      /* if adjusted coefficient will definitely not fit, give up now */
5904      if ((lhs->digits-adjust)>reqdigits) {
5905	*status|=DEC_Invalid_operation;
5906	break;
5907	}
5908
5909      if (adjust>0) {			     /* increasing exponent */
5910	/* this will decrease the length of the coefficient by adjust */
5911	/* digits, and must round as it does so */
5912	decContext workset;		     /* work */
5913	workset=*set;			     /* clone rounding, etc. */
5914	workset.digits=lhs->digits-adjust;   /* set requested length */
5915	/* [note that the latter can be <1, here] */
5916	decCopyFit(res, lhs, &workset, &residue, status); /* fit to result */
5917	decApplyRound(res, &workset, residue, status);	  /* .. and round */
5918	residue=0;					  /* [used] */
5919	/* If just rounded a 999s case, exponent will be off by one; */
5920	/* adjust back (after checking space), if so. */
5921	if (res->exponent>reqexp) {
5922	  /* re-check needed, e.g., for quantize(0.9999, 0.001) under */
5923	  /* set->digits==3 */
5924	  if (res->digits==reqdigits) {      /* cannot shift by 1 */
5925	    *status&=~(DEC_Inexact | DEC_Rounded); /* [clean these] */
5926	    *status|=DEC_Invalid_operation;
5927	    break;
5928	    }
5929	  res->digits=decShiftToMost(res->lsu, res->digits, 1); /* shift */
5930	  res->exponent--;		     /* (re)adjust the exponent. */
5931	  }
5932	#if DECSUBSET
5933	if (ISZERO(res) && !set->extended) res->bits=0; /* subset; no -0 */
5934	#endif
5935	} /* increase */
5936       else /* adjust<=0 */ {		     /* decreasing or = exponent */
5937	/* this will increase the length of the coefficient by -adjust */
5938	/* digits, by adding zero or more trailing zeros; this is */
5939	/* already checked for fit, above */
5940	decNumberCopy(res, lhs);	     /* [it will fit] */
5941	/* if padding needed (adjust<0), add it now... */
5942	if (adjust<0) {
5943	  res->digits=decShiftToMost(res->lsu, res->digits, -adjust);
5944	  res->exponent+=adjust;	     /* adjust the exponent */
5945	  }
5946	} /* decrease */
5947      } /* non-zero */
5948
5949    /* Check for overflow [do not use Finalize in this case, as an */
5950    /* overflow here is a "don't fit" situation] */
5951    if (res->exponent>set->emax-res->digits+1) {  /* too big */
5952      *status|=DEC_Invalid_operation;
5953      break;
5954      }
5955     else {
5956      decFinalize(res, set, &residue, status);	  /* set subnormal flags */
5957      *status&=~DEC_Underflow;		/* suppress Underflow [as per 754] */
5958      }
5959    } while(0); 			/* end protected */
5960
5961  #if DECSUBSET
5962  free(allocrhs);	/* drop any storage used */
5963  free(alloclhs);	/* .. */
5964  #endif
5965  return res;
5966  } /* decQuantizeOp */
5967
5968/* ------------------------------------------------------------------ */
5969/* decCompareOp -- compare, min, or max two Numbers		      */
5970/*								      */
5971/*   This computes C = A ? B and carries out one of four operations:  */
5972/*     COMPARE	  -- returns the signum (as a number) giving the      */
5973/*		     result of a comparison unless one or both	      */
5974/*		     operands is a NaN (in which case a NaN results)  */
5975/*     COMPSIG	  -- as COMPARE except that a quiet NaN raises	      */
5976/*		     Invalid operation. 			      */
5977/*     COMPMAX	  -- returns the larger of the operands, using the    */
5978/*		     754 maxnum operation			      */
5979/*     COMPMAXMAG -- ditto, comparing absolute values		      */
5980/*     COMPMIN	  -- the 754 minnum operation			      */
5981/*     COMPMINMAG -- ditto, comparing absolute values		      */
5982/*     COMTOTAL   -- returns the signum (as a number) giving the      */
5983/*		     result of a comparison using 754 total ordering  */
5984/*								      */
5985/*   res is C, the result.  C may be A and/or B (e.g., X=X?X)	      */
5986/*   lhs is A							      */
5987/*   rhs is B							      */
5988/*   set is the context 					      */
5989/*   op  is the operation flag					      */
5990/*   status is the usual accumulator				      */
5991/*								      */
5992/* C must have space for one digit for COMPARE or set->digits for     */
5993/* COMPMAX, COMPMIN, COMPMAXMAG, or COMPMINMAG. 		      */
5994/* ------------------------------------------------------------------ */
5995/* The emphasis here is on speed for common cases, and avoiding       */
5996/* coefficient comparison if possible.				      */
5997/* ------------------------------------------------------------------ */
5998decNumber * decCompareOp(decNumber *res, const decNumber *lhs,
5999			 const decNumber *rhs, decContext *set,
6000			 Flag op, uInt *status) {
6001  #if DECSUBSET
6002  decNumber *alloclhs=NULL;	   /* non-NULL if rounded lhs allocated */
6003  decNumber *allocrhs=NULL;	   /* .., rhs */
6004  #endif
6005  Int	result=0;		   /* default result value */
6006  uByte merged; 		   /* work */
6007
6008  #if DECCHECK
6009  if (decCheckOperands(res, lhs, rhs, set)) return res;
6010  #endif
6011
6012  do {				   /* protect allocated storage */
6013    #if DECSUBSET
6014    if (!set->extended) {
6015      /* reduce operands and set lostDigits status, as needed */
6016      if (lhs->digits>set->digits) {
6017	alloclhs=decRoundOperand(lhs, set, status);
6018	if (alloclhs==NULL) {result=BADINT; break;}
6019	lhs=alloclhs;
6020	}
6021      if (rhs->digits>set->digits) {
6022	allocrhs=decRoundOperand(rhs, set, status);
6023	if (allocrhs==NULL) {result=BADINT; break;}
6024	rhs=allocrhs;
6025	}
6026      }
6027    #endif
6028    /* [following code does not require input rounding] */
6029
6030    /* If total ordering then handle differing signs 'up front' */
6031    if (op==COMPTOTAL) {		/* total ordering */
6032      if (decNumberIsNegative(lhs) & !decNumberIsNegative(rhs)) {
6033	result=-1;
6034	break;
6035	}
6036      if (!decNumberIsNegative(lhs) & decNumberIsNegative(rhs)) {
6037	result=+1;
6038	break;
6039	}
6040      }
6041
6042    /* handle NaNs specially; let infinities drop through */
6043    /* This assumes sNaN (even just one) leads to NaN. */
6044    merged=(lhs->bits | rhs->bits) & (DECSNAN | DECNAN);
6045    if (merged) {			/* a NaN bit set */
6046      if (op==COMPARE); 		/* result will be NaN */
6047       else if (op==COMPSIG)		/* treat qNaN as sNaN */
6048	*status|=DEC_Invalid_operation | DEC_sNaN;
6049       else if (op==COMPTOTAL) {	/* total ordering, always finite */
6050	/* signs are known to be the same; compute the ordering here */
6051	/* as if the signs are both positive, then invert for negatives */
6052	if (!decNumberIsNaN(lhs)) result=-1;
6053	 else if (!decNumberIsNaN(rhs)) result=+1;
6054	 /* here if both NaNs */
6055	 else if (decNumberIsSNaN(lhs) && decNumberIsQNaN(rhs)) result=-1;
6056	 else if (decNumberIsQNaN(lhs) && decNumberIsSNaN(rhs)) result=+1;
6057	 else { /* both NaN or both sNaN */
6058	  /* now it just depends on the payload */
6059	  result=decUnitCompare(lhs->lsu, D2U(lhs->digits),
6060				rhs->lsu, D2U(rhs->digits), 0);
6061	  /* [Error not possible, as these are 'aligned'] */
6062	  } /* both same NaNs */
6063	if (decNumberIsNegative(lhs)) result=-result;
6064	break;
6065	} /* total order */
6066
6067       else if (merged & DECSNAN);	     /* sNaN -> qNaN */
6068       else { /* here if MIN or MAX and one or two quiet NaNs */
6069	/* min or max -- 754 rules ignore single NaN */
6070	if (!decNumberIsNaN(lhs) || !decNumberIsNaN(rhs)) {
6071	  /* just one NaN; force choice to be the non-NaN operand */
6072	  op=COMPMAX;
6073	  if (lhs->bits & DECNAN) result=-1; /* pick rhs */
6074			     else result=+1; /* pick lhs */
6075	  break;
6076	  }
6077	} /* max or min */
6078      op=COMPNAN;			     /* use special path */
6079      decNaNs(res, lhs, rhs, set, status);   /* propagate NaN */
6080      break;
6081      }
6082    /* have numbers */
6083    if (op==COMPMAXMAG || op==COMPMINMAG) result=decCompare(lhs, rhs, 1);
6084     else result=decCompare(lhs, rhs, 0);    /* sign matters */
6085    } while(0); 			     /* end protected */
6086
6087  if (result==BADINT) *status|=DEC_Insufficient_storage; /* rare */
6088   else {
6089    if (op==COMPARE || op==COMPSIG ||op==COMPTOTAL) { /* returning signum */
6090      if (op==COMPTOTAL && result==0) {
6091	/* operands are numerically equal or same NaN (and same sign, */
6092	/* tested first); if identical, leave result 0 */
6093	if (lhs->exponent!=rhs->exponent) {
6094	  if (lhs->exponent<rhs->exponent) result=-1;
6095	   else result=+1;
6096	  if (decNumberIsNegative(lhs)) result=-result;
6097	  } /* lexp!=rexp */
6098	} /* total-order by exponent */
6099      decNumberZero(res);		/* [always a valid result] */
6100      if (result!=0) {			/* must be -1 or +1 */
6101	*res->lsu=1;
6102	if (result<0) res->bits=DECNEG;
6103	}
6104      }
6105     else if (op==COMPNAN);		/* special, drop through */
6106     else {				/* MAX or MIN, non-NaN result */
6107      Int residue=0;			/* rounding accumulator */
6108      /* choose the operand for the result */
6109      const decNumber *choice;
6110      if (result==0) { /* operands are numerically equal */
6111	/* choose according to sign then exponent (see 754) */
6112	uByte slhs=(lhs->bits & DECNEG);
6113	uByte srhs=(rhs->bits & DECNEG);
6114	#if DECSUBSET
6115	if (!set->extended) {		/* subset: force left-hand */
6116	  op=COMPMAX;
6117	  result=+1;
6118	  }
6119	else
6120	#endif
6121	if (slhs!=srhs) {	   /* signs differ */
6122	  if (slhs) result=-1;	   /* rhs is max */
6123	       else result=+1;	   /* lhs is max */
6124	  }
6125	 else if (slhs && srhs) {  /* both negative */
6126	  if (lhs->exponent<rhs->exponent) result=+1;
6127				      else result=-1;
6128	  /* [if equal, use lhs, technically identical] */
6129	  }
6130	 else { 		   /* both positive */
6131	  if (lhs->exponent>rhs->exponent) result=+1;
6132				      else result=-1;
6133	  /* [ditto] */
6134	  }
6135	} /* numerically equal */
6136      /* here result will be non-0; reverse if looking for MIN */
6137      if (op==COMPMIN || op==COMPMINMAG) result=-result;
6138      choice=(result>0 ? lhs : rhs);	/* choose */
6139      /* copy chosen to result, rounding if need be */
6140      decCopyFit(res, choice, set, &residue, status);
6141      decFinish(res, set, &residue, status);
6142      }
6143    }
6144  #if DECSUBSET
6145  free(allocrhs);	/* free any storage used */
6146  free(alloclhs);	/* .. */
6147  #endif
6148  return res;
6149  } /* decCompareOp */
6150
6151/* ------------------------------------------------------------------ */
6152/* decCompare -- compare two decNumbers by numerical value	      */
6153/*								      */
6154/*  This routine compares A ? B without altering them.		      */
6155/*								      */
6156/*  Arg1 is A, a decNumber which is not a NaN			      */
6157/*  Arg2 is B, a decNumber which is not a NaN			      */
6158/*  Arg3 is 1 for a sign-independent compare, 0 otherwise	      */
6159/*								      */
6160/*  returns -1, 0, or 1 for A<B, A==B, or A>B, or BADINT if failure   */
6161/*  (the only possible failure is an allocation error)		      */
6162/* ------------------------------------------------------------------ */
6163static Int decCompare(const decNumber *lhs, const decNumber *rhs,
6164		      Flag abs) {
6165  Int	result; 		   /* result value */
6166  Int	sigr;			   /* rhs signum */
6167  Int	compare;		   /* work */
6168
6169  result=1;				     /* assume signum(lhs) */
6170  if (ISZERO(lhs)) result=0;
6171  if (abs) {
6172    if (ISZERO(rhs)) return result;	     /* LHS wins or both 0 */
6173    /* RHS is non-zero */
6174    if (result==0) return -1;		     /* LHS is 0; RHS wins */
6175    /* [here, both non-zero, result=1] */
6176    }
6177   else {				     /* signs matter */
6178    if (result && decNumberIsNegative(lhs)) result=-1;
6179    sigr=1;				     /* compute signum(rhs) */
6180    if (ISZERO(rhs)) sigr=0;
6181     else if (decNumberIsNegative(rhs)) sigr=-1;
6182    if (result > sigr) return +1;	     /* L > R, return 1 */
6183    if (result < sigr) return -1;	     /* L < R, return -1 */
6184    if (result==0) return 0;		       /* both 0 */
6185    }
6186
6187  /* signums are the same; both are non-zero */
6188  if ((lhs->bits | rhs->bits) & DECINF) {    /* one or more infinities */
6189    if (decNumberIsInfinite(rhs)) {
6190      if (decNumberIsInfinite(lhs)) result=0;/* both infinite */
6191       else result=-result;		     /* only rhs infinite */
6192      }
6193    return result;
6194    }
6195  /* must compare the coefficients, allowing for exponents */
6196  if (lhs->exponent>rhs->exponent) {	     /* LHS exponent larger */
6197    /* swap sides, and sign */
6198    const decNumber *temp=lhs;
6199    lhs=rhs;
6200    rhs=temp;
6201    result=-result;
6202    }
6203  compare=decUnitCompare(lhs->lsu, D2U(lhs->digits),
6204			 rhs->lsu, D2U(rhs->digits),
6205			 rhs->exponent-lhs->exponent);
6206  if (compare!=BADINT) compare*=result;      /* comparison succeeded */
6207  return compare;
6208  } /* decCompare */
6209
6210/* ------------------------------------------------------------------ */
6211/* decUnitCompare -- compare two >=0 integers in Unit arrays	      */
6212/*								      */
6213/*  This routine compares A ? B*10**E where A and B are unit arrays   */
6214/*  A is a plain integer					      */
6215/*  B has an exponent of E (which must be non-negative) 	      */
6216/*								      */
6217/*  Arg1 is A first Unit (lsu)					      */
6218/*  Arg2 is A length in Units					      */
6219/*  Arg3 is B first Unit (lsu)					      */
6220/*  Arg4 is B length in Units					      */
6221/*  Arg5 is E (0 if the units are aligned)			      */
6222/*								      */
6223/*  returns -1, 0, or 1 for A<B, A==B, or A>B, or BADINT if failure   */
6224/*  (the only possible failure is an allocation error, which can      */
6225/*  only occur if E!=0) 					      */
6226/* ------------------------------------------------------------------ */
6227static Int decUnitCompare(const Unit *a, Int alength,
6228			  const Unit *b, Int blength, Int exp) {
6229  Unit	*acc;			   /* accumulator for result */
6230  Unit	accbuff[SD2U(DECBUFFER*2+1)]; /* local buffer */
6231  Unit	*allocacc=NULL; 	   /* -> allocated acc buffer, iff allocated */
6232  Int	accunits, need; 	   /* units in use or needed for acc */
6233  const Unit *l, *r, *u;	   /* work */
6234  Int	expunits, exprem, result;  /* .. */
6235
6236  if (exp==0) { 		   /* aligned; fastpath */
6237    if (alength>blength) return 1;
6238    if (alength<blength) return -1;
6239    /* same number of units in both -- need unit-by-unit compare */
6240    l=a+alength-1;
6241    r=b+alength-1;
6242    for (;l>=a; l--, r--) {
6243      if (*l>*r) return 1;
6244      if (*l<*r) return -1;
6245      }
6246    return 0;			   /* all units match */
6247    } /* aligned */
6248
6249  /* Unaligned.  If one is >1 unit longer than the other, padded */
6250  /* approximately, then can return easily */
6251  if (alength>blength+(Int)D2U(exp)) return 1;
6252  if (alength+1<blength+(Int)D2U(exp)) return -1;
6253
6254  /* Need to do a real subtract.  For this, a result buffer is needed */
6255  /* even though only the sign is of interest.	Its length needs */
6256  /* to be the larger of alength and padded blength, +2 */
6257  need=blength+D2U(exp);		/* maximum real length of B */
6258  if (need<alength) need=alength;
6259  need+=2;
6260  acc=accbuff;				/* assume use local buffer */
6261  if (need*sizeof(Unit)>sizeof(accbuff)) {
6262    allocacc=(Unit *)malloc(need*sizeof(Unit));
6263    if (allocacc==NULL) return BADINT;	/* hopeless -- abandon */
6264    acc=allocacc;
6265    }
6266  /* Calculate units and remainder from exponent. */
6267  expunits=exp/DECDPUN;
6268  exprem=exp%DECDPUN;
6269  /* subtract [A+B*(-m)] */
6270  accunits=decUnitAddSub(a, alength, b, blength, expunits, acc,
6271			 -(Int)powers[exprem]);
6272  /* [UnitAddSub result may have leading zeros, even on zero] */
6273  if (accunits<0) result=-1;		/* negative result */
6274   else {				/* non-negative result */
6275    /* check units of the result before freeing any storage */
6276    for (u=acc; u<acc+accunits-1 && *u==0;) u++;
6277    result=(*u==0 ? 0 : +1);
6278    }
6279  /* clean up and return the result */
6280  free(allocacc);	/* drop any storage used */
6281  return result;
6282  } /* decUnitCompare */
6283
6284/* ------------------------------------------------------------------ */
6285/* decUnitAddSub -- add or subtract two >=0 integers in Unit arrays   */
6286/*								      */
6287/*  This routine performs the calculation:			      */
6288/*								      */
6289/*  C=A+(B*M)							      */
6290/*								      */
6291/*  Where M is in the range -DECDPUNMAX through +DECDPUNMAX.	      */
6292/*								      */
6293/*  A may be shorter or longer than B.				      */
6294/*								      */
6295/*  Leading zeros are not removed after a calculation.	The result is */
6296/*  either the same length as the longer of A and B (adding any       */
6297/*  shift), or one Unit longer than that (if a Unit carry occurred).  */
6298/*								      */
6299/*  A and B content are not altered unless C is also A or B.	      */
6300/*  C may be the same array as A or B, but only if no zero padding is */
6301/*  requested (that is, C may be B only if bshift==0).		      */
6302/*  C is filled from the lsu; only those units necessary to complete  */
6303/*  the calculation are referenced.				      */
6304/*								      */
6305/*  Arg1 is A first Unit (lsu)					      */
6306/*  Arg2 is A length in Units					      */
6307/*  Arg3 is B first Unit (lsu)					      */
6308/*  Arg4 is B length in Units					      */
6309/*  Arg5 is B shift in Units  (>=0; pads with 0 units if positive)    */
6310/*  Arg6 is C first Unit (lsu)					      */
6311/*  Arg7 is M, the multiplier					      */
6312/*								      */
6313/*  returns the count of Units written to C, which will be non-zero   */
6314/*  and negated if the result is negative.  That is, the sign of the  */
6315/*  returned Int is the sign of the result (positive for zero) and    */
6316/*  the absolute value of the Int is the count of Units.	      */
6317/*								      */
6318/*  It is the caller's responsibility to make sure that C size is     */
6319/*  safe, allowing space if necessary for a one-Unit carry.	      */
6320/*								      */
6321/*  This routine is severely performance-critical; *any* change here  */
6322/*  must be measured (timed) to assure no performance degradation.    */
6323/*  In particular, trickery here tends to be counter-productive, as   */
6324/*  increased complexity of code hurts register optimizations on      */
6325/*  register-poor architectures.  Avoiding divisions is nearly	      */
6326/*  always a Good Idea, however.				      */
6327/*								      */
6328/* Special thanks to Rick McGuire (IBM Cambridge, MA) and Dave Clark  */
6329/* (IBM Warwick, UK) for some of the ideas used in this routine.      */
6330/* ------------------------------------------------------------------ */
6331static Int decUnitAddSub(const Unit *a, Int alength,
6332			 const Unit *b, Int blength, Int bshift,
6333			 Unit *c, Int m) {
6334  const Unit *alsu=a;		   /* A lsu [need to remember it] */
6335  Unit *clsu=c; 		   /* C ditto */
6336  Unit *minC;			   /* low water mark for C */
6337  Unit *maxC;			   /* high water mark for C */
6338  eInt carry=0; 		   /* carry integer (could be Long) */
6339  Int  add;			   /* work */
6340  #if DECDPUN<=4		   /* myriadal, millenary, etc. */
6341  Int  est;			   /* estimated quotient */
6342  #endif
6343
6344  #if DECTRACE
6345  if (alength<1 || blength<1)
6346    printf("decUnitAddSub: alen blen m %ld %ld [%ld]\n", alength, blength, m);
6347  #endif
6348
6349  maxC=c+alength;		   /* A is usually the longer */
6350  minC=c+blength;		   /* .. and B the shorter */
6351  if (bshift!=0) {		   /* B is shifted; low As copy across */
6352    minC+=bshift;
6353    /* if in place [common], skip copy unless there's a gap [rare] */
6354    if (a==c && bshift<=alength) {
6355      c+=bshift;
6356      a+=bshift;
6357      }
6358     else for (; c<clsu+bshift; a++, c++) {  /* copy needed */
6359      if (a<alsu+alength) *c=*a;
6360       else *c=0;
6361      }
6362    }
6363  if (minC>maxC) { /* swap */
6364    Unit *hold=minC;
6365    minC=maxC;
6366    maxC=hold;
6367    }
6368
6369  /* For speed, do the addition as two loops; the first where both A */
6370  /* and B contribute, and the second (if necessary) where only one or */
6371  /* other of the numbers contribute. */
6372  /* Carry handling is the same (i.e., duplicated) in each case. */
6373  for (; c<minC; c++) {
6374    carry+=*a;
6375    a++;
6376    carry+=((eInt)*b)*m;		/* [special-casing m=1/-1 */
6377    b++;				/* here is not a win] */
6378    /* here carry is new Unit of digits; it could be +ve or -ve */
6379    if ((ueInt)carry<=DECDPUNMAX) {	/* fastpath 0-DECDPUNMAX */
6380      *c=(Unit)carry;
6381      carry=0;
6382      continue;
6383      }
6384    #if DECDPUN==4			     /* use divide-by-multiply */
6385      if (carry>=0) {
6386	est=(((ueInt)carry>>11)*53687)>>18;
6387	*c=(Unit)(carry-est*(DECDPUNMAX+1)); /* remainder */
6388	carry=est;			     /* likely quotient [89%] */
6389	if (*c<DECDPUNMAX+1) continue;	     /* estimate was correct */
6390	carry++;
6391	*c-=DECDPUNMAX+1;
6392	continue;
6393	}
6394      /* negative case */
6395      carry=carry+(eInt)(DECDPUNMAX+1)*(DECDPUNMAX+1); /* make positive */
6396      est=(((ueInt)carry>>11)*53687)>>18;
6397      *c=(Unit)(carry-est*(DECDPUNMAX+1));
6398      carry=est-(DECDPUNMAX+1); 	     /* correctly negative */
6399      if (*c<DECDPUNMAX+1) continue;	     /* was OK */
6400      carry++;
6401      *c-=DECDPUNMAX+1;
6402    #elif DECDPUN==3
6403      if (carry>=0) {
6404	est=(((ueInt)carry>>3)*16777)>>21;
6405	*c=(Unit)(carry-est*(DECDPUNMAX+1)); /* remainder */
6406	carry=est;			     /* likely quotient [99%] */
6407	if (*c<DECDPUNMAX+1) continue;	     /* estimate was correct */
6408	carry++;
6409	*c-=DECDPUNMAX+1;
6410	continue;
6411	}
6412      /* negative case */
6413      carry=carry+(eInt)(DECDPUNMAX+1)*(DECDPUNMAX+1); /* make positive */
6414      est=(((ueInt)carry>>3)*16777)>>21;
6415      *c=(Unit)(carry-est*(DECDPUNMAX+1));
6416      carry=est-(DECDPUNMAX+1); 	     /* correctly negative */
6417      if (*c<DECDPUNMAX+1) continue;	     /* was OK */
6418      carry++;
6419      *c-=DECDPUNMAX+1;
6420    #elif DECDPUN<=2
6421      /* Can use QUOT10 as carry <= 4 digits */
6422      if (carry>=0) {
6423	est=QUOT10(carry, DECDPUN);
6424	*c=(Unit)(carry-est*(DECDPUNMAX+1)); /* remainder */
6425	carry=est;			     /* quotient */
6426	continue;
6427	}
6428      /* negative case */
6429      carry=carry+(eInt)(DECDPUNMAX+1)*(DECDPUNMAX+1); /* make positive */
6430      est=QUOT10(carry, DECDPUN);
6431      *c=(Unit)(carry-est*(DECDPUNMAX+1));
6432      carry=est-(DECDPUNMAX+1); 	     /* correctly negative */
6433    #else
6434      /* remainder operator is undefined if negative, so must test */
6435      if ((ueInt)carry<(DECDPUNMAX+1)*2) {   /* fastpath carry +1 */
6436	*c=(Unit)(carry-(DECDPUNMAX+1));     /* [helps additions] */
6437	carry=1;
6438	continue;
6439	}
6440      if (carry>=0) {
6441	*c=(Unit)(carry%(DECDPUNMAX+1));
6442	carry=carry/(DECDPUNMAX+1);
6443	continue;
6444	}
6445      /* negative case */
6446      carry=carry+(eInt)(DECDPUNMAX+1)*(DECDPUNMAX+1); /* make positive */
6447      *c=(Unit)(carry%(DECDPUNMAX+1));
6448      carry=carry/(DECDPUNMAX+1)-(DECDPUNMAX+1);
6449    #endif
6450    } /* c */
6451
6452  /* now may have one or other to complete */
6453  /* [pretest to avoid loop setup/shutdown] */
6454  if (c<maxC) for (; c<maxC; c++) {
6455    if (a<alsu+alength) {		/* still in A */
6456      carry+=*a;
6457      a++;
6458      }
6459     else {				/* inside B */
6460      carry+=((eInt)*b)*m;
6461      b++;
6462      }
6463    /* here carry is new Unit of digits; it could be +ve or -ve and */
6464    /* magnitude up to DECDPUNMAX squared */
6465    if ((ueInt)carry<=DECDPUNMAX) {	/* fastpath 0-DECDPUNMAX */
6466      *c=(Unit)carry;
6467      carry=0;
6468      continue;
6469      }
6470    /* result for this unit is negative or >DECDPUNMAX */
6471    #if DECDPUN==4			     /* use divide-by-multiply */
6472      if (carry>=0) {
6473	est=(((ueInt)carry>>11)*53687)>>18;
6474	*c=(Unit)(carry-est*(DECDPUNMAX+1)); /* remainder */
6475	carry=est;			     /* likely quotient [79.7%] */
6476	if (*c<DECDPUNMAX+1) continue;	     /* estimate was correct */
6477	carry++;
6478	*c-=DECDPUNMAX+1;
6479	continue;
6480	}
6481      /* negative case */
6482      carry=carry+(eInt)(DECDPUNMAX+1)*(DECDPUNMAX+1); /* make positive */
6483      est=(((ueInt)carry>>11)*53687)>>18;
6484      *c=(Unit)(carry-est*(DECDPUNMAX+1));
6485      carry=est-(DECDPUNMAX+1); 	     /* correctly negative */
6486      if (*c<DECDPUNMAX+1) continue;	     /* was OK */
6487      carry++;
6488      *c-=DECDPUNMAX+1;
6489    #elif DECDPUN==3
6490      if (carry>=0) {
6491	est=(((ueInt)carry>>3)*16777)>>21;
6492	*c=(Unit)(carry-est*(DECDPUNMAX+1)); /* remainder */
6493	carry=est;			     /* likely quotient [99%] */
6494	if (*c<DECDPUNMAX+1) continue;	     /* estimate was correct */
6495	carry++;
6496	*c-=DECDPUNMAX+1;
6497	continue;
6498	}
6499      /* negative case */
6500      carry=carry+(eInt)(DECDPUNMAX+1)*(DECDPUNMAX+1); /* make positive */
6501      est=(((ueInt)carry>>3)*16777)>>21;
6502      *c=(Unit)(carry-est*(DECDPUNMAX+1));
6503      carry=est-(DECDPUNMAX+1); 	     /* correctly negative */
6504      if (*c<DECDPUNMAX+1) continue;	     /* was OK */
6505      carry++;
6506      *c-=DECDPUNMAX+1;
6507    #elif DECDPUN<=2
6508      if (carry>=0) {
6509	est=QUOT10(carry, DECDPUN);
6510	*c=(Unit)(carry-est*(DECDPUNMAX+1)); /* remainder */
6511	carry=est;			     /* quotient */
6512	continue;
6513	}
6514      /* negative case */
6515      carry=carry+(eInt)(DECDPUNMAX+1)*(DECDPUNMAX+1); /* make positive */
6516      est=QUOT10(carry, DECDPUN);
6517      *c=(Unit)(carry-est*(DECDPUNMAX+1));
6518      carry=est-(DECDPUNMAX+1); 	     /* correctly negative */
6519    #else
6520      if ((ueInt)carry<(DECDPUNMAX+1)*2){    /* fastpath carry 1 */
6521	*c=(Unit)(carry-(DECDPUNMAX+1));
6522	carry=1;
6523	continue;
6524	}
6525      /* remainder operator is undefined if negative, so must test */
6526      if (carry>=0) {
6527	*c=(Unit)(carry%(DECDPUNMAX+1));
6528	carry=carry/(DECDPUNMAX+1);
6529	continue;
6530	}
6531      /* negative case */
6532      carry=carry+(eInt)(DECDPUNMAX+1)*(DECDPUNMAX+1); /* make positive */
6533      *c=(Unit)(carry%(DECDPUNMAX+1));
6534      carry=carry/(DECDPUNMAX+1)-(DECDPUNMAX+1);
6535    #endif
6536    } /* c */
6537
6538  /* OK, all A and B processed; might still have carry or borrow */
6539  /* return number of Units in the result, negated if a borrow */
6540  if (carry==0) return c-clsu;	   /* no carry, so no more to do */
6541  if (carry>0) {		   /* positive carry */
6542    *c=(Unit)carry;		   /* place as new unit */
6543    c++;			   /* .. */
6544    return c-clsu;
6545    }
6546  /* -ve carry: it's a borrow; complement needed */
6547  add=1;			   /* temporary carry... */
6548  for (c=clsu; c<maxC; c++) {
6549    add=DECDPUNMAX+add-*c;
6550    if (add<=DECDPUNMAX) {
6551      *c=(Unit)add;
6552      add=0;
6553      }
6554     else {
6555      *c=0;
6556      add=1;
6557      }
6558    }
6559  /* add an extra unit iff it would be non-zero */
6560  #if DECTRACE
6561    printf("UAS borrow: add %ld, carry %ld\n", add, carry);
6562  #endif
6563  if ((add-carry-1)!=0) {
6564    *c=(Unit)(add-carry-1);
6565    c++;		      /* interesting, include it */
6566    }
6567  return clsu-c;	      /* -ve result indicates borrowed */
6568  } /* decUnitAddSub */
6569
6570/* ------------------------------------------------------------------ */
6571/* decTrim -- trim trailing zeros or normalize			      */
6572/*								      */
6573/*   dn is the number to trim or normalize			      */
6574/*   set is the context to use to check for clamp		      */
6575/*   all is 1 to remove all trailing zeros, 0 for just fraction ones  */
6576/*   noclamp is 1 to unconditional (unclamped) trim		      */
6577/*   dropped returns the number of discarded trailing zeros	      */
6578/*   returns dn 						      */
6579/*								      */
6580/* If clamp is set in the context then the number of zeros trimmed    */
6581/* may be limited if the exponent is high.			      */
6582/* All fields are updated as required.	This is a utility operation,  */
6583/* so special values are unchanged and no error is possible.	      */
6584/* ------------------------------------------------------------------ */
6585static decNumber * decTrim(decNumber *dn, decContext *set, Flag all,
6586			   Flag noclamp, Int *dropped) {
6587  Int	d, exp; 		   /* work */
6588  uInt	cut;			   /* .. */
6589  Unit	*up;			   /* -> current Unit */
6590
6591  #if DECCHECK
6592  if (decCheckOperands(dn, DECUNUSED, DECUNUSED, DECUNCONT)) return dn;
6593  #endif
6594
6595  *dropped=0;				/* assume no zeros dropped */
6596  if ((dn->bits & DECSPECIAL)		/* fast exit if special .. */
6597    || (*dn->lsu & 0x01)) return dn;	/* .. or odd */
6598  if (ISZERO(dn)) {			/* .. or 0 */
6599    dn->exponent=0;			/* (sign is preserved) */
6600    return dn;
6601    }
6602
6603  /* have a finite number which is even */
6604  exp=dn->exponent;
6605  cut=1;			   /* digit (1-DECDPUN) in Unit */
6606  up=dn->lsu;			   /* -> current Unit */
6607  for (d=0; d<dn->digits-1; d++) { /* [don't strip the final digit] */
6608    /* slice by powers */
6609    #if DECDPUN<=4
6610      uInt quot=QUOT10(*up, cut);
6611      if ((*up-quot*powers[cut])!=0) break;  /* found non-0 digit */
6612    #else
6613      if (*up%powers[cut]!=0) break;	     /* found non-0 digit */
6614    #endif
6615    /* have a trailing 0 */
6616    if (!all) { 		   /* trimming */
6617      /* [if exp>0 then all trailing 0s are significant for trim] */
6618      if (exp<=0) {		   /* if digit might be significant */
6619	if (exp==0) break;	   /* then quit */
6620	exp++;			   /* next digit might be significant */
6621	}
6622      }
6623    cut++;			   /* next power */
6624    if (cut>DECDPUN) {		   /* need new Unit */
6625      up++;
6626      cut=1;
6627      }
6628    } /* d */
6629  if (d==0) return dn;		   /* none to drop */
6630
6631  /* may need to limit drop if clamping */
6632  if (set->clamp && !noclamp) {
6633    Int maxd=set->emax-set->digits+1-dn->exponent;
6634    if (maxd<=0) return dn;	   /* nothing possible */
6635    if (d>maxd) d=maxd;
6636    }
6637
6638  /* effect the drop */
6639  decShiftToLeast(dn->lsu, D2U(dn->digits), d);
6640  dn->exponent+=d;		   /* maintain numerical value */
6641  dn->digits-=d;		   /* new length */
6642  *dropped=d;			   /* report the count */
6643  return dn;
6644  } /* decTrim */
6645
6646/* ------------------------------------------------------------------ */
6647/* decReverse -- reverse a Unit array in place			      */
6648/*								      */
6649/*   ulo    is the start of the array				      */
6650/*   uhi    is the end of the array (highest Unit to include)	      */
6651/*								      */
6652/* The units ulo through uhi are reversed in place (if the number     */
6653/* of units is odd, the middle one is untouched).  Note that the      */
6654/* digit(s) in each unit are unaffected.			      */
6655/* ------------------------------------------------------------------ */
6656static void decReverse(Unit *ulo, Unit *uhi) {
6657  Unit temp;
6658  for (; ulo<uhi; ulo++, uhi--) {
6659    temp=*ulo;
6660    *ulo=*uhi;
6661    *uhi=temp;
6662    }
6663  return;
6664  } /* decReverse */
6665
6666/* ------------------------------------------------------------------ */
6667/* decShiftToMost -- shift digits in array towards most significant   */
6668/*								      */
6669/*   uar    is the array					      */
6670/*   digits is the count of digits in use in the array		      */
6671/*   shift  is the number of zeros to pad with (least significant);   */
6672/*     it must be zero or positive				      */
6673/*								      */
6674/*   returns the new length of the integer in the array, in digits    */
6675/*								      */
6676/* No overflow is permitted (that is, the uar array must be known to  */
6677/* be large enough to hold the result, after shifting). 	      */
6678/* ------------------------------------------------------------------ */
6679static Int decShiftToMost(Unit *uar, Int digits, Int shift) {
6680  Unit	*target, *source, *first;  /* work */
6681  Int	cut;			   /* odd 0's to add */
6682  uInt	next;			   /* work */
6683
6684  if (shift==0) return digits;	   /* [fastpath] nothing to do */
6685  if ((digits+shift)<=DECDPUN) {   /* [fastpath] single-unit case */
6686    *uar=(Unit)(*uar*powers[shift]);
6687    return digits+shift;
6688    }
6689
6690  next=0;			   /* all paths */
6691  source=uar+D2U(digits)-1;	   /* where msu comes from */
6692  target=source+D2U(shift);	   /* where upper part of first cut goes */
6693  cut=DECDPUN-MSUDIGITS(shift);    /* where to slice */
6694  if (cut==0) { 		   /* unit-boundary case */
6695    for (; source>=uar; source--, target--) *target=*source;
6696    }
6697   else {
6698    first=uar+D2U(digits+shift)-1; /* where msu of source will end up */
6699    for (; source>=uar; source--, target--) {
6700      /* split the source Unit and accumulate remainder for next */
6701      #if DECDPUN<=4
6702	uInt quot=QUOT10(*source, cut);
6703	uInt rem=*source-quot*powers[cut];
6704	next+=quot;
6705      #else
6706	uInt rem=*source%powers[cut];
6707	next+=*source/powers[cut];
6708      #endif
6709      if (target<=first) *target=(Unit)next;   /* write to target iff valid */
6710      next=rem*powers[DECDPUN-cut];	       /* save remainder for next Unit */
6711      }
6712    } /* shift-move */
6713
6714  /* propagate any partial unit to one below and clear the rest */
6715  for (; target>=uar; target--) {
6716    *target=(Unit)next;
6717    next=0;
6718    }
6719  return digits+shift;
6720  } /* decShiftToMost */
6721
6722/* ------------------------------------------------------------------ */
6723/* decShiftToLeast -- shift digits in array towards least significant */
6724/*								      */
6725/*   uar   is the array 					      */
6726/*   units is length of the array, in units			      */
6727/*   shift is the number of digits to remove from the lsu end; it     */
6728/*     must be zero or positive and <= than units*DECDPUN.	      */
6729/*								      */
6730/*   returns the new length of the integer in the array, in units     */
6731/*								      */
6732/* Removed digits are discarded (lost).  Units not required to hold   */
6733/* the final result are unchanged.				      */
6734/* ------------------------------------------------------------------ */
6735static Int decShiftToLeast(Unit *uar, Int units, Int shift) {
6736  Unit	*target, *up;		   /* work */
6737  Int	cut, count;		   /* work */
6738  Int	quot, rem;		   /* for division */
6739
6740  if (shift==0) return units;	   /* [fastpath] nothing to do */
6741  if (shift==units*DECDPUN) {	   /* [fastpath] little to do */
6742    *uar=0;			   /* all digits cleared gives zero */
6743    return 1;			   /* leaves just the one */
6744    }
6745
6746  target=uar;			   /* both paths */
6747  cut=MSUDIGITS(shift);
6748  if (cut==DECDPUN) {		   /* unit-boundary case; easy */
6749    up=uar+D2U(shift);
6750    for (; up<uar+units; target++, up++) *target=*up;
6751    return target-uar;
6752    }
6753
6754  /* messier */
6755  up=uar+D2U(shift-cut);	   /* source; correct to whole Units */
6756  count=units*DECDPUN-shift;	   /* the maximum new length */
6757  #if DECDPUN<=4
6758    quot=QUOT10(*up, cut);
6759  #else
6760    quot=*up/powers[cut];
6761  #endif
6762  for (; ; target++) {
6763    *target=(Unit)quot;
6764    count-=(DECDPUN-cut);
6765    if (count<=0) break;
6766    up++;
6767    quot=*up;
6768    #if DECDPUN<=4
6769      quot=QUOT10(quot, cut);
6770      rem=*up-quot*powers[cut];
6771    #else
6772      rem=quot%powers[cut];
6773      quot=quot/powers[cut];
6774    #endif
6775    *target=(Unit)(*target+rem*powers[DECDPUN-cut]);
6776    count-=cut;
6777    if (count<=0) break;
6778    }
6779  return target-uar+1;
6780  } /* decShiftToLeast */
6781
6782#if DECSUBSET
6783/* ------------------------------------------------------------------ */
6784/* decRoundOperand -- round an operand	[used for subset only]	      */
6785/*								      */
6786/*   dn is the number to round (dn->digits is > set->digits)	      */
6787/*   set is the relevant context				      */
6788/*   status is the status accumulator				      */
6789/*								      */
6790/*   returns an allocated decNumber with the rounded result.	      */
6791/*								      */
6792/* lostDigits and other status may be set by this.		      */
6793/*								      */
6794/* Since the input is an operand, it must not be modified.	      */
6795/* Instead, return an allocated decNumber, rounded as required.       */
6796/* It is the caller's responsibility to free the allocated storage.   */
6797/*								      */
6798/* If no storage is available then the result cannot be used, so NULL */
6799/* is returned. 						      */
6800/* ------------------------------------------------------------------ */
6801static decNumber *decRoundOperand(const decNumber *dn, decContext *set,
6802				  uInt *status) {
6803  decNumber *res;			/* result structure */
6804  uInt newstatus=0;			/* status from round */
6805  Int  residue=0;			/* rounding accumulator */
6806
6807  /* Allocate storage for the returned decNumber, big enough for the */
6808  /* length specified by the context */
6809  res=(decNumber *)malloc(sizeof(decNumber)
6810			  +(D2U(set->digits)-1)*sizeof(Unit));
6811  if (res==NULL) {
6812    *status|=DEC_Insufficient_storage;
6813    return NULL;
6814    }
6815  decCopyFit(res, dn, set, &residue, &newstatus);
6816  decApplyRound(res, set, residue, &newstatus);
6817
6818  /* If that set Inexact then "lost digits" is raised... */
6819  if (newstatus & DEC_Inexact) newstatus|=DEC_Lost_digits;
6820  *status|=newstatus;
6821  return res;
6822  } /* decRoundOperand */
6823#endif
6824
6825/* ------------------------------------------------------------------ */
6826/* decCopyFit -- copy a number, truncating the coefficient if needed  */
6827/*								      */
6828/*   dest is the target decNumber				      */
6829/*   src  is the source decNumber				      */
6830/*   set is the context [used for length (digits) and rounding mode]  */
6831/*   residue is the residue accumulator 			      */
6832/*   status contains the current status to be updated		      */
6833/*								      */
6834/* (dest==src is allowed and will be a no-op if fits)		      */
6835/* All fields are updated as required.				      */
6836/* ------------------------------------------------------------------ */
6837static void decCopyFit(decNumber *dest, const decNumber *src,
6838		       decContext *set, Int *residue, uInt *status) {
6839  dest->bits=src->bits;
6840  dest->exponent=src->exponent;
6841  decSetCoeff(dest, set, src->lsu, src->digits, residue, status);
6842  } /* decCopyFit */
6843
6844/* ------------------------------------------------------------------ */
6845/* decSetCoeff -- set the coefficient of a number		      */
6846/*								      */
6847/*   dn    is the number whose coefficient array is to be set.	      */
6848/*	   It must have space for set->digits digits		      */
6849/*   set   is the context [for size]				      */
6850/*   lsu   -> lsu of the source coefficient [may be dn->lsu]	      */
6851/*   len   is digits in the source coefficient [may be dn->digits]    */
6852/*   residue is the residue accumulator.  This has values as in       */
6853/*	   decApplyRound, and will be unchanged unless the	      */
6854/*	   target size is less than len.  In this case, the	      */
6855/*	   coefficient is truncated and the residue is updated to     */
6856/*	   reflect the previous residue and the dropped digits.       */
6857/*   status is the status accumulator, as usual 		      */
6858/*								      */
6859/* The coefficient may already be in the number, or it can be an      */
6860/* external intermediate array.  If it is in the number, lsu must ==  */
6861/* dn->lsu and len must == dn->digits.				      */
6862/*								      */
6863/* Note that the coefficient length (len) may be < set->digits, and   */
6864/* in this case this merely copies the coefficient (or is a no-op     */
6865/* if dn->lsu==lsu).						      */
6866/*								      */
6867/* Note also that (only internally, from decQuantizeOp and	      */
6868/* decSetSubnormal) the value of set->digits may be less than one,    */
6869/* indicating a round to left.	This routine handles that case	      */
6870/* correctly; caller ensures space.				      */
6871/*								      */
6872/* dn->digits, dn->lsu (and as required), and dn->exponent are	      */
6873/* updated as necessary.   dn->bits (sign) is unchanged.	      */
6874/*								      */
6875/* DEC_Rounded status is set if any digits are discarded.	      */
6876/* DEC_Inexact status is set if any non-zero digits are discarded, or */
6877/*			 incoming residue was non-0 (implies rounded) */
6878/* ------------------------------------------------------------------ */
6879/* mapping array: maps 0-9 to canonical residues, so that a residue */
6880/* can be adjusted in the range [-1, +1] and achieve correct rounding */
6881/*			       0  1  2	3  4  5  6  7  8  9 */
6882static const uByte resmap[10]={0, 3, 3, 3, 3, 5, 7, 7, 7, 7};
6883static void decSetCoeff(decNumber *dn, decContext *set, const Unit *lsu,
6884			Int len, Int *residue, uInt *status) {
6885  Int	discard;	      /* number of digits to discard */
6886  uInt	cut;		      /* cut point in Unit */
6887  const Unit *up;	      /* work */
6888  Unit	*target;	      /* .. */
6889  Int	count;		      /* .. */
6890  #if DECDPUN<=4
6891  uInt	temp;		      /* .. */
6892  #endif
6893
6894  discard=len-set->digits;    /* digits to discard */
6895  if (discard<=0) {	      /* no digits are being discarded */
6896    if (dn->lsu!=lsu) {       /* copy needed */
6897      /* copy the coefficient array to the result number; no shift needed */
6898      count=len;	      /* avoids D2U */
6899      up=lsu;
6900      for (target=dn->lsu; count>0; target++, up++, count-=DECDPUN)
6901	*target=*up;
6902      dn->digits=len;	      /* set the new length */
6903      }
6904    /* dn->exponent and residue are unchanged, record any inexactitude */
6905    if (*residue!=0) *status|=(DEC_Inexact | DEC_Rounded);
6906    return;
6907    }
6908
6909  /* some digits must be discarded ... */
6910  dn->exponent+=discard;      /* maintain numerical value */
6911  *status|=DEC_Rounded;       /* accumulate Rounded status */
6912  if (*residue>1) *residue=1; /* previous residue now to right, so reduce */
6913
6914  if (discard>len) {	      /* everything, +1, is being discarded */
6915    /* guard digit is 0 */
6916    /* residue is all the number [NB could be all 0s] */
6917    if (*residue<=0) {	      /* not already positive */
6918      count=len;	      /* avoids D2U */
6919      for (up=lsu; count>0; up++, count-=DECDPUN) if (*up!=0) { /* found non-0 */
6920	*residue=1;
6921	break;		      /* no need to check any others */
6922	}
6923      }
6924    if (*residue!=0) *status|=DEC_Inexact; /* record inexactitude */
6925    *dn->lsu=0; 	      /* coefficient will now be 0 */
6926    dn->digits=1;	      /* .. */
6927    return;
6928    } /* total discard */
6929
6930  /* partial discard [most common case] */
6931  /* here, at least the first (most significant) discarded digit exists */
6932
6933  /* spin up the number, noting residue during the spin, until get to */
6934  /* the Unit with the first discarded digit.  When reach it, extract */
6935  /* it and remember its position */
6936  count=0;
6937  for (up=lsu;; up++) {
6938    count+=DECDPUN;
6939    if (count>=discard) break; /* full ones all checked */
6940    if (*up!=0) *residue=1;
6941    } /* up */
6942
6943  /* here up -> Unit with first discarded digit */
6944  cut=discard-(count-DECDPUN)-1;
6945  if (cut==DECDPUN-1) {       /* unit-boundary case (fast) */
6946    Unit half=(Unit)powers[DECDPUN]>>1;
6947    /* set residue directly */
6948    if (*up>=half) {
6949      if (*up>half) *residue=7;
6950      else *residue+=5;       /* add sticky bit */
6951      }
6952     else { /* <half */
6953      if (*up!=0) *residue=3; /* [else is 0, leave as sticky bit] */
6954      }
6955    if (set->digits<=0) {     /* special for Quantize/Subnormal :-( */
6956      *dn->lsu=0;	      /* .. result is 0 */
6957      dn->digits=1;	      /* .. */
6958      }
6959     else {		      /* shift to least */
6960      count=set->digits;      /* now digits to end up with */
6961      dn->digits=count;       /* set the new length */
6962      up++;		      /* move to next */
6963      /* on unit boundary, so shift-down copy loop is simple */
6964      for (target=dn->lsu; count>0; target++, up++, count-=DECDPUN)
6965	*target=*up;
6966      }
6967    } /* unit-boundary case */
6968
6969   else { /* discard digit is in low digit(s), and not top digit */
6970    uInt  discard1;		   /* first discarded digit */
6971    uInt  quot, rem;		   /* for divisions */
6972    if (cut==0) quot=*up;	   /* is at bottom of unit */
6973     else /* cut>0 */ { 	   /* it's not at bottom of unit */
6974      #if DECDPUN<=4
6975	quot=QUOT10(*up, cut);
6976	rem=*up-quot*powers[cut];
6977      #else
6978	rem=*up%powers[cut];
6979	quot=*up/powers[cut];
6980      #endif
6981      if (rem!=0) *residue=1;
6982      }
6983    /* discard digit is now at bottom of quot */
6984    #if DECDPUN<=4
6985      temp=(quot*6554)>>16;	   /* fast /10 */
6986      /* Vowels algorithm here not a win (9 instructions) */
6987      discard1=quot-X10(temp);
6988      quot=temp;
6989    #else
6990      discard1=quot%10;
6991      quot=quot/10;
6992    #endif
6993    /* here, discard1 is the guard digit, and residue is everything */
6994    /* else [use mapping array to accumulate residue safely] */
6995    *residue+=resmap[discard1];
6996    cut++;			   /* update cut */
6997    /* here: up -> Unit of the array with bottom digit */
6998    /*	     cut is the division point for each Unit */
6999    /*	     quot holds the uncut high-order digits for the current unit */
7000    if (set->digits<=0) {	   /* special for Quantize/Subnormal :-( */
7001      *dn->lsu=0;		   /* .. result is 0 */
7002      dn->digits=1;		   /* .. */
7003      }
7004     else {			   /* shift to least needed */
7005      count=set->digits;	   /* now digits to end up with */
7006      dn->digits=count; 	   /* set the new length */
7007      /* shift-copy the coefficient array to the result number */
7008      for (target=dn->lsu; ; target++) {
7009	*target=(Unit)quot;
7010	count-=(DECDPUN-cut);
7011	if (count<=0) break;
7012	up++;
7013	quot=*up;
7014	#if DECDPUN<=4
7015	  quot=QUOT10(quot, cut);
7016	  rem=*up-quot*powers[cut];
7017	#else
7018	  rem=quot%powers[cut];
7019	  quot=quot/powers[cut];
7020	#endif
7021	*target=(Unit)(*target+rem*powers[DECDPUN-cut]);
7022	count-=cut;
7023	if (count<=0) break;
7024	} /* shift-copy loop */
7025      } /* shift to least */
7026    } /* not unit boundary */
7027
7028  if (*residue!=0) *status|=DEC_Inexact; /* record inexactitude */
7029  return;
7030  } /* decSetCoeff */
7031
7032/* ------------------------------------------------------------------ */
7033/* decApplyRound -- apply pending rounding to a number		      */
7034/*								      */
7035/*   dn    is the number, with space for set->digits digits	      */
7036/*   set   is the context [for size and rounding mode]		      */
7037/*   residue indicates pending rounding, being any accumulated	      */
7038/*	   guard and sticky information.  It may be:		      */
7039/*	   6-9: rounding digit is >5				      */
7040/*	   5:	rounding digit is exactly half-way		      */
7041/*	   1-4: rounding digit is <5 and >0			      */
7042/*	   0:	the coefficient is exact			      */
7043/*	  -1:	as 1, but the hidden digits are subtractive, that     */
7044/*		is, of the opposite sign to dn.  In this case the     */
7045/*		coefficient must be non-0.  This case occurs when     */
7046/*		subtracting a small number (which can be reduced to   */
7047/*		a sticky bit); see decAddOp.			      */
7048/*   status is the status accumulator, as usual 		      */
7049/*								      */
7050/* This routine applies rounding while keeping the length of the      */
7051/* coefficient constant.  The exponent and status are unchanged       */
7052/* except if:							      */
7053/*								      */
7054/*   -- the coefficient was increased and is all nines (in which      */
7055/*	case Overflow could occur, and is handled directly here so    */
7056/*	the caller does not need to re-test for overflow)	      */
7057/*								      */
7058/*   -- the coefficient was decreased and becomes all nines (in which */
7059/*	case Underflow could occur, and is also handled directly).    */
7060/*								      */
7061/* All fields in dn are updated as required.			      */
7062/*								      */
7063/* ------------------------------------------------------------------ */
7064static void decApplyRound(decNumber *dn, decContext *set, Int residue,
7065			  uInt *status) {
7066  Int  bump;		      /* 1 if coefficient needs to be incremented */
7067			      /* -1 if coefficient needs to be decremented */
7068
7069  if (residue==0) return;     /* nothing to apply */
7070
7071  bump=0;		      /* assume a smooth ride */
7072
7073  /* now decide whether, and how, to round, depending on mode */
7074  switch (set->round) {
7075    case DEC_ROUND_05UP: {    /* round zero or five up (for reround) */
7076      /* This is the same as DEC_ROUND_DOWN unless there is a */
7077      /* positive residue and the lsd of dn is 0 or 5, in which case */
7078      /* it is bumped; when residue is <0, the number is therefore */
7079      /* bumped down unless the final digit was 1 or 6 (in which */
7080      /* case it is bumped down and then up -- a no-op) */
7081      Int lsd5=*dn->lsu%5;     /* get lsd and quintate */
7082      if (residue<0 && lsd5!=1) bump=-1;
7083       else if (residue>0 && lsd5==0) bump=1;
7084      /* [bump==1 could be applied directly; use common path for clarity] */
7085      break;} /* r-05 */
7086
7087    case DEC_ROUND_DOWN: {
7088      /* no change, except if negative residue */
7089      if (residue<0) bump=-1;
7090      break;} /* r-d */
7091
7092    case DEC_ROUND_HALF_DOWN: {
7093      if (residue>5) bump=1;
7094      break;} /* r-h-d */
7095
7096    case DEC_ROUND_HALF_EVEN: {
7097      if (residue>5) bump=1;		/* >0.5 goes up */
7098       else if (residue==5) {		/* exactly 0.5000... */
7099	/* 0.5 goes up iff [new] lsd is odd */
7100	if (*dn->lsu & 0x01) bump=1;
7101	}
7102      break;} /* r-h-e */
7103
7104    case DEC_ROUND_HALF_UP: {
7105      if (residue>=5) bump=1;
7106      break;} /* r-h-u */
7107
7108    case DEC_ROUND_UP: {
7109      if (residue>0) bump=1;
7110      break;} /* r-u */
7111
7112    case DEC_ROUND_CEILING: {
7113      /* same as _UP for positive numbers, and as _DOWN for negatives */
7114      /* [negative residue cannot occur on 0] */
7115      if (decNumberIsNegative(dn)) {
7116	if (residue<0) bump=-1;
7117	}
7118       else {
7119	if (residue>0) bump=1;
7120	}
7121      break;} /* r-c */
7122
7123    case DEC_ROUND_FLOOR: {
7124      /* same as _UP for negative numbers, and as _DOWN for positive */
7125      /* [negative residue cannot occur on 0] */
7126      if (!decNumberIsNegative(dn)) {
7127	if (residue<0) bump=-1;
7128	}
7129       else {
7130	if (residue>0) bump=1;
7131	}
7132      break;} /* r-f */
7133
7134    default: {	    /* e.g., DEC_ROUND_MAX */
7135      *status|=DEC_Invalid_context;
7136      #if DECTRACE || (DECCHECK && DECVERB)
7137      printf("Unknown rounding mode: %d\n", set->round);
7138      #endif
7139      break;}
7140    } /* switch */
7141
7142  /* now bump the number, up or down, if need be */
7143  if (bump==0) return;			     /* no action required */
7144
7145  /* Simply use decUnitAddSub unless bumping up and the number is */
7146  /* all nines.  In this special case set to 100... explicitly */
7147  /* and adjust the exponent by one (as otherwise could overflow */
7148  /* the array) */
7149  /* Similarly handle all-nines result if bumping down. */
7150  if (bump>0) {
7151    Unit *up;				     /* work */
7152    uInt count=dn->digits;		     /* digits to be checked */
7153    for (up=dn->lsu; ; up++) {
7154      if (count<=DECDPUN) {
7155	/* this is the last Unit (the msu) */
7156	if (*up!=powers[count]-1) break;     /* not still 9s */
7157	/* here if it, too, is all nines */
7158	*up=(Unit)powers[count-1];	     /* here 999 -> 100 etc. */
7159	for (up=up-1; up>=dn->lsu; up--) *up=0; /* others all to 0 */
7160	dn->exponent++; 		     /* and bump exponent */
7161	/* [which, very rarely, could cause Overflow...] */
7162	if ((dn->exponent+dn->digits)>set->emax+1) {
7163	  decSetOverflow(dn, set, status);
7164	  }
7165	return; 			     /* done */
7166	}
7167      /* a full unit to check, with more to come */
7168      if (*up!=DECDPUNMAX) break;	     /* not still 9s */
7169      count-=DECDPUN;
7170      } /* up */
7171    } /* bump>0 */
7172   else {				     /* -1 */
7173    /* here checking for a pre-bump of 1000... (leading 1, all */
7174    /* other digits zero) */
7175    Unit *up, *sup;			     /* work */
7176    uInt count=dn->digits;		     /* digits to be checked */
7177    for (up=dn->lsu; ; up++) {
7178      if (count<=DECDPUN) {
7179	/* this is the last Unit (the msu) */
7180	if (*up!=powers[count-1]) break;     /* not 100.. */
7181	/* here if have the 1000... case */
7182	sup=up; 			     /* save msu pointer */
7183	*up=(Unit)powers[count]-1;	     /* here 100 in msu -> 999 */
7184	/* others all to all-nines, too */
7185	for (up=up-1; up>=dn->lsu; up--) *up=(Unit)powers[DECDPUN]-1;
7186	dn->exponent--; 		     /* and bump exponent */
7187
7188	/* iff the number was at the subnormal boundary (exponent=etiny) */
7189	/* then the exponent is now out of range, so it will in fact get */
7190	/* clamped to etiny and the final 9 dropped. */
7191	/* printf(">> emin=%d exp=%d sdig=%d\n", set->emin, */
7192	/*	  dn->exponent, set->digits); */
7193	if (dn->exponent+1==set->emin-set->digits+1) {
7194	  if (count==1 && dn->digits==1) *sup=0;  /* here 9 -> 0[.9] */
7195	   else {
7196	    *sup=(Unit)powers[count-1]-1;    /* here 999.. in msu -> 99.. */
7197	    dn->digits--;
7198	    }
7199	  dn->exponent++;
7200	  *status|=DEC_Underflow | DEC_Subnormal | DEC_Inexact | DEC_Rounded;
7201	  }
7202	return; 			     /* done */
7203	}
7204
7205      /* a full unit to check, with more to come */
7206      if (*up!=0) break;		     /* not still 0s */
7207      count-=DECDPUN;
7208      } /* up */
7209
7210    } /* bump<0 */
7211
7212  /* Actual bump needed.  Do it. */
7213  decUnitAddSub(dn->lsu, D2U(dn->digits), uarrone, 1, 0, dn->lsu, bump);
7214  } /* decApplyRound */
7215
7216#if DECSUBSET
7217/* ------------------------------------------------------------------ */
7218/* decFinish -- finish processing a number			      */
7219/*								      */
7220/*   dn is the number						      */
7221/*   set is the context 					      */
7222/*   residue is the rounding accumulator (as in decApplyRound)	      */
7223/*   status is the accumulator					      */
7224/*								      */
7225/* This finishes off the current number by:			      */
7226/*    1. If not extended:					      */
7227/*	 a. Converting a zero result to clean '0'		      */
7228/*	 b. Reducing positive exponents to 0, if would fit in digits  */
7229/*    2. Checking for overflow and subnormals (always)		      */
7230/* Note this is just Finalize when no subset arithmetic.	      */
7231/* All fields are updated as required.				      */
7232/* ------------------------------------------------------------------ */
7233static void decFinish(decNumber *dn, decContext *set, Int *residue,
7234		      uInt *status) {
7235  if (!set->extended) {
7236    if ISZERO(dn) {		   /* value is zero */
7237      dn->exponent=0;		   /* clean exponent .. */
7238      dn->bits=0;		   /* .. and sign */
7239      return;			   /* no error possible */
7240      }
7241    if (dn->exponent>=0) {	   /* non-negative exponent */
7242      /* >0; reduce to integer if possible */
7243      if (set->digits >= (dn->exponent+dn->digits)) {
7244	dn->digits=decShiftToMost(dn->lsu, dn->digits, dn->exponent);
7245	dn->exponent=0;
7246	}
7247      }
7248    } /* !extended */
7249
7250  decFinalize(dn, set, residue, status);
7251  } /* decFinish */
7252#endif
7253
7254/* ------------------------------------------------------------------ */
7255/* decFinalize -- final check, clamp, and round of a number	      */
7256/*								      */
7257/*   dn is the number						      */
7258/*   set is the context 					      */
7259/*   residue is the rounding accumulator (as in decApplyRound)	      */
7260/*   status is the status accumulator				      */
7261/*								      */
7262/* This finishes off the current number by checking for subnormal     */
7263/* results, applying any pending rounding, checking for overflow,     */
7264/* and applying any clamping.					      */
7265/* Underflow and overflow conditions are raised as appropriate.       */
7266/* All fields are updated as required.				      */
7267/* ------------------------------------------------------------------ */
7268static void decFinalize(decNumber *dn, decContext *set, Int *residue,
7269			uInt *status) {
7270  Int shift;				/* shift needed if clamping */
7271  Int tinyexp=set->emin-dn->digits+1;	/* precalculate subnormal boundary */
7272
7273  /* Must be careful, here, when checking the exponent as the */
7274  /* adjusted exponent could overflow 31 bits [because it may already */
7275  /* be up to twice the expected]. */
7276
7277  /* First test for subnormal.	This must be done before any final */
7278  /* round as the result could be rounded to Nmin or 0. */
7279  if (dn->exponent<=tinyexp) {		/* prefilter */
7280    Int comp;
7281    decNumber nmin;
7282    /* A very nasty case here is dn == Nmin and residue<0 */
7283    if (dn->exponent<tinyexp) {
7284      /* Go handle subnormals; this will apply round if needed. */
7285      decSetSubnormal(dn, set, residue, status);
7286      return;
7287      }
7288    /* Equals case: only subnormal if dn=Nmin and negative residue */
7289    decNumberZero(&nmin);
7290    nmin.lsu[0]=1;
7291    nmin.exponent=set->emin;
7292    comp=decCompare(dn, &nmin, 1);		  /* (signless compare) */
7293    if (comp==BADINT) { 			  /* oops */
7294      *status|=DEC_Insufficient_storage;	  /* abandon... */
7295      return;
7296      }
7297    if (*residue<0 && comp==0) {		  /* neg residue and dn==Nmin */
7298      decApplyRound(dn, set, *residue, status);   /* might force down */
7299      decSetSubnormal(dn, set, residue, status);
7300      return;
7301      }
7302    }
7303
7304  /* now apply any pending round (this could raise overflow). */
7305  if (*residue!=0) decApplyRound(dn, set, *residue, status);
7306
7307  /* Check for overflow [redundant in the 'rare' case] or clamp */
7308  if (dn->exponent<=set->emax-set->digits+1) return;   /* neither needed */
7309
7310
7311  /* here when might have an overflow or clamp to do */
7312  if (dn->exponent>set->emax-dn->digits+1) {	       /* too big */
7313    decSetOverflow(dn, set, status);
7314    return;
7315    }
7316  /* here when the result is normal but in clamp range */
7317  if (!set->clamp) return;
7318
7319  /* here when need to apply the IEEE exponent clamp (fold-down) */
7320  shift=dn->exponent-(set->emax-set->digits+1);
7321
7322  /* shift coefficient (if non-zero) */
7323  if (!ISZERO(dn)) {
7324    dn->digits=decShiftToMost(dn->lsu, dn->digits, shift);
7325    }
7326  dn->exponent-=shift;	 /* adjust the exponent to match */
7327  *status|=DEC_Clamped;  /* and record the dirty deed */
7328  return;
7329  } /* decFinalize */
7330
7331/* ------------------------------------------------------------------ */
7332/* decSetOverflow -- set number to proper overflow value	      */
7333/*								      */
7334/*   dn is the number (used for sign [only] and result) 	      */
7335/*   set is the context [used for the rounding mode, etc.]	      */
7336/*   status contains the current status to be updated		      */
7337/*								      */
7338/* This sets the sign of a number and sets its value to either	      */
7339/* Infinity or the maximum finite value, depending on the sign of     */
7340/* dn and the rounding mode, following IEEE 754 rules.		      */
7341/* ------------------------------------------------------------------ */
7342static void decSetOverflow(decNumber *dn, decContext *set, uInt *status) {
7343  Flag needmax=0;		   /* result is maximum finite value */
7344  uByte sign=dn->bits&DECNEG;	   /* clean and save sign bit */
7345
7346  if (ISZERO(dn)) {		   /* zero does not overflow magnitude */
7347    Int emax=set->emax; 		     /* limit value */
7348    if (set->clamp) emax-=set->digits-1;     /* lower if clamping */
7349    if (dn->exponent>emax) {		     /* clamp required */
7350      dn->exponent=emax;
7351      *status|=DEC_Clamped;
7352      }
7353    return;
7354    }
7355
7356  decNumberZero(dn);
7357  switch (set->round) {
7358    case DEC_ROUND_DOWN: {
7359      needmax=1;		   /* never Infinity */
7360      break;} /* r-d */
7361    case DEC_ROUND_05UP: {
7362      needmax=1;		   /* never Infinity */
7363      break;} /* r-05 */
7364    case DEC_ROUND_CEILING: {
7365      if (sign) needmax=1;	   /* Infinity if non-negative */
7366      break;} /* r-c */
7367    case DEC_ROUND_FLOOR: {
7368      if (!sign) needmax=1;	   /* Infinity if negative */
7369      break;} /* r-f */
7370    default: break;		   /* Infinity in all other cases */
7371    }
7372  if (needmax) {
7373    decSetMaxValue(dn, set);
7374    dn->bits=sign;		   /* set sign */
7375    }
7376   else dn->bits=sign|DECINF;	   /* Value is +/-Infinity */
7377  *status|=DEC_Overflow | DEC_Inexact | DEC_Rounded;
7378  } /* decSetOverflow */
7379
7380/* ------------------------------------------------------------------ */
7381/* decSetMaxValue -- set number to +Nmax (maximum normal value)       */
7382/*								      */
7383/*   dn is the number to set					      */
7384/*   set is the context [used for digits and emax]		      */
7385/*								      */
7386/* This sets the number to the maximum positive value.		      */
7387/* ------------------------------------------------------------------ */
7388static void decSetMaxValue(decNumber *dn, decContext *set) {
7389  Unit *up;			   /* work */
7390  Int count=set->digits;	   /* nines to add */
7391  dn->digits=count;
7392  /* fill in all nines to set maximum value */
7393  for (up=dn->lsu; ; up++) {
7394    if (count>DECDPUN) *up=DECDPUNMAX;	/* unit full o'nines */
7395     else {				/* this is the msu */
7396      *up=(Unit)(powers[count]-1);
7397      break;
7398      }
7399    count-=DECDPUN;		   /* filled those digits */
7400    } /* up */
7401  dn->bits=0;			   /* + sign */
7402  dn->exponent=set->emax-set->digits+1;
7403  } /* decSetMaxValue */
7404
7405/* ------------------------------------------------------------------ */
7406/* decSetSubnormal -- process value whose exponent is <Emin	      */
7407/*								      */
7408/*   dn is the number (used as input as well as output; it may have   */
7409/*	   an allowed subnormal value, which may need to be rounded)  */
7410/*   set is the context [used for the rounding mode]		      */
7411/*   residue is any pending residue				      */
7412/*   status contains the current status to be updated		      */
7413/*								      */
7414/* If subset mode, set result to zero and set Underflow flags.	      */
7415/*								      */
7416/* Value may be zero with a low exponent; this does not set Subnormal */
7417/* but the exponent will be clamped to Etiny.			      */
7418/*								      */
7419/* Otherwise ensure exponent is not out of range, and round as	      */
7420/* necessary.  Underflow is set if the result is Inexact.	      */
7421/* ------------------------------------------------------------------ */
7422static void decSetSubnormal(decNumber *dn, decContext *set, Int *residue,
7423			    uInt *status) {
7424  decContext workset;	      /* work */
7425  Int	     etiny, adjust;   /* .. */
7426
7427  #if DECSUBSET
7428  /* simple set to zero and 'hard underflow' for subset */
7429  if (!set->extended) {
7430    decNumberZero(dn);
7431    /* always full overflow */
7432    *status|=DEC_Underflow | DEC_Subnormal | DEC_Inexact | DEC_Rounded;
7433    return;
7434    }
7435  #endif
7436
7437  /* Full arithmetic -- allow subnormals, rounded to minimum exponent */
7438  /* (Etiny) if needed */
7439  etiny=set->emin-(set->digits-1);	/* smallest allowed exponent */
7440
7441  if ISZERO(dn) {			/* value is zero */
7442    /* residue can never be non-zero here */
7443    #if DECCHECK
7444      if (*residue!=0) {
7445	printf("++ Subnormal 0 residue %ld\n", (LI)*residue);
7446	*status|=DEC_Invalid_operation;
7447	}
7448    #endif
7449    if (dn->exponent<etiny) {		/* clamp required */
7450      dn->exponent=etiny;
7451      *status|=DEC_Clamped;
7452      }
7453    return;
7454    }
7455
7456  *status|=DEC_Subnormal;		/* have a non-zero subnormal */
7457  adjust=etiny-dn->exponent;		/* calculate digits to remove */
7458  if (adjust<=0) {			/* not out of range; unrounded */
7459    /* residue can never be non-zero here, except in the Nmin-residue */
7460    /* case (which is a subnormal result), so can take fast-path here */
7461    /* it may already be inexact (from setting the coefficient) */
7462    if (*status&DEC_Inexact) *status|=DEC_Underflow;
7463    return;
7464    }
7465
7466  /* adjust>0, so need to rescale the result so exponent becomes Etiny */
7467  /* [this code is similar to that in rescale] */
7468  workset=*set; 			/* clone rounding, etc. */
7469  workset.digits=dn->digits-adjust;	/* set requested length */
7470  workset.emin-=adjust; 		/* and adjust emin to match */
7471  /* [note that the latter can be <1, here, similar to Rescale case] */
7472  decSetCoeff(dn, &workset, dn->lsu, dn->digits, residue, status);
7473  decApplyRound(dn, &workset, *residue, status);
7474
7475  /* Use 754 default rule: Underflow is set iff Inexact */
7476  /* [independent of whether trapped] */
7477  if (*status&DEC_Inexact) *status|=DEC_Underflow;
7478
7479  /* if rounded up a 999s case, exponent will be off by one; adjust */
7480  /* back if so [it will fit, because it was shortened earlier] */
7481  if (dn->exponent>etiny) {
7482    dn->digits=decShiftToMost(dn->lsu, dn->digits, 1);
7483    dn->exponent--;			/* (re)adjust the exponent. */
7484    }
7485
7486  /* if rounded to zero, it is by definition clamped... */
7487  if (ISZERO(dn)) *status|=DEC_Clamped;
7488  } /* decSetSubnormal */
7489
7490/* ------------------------------------------------------------------ */
7491/* decCheckMath - check entry conditions for a math function	      */
7492/*								      */
7493/*   This checks the context and the operand			      */
7494/*								      */
7495/*   rhs is the operand to check				      */
7496/*   set is the context to check				      */
7497/*   status is unchanged if both are good			      */
7498/*								      */
7499/* returns non-zero if status is changed, 0 otherwise		      */
7500/*								      */
7501/* Restrictions enforced:					      */
7502/*								      */
7503/*   digits, emax, and -emin in the context must be less than	      */
7504/*   DEC_MAX_MATH (999999), and A must be within these bounds if      */
7505/*   non-zero.	Invalid_operation is set in the status if a	      */
7506/*   restriction is violated.					      */
7507/* ------------------------------------------------------------------ */
7508static uInt decCheckMath(const decNumber *rhs, decContext *set,
7509			 uInt *status) {
7510  uInt save=*status;			     /* record */
7511  if (set->digits>DEC_MAX_MATH
7512   || set->emax>DEC_MAX_MATH
7513   || -set->emin>DEC_MAX_MATH) *status|=DEC_Invalid_context;
7514   else if ((rhs->digits>DEC_MAX_MATH
7515     || rhs->exponent+rhs->digits>DEC_MAX_MATH+1
7516     || rhs->exponent+rhs->digits<2*(1-DEC_MAX_MATH))
7517     && !ISZERO(rhs)) *status|=DEC_Invalid_operation;
7518  return (*status!=save);
7519  } /* decCheckMath */
7520
7521/* ------------------------------------------------------------------ */
7522/* decGetInt -- get integer from a number			      */
7523/*								      */
7524/*   dn is the number [which will not be altered]		      */
7525/*								      */
7526/*   returns one of:						      */
7527/*     BADINT if there is a non-zero fraction			      */
7528/*     the converted integer					      */
7529/*     BIGEVEN if the integer is even and magnitude > 2*10**9	      */
7530/*     BIGODD  if the integer is odd  and magnitude > 2*10**9	      */
7531/*								      */
7532/* This checks and gets a whole number from the input decNumber.      */
7533/* The sign can be determined from dn by the caller when BIGEVEN or   */
7534/* BIGODD is returned.						      */
7535/* ------------------------------------------------------------------ */
7536static Int decGetInt(const decNumber *dn) {
7537  Int  theInt;				/* result accumulator */
7538  const Unit *up;			/* work */
7539  Int  got;				/* digits (real or not) processed */
7540  Int  ilength=dn->digits+dn->exponent; /* integral length */
7541  Flag neg=decNumberIsNegative(dn);	/* 1 if -ve */
7542
7543  /* The number must be an integer that fits in 10 digits */
7544  /* Assert, here, that 10 is enough for any rescale Etiny */
7545  #if DEC_MAX_EMAX > 999999999
7546    #error GetInt may need updating [for Emax]
7547  #endif
7548  #if DEC_MIN_EMIN < -999999999
7549    #error GetInt may need updating [for Emin]
7550  #endif
7551  if (ISZERO(dn)) return 0;		/* zeros are OK, with any exponent */
7552
7553  up=dn->lsu;				/* ready for lsu */
7554  theInt=0;				/* ready to accumulate */
7555  if (dn->exponent>=0) {		/* relatively easy */
7556    /* no fractional part [usual]; allow for positive exponent */
7557    got=dn->exponent;
7558    }
7559   else { /* -ve exponent; some fractional part to check and discard */
7560    Int count=-dn->exponent;		/* digits to discard */
7561    /* spin up whole units until reach the Unit with the unit digit */
7562    for (; count>=DECDPUN; up++) {
7563      if (*up!=0) return BADINT;	/* non-zero Unit to discard */
7564      count-=DECDPUN;
7565      }
7566    if (count==0) got=0;		/* [a multiple of DECDPUN] */
7567     else {				/* [not multiple of DECDPUN] */
7568      Int rem;				/* work */
7569      /* slice off fraction digits and check for non-zero */
7570      #if DECDPUN<=4
7571	theInt=QUOT10(*up, count);
7572	rem=*up-theInt*powers[count];
7573      #else
7574	rem=*up%powers[count];		/* slice off discards */
7575	theInt=*up/powers[count];
7576      #endif
7577      if (rem!=0) return BADINT;	/* non-zero fraction */
7578      /* it looks good */
7579      got=DECDPUN-count;		/* number of digits so far */
7580      up++;				/* ready for next */
7581      }
7582    }
7583  /* now it's known there's no fractional part */
7584
7585  /* tricky code now, to accumulate up to 9.3 digits */
7586  if (got==0) {theInt=*up; got+=DECDPUN; up++;} /* ensure lsu is there */
7587
7588  if (ilength<11) {
7589    Int save=theInt;
7590    /* collect any remaining unit(s) */
7591    for (; got<ilength; up++) {
7592      theInt+=*up*powers[got];
7593      got+=DECDPUN;
7594      }
7595    if (ilength==10) {			/* need to check for wrap */
7596      if (theInt/(Int)powers[got-DECDPUN]!=(Int)*(up-1)) ilength=11;
7597	 /* [that test also disallows the BADINT result case] */
7598       else if (neg && theInt>1999999997) ilength=11;
7599       else if (!neg && theInt>999999999) ilength=11;
7600      if (ilength==11) theInt=save;	/* restore correct low bit */
7601      }
7602    }
7603
7604  if (ilength>10) {			/* too big */
7605    if (theInt&1) return BIGODD;	/* bottom bit 1 */
7606    return BIGEVEN;			/* bottom bit 0 */
7607    }
7608
7609  if (neg) theInt=-theInt;		/* apply sign */
7610  return theInt;
7611  } /* decGetInt */
7612
7613/* ------------------------------------------------------------------ */
7614/* decDecap -- decapitate the coefficient of a number		      */
7615/*								      */
7616/*   dn   is the number to be decapitated			      */
7617/*   drop is the number of digits to be removed from the left of dn;  */
7618/*     this must be <= dn->digits (if equal, the coefficient is       */
7619/*     set to 0)						      */
7620/*								      */
7621/* Returns dn; dn->digits will be <= the initial digits less drop     */
7622/* (after removing drop digits there may be leading zero digits       */
7623/* which will also be removed).  Only dn->lsu and dn->digits change.  */
7624/* ------------------------------------------------------------------ */
7625static decNumber *decDecap(decNumber *dn, Int drop) {
7626  Unit *msu;				/* -> target cut point */
7627  Int cut;				/* work */
7628  if (drop>=dn->digits) {		/* losing the whole thing */
7629    #if DECCHECK
7630    if (drop>dn->digits)
7631      printf("decDecap called with drop>digits [%ld>%ld]\n",
7632	     (LI)drop, (LI)dn->digits);
7633    #endif
7634    dn->lsu[0]=0;
7635    dn->digits=1;
7636    return dn;
7637    }
7638  msu=dn->lsu+D2U(dn->digits-drop)-1;	/* -> likely msu */
7639  cut=MSUDIGITS(dn->digits-drop);	/* digits to be in use in msu */
7640  if (cut!=DECDPUN) *msu%=powers[cut];	/* clear left digits */
7641  /* that may have left leading zero digits, so do a proper count... */
7642  dn->digits=decGetDigits(dn->lsu, msu-dn->lsu+1);
7643  return dn;
7644  } /* decDecap */
7645
7646/* ------------------------------------------------------------------ */
7647/* decBiStr -- compare string with pairwise options		      */
7648/*								      */
7649/*   targ is the string to compare				      */
7650/*   str1 is one of the strings to compare against (length may be 0)  */
7651/*   str2 is the other; it must be the same length as str1	      */
7652/*								      */
7653/*   returns 1 if strings compare equal, (that is, it is the same     */
7654/*   length as str1 and str2, and each character of targ is in either */
7655/*   str1 or str2 in the corresponding position), or 0 otherwise      */
7656/*								      */
7657/* This is used for generic caseless compare, including the awkward   */
7658/* case of the Turkish dotted and dotless Is.  Use as (for example):  */
7659/*   if (decBiStr(test, "mike", "MIKE")) ...			      */
7660/* ------------------------------------------------------------------ */
7661static Flag decBiStr(const char *targ, const char *str1, const char *str2) {
7662  for (;;targ++, str1++, str2++) {
7663    if (*targ!=*str1 && *targ!=*str2) return 0;
7664    /* *targ has a match in one (or both, if terminator) */
7665    if (*targ=='\0') break;
7666    } /* forever */
7667  return 1;
7668  } /* decBiStr */
7669
7670/* ------------------------------------------------------------------ */
7671/* decNaNs -- handle NaN operand or operands			      */
7672/*								      */
7673/*   res     is the result number				      */
7674/*   lhs     is the first operand				      */
7675/*   rhs     is the second operand, or NULL if none		      */
7676/*   context is used to limit payload length			      */
7677/*   status  contains the current status			      */
7678/*   returns res in case convenient				      */
7679/*								      */
7680/* Called when one or both operands is a NaN, and propagates the      */
7681/* appropriate result to res.  When an sNaN is found, it is changed   */
7682/* to a qNaN and Invalid operation is set.			      */
7683/* ------------------------------------------------------------------ */
7684static decNumber * decNaNs(decNumber *res, const decNumber *lhs,
7685			   const decNumber *rhs, decContext *set,
7686			   uInt *status) {
7687  /* This decision tree ends up with LHS being the source pointer, */
7688  /* and status updated if need be */
7689  if (lhs->bits & DECSNAN)
7690    *status|=DEC_Invalid_operation | DEC_sNaN;
7691   else if (rhs==NULL);
7692   else if (rhs->bits & DECSNAN) {
7693    lhs=rhs;
7694    *status|=DEC_Invalid_operation | DEC_sNaN;
7695    }
7696   else if (lhs->bits & DECNAN);
7697   else lhs=rhs;
7698
7699  /* propagate the payload */
7700  if (lhs->digits<=set->digits) decNumberCopy(res, lhs); /* easy */
7701   else { /* too long */
7702    const Unit *ul;
7703    Unit *ur, *uresp1;
7704    /* copy safe number of units, then decapitate */
7705    res->bits=lhs->bits;		/* need sign etc. */
7706    uresp1=res->lsu+D2U(set->digits);
7707    for (ur=res->lsu, ul=lhs->lsu; ur<uresp1; ur++, ul++) *ur=*ul;
7708    res->digits=D2U(set->digits)*DECDPUN;
7709    /* maybe still too long */
7710    if (res->digits>set->digits) decDecap(res, res->digits-set->digits);
7711    }
7712
7713  res->bits&=~DECSNAN;	      /* convert any sNaN to NaN, while */
7714  res->bits|=DECNAN;	      /* .. preserving sign */
7715  res->exponent=0;	      /* clean exponent */
7716			      /* [coefficient was copied/decapitated] */
7717  return res;
7718  } /* decNaNs */
7719
7720/* ------------------------------------------------------------------ */
7721/* decStatus -- apply non-zero status				      */
7722/*								      */
7723/*   dn     is the number to set if error			      */
7724/*   status contains the current status (not yet in context)	      */
7725/*   set    is the context					      */
7726/*								      */
7727/* If the status is an error status, the number is set to a NaN,      */
7728/* unless the error was an overflow, divide-by-zero, or underflow,    */
7729/* in which case the number will have already been set. 	      */
7730/*								      */
7731/* The context status is then updated with the new status.  Note that */
7732/* this may raise a signal, so control may never return from this     */
7733/* routine (hence resources must be recovered before it is called).   */
7734/* ------------------------------------------------------------------ */
7735static void decStatus(decNumber *dn, uInt status, decContext *set) {
7736  if (status & DEC_NaNs) {		/* error status -> NaN */
7737    /* if cause was an sNaN, clear and propagate [NaN is already set up] */
7738    if (status & DEC_sNaN) status&=~DEC_sNaN;
7739     else {
7740      decNumberZero(dn);		/* other error: clean throughout */
7741      dn->bits=DECNAN;			/* and make a quiet NaN */
7742      }
7743    }
7744  decContextSetStatus(set, status);	/* [may not return] */
7745  return;
7746  } /* decStatus */
7747
7748/* ------------------------------------------------------------------ */
7749/* decGetDigits -- count digits in a Units array		      */
7750/*								      */
7751/*   uar is the Unit array holding the number (this is often an       */
7752/*	    accumulator of some sort)				      */
7753/*   len is the length of the array in units [>=1]		      */
7754/*								      */
7755/*   returns the number of (significant) digits in the array	      */
7756/*								      */
7757/* All leading zeros are excluded, except the last if the array has   */
7758/* only zero Units.						      */
7759/* ------------------------------------------------------------------ */
7760/* This may be called twice during some operations. */
7761static Int decGetDigits(Unit *uar, Int len) {
7762  Unit *up=uar+(len-1); 	   /* -> msu */
7763  Int  digits=(len-1)*DECDPUN+1;   /* possible digits excluding msu */
7764  #if DECDPUN>4
7765  uInt const *pow;		   /* work */
7766  #endif
7767				   /* (at least 1 in final msu) */
7768  #if DECCHECK
7769  if (len<1) printf("decGetDigits called with len<1 [%ld]\n", (LI)len);
7770  #endif
7771
7772  for (; up>=uar; up--) {
7773    if (*up==0) {		   /* unit is all 0s */
7774      if (digits==1) break;	   /* a zero has one digit */
7775      digits-=DECDPUN;		   /* adjust for 0 unit */
7776      continue;}
7777    /* found the first (most significant) non-zero Unit */
7778    #if DECDPUN>1		   /* not done yet */
7779    if (*up<10) break;		   /* is 1-9 */
7780    digits++;
7781    #if DECDPUN>2		   /* not done yet */
7782    if (*up<100) break; 	   /* is 10-99 */
7783    digits++;
7784    #if DECDPUN>3		   /* not done yet */
7785    if (*up<1000) break;	   /* is 100-999 */
7786    digits++;
7787    #if DECDPUN>4		   /* count the rest ... */
7788    for (pow=&powers[4]; *up>=*pow; pow++) digits++;
7789    #endif
7790    #endif
7791    #endif
7792    #endif
7793    break;
7794    } /* up */
7795  return digits;
7796  } /* decGetDigits */
7797
7798#if DECTRACE | DECCHECK
7799/* ------------------------------------------------------------------ */
7800/* decNumberShow -- display a number [debug aid]		      */
7801/*   dn is the number to show					      */
7802/*								      */
7803/* Shows: sign, exponent, coefficient (msu first), digits	      */
7804/*    or: sign, special-value					      */
7805/* ------------------------------------------------------------------ */
7806/* this is public so other modules can use it */
7807void decNumberShow(const decNumber *dn) {
7808  const Unit *up;		   /* work */
7809  uInt u, d;			   /* .. */
7810  Int cut;			   /* .. */
7811  char isign='+';		   /* main sign */
7812  if (dn==NULL) {
7813    printf("NULL\n");
7814    return;}
7815  if (decNumberIsNegative(dn)) isign='-';
7816  printf(" >> %c ", isign);
7817  if (dn->bits&DECSPECIAL) {	   /* Is a special value */
7818    if (decNumberIsInfinite(dn)) printf("Infinity");
7819     else {				     /* a NaN */
7820      if (dn->bits&DECSNAN) printf("sNaN");  /* signalling NaN */
7821       else printf("NaN");
7822      }
7823    /* if coefficient and exponent are 0, no more to do */
7824    if (dn->exponent==0 && dn->digits==1 && *dn->lsu==0) {
7825      printf("\n");
7826      return;}
7827    /* drop through to report other information */
7828    printf(" ");
7829    }
7830
7831  /* now carefully display the coefficient */
7832  up=dn->lsu+D2U(dn->digits)-1; 	/* msu */
7833  printf("%ld", (LI)*up);
7834  for (up=up-1; up>=dn->lsu; up--) {
7835    u=*up;
7836    printf(":");
7837    for (cut=DECDPUN-1; cut>=0; cut--) {
7838      d=u/powers[cut];
7839      u-=d*powers[cut];
7840      printf("%ld", (LI)d);
7841      } /* cut */
7842    } /* up */
7843  if (dn->exponent!=0) {
7844    char esign='+';
7845    if (dn->exponent<0) esign='-';
7846    printf(" E%c%ld", esign, (LI)abs(dn->exponent));
7847    }
7848  printf(" [%ld]\n", (LI)dn->digits);
7849  } /* decNumberShow */
7850#endif
7851
7852#if DECTRACE || DECCHECK
7853/* ------------------------------------------------------------------ */
7854/* decDumpAr -- display a unit array [debug/check aid]		      */
7855/*   name is a single-character tag name			      */
7856/*   ar   is the array to display				      */
7857/*   len  is the length of the array in Units			      */
7858/* ------------------------------------------------------------------ */
7859static void decDumpAr(char name, const Unit *ar, Int len) {
7860  Int i;
7861  const char *spec;
7862  #if DECDPUN==9
7863    spec="%09d ";
7864  #elif DECDPUN==8
7865    spec="%08d ";
7866  #elif DECDPUN==7
7867    spec="%07d ";
7868  #elif DECDPUN==6
7869    spec="%06d ";
7870  #elif DECDPUN==5
7871    spec="%05d ";
7872  #elif DECDPUN==4
7873    spec="%04d ";
7874  #elif DECDPUN==3
7875    spec="%03d ";
7876  #elif DECDPUN==2
7877    spec="%02d ";
7878  #else
7879    spec="%d ";
7880  #endif
7881  printf("  :%c: ", name);
7882  for (i=len-1; i>=0; i--) {
7883    if (i==len-1) printf("%ld ", (LI)ar[i]);
7884     else printf(spec, ar[i]);
7885    }
7886  printf("\n");
7887  return;}
7888#endif
7889
7890#if DECCHECK
7891/* ------------------------------------------------------------------ */
7892/* decCheckOperands -- check operand(s) to a routine		      */
7893/*   res is the result structure (not checked; it will be set to      */
7894/*	    quiet NaN if error found (and it is not NULL))	      */
7895/*   lhs is the first operand (may be DECUNRESU)		      */
7896/*   rhs is the second (may be DECUNUSED)			      */
7897/*   set is the context (may be DECUNCONT)			      */
7898/*   returns 0 if both operands, and the context are clean, or 1      */
7899/*     otherwise (in which case the context will show an error,       */
7900/*     unless NULL).  Note that res is not cleaned; caller should     */
7901/*     handle this so res=NULL case is safe.			      */
7902/* The caller is expected to abandon immediately if 1 is returned.    */
7903/* ------------------------------------------------------------------ */
7904static Flag decCheckOperands(decNumber *res, const decNumber *lhs,
7905			     const decNumber *rhs, decContext *set) {
7906  Flag bad=0;
7907  if (set==NULL) {		   /* oops; hopeless */
7908    #if DECTRACE || DECVERB
7909    printf("Reference to context is NULL.\n");
7910    #endif
7911    bad=1;
7912    return 1;}
7913   else if (set!=DECUNCONT
7914     && (set->digits<1 || set->round>=DEC_ROUND_MAX)) {
7915    bad=1;
7916    #if DECTRACE || DECVERB
7917    printf("Bad context [digits=%ld round=%ld].\n",
7918	   (LI)set->digits, (LI)set->round);
7919    #endif
7920    }
7921   else {
7922    if (res==NULL) {
7923      bad=1;
7924      #if DECTRACE
7925      /* this one not DECVERB as standard tests include NULL */
7926      printf("Reference to result is NULL.\n");
7927      #endif
7928      }
7929    if (!bad && lhs!=DECUNUSED) bad=(decCheckNumber(lhs));
7930    if (!bad && rhs!=DECUNUSED) bad=(decCheckNumber(rhs));
7931    }
7932  if (bad) {
7933    if (set!=DECUNCONT) decContextSetStatus(set, DEC_Invalid_operation);
7934    if (res!=DECUNRESU && res!=NULL) {
7935      decNumberZero(res);
7936      res->bits=DECNAN;       /* qNaN */
7937      }
7938    }
7939  return bad;
7940  } /* decCheckOperands */
7941
7942/* ------------------------------------------------------------------ */
7943/* decCheckNumber -- check a number				      */
7944/*   dn is the number to check					      */
7945/*   returns 0 if the number is clean, or 1 otherwise		      */
7946/*								      */
7947/* The number is considered valid if it could be a result from some   */
7948/* operation in some valid context.				      */
7949/* ------------------------------------------------------------------ */
7950static Flag decCheckNumber(const decNumber *dn) {
7951  const Unit *up;	      /* work */
7952  uInt maxuint; 	      /* .. */
7953  Int ae, d, digits;	      /* .. */
7954  Int emin, emax;	      /* .. */
7955
7956  if (dn==NULL) {	      /* hopeless */
7957    #if DECTRACE
7958    /* this one not DECVERB as standard tests include NULL */
7959    printf("Reference to decNumber is NULL.\n");
7960    #endif
7961    return 1;}
7962
7963  /* check special values */
7964  if (dn->bits & DECSPECIAL) {
7965    if (dn->exponent!=0) {
7966      #if DECTRACE || DECVERB
7967      printf("Exponent %ld (not 0) for a special value [%02x].\n",
7968	     (LI)dn->exponent, dn->bits);
7969      #endif
7970      return 1;}
7971
7972    /* 2003.09.08: NaNs may now have coefficients, so next tests Inf only */
7973    if (decNumberIsInfinite(dn)) {
7974      if (dn->digits!=1) {
7975	#if DECTRACE || DECVERB
7976	printf("Digits %ld (not 1) for an infinity.\n", (LI)dn->digits);
7977	#endif
7978	return 1;}
7979      if (*dn->lsu!=0) {
7980	#if DECTRACE || DECVERB
7981	printf("LSU %ld (not 0) for an infinity.\n", (LI)*dn->lsu);
7982	#endif
7983	decDumpAr('I', dn->lsu, D2U(dn->digits));
7984	return 1;}
7985      } /* Inf */
7986    /* 2002.12.26: negative NaNs can now appear through proposed IEEE */
7987    /*		   concrete formats (decimal64, etc.). */
7988    return 0;
7989    }
7990
7991  /* check the coefficient */
7992  if (dn->digits<1 || dn->digits>DECNUMMAXP) {
7993    #if DECTRACE || DECVERB
7994    printf("Digits %ld in number.\n", (LI)dn->digits);
7995    #endif
7996    return 1;}
7997
7998  d=dn->digits;
7999
8000  for (up=dn->lsu; d>0; up++) {
8001    if (d>DECDPUN) maxuint=DECDPUNMAX;
8002     else {		      /* reached the msu */
8003      maxuint=powers[d]-1;
8004      if (dn->digits>1 && *up<powers[d-1]) {
8005	#if DECTRACE || DECVERB
8006	printf("Leading 0 in number.\n");
8007	decNumberShow(dn);
8008	#endif
8009	return 1;}
8010      }
8011    if (*up>maxuint) {
8012      #if DECTRACE || DECVERB
8013      printf("Bad Unit [%08lx] in %ld-digit number at offset %ld [maxuint %ld].\n",
8014	      (LI)*up, (LI)dn->digits, (LI)(up-dn->lsu), (LI)maxuint);
8015      #endif
8016      return 1;}
8017    d-=DECDPUN;
8018    }
8019
8020  /* check the exponent.  Note that input operands can have exponents */
8021  /* which are out of the set->emin/set->emax and set->digits range */
8022  /* (just as they can have more digits than set->digits). */
8023  ae=dn->exponent+dn->digits-1;    /* adjusted exponent */
8024  emax=DECNUMMAXE;
8025  emin=DECNUMMINE;
8026  digits=DECNUMMAXP;
8027  if (ae<emin-(digits-1)) {
8028    #if DECTRACE || DECVERB
8029    printf("Adjusted exponent underflow [%ld].\n", (LI)ae);
8030    decNumberShow(dn);
8031    #endif
8032    return 1;}
8033  if (ae>+emax) {
8034    #if DECTRACE || DECVERB
8035    printf("Adjusted exponent overflow [%ld].\n", (LI)ae);
8036    decNumberShow(dn);
8037    #endif
8038    return 1;}
8039
8040  return 0;		 /* it's OK */
8041  } /* decCheckNumber */
8042
8043/* ------------------------------------------------------------------ */
8044/* decCheckInexact -- check a normal finite inexact result has digits */
8045/*   dn is the number to check					      */
8046/*   set is the context (for status and precision)		      */
8047/*   sets Invalid operation, etc., if some digits are missing	      */
8048/* [this check is not made for DECSUBSET compilation or when	      */
8049/* subnormal is not set]					      */
8050/* ------------------------------------------------------------------ */
8051static void decCheckInexact(const decNumber *dn, decContext *set) {
8052  #if !DECSUBSET && DECEXTFLAG
8053    if ((set->status & (DEC_Inexact|DEC_Subnormal))==DEC_Inexact
8054     && (set->digits!=dn->digits) && !(dn->bits & DECSPECIAL)) {
8055      #if DECTRACE || DECVERB
8056      printf("Insufficient digits [%ld] on normal Inexact result.\n",
8057	     (LI)dn->digits);
8058      decNumberShow(dn);
8059      #endif
8060      decContextSetStatus(set, DEC_Invalid_operation);
8061      }
8062  #else
8063    /* next is a noop for quiet compiler */
8064    if (dn!=NULL && dn->digits==0) set->status|=DEC_Invalid_operation;
8065  #endif
8066  return;
8067  } /* decCheckInexact */
8068#endif
8069
8070#if DECALLOC
8071#undef malloc
8072#undef free
8073/* ------------------------------------------------------------------ */
8074/* decMalloc -- accountable allocation routine			      */
8075/*   n is the number of bytes to allocate			      */
8076/*								      */
8077/* Semantics is the same as the stdlib malloc routine, but bytes      */
8078/* allocated are accounted for globally, and corruption fences are    */
8079/* added before and after the 'actual' storage. 		      */
8080/* ------------------------------------------------------------------ */
8081/* This routine allocates storage with an extra twelve bytes; 8 are   */
8082/* at the start and hold:					      */
8083/*   0-3 the original length requested				      */
8084/*   4-7 buffer corruption detection fence (DECFENCE, x4)	      */
8085/* The 4 bytes at the end also hold a corruption fence (DECFENCE, x4) */
8086/* ------------------------------------------------------------------ */
8087static void *decMalloc(size_t n) {
8088  uInt	size=n+12;		   /* true size */
8089  void	*alloc; 		   /* -> allocated storage */
8090  uByte *b, *b0;		   /* work */
8091  uInt	uiwork; 		   /* for macros */
8092
8093  alloc=malloc(size);		   /* -> allocated storage */
8094  if (alloc==NULL) return NULL;    /* out of strorage */
8095  b0=(uByte *)alloc;		   /* as bytes */
8096  decAllocBytes+=n;		   /* account for storage */
8097  UBFROMUI(alloc, n);		   /* save n */
8098  /* printf(" alloc ++ dAB: %ld (%ld)\n", (LI)decAllocBytes, (LI)n); */
8099  for (b=b0+4; b<b0+8; b++) *b=DECFENCE;
8100  for (b=b0+n+8; b<b0+n+12; b++) *b=DECFENCE;
8101  return b0+8;			   /* -> play area */
8102  } /* decMalloc */
8103
8104/* ------------------------------------------------------------------ */
8105/* decFree -- accountable free routine				      */
8106/*   alloc is the storage to free				      */
8107/*								      */
8108/* Semantics is the same as the stdlib malloc routine, except that    */
8109/* the global storage accounting is updated and the fences are	      */
8110/* checked to ensure that no routine has written 'out of bounds'.     */
8111/* ------------------------------------------------------------------ */
8112/* This routine first checks that the fences have not been corrupted. */
8113/* It then frees the storage using the 'truw' storage address (that   */
8114/* is, offset by 8).						      */
8115/* ------------------------------------------------------------------ */
8116static void decFree(void *alloc) {
8117  uInt	n;			   /* original length */
8118  uByte *b, *b0;		   /* work */
8119  uInt	uiwork; 		   /* for macros */
8120
8121  if (alloc==NULL) return;	   /* allowed; it's a nop */
8122  b0=(uByte *)alloc;		   /* as bytes */
8123  b0-=8;			   /* -> true start of storage */
8124  n=UBTOUI(b0); 		   /* lift length */
8125  for (b=b0+4; b<b0+8; b++) if (*b!=DECFENCE)
8126    printf("=== Corrupt byte [%02x] at offset %d from %ld ===\n", *b,
8127	   b-b0-8, (LI)b0);
8128  for (b=b0+n+8; b<b0+n+12; b++) if (*b!=DECFENCE)
8129    printf("=== Corrupt byte [%02x] at offset +%d from %ld, n=%ld ===\n", *b,
8130	   b-b0-8, (LI)b0, (LI)n);
8131  free(b0);			   /* drop the storage */
8132  decAllocBytes-=n;		   /* account for storage */
8133  /* printf(" free -- dAB: %d (%d)\n", decAllocBytes, -n); */
8134  } /* decFree */
8135#define malloc(a) decMalloc(a)
8136#define free(a) decFree(a)
8137#endif
8138