subroutine aptbadd (nbase, idiga, ndiga, idigb, ndigb,
     &                    idigcw, ndigm, idigc, ndigc, nerr)

ccbeg.
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
c
c                             SUBROUTINE APTBADD
c
c     call aptbadd (nbase, idiga, ndiga, idigb, ndigb,
c    &              idigcw, ndigm, idigc, ndigc, nerr)
c
c     Version:  aptbadd  Updated    2006 May 12 13:40.
c               aptbadd  Originated 2005 May 23 14:50.
c
c     Author:   Arthur L. Edwards, LLNL, L-298, Telephone (925) 422-4123.
c
c
c     Purpose:  To add the big integers "a" and "b", stored as the arrays of
c               non-negative base nbase digits idiga and idigb, of lengths
c               ndiga and ndigb, respectively, to get the big integer
c               "c", stored as the array of non-negative base nbase digits
c               idigc, of length ndigc.
c
c               The digits of idiga, idigb and idigc are the base nbase
c               digits representing the non-negative decimal integers ideca,
c               idecb and idecc, in order from most significant to least
c               significant, using the equation:
c               ideca = sum (idiga(n) * nbase^(N-n), n = 1, N = ndiga).
c               idecb = sum (idigb(n) * nbase^(N-n), n = 1, N = ndigb).
c               idecc = sum (idigc(n) * nbase^(N-n), n = 1, N = ndigc).
c               Flag nerr indicates any input error.
c
c               See aptbtod, aptdtob, aptbsub, aptbmul, aptbdiv, aptbpow,
c               aptbrtn, aptbfac.
c
c     Input:    nbase, idiga, ndiga, idigb, ndigb, idigcw, ndigm.
c
c     Output:   idigc, ndigc, nerr.
c
c     Glossary:
c
c     idiga     Input    A big integer "a", stored as an array of ndiga
c                          non-negative base nbase digits, in order from most
c                          to least significant.  If nbase exceeds 10, each
c                          "digit" may require 2 or more integers.  For example,
c                          for decimal integer 4821, nbase = 16 (hexadecimal),
c                          idiga(n) = (5, 13, 2, 1), with ndiga = 4, or
c                          4821 (dec) =  5 * 1 + 13 * 16 + 2 * 256 + 1 * 4096
c
c     idigb     Input    See idiga.  Array idigb may be idiga or idigc.
c
c     idigc     Input    See idiga.  Array idigc may be idiga or idigb.
c
c     idigcw    Input    Temporary working space for idigc.  See idiga.  Array
c                          idigcw must not be idiga, idigb or idigc, but must
c                          have its own memory space, which must be at least
c                          ndigm.
c
c     nbase     Input    The number base for which the digits of integer arrays
c                          idiga, idigb and idigc are the coefficients of
c                          the powers of nbase, in order from most to least
c                          significant.
c
c     ndiga     Input    The length of the integer array idiga.
c
c     ndigb     Input    The length of the integer array idigb.
c
c     ndigc     Output   The length of the integer array idigc.
c
c     ndigm     Input    The maximum number of words allowed in integer array
c                          idigc.  Memory space for idigc must be at least
c                          ndigm, and ndigm must be at least as big as
c                          1 + max (ndiga, ndigb).
c
c     nerr      Output   Indicates an input or a result error, if not zero.
c                          1 if nbase is less than 2.
c                          2 if ndiga is not positive.
c                          3 if any digits of idiga are negative.
c                          4 if ndigb is not positive.
c                          5 if any digits of idigb are negative.
c                          6 if ndigm is less than 1 + max (ndiga, ndigb).
c
cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
ccend.

c.... Dimensioned arguments.

      integer idiga(1)
      integer idigb(1)
      integer idigc(1)
      integer idigcw(1)

c.... Local variables.

      integer icarry
      integer itotal

cbugc***DEBUG begins.
cbug 9900 format (/)
cbug 9901 format (/ 'aptbadd adding the base nbase digit arrays',
cbug     &  ' idiga and idigb' /
cbug     &  '  to get base nbase digit array idigc.' /
cbug     &  '  nbase =',i7,', ndiga =',i20,', ndigb =',i20'.' )
cbug 9902 format ('  n =',i7,', idiga =',i7,'.')
cbug 9903 format ('  n =',i7,', idigb =',i7,'.')
cbug      write ( 3, 9901) nbase, ndiga, ndigb
cbug      write ( 3, 9900)
cbug      write ( 3, 9902) (n, idiga(n), n = 1, ndiga)
cbug      write ( 3, 9900)
cbug      write ( 3, 9903) (n, idigb(n), n = 1, ndigb)
cbugc***DEBUG ends.

c.... Test for input errors.

      nerr    = 0

      if (nbase .lt. 2) then
        nerr = 1
        go to 210
      endif

      if (ndiga .lt. 0) then
        nerr = 2
        go to 210
      endif

      if (ndiga .gt. 0) then
        do n = 1, ndiga
          if (idiga(n) .lt. 0) then
            nerr = 3
            go to 210
          endif
        enddo
      endif

      if (ndigb .lt. 0) then
        nerr = 4
        go to 210
      endif

      if (ndigb .gt. 0) then
        do n = 1, ndigb
          if (idigb(n) .lt. 0) then
            nerr = 5
            go to 210
          endif
        enddo
      endif

      nmax = 1 + max (ndiga, ndigb)

      if (ndigm .lt. nmax) then
        nerr = 6
        go to 210
      endif

c.... Initialize.

c.... Zero out tempory sum "cw".

      ndigcw = 1
      do n = 1, ndigm
        idigcw(n) = 0
      enddo

c.... Add "b" to "a" to get temporary sum "cw".

      icarry  = 0

      do n = 1, nmax
        na = 1 + ndiga - n
        nb = 1 + ndigb - n
        itotal = icarry

        if (n .le. ndiga) then
          itotal = itotal + idiga(na)
        endif

        if (n .le. ndigb) then
          itotal = itotal + idigb(nb)
        endif

        icarry     = itotal / nbase
        idigcw(n) = mod (itotal, nbase)

        if (idigcw(n) .gt. 0) then
          ndigcw = n
        endif

      enddo

c.... Store reversed tempory sum "cw" into "c".  Zero out "cw".

      ndigc = ndigcw
      do n = 1, ndigc
        nc = ndigc + 1 - n
        idigc(nc) = idigcw(n)
        idigcw(n) = 0
      enddo

  210 continue

      if (nerr .ne. 0) then
        ndigc = 0
        do n = 1, ndigm
          idigc(n) = -999999
        enddo
      endif

cbugc***DEBUG begins.
cbug 9911 format (/ 'aptbadd results:  nerr=',i2,', ndigc =',i7,'.')
cbug 9913 format ('  sum  n =',i7,', idigc =',i7,'.')
cbug      write ( 3, 9911) nerr, ndigc
cbug      write ( 3, 9900)
cbug      write ( 3, 9913) (n, idigc(n), n = 1, ndigc)
cbugc***DEBUG ends.
      return

c.... End of subroutine aptbadd.      (+1 line.)
      end

UCRL-WEB-209832