QUANTUM ALGEBRAIC SPACE

Most visitors of this webpage have no clue what the Quantum Algebra is: Quantum Algebraic Space is very strange field of numbers whereas the hypercube is a ball because number of quant alongside diagonal is equal to the number of quant on edge of the hypercube. Hyper cube in 2D space is just a square and the following figure best portraits the situation:

Pythagorean Theorem does not rule in Quantum Algebraic Space, therefore the diagonal of rectangle is:

Diagonal of rectangle in Real Algebraic Space is:

Quantum Algebraic Space offers some outstanding methods for optimization of integer algorithms when it is used to mimic Real Algebraic Space. In this case, the objective is to keep discrepancy of Quantum Curve less than a single quant in respect to Real Curve, i.e. to keep accumulated error below a pixel because than it cannot be exposed. Single pixel on screen matches a quant in Quantum Algebraic Space and therefore Quantum Algebraic Theory is fully applicable as representation of Pixel Computer Graphic. It is interesting that genuine Bresenham line drawing algorithm has side segments twice shorter than inner ones while my algorithm maintains all segments equal and this is achieved by adjustment of quantum LP norm only. I had later expanded this theory of LP Norm Test in Quantum Space to the Real Space too.
Both of my first two books heavily exploited Quantum Algebra in series of generalization, including generalized Bresenham method with variable LP norms and also some other cyclic integer algorithms too. Sadly, with the advancement of progress an ultimate imperative of integer algorithms usage started to fade leaving most of these neat achievements of mine out of limelight, practically relinquishing them to oblivion. I still stand that integer algorithms should be used whenever possible instead of real ones, i.e. floating point ones because error accumulation control is much better managed.Therefore quantum integer algorithms should be used prior real ones, despite the fact that real, i.e. floating point algorithms are way much easier for comprehension and handling.

 

Algorithms

This web page contains algorithms that I had been developing over the years and that were publishes in my book mentioned on the C.V. page. The algorithms belong to the domain of Computer Raster Graphics, Integer Computations and Numerical Analysis.
The algorithms from the area of the Computer Raster Graphics and Integer Computations are based on the theorem of eushaustia (i.e. searching) in quantum field that claims that we can find target quantum position in the quantum domain in the finite number of iterations with the binary search approach.
These algorithms are especially suitable for implementation in silicon.
Further in the text it will be shown that the quantum algorithm can compute the cosines, logarithm and exponent. Although the approach is not fast it is very accurate.

 


 



 

Quantum Dividing Algorithm

Dividing algorithm is very simple and yet really effective. Usage of the algorithm is demonstrated in the program BigNum freely available for download on the site.

Quantum Dividing Algorithm

DECLARE SUB QDIV (c%, a%, b%)
DECLARE SUB PUSH (a%)
DECLARE SUB POP (a%)
CLS
DIM SHARED STCK(1000) AS INTEGER, SP AS INTEGER
SP = 0
INPUT "A = ", a%
INPUT "B = ", b%
PRINT a%; "\"; b%; "=";
QDIV c%, a%, b%
PRINT c%, a%
END

SUB QDIV (DX%, AX%, CX%)
    DX% = 1
    DX% = AX%
    DO
        CX% = -DX%
        CX% = DX% AND CX%
        DX% = DX% - CX%
        LOOP WHILE DX%
            SWAP CX%, DX%
            SI% = DX%
        DO
        DX% = DX% \ 2
        CX% = CX% + 1
    LOOP WHILE DX%
    CX% = CX% - 1
    DX% = SI%
    DI% = CX%
    SI% = SI% \ 2
    DO
        DI% = DI% \ 2
        IF DX% + SI% <= AX% THEN
            DX% = DX% + SI%
            CX% = CX% + DI%
        END IF
        SI% = SI% \ 2
    LOOP WHILE SI%
END SUB

Demonstration of the quantum integer-dividing algorithm is available in the source of the calculator’s program “BigNum” available on the site.

This algorithm is neither public domain nor freeware. If you charge money using it within a product you sell, you require a commercial license.

 


 



 

Quantum Integer Square Rooting

The algorithm uses only simple processor arithmetic instructions like addition, subtraction, shifting and comparation. Furthermore, the algorithm is scalable and it can be applied on the input argument of arbitrary size. It has fixed number of iterations. The number of iterations that are necessary to reach correct result is equal to the half number of bits of input argument or the number of bits in output argument that holds the result, not the other one that holds remainder. All the variables in the routine have the same size in bits as the input parameter.
The algorithm yields the results and remainder too. It uses only addition, subtraction and shifting and thus it is very suitable to be utilized into chips.
It is completely based on the theory of dividing of the interval based on the formula:

(1)

(x ± Δx)2 =  x2 ± 2 · x · Δx  + Δx2

So we have the basic idea described by the routine:

FUNCTION SQRI (IN)
    DX = 128
    DX2 = 16384
    X = 0
    DO
        X21 = X2 + 2 * X * DX + DX2
        DO WHILE X21 > IN
            DX = DX / 2
            DX2 = DX2 / 4
            X21 = X2 + 2 * X * DX + DX2
        LOOP
        X2 = X21
        X = X + DX
        DX = DX / 2
        DX2 = DX2 / 4
    LOOP WHILE DX
    SQRI = X
END FUNCTION

After a few rudimental optimizations we have:

Quantum Square Rooting Algorithm

DECLARE FUNCTION ISQR% (DI%)
DEFINT A-Z
INPUT "X = ", DI
PRINT ISQR(DI)
END

FUNCTION ISQR% (DI)
    SI = 0
    DX = 0
    AL = 0
    AH = 128
    BX = 16384
    DO
        CX = SI + DX + BX
        DX = DX \ 2
        IF DI >= CX THEN
            SI = CX
            AL = AL + AH
            DX = DX + BX
        END IF
        BX = BX \ 4
        AH = AH \ 2
    LOOP WHILE AH
    ISQR% = AL
END FUNCTION

The above algorithm could be more optimized and then it becomes:

‘AX = Input
‘DX = Output
‘BX = Remainder
Sub SQRT(AX As Long, DX As Long, BX As Long)
    Dim SI As Long, DI As Long
    BX = 0
    DX = 0
    DI = 1073741824 'I.e. 2n-2
    Do
        SI = BX + DX + DI
        DX = DX \ 2
        If AX >= SI Then
            BX = SI
            DX = DX + DI
        End If
        DI = DI \ 4
    Loop While DI
    BX = AX - BX
End Sub

The basic demonstration of the routine is given by the following DOS program in I80286 assembly language that computes square root from the users’ input:

;Author of program & algorithm:
;Andrija Radovic
;E-mail: andrija_radovic@andrijar.com
;Web: http:www.andrijar.com
;Adress:
;Nike Strugara 13a
;11030 Beograd,
;Yugoslavia
;Copyright C1990-2003
.MODEL  TINY
.386C
.CODE
ORG     100H
SQRTD3_4:
PUSH    CS
PUSH    CS
POP     DS
POP     ES
M_DO:
        LEA     SI, WC
        LEA     DI, W8
        CALL    COPYSTD
        CALL    PUT_WL
        CALL    TSPACE
        LEA     SI, WC
        LEA     DI, W8
        CALL    COPYSTD
        CALL    SQRT_WX
        CALL    PUT_WL
        CALL    TSPACE
        LEA     SI, W9
        LEA     DI, W8
        CALL    COPYSTD
        CALL    PUT_WL
        CALL    NEW_ROW
        LEA     DI, WC
        ;LEA    SI, WADD
        LEA     SI, W9
        CALL    ADD_DS
        MOV     AH, 6
        MOV     DL, 0FFH
        INT     21H
        CMP     AL, 27
JNZ     M_DO
RET

CELLS   EQU     6
STEP    EQU     4
TOTAL   EQU     STEP * CELLS
COUNT   EQU     TOTAL - STEP

TSPACE  PROC
        LEA     DX, SPCL
        MOV     AH, 9
        INT     21H
        RET
TSPACE  ENDP

NEW_ROW PROC
        LEA     DX, NEWROWL
        MOV     AH, 9
        INT     21H
        RET
NEW_ROW ENDP

ADD_DS  PROC
        STD
        MOV     ECX, CELLS
        ADD     SI, COUNT
        SUB     DI, STEP
        CLC
        ADD_DS_D0:
                LODSD
                ADC     [EDI + STEP * ECX], EAX
        LOOP    ADD_DS_D0
        RET
ADD_DS  ENDP

SUB_DS  PROC
        STD
        MOV     ECX, CELLS
        ADD     SI, COUNT
        SUB     DI, STEP
        CLC
        SUB_DS_D0:
                LODSD
                SBB     [EDI + STEP * ECX], EAX
        LOOP    SUB_DS_D0
        RET
SUB_DS  ENDP

CMP_DS  PROC
        STD
        MOV     ECX, CELLS
        ADD     SI, COUNT
        SUB     DI, STEP
        CLC
        CMP_DS_D0:
                LODSD
                SBB     EAX, [EDI + STEP * ECX]
        LOOP    CMP_DS_D0
        RET
CMP_DS  ENDP

SHR_D   PROC
        XOR     EBX, EBX
        MOV     ECX, CELLS
        SHR_D_D0:
                RCR     DWORD PTR [EDI + STEP * EBX], 1
                INC     EBX
        LOOP    SHR_D_D0
        RET
SHR_D   ENDP

IS_ZERO PROC
        MOV     ECX, CELLS
        SUB     EDI, STEP
        XOR     EBX, EBX
        IS_ZERO_DO:
                OR      EBX, [EDI + STEP * ECX]
        LOOP    IS_ZERO_DO
        RET
IS_ZERO ENDP

SETZD   PROC
        CLD
        XOR     EAX, EAX
        MOV     ECX, CELLS
        REP     STOSD
        RET
SETZD   ENDP

COPYSTD PROC
        CLD
        MOV     ECX, CELLS
        REP     MOVSD
        RET
COPYSTD ENDP

SQRT_WX PROC
        LEA     DI, QSI
        CALL    SETZD
        LEA     DI, QDX
        CALL    SETZD
        LEA     SI, QV1
        LEA     DI, QBX
        CALL    COPYSTD
        START_DO:
                LEA     SI, QSI
                LEA     DI, QCX
                CALL    COPYSTD
                LEA     SI, QDX
                LEA     DI, QCX
                CALL    ADD_DS
                LEA     SI, QBX
                LEA     DI, QCX
                CALL    ADD_DS
                LEA     DI, QDX
                CALL    SHR_D
                LEA     SI, W8
                LEA     DI, QCX
                CALL    CMP_DS
                JC      END_IF
                        LEA     SI, QCX
                        LEA     DI, QSI
                        CALL    COPYSTD
                        LEA     DI, QDX
                        LEA     SI, QBX
                        CALL    ADD_DS
                END_IF:
                LEA     DI, QBX
                CALL    SHR_D
                CALL    SHR_D
                CALL    IS_ZERO
        JNZ     START_DO
        LEA     SI, W8
        LEA     DI, W9
        CALL    COPYSTD
        LEA     DI, W9
        LEA     SI, QSI
        CALL    SUB_DS
        LEA     SI, QDX
        LEA     DI, W8
        CALL    COPYSTD
        RET
SQRT_WX ENDP

PUT_WL  PROC
        LEA     SI, RESULT
        CLD
        MOV     EBP, 10
        W8_DO0:
                LEA     DI, W8
                XOR     EDX, EDX
                MOV     EBX, EDX
                MOV     CX, CELLS - 1
                W8_DO1:
                        MOV     EAX, [DI]
                        DIV     EBP
                        STOSD
                        OR      BX, AX
                LOOP    W8_DO1
                MOV     EAX, [DI]
                DIV     EBP
                MOV     [DI], EAX
                DEC     SI
                ADD     DL, 48
                MOV     [SI], DL
                OR      EBX, EAX
        JNZ     W8_DO0
        MOV     DX, SI
        MOV     AH, 9
        INT     21H
        RET
PUT_WL  ENDP

INTRES  DB      60 DUP(?)
RESULT  DB      '$'
SPCL    DB      '      $'
NEWROWL DB      13, 10, '$'

WADD    DD      0, 0, 1, 431E0FAEH, 6D7217CAH, 0A0000000H
WC      DD      28C87CB5H, 0C89A2571H, 0EBFDCB54H, 864ADA83H, 4A000000H, 0
QV1     DD      40000000H, (CELLS - 1) DUP(0)
W8      DD      CELLS DUP(?)
W9      DD      CELLS DUP(?)
QSI     DD      CELLS DUP(?)
QDX     DD      CELLS DUP(?)
QBX     DD      CELLS DUP(?)
QCX     DD      CELLS DUP(?)
QAH     DD      CELLS DUP(?)
QDI     DD      CELLS DUP(?)

END     SQRTD3_4

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved.
If you charge money using it within a product you sell, you require a commercial license!

 

Source code is availabe below:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved. The algorithm is property of its author and it cannot be incorporated in any chip or hardware without prior explicit author’s agreement.
If you charge money using it within a product you sell, you require a commercial license!

Demo routine given in ASM that demonstrate the integer square rooting of the 24 byte long input arguments and the biggest number that has to be sent to the routine is 6277101735386680763835789423207666416102355444464034512895. The routine is quite scalable and its precision can be easily extended.
Its output is shown on the picture below:

You can download demo program by pressing the button below:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved.
If you charge money using it within a product you sell, you require a commercial license!

 

You can download its source code in Masm assembly language by pressing the button below:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved.
The algorithm is property of its author and it cannot be incorporated in any chip or hardware without prior explicit author’s agreement.
If you charge money using it within a product you sell, you require a commercial license!

These routine should work in DOS or DOS Windows.

 


 



 

Quantum Line Drawing algorithm

There are several algorithms for line drawing too. These algorithms have only one question per break and one integer dividing on the beginning. The algorithms are extremely fast and suitable for silicon’s implementation.
The algorithm is based on the quite different premises than the Bresenham’s one.
The algorithm is especially optimized to work with the bit-planes and black/white images and thus it is suitable to be utilized in laser printers.
The main characteristic of the algorithm is equal widths of middle-breaks of line as it is shown on the picture right of the text.
Basic demonstration of the algorithm is given on the following listing:

SCREEN 12
    FOR i% = 0 TO 639 STEP 10
        KOSLINE 0, 0, i%, 199
    NEXT
    FOR i% = 195 TO 0 STEP -5
        KLINE 0, 0, 639, i%
    NEXT
END

SUB HLINE (x1%, x2%, y%)
    LINE (x1%, y%)-(x2%, y%)
END SUB

SUB KLINE (x1%, y1%, x2%, y2%)
    dx% = ABS(x2% - x1%) + 1
    dy% = ABS(y2% - y1%) + 1
    b% = dy% - dx%
    IF b% < 0 THEN
        IF x1% > x2% THEN
            SWAP x1%, x2%
            SWAP y1%, y2%
        END IF
        IF y1% > y2% THEN
            sign% = -1
        ELSE
            sign% = 1
        END IF
        c1% = dx% \ dy%
        b% = b% + dx% - dx% MOD dy%
        c1% = c1% + 1
        xt% = x1%
        e% = b% - 1
        FOR y1% = y1% TO y2% STEP sign%
            IF b% > 0 THEN
                b% = b% - dy%
                x1% = x1% - 1
            END IF
            b% = b% + e%
            x1% = x1% + c1%
            HLINE xt%, x1% - 1, y1%
            xt% = x1%
        NEXT
    ELSE
        IF y1% > y2% THEN
            SWAP x1%, x2%
            SWAP y1%, y2%
        END IF
        IF x1% > x2% THEN
            sign% = -1
        ELSE
            sign% = 1
        END IF
        c1% = dy% \ dx%
        b% = -b% + dy% - dy% MOD dx%
        c1% = c1% + 1
        e% = b% - 1
        yt% = y1%
        FOR x1% = x1% TO x2% STEP sign%
            IF b% > 0 THEN
                b% = b% - dx%
                y1% = y1% - 1
            END IF
            b% = b% + e%
            y1% = y1% + c1%
            VLINE x1%, yt%, y1% - 1
            yt% = y1%
        NEXT
    END IF
END SUB

SUB VLINE (x%, y1%, y2%)
    LINE (x%, y1%)-(x%, y2%)
END SUB

Screen of the DEMOVGA  assembly program:

For downloading demonstration code written for VGA DOS mode 12 in 80X86 assembler press the button (press any key for next stage):

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved.
If you charge money using it within a product you sell, you require a commercial license.

 

For download of assembly source press button below:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved. The algorithm is property of its author and it cannot be incorporated in any chip or hardware without prior explicit author’s agreement.
If you charge money using it within a product you sell, you require a commercial license.


Ega3d demo

For download of the algorithm that demonstrates the ability of its usage on the specific embedded weak hardware with monochrome video memory is demonstrated by the following program:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved.
If you charge money using it within a product you sell, you require a commercial license!

 

For download of assembly source press button below:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved. The algorithm is property of its author and it cannot be incorporated in any chip or hardware without prior explicit author’s agreement.
If you charge money using it within a product you sell, you require a commercial license!

The routine designed to the True Color video devices is a different one and it optimized to deal with the bigger piles of data dedicated to pixels consisted at least of byte triplets.
Lines draw by the algorithm are shown on the right picture.
The essential of the algorithm is presented by the following listing in Basic:

SCREEN 13
    DEF SEG = &HA000
    CLS
    FOR i% = 0 TO 319
        kline1 0, 0, i%, 199, (i% MOD 254) + 1
    NEXT
    FOR i% = 199 TO 0 STEP -1
        kline1 0, 0, 319, i%, (i% MOD 254) + 1
    NEXT
END

SUB hline (a%, b%, c%)
    LINE (a%, c%)-(b%, c%)
END SUB

SUB kline1 (x1%, y1%, x2%, y2%, col%)
    dx% = ABS(x2% - x1%) + 1
    dy% = ABS(y2% - y1%) + 1
    IF dx% > dy% THEN
        IF x1% > x2% THEN
            SWAP x1%, x2%
            SWAP y1%, y2%
        END IF
        IF y1% > y2% THEN dl% = -320 ELSE dl% = 320
        c% = dy%
        l% = dx% \ dy%
        o% = 2 * (dx% MOD dy%)
        a& = y1% * 320& + x1%
        FOR i% = 1 TO dy%
            k% = l%
            c% = c% - o%
            IF c% < 0 THEN
                c% = c% + 2 * dy%
                k% = k% + 1
            END IF
            FOR j% = 1 TO k%
                POKE a&, col%
                a& = a& + 1
            NEXT
            a& = a& + dl%
        NEXT
    ELSE
        IF y1% > y2% THEN
            SWAP x1%, x2%
            SWAP y1%, y2%
        END IF
        IF x1% > x2% THEN dl% = -1 ELSE dl% = 1
        c% = dx%
        l% = dy% \ dx%
        o% = 2 * (dy% MOD dx%)
        a& = y1% * 320& + x1%
        FOR i% = 1 TO dx%
            k% = l%
            c% = c% - o%
            IF c% < 0 THEN
                c% = c% + 2 * dx%
                k% = k% + 1
            END IF
            FOR j% = 1 TO k%
                POKE a&, col%
                a& = a& + 320
            NEXT
            a& = a& + dl%
        NEXT
    END IF
END SUB

SUB vline (a%, b%, c%)
    LINE (a%, b%)-(a%, c%)
END SUB

For download of the assembly-coded program that demonstrates the algorithm press the button below (press any key for next stage):

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved.
If you charge money using it within a product you sell, you require a commercial license!

 

For download of assembly source press button below:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved. The algorithm is property of its author and it cannot be incorporated in any chip or hardware without prior explicit author’s agreement.
If you charge money using it within a product you sell, you require a commercial license!

 


 



 

Quantum Ellipse Drawing Algorithm

The algorithm is based on the same premises as the Bresenham’s Circle drawing algorithm. The algorithm uses few multiplications on its start and it is able to draw ellipse with the addition and subtraction. Maximal width in bits of the registers used in the routine is twice of width of input parameters. 

Algorithm is given by following listing:

DECLARE SUB elipse (xx%, yy%, r1%, r2%)
DECLARE SUB eplot (x%, y%, a%, b%)
SCREEN 11
elipse 320, 240, 310, 100
elipse 320, 240, 100, 230
END

SUB elipse (xx%, yy%, r1%, r2%)
    rr1& = r1% * CLNG(r1%)
    r21& = rr1& + rr1&
    r41& = r21& + r21&
    rr2& = r2% * CLNG(r2%)
    r22& = rr2& + rr2&
    r42& = r22& + r22&
    k& = r2% * r21&
    p& = r41& + r42&
    cc& = r22& + rr1& - k&
    k& = k& + k&
    rf2& = -r41&
    r22& = r22& + p&
    x% = 0
    y% = r2%
    DO
        eplot xx%, yy%, x%, y%
        IF cc& >= 0 THEN
            y% = y% - 1
            k& = k& - r41&
            cc& = cc& - k&
        END IF
        cc& = cc& + rf2& + r22&
        rf2& = rf2& + r42&
        x% = x% + 1
    LOOP UNTIL rf2& > k&
    r22& = r22& - p&
    k& = r1% * r22&
    cc& = r21& + rr2& - k&
    k& = k& + k&
    rf1& = -r42&
    r21& = r21& + p&
    x% = r1%
    y% = 0
    DO
        eplot xx%, yy%, x%, y%
        IF cc& >= 0 THEN
            x% = x% - 1
            k& = k& - r42&
            cc& = cc& - k&
        END IF
        cc& = cc& + rf1& + r21&
        rf1& = rf1& + r41&
        y% = y% + 1
    LOOP UNTIL rf1& > k&
END SUB

SUB eplot (x%, y%, a%, b%)
    PSET (x% + a%, y% + b%)
    PSET (x% + a%, y% - b%)
    PSET (x% - a%, y% + b%)
    PSET (x% - a%, y% - b%)
END SUB

All rights reserved. The algorithm is property of its author and it cannot be incorporated in any chip or hardware without prior explicit author’s agreement.
If you charge money using it within a product you sell, you require a commercial license!

 


 



 

TRANSCEDENTAL FUNCTIONS AND QUANTUM SPACE

Algebriac Quantum theory (i.e. finite ring of rational numbers) is able to compute the values of the classic transcendental functions like sinus, cosines, exponential and logarithm although it is not recommended way of computing these functions. These methods are important for theoretical aspects only. These all show that formal mathematics is the most powerful on the analytical functions and its ability to bring us computational solutions of arbitrary analytical function by Taylor’s actually feeds its power from the analytical definitions of their derivations. It means that actually we are not able to find the whole curve only by one its point and we are able to do this on the analytical curves: we first find the values in the convergence radius away from the beginning point and so one. Recursively we can reach every point on the curve on the way.
So, we can agree that the following relations are neither the magic nor the hoax because these rules are applicable only on analytical functions.

LOGARITHM FUNCTION IN QUANTUM SPACE

The following relation defines logarithm function:

(2)

So we have:

(3)

And:

(4)

The following program computes the value of LOGn(x) in the predefined interval:

DEFDBL A-Z
fa = 0#
fb = 10#
a = 1#
b = 1024#
e = 0#
DO
    INPUT "k = ", k
    IF k >= a AND k <= b THEN EXIT DO
    PRINT "k must be between 1 & 1024."
    PRINT
LOOP
DO
    c = SQR(a * b)
    fc = .5# * (fa + fb)
    IF k < c THEN
        b = c
        fb = fc
    ELSE
        a = c
        fa = fc
    END IF
    PRINT a; b; c, fc
LOOP UNTIL ABS(c - k) <= e
PRINT
PRINT
PRINT "LOG(" + STR$(k) + " ) ="; STR$(fc)
END

EXPONENTIAL FUNCTION IN QUANTUM SPACE

Exponential function is defined by the following relation:

(5)

The following program demonstrates computing of the exponential function:

DEFDBL A-Z
fa = 1#
fb = 1024#
a = 0#
b = 10#
e = 0#
DO
    INPUT "k = ", k
    IF k >= a AND k <= b THEN EXIT DO
    PRINT "k must be between 0 & 10."
    PRINT
LOOP
DO
    c = .5# * (a + b)
    fc = SQR(fa * fb)
    IF k < c THEN
        b = c
        fb = fc
    ELSE
        a = c
        fa = fc
    END IF
    PRINT a; b; c, fc
LOOP UNTIL ABS(c - k) <= e
PRINT
PRINT
PRINT "EXP(" + STR$(k) + " ) ="; STR$(fc)
END

SINE and COSINE

The following relation defines cosine function:

(6)

The following program demonstrates computing of the cosines function:

CLS
INPUT x#
r# = 3.1415926589793#
'r# = 180#
l# = 0#
cr# = -1
cl# = 1
a# = .5# * (r# + l#)
ca# = 0
'PRINT ca#: STOP
i% = 0
e# = .000000000000001#
DO
    i% = i% + 1
    PRINT "Pokusaj"; i%, a#, x#, ca#
    IF x# < a# THEN
        r# = a#
        cr# = ca#
    ELSE
        l# = a#
        cl# = ca#
    END IF
    a# = .5# * (l# + r#)
    ca0# = ca#
    ca# = .5# * (SQR((1# + cl#) * (1# + cr#)) - SQR((1# - cr#) * (1# - cl#)))
LOOP WHILE ABS(ca# - ca0#) > e#
PRINT
PRINT ca#, COS(x#)
END

Sine function is just π/2 translated Cosine function:

(7)

COS(x) = SIN(x + π / 2)

I.e.

(8)

SIN(x) = COS(x - π / 2)

These all are sufficient enough for computing of the Sine and Cosine functions.

 

DAY in Week

Following program computes day in week in wide range of dates using only integer arithmetic. The algorithm is much better then classic one because it is not limited only to years after 1980. It covers whole AD range of time. So, you can compute the day when the Newton or Shakespeare was born.
Program source:

DIM a$(6)
FOR i% = 0 TO 6
READ a$(i%)
NEXT
b$ = COMMAND$
IF b$ = "" THEN INPUT "Year-Month-Day: ", b$
IF LTRIM$(RTRIM$(b$)) = "" THEN END i% = INSTR(b$, ".")
DO WHILE i%
  MID$(b$, i%, 1) = "-"
  i% = INSTR(i% + 1, b$, ".")
LOOP i% = INSTR(b$, "-")
IF i% = 0 THEN END
j% = INSTR(i% + 1, b$, "-")
IF j% = 0 THEN END
g% = VAL(LEFT$(b$, i% - 1))
m% = VAL(MID$(b$, i% + 1, j% - i% - 1))
d% = VAL(MID$(b$, j% + 1, LEN(b$)))
IF m% < 1 OR m% > 12 THEN END
IF d% < 1 OR d% > 31 THEN END
a& = 1200& * g% + 100& * m% - 285&
b& = 100& * ((367& * a& \ 1200&) + d%) - 175& * (a& \ 1200&)
c& = 75& * (a& \ 120000)
dan% = (((b& - b& MOD 100& - c&) \ 100&) + 1721115) MOD 7&
PRINT "(C) Andrija Radovic"
PRINT "Day:"; d%
PRINT "Month:"; m%
PRINT "Year:"; g%
PRINT PRINT "Day: "; a$(dan%)
END
DATA "Monday","Tuesday","Wednesday","Thursday","Friday","Saturday","Sunday"

All rights reserved. The algorithm is property of its author and it cannot be incorporated in any chip or hardware without prior explicit author’s agreement.
If you charge money using it within a product you sell, you require a commercial license!

 


 



 

Assembly Haiku Poetry

And finally the abstract art of the haiku poetry in 80X86 assembly language: very short and very nice b/w plot routine for video mode 640x480x2:

PLOT    PROC       ; DX = X, BX = Y
        SHL        BX, 4
        XOR        DX, 7
        BTS        WORD PTR [EBX + 4 * EBX], DX
        RET
PLOT    ENDP

This routine demonstrates that the 80X86 processors’ architecture still could be very effective for use in laser printers as main graphic processor.

You can download the complete program that demonstrates implementation of the Bresenham circle by pressing the following button:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved.
If you charge money using it within a product you sell, you require a commercial license!

For download of assembly source press button below:

This algorithm is protected by copyright low and thus it can be distributed under certain conditions only: the algorithm is free for non-commercial use.
The author will not be responsible for any kind of loss occurring by the usage of the one. The name of the author must stay visible on a program that uses the algorithm. All rights reserved. The algorithm is property of its author and it cannot be incorporated in any chip or hardware without prior explicit author’s agreement.
If you charge money using it within a product you sell, you require a commercial license!

 


 

BINARY TO DECIMAL ASCII STRING

This text describes 6 methods for the conversion of binary value into the decimal ASCII string. Proper tutorial for such operation virtually does not exist on the Internet and all the proposed methods are AD-Hoc written ones mainly without appropriate theoretical background with the lack of experience in assembly language optimizations. Most of described method are quite unique in public publishing and often are rarely used despite their great quality. This is mainly caused by deterioration of programming skill and increase of coding efforts by assembling of routines from libraries in DLL-s existing on the market. The programmers essentially remains without the knowledge of operation of the basic knowledge of the routines they are assembling in the programs and therefore they hardly can guarantee the quality of their products. This article is one modest attempt to explain people that there are at least non trivial ways to convert binary content into corresponding ASCII string and that there is one trivial way for that to be done – by usage of the appropriate windows API call which is also tremendously slow:

;Author of the program and of all algorithms is Andrija Radovic,
;All Rights Reserved, ©2010.
;This code should be assembled with:
;\masm32\bin\ML.EXE /c /coff /Cp /nologo /I\Masm32\Include ASCIIwin.asm
;and linked with the following line:
;\masm32\bin\LINK.EXE /SUBSYSTEM:CONSOLE /RELEASE /VERSION:4.0 /LIBPATH:"\Masm32\Lib" /section:".text",ERW ASCIIwin.obj /OUT:ASCIIwin.exe
.686
.MODEL		flat, stdcall
OPTION		casemap :none						;case sensitive
INCLUDE 	\masm32\include\windows.inc
INCLUDE 	\masm32\include\kernel32.inc
INCLUDELIB	\masm32\lib\kernel32.lib
INCLUDE 	\masm32\include\user32.inc
INCLUDELIB	\masm32\lib\user32.lib
INCLUDE 	\masm32\include\masm32.inc
INCLUDELIB	\masm32\lib\masm32.lib

;---------------------------------------------------------------------------------------------------------

.DATA
TESTS		DB	"This is the test...", 13, 10, 0
INTRES		DB	0, 0, 0, 0, 0, 0, 0, 0, 0, 0
RESULT		DB	0

;---------------------------------------------------------------------------------------------------------

.STACK	20000

;---------------------------------------------------------------------------------------------------------

.CODE
ASCII:
	INVOKE	StdOut, ADDR TESTS
	CALL	TESTR
	INVOKE	StdOut, ADDR TESTS
	CALL	MAINN
	INVOKE	StdOut, ADDR TESTS
INVOKE	ExitProcess, 0

;---------------------------------------------------------------------------------------------------------

TESTV	DD	0
TESTR	PROC
	MOV	TESTV, 3000000000
	MOV	EDX, TESTV
		CALL	EDX2DEC
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 1
		CALL	EAX2SUB
	CALL	NEW_ROW
	MOV	ESI, TESTV
		ADD	ESI, 2
		CALL	ESI2ASC
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 3
		CALL	EAX2ASC
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 4
		CALL	EAX2AST
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 5
		CALL	EAX2AFL
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 6
		CALL	EAX2DEC
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 7
		CALL	EAX2BTR
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 8
		CALL	EAXCMOV
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 9
		CALL	EAX2WIN
	CALL	NEW_ROW
	MOV	EAX, TESTV
		ADD	EAX, 10
		CALL	EAX2BCD
	CALL	NEW_ROW
	RET
TESTR	ENDP

;---------------------------------------------------------------------------------------------------------

MAINN	PROC
	MOV	TESTV, 1000000000
	LL0:
		;MOV	EDX, TESTV
		;CALL	EDX2DEC
		MOV	EAX, TESTV
		;CALL	EAX2ASC
		;CALL	EAX2DEC
		;CALL	EAX2AST
		;CALL	EAX2AFL
		;CALL	EAX2BTR
		;CALL	EAXCMOV
		CALL	EAX2BCD
		CALL	S_EQU
		MOV	EAX, TESTV
		CALL	EAX_SQR
		PUSH	EDX
		;CALL	EAX2DEC
		;CALL	EAX2BTR
		;CALL	EAXCMOV
		CALL	EAX2ASC
		;CALL	EAX2AST
		;CALL	EAX2AFL
		;MOV	ESI, EAX
		;CALL	ESI2ASC
		CALL	S_PLUS
		;POP	EAX
		;CALL	EAX2SUB
		POP	EAX
		;CALL	EAX2ASC
		CALL	EAX2DEC
		;CALL	EAX2ASF
		;CALL	EAX2AST
		;CALL	EAX2AFL
		CALL	NEW_ROW
		INC	TESTV
		CMP	TESTV, 1000000100
	JLE	LL0
	RET
MAINN	ENDP

;---------------------------------------------------------------------------------------------------------

SPCL	DB	9, 0

TSPACE	PROC
	INVOKE	StdOut, ADDR SPCL
	RET
TSPACE	ENDP

;---------------------------------------------------------------------------------------------------------

NEWROWL DB	13, 10, 0

NEW_ROW PROC
	INVOKE	StdOut, ADDR NEWROWL
	RET
NEW_ROW ENDP

;---------------------------------------------------------------------------------------------------------

EPE	DB	253, " + ", 0

S_PLUS	PROC
	INVOKE	StdOut, ADDR EPE
	RET
S_PLUS	ENDP

;---------------------------------------------------------------------------------------------------------

EQE	DB	" = ", 0

S_EQU	PROC
	INVOKE	StdOut, ADDR EQE
	RET
S_EQU	ENDP

;---------------------------------------------------------------------------------------------------------

D00	DB	02, 1
D01	DB	02, 2
D02	DB	02, 4
D03	DB	03, 8, 0
D04	DB	03, 6, 1
D05	DB	03, 2, 3
D06	DB	04, 4, 6, 0
D07	DB	04, 8, 2, 1
D08	DB	04, 6, 5, 2
D09	DB	05, 2, 1, 5, 0
D10	DB	05, 4, 2, 0, 1
D11	DB	05, 8, 4, 0, 2
D12	DB	05, 6, 9, 0, 4
D13	DB	06, 2, 9, 1, 8, 0
D14	DB	06, 4, 8, 3, 6, 1
D15	DB	06, 8, 6, 7, 2, 3
D16	DB	07, 6, 3, 5, 5, 6, 0
D17	DB	07, 2, 7, 0, 1, 3, 1
D18	DB	07, 4, 4, 1, 2, 6, 2
D19	DB	08, 8, 8, 2, 4, 2, 5, 0
D20	DB	08, 6, 7, 5, 8, 4, 0, 1
D21	DB	08, 2, 5, 1, 7, 9, 0, 2
D22	DB	08, 4, 0, 3, 4, 9, 1, 4
D23	DB	09, 8, 0, 6, 8, 8, 3, 8, 0
D24	DB	09, 6, 1, 2, 7, 7, 7, 6, 1
D25	DB	09, 2, 3, 4, 4, 5, 5, 3, 3
D26	DB	10, 4, 6, 8, 8, 0, 1, 7, 6, 0
D27	DB	10, 8, 2, 7, 7, 1, 2, 4, 3, 1
D28	DB	10, 6, 5, 4, 5, 3, 4, 8, 6, 2
D29	DB	11, 2, 1, 9, 0, 7, 8, 6, 3, 5, 0
D30	DB	11, 4, 2, 8, 1, 4, 7, 3, 7, 0, 1
D31	DB	11, 8, 4, 6, 3, 8, 4, 7, 4, 1, 2

EDX2DEC PROC								;The routine prints ASCII
	STD								;decimal content of EDX register
	MOV	DWORD PTR INTRES, 0					;via BCD arithmetic AAA
	MOV	DWORD PTR INTRES + 4, 0 				;instruction.
	MOV	WORD PTR INTRES + 8, 0					;Author: Andrija Radovic, ©2011
	LEA	EBX, D00
	LEA	EDI, 9 + INTRES
	PUT_I_DO:
		MOVZX	ECX, BYTE PTR [EBX]
		SHR	EDX, 1
		JNC	PUT_I_END_IF
			INC	EBX
			DEC	ECX
			XOR	AX, AX
			LEA	EDI, 9 + INTRES
			PUT_I_DO1:
				MOVZX	AX, AH
				ADD	AL, BYTE PTR [EDI]
				ADD	AL, BYTE PTR [EBX]
				AAA
				STOSB
				INC	EBX
			LOOPD	PUT_I_DO1
		PUT_I_END_IF:
		ADD	EBX, ECX
		TEST	EDX, EDX
	JNZ	PUT_I_DO
	INC	EDI
	OR	DWORD PTR INTRES, "0000"
	OR	DWORD PTR INTRES + 4, "0000"
	OR	WORD PTR INTRES + 8, "00"
	XOR	EDX, EDX
	CMP	BYTE PTR [EDI], "0"
	SETZ	DL
	ADD	EDX, EDI
	CMP	EDX, OFFSET RESULT
	SETZ	CL
	SUB	EDX, ECX
	CLD
	INVOKE	StdOut, EDX
	RET
EDX2DEC ENDP

;---------------------------------------------------------------------------------------------------------

ADDIT	DW	"00", "01", "02", "03", "04", "05", "06", "07", "08"
	DW	"09", "10", "11", "12", "13", "14", "15", "16", "17"
	DW	"18", "19", "20", "21", "22", "23", "24", "25", "26"
	DW	"27", "28", "29", "30"
WC	DB	02, "1"
	DB	02, "2"
	DB	02, "4"
	DB	03, "8", "0"
	DB	03, "6", "1"
	DB	03, "2", "3"
	DB	04, "4", "6", "0"
	DB	04, "8", "2", "1"
	DB	04, "6", "5", "2"
	DB	05, "2", "1", "5", "0"
	DB	05, "4", "2", "0", "1"
	DB	05, "8", "4", "0", "2"
	DB	05, "6", "9", "0", "4"
	DB	06, "2", "9", "1", "8", "0"
	DB	06, "4", "8", "3", "6", "1"
	DB	06, "8", "6", "7", "2", "3"
	DB	07, "6", "3", "5", "5", "6", "0"
	DB	07, "2", "7", "0", "1", "3", "1"
	DB	07, "4", "4", "1", "2", "6", "2"
	DB	08, "8", "8", "2", "4", "2", "5", "0"
	DB	08, "6", "7", "5", "8", "4", "0", "1"
	DB	08, "2", "5", "1", "7", "9", "0", "2"
	DB	08, "4", "0", "3", "4", "9", "1", "4"
	DB	09, "8", "0", "6", "8", "8", "3", "8", "0"
	DB	09, "6", "1", "2", "7", "7", "7", "6", "1"
	DB	09, "2", "3", "4", "4", "5", "5", "3", "3"
	DB	10, "4", "6", "8", "8", "0", "1", "7", "6", "0"
	DB	10, "8", "2", "7", "7", "1", "2", "4", "3", "1"
	DB	10, "6", "5", "4", "5", "3", "4", "8", "6", "2"
	DB	11, "2", "1", "9", "0", "7", "8", "6", "3", "5", "0"
	DB	11, "4", "2", "8", "1", "4", "7", "3", "7", "0", "1"
	DB	11, "8", "4", "6", "3", "8", "4", "7", "4", "1", "2"

EAX2BCD PROC								;The routine prints ASCII
	MOV	DWORD PTR INTRES, "0000"                                ;decimal content of EDX register
	MOV	DWORD PTR INTRES + 4, "0000"                            ;via BCD arithmetics on the
	MOV	WORD PTR INTRES + 8, "00"                               ;ADDIT array.
	LEA	EBX, WC 						;No specific instruction is used.
	LEA	EDI, 9 + INTRES 					;Author: Andrija Radovic, ©2011
	EAX2BCD_DO:
		MOVZX	ECX, BYTE PTR [EBX]
		SHR	EAX, 1
		JNC	EAX2BCD_END_IF
			INC	EBX
			DEC	ECX
			MOV	DH, "0"
			LEA	EDI, 9 + INTRES
			SUB	EDI, ECX
			EAX2BCD_DO1:
				MOVZX	EDX, DH
				ADD	DL, BYTE PTR [EDI + ECX]
				ADD	DL, BYTE PTR [EBX]
				MOV	DX, WORD PTR [2 * EDX + OFFSET ADDIT - 6 * "0"]
				MOV	BYTE PTR [EDI + ECX], DL
				INC	EBX
			LOOPD	EAX2BCD_DO1
		EAX2BCD_END_IF:
		ADD	EBX, ECX
		TEST	EAX, EAX
	JNZ	EAX2BCD_DO
	INC	EDI
	XOR	EDX, EDX
	CMP	BYTE PTR [EDI], "0"
	SETZ	DL
	ADD	EDX, EDI
	CMP	EDX, OFFSET RESULT
	SETZ	CL
	SUB	EDX, ECX
	INVOKE	StdOut, EDX
	RET
EAX2BCD ENDP

;---------------------------------------------------------------------------------------------------------

BASES	DD	1000000000, 100000000, 10000000, 1000000, 100000, 10000, 1000, 100, 10, 1
NUMDIG	DB	9, 9, 9, 8, 8, 8, 7, 7, 7, 6, 6, 6, 6, 5, 5, 5, 4, 4, 4, 3, 3, 3, 3, 2, 2, 2
	DB	1, 1, 1, 0, 0, 0

EAX2SUB PROC								;The routine prints ASCII
	MOV	DX, "00" - 101H                                         ;decimal content of EAX register
	BSR	EDI, EAX						;by repetitive subtractions
	CMOVZ	EDI, EAX						;with coefficients pulled from
	MOVZX	EDI, BYTE PTR [EDI + OFFSET NUMDIG]			;array with reducted number
	PUSH	EDI							;of iteration.
	EAX2SUB_DO1:							;Author: Andrija Radovic, ©2011
		MOV	EBX, DWORD PTR [4 * EDI + OFFSET BASES]
		EBX_DO2:
			INC	DL
			SUB	EAX, EBX
		JNC	EBX_DO2
		MOV	BYTE PTR [EDI + OFFSET INTRES], DL
		INC	EDI
		MOV	DL, DH
		ADD	EAX, EBX
	JNZ	EAX2SUB_DO1
	POP	EDI
	CMP	BYTE PTR [EDI + OFFSET INTRES], "0"
	SETZ	AL
	LEA	EDI, [EDI + EAX + OFFSET INTRES]
	CMP	EDI, OFFSET INTRES + 10
	SETZ	AL
	SUB	EDI, EAX
	INVOKE	StdOut, EDI
	RET
EAX2SUB ENDP

;---------------------------------------------------------------------------------------------------------

ESI2ASC PROC								;The routine prints ASCII
	LEA	EDI, INTRES						;decimal content of ESI register
	MOV	AX, "00" - 101H                                         ;by repetitive subtractions
	PUSH	DWORD PTR 0						;with coefficients pulled from
	PUSH	DWORD PTR 1						;stack without counter.
	PUSH	DWORD PTR 10						;Author: Andrija Radovic, ©2011
	PUSH	DWORD PTR 100
	PUSH	DWORD PTR 1000
	PUSH	DWORD PTR 10000
	PUSH	DWORD PTR 100000
	PUSH	DWORD PTR 1000000
	PUSH	DWORD PTR 10000000
	PUSH	DWORD PTR 100000000
	MOV	EBX, 1000000000
	CLD
	EAS_DO1:
		EAS_DO2:
			INC	AX
			SUB	ESI, EBX
		JNC	EAS_DO2
		ADD	ESI, EBX
		STOSB
		MOV	AL, AH
		POP	EBX
		TEST	EBX, EBX
	JNZ	EAS_DO1
	MOV	AL, "0"
	MOV	ECX, 10
	LEA	EDI, INTRES
	REPE	SCASB
	DEC	EDI
	INVOKE	StdOut, EDI
	RET
ESI2ASC ENDP

;---------------------------------------------------------------------------------------------------------

ASCII_TABLE	DW	"00", "10", "20", "30", "40", "50", "60", "70", "80", "90", "00", "00"
		DW	"00", "00", "00", "00", "01", "11", "21", "31", "41", "51", "61", "71"
		DW	"81", "91", "00", "00", "00", "00", "00", "00", "02", "12", "22", "32"
		DW	"42", "52", "62", "72", "82", "92", "00", "00", "00", "00", "00", "00"
		DW	"03", "13", "23", "33", "43", "53", "63", "73", "83", "93", "00", "00"
		DW	"00", "00", "00", "00", "04", "14", "24", "34", "44", "54", "64", "74"
		DW	"84", "94", "00", "00", "00", "00", "00", "00", "05", "15", "25", "35"
		DW	"45", "55", "65", "75", "85", "95", "00", "00", "00", "00", "00", "00"
		DW	"06", "16", "26", "36", "46", "56", "66", "76", "86", "96", "00", "00"
		DW	"00", "00", "00", "00", "07", "17", "27", "37", "47", "57", "67", "77"
		DW	"87", "97", "00", "00", "00", "00", "00", "00", "08", "18", "28", "38"
		DW	"48", "58", "68", "78", "88", "98", "00", "00", "00", "00", "00", "00"
		DW	"09", "19", "29", "39", "49", "59", "69", "79", "89", "99", "00", "00"
BCRESUL 	DT	0

EAX2AST PROC								;The routine prints ASCII
	MOV	DWORD PTR BCRESUL, EAX					;decimal content of EAX register
	MOV	DWORD PTR BCRESUL + 4, 0				;by usage of coprocessor FBSTP
	FILD	QWORD PTR BCRESUL					;instruction which converts
	FBSTP	BCRESUL 						;number into the packed BCD.
	LEA	EDI, INTRES						;Unpacking of BCD is done via
	MOV	ECX, 5							;the table of unpacked values.
	CLD								;Author: Andrija Radovic, ©2011
	EAX2AST_DO:
		MOVZX	EAX, BYTE PTR [ECX + OFFSET BCRESUL - 1]
		MOV	AX, WORD PTR [2 * EAX + OFFSET ASCII_TABLE]
		STOSW
	LOOPD	EAX2AST_DO
	MOV	AL, "0"
	MOV	ECX, 10
	LEA	EDI, INTRES
	REPE	SCASB
	DEC	EDI
	INVOKE	StdOut, EDI
	RET
EAX2AST ENDP

;---------------------------------------------------------------------------------------------------------

BCDEX	DT	0

EAX2AFL PROC								;The routine prints ASCII
	STD								;decimal content of EAX register
	MOV	DWORD PTR BCDEX, EAX					;by usage of coprocessor FBSTP
	MOV	DWORD PTR BCDEX + 4, 0					;instruction which converts
	FILD	QWORD PTR BCDEX 					;number into the packed BCD.
	FBSTP	BCDEX							;Unpacking of BCD is done via
	MOV	EDX, DWORD PTR BCDEX					;SHR and SHRD instructions.
	MOVZX	EBX, WORD PTR BCDEX + 4 				;Author: Andrija Radovic, ©2011
	LEA	EDI, 9 + INTRES
	EAX2AFL_DO:
		MOV	EAX, EDX
		AND	EAX, 15
		OR	AL, "0"
		STOSB
		SHRD	EDX, EBX, 4
		SHR	EBX, 4
		MOV	EAX, EDX
		OR	EAX, EBX
	JNZ	EAX2AFL_DO
	LEA	EDX, [EDI + 1]
	CLD
	INVOKE	StdOut, EDX
	RET
EAX2AFL ENDP

;---------------------------------------------------------------------------------------------------------

EAX2DEC PROC								;This routine prints ASCII
	LEA	ECX, INTRES + 9 					;decimal content of EAX register
	MOV	EBX, 10 						;by its repetitive dividing by
	EAX2DEC_DO:							;10 using DIV instruction that
		XOR	EDX, EDX					;simultaneously yields result
		DIV	EBX						;and remainder which denotes
		OR	EDX, "0"                                        ;current decimal digit.
		MOV	BYTE PTR [ECX], DL				;Author: Andrija Radovic, ©2011
		TEST	EAX, EAX
	LOOPNZD EAX2DEC_DO
	LEA	EDX, [ECX + 1]
	INVOKE	StdOut, EDX
	RET
EAX2DEC ENDP

;---------------------------------------------------------------------------------------------------------

EAX2ASC PROC								;This routine prints ASCII
	LEA	ECX, INTRES + 9 					;decimal content of EAX register
	MOV	EDI, 858993459						;by its repetitive dividing by
	MOV	EBX, EAX						;10 using MUL instruction to
	AX2ASC_DO:							;divide by 10 via multiplication
		LEA	EAX, [EBX + 1]					;with the appropriate constant.
		MUL	EDI						;Author: Andrija Radovic, ©2011
		SHR	EDX, 1
		LEA	EAX, [4 * EDX + EDX]
		NEG	EAX
		LEA	EAX, [EBX + 2 * EAX + "0"]
		MOV	BYTE PTR [ECX], AL
		MOV	EBX, EDX
	LOOPNZD AX2ASC_DO
	LEA	EDX, [ECX + 1]
	INVOKE	StdOut, EDX
	RET
EAX2ASC ENDP

;---------------------------------------------------------------------------------------------------------

LB	DB	0F0H,0F1H, 1,3, 0F2H,4, 0F3H,0F4H, 2,7, 0F5H,0F6H, 6,8, 0F7H,9, 0F8H,0F9H
D	DD	0,1,2,3,4,5,6,7,8,9
	DD	00,10,20,30,40,50,60,70,80,90
	DD	000,100,200,300,400,500,600,700,800,900
	DD	0000,1000,2000,3000,4000,5000,6000,7000,8000,9000
	DD	00000,10000,20000,30000,40000,50000,60000,70000,80000,90000
	DD	000000,100000,200000,300000,400000,500000,600000,700000,800000,900000
	DD	0000000,1000000,2000000,3000000,4000000,5000000,6000000,7000000,8000000,9000000
	DD	00000000,10000000,20000000,30000000,40000000,50000000,60000000,70000000,80000000,90000000
	DD	000000000,100000000,200000000,300000000,400000000,500000000,600000000,700000000,800000000
	DD	900000000
	DD	0000000000,1000000000,2000000000,3000000000,4000000000,4294967295,4294967295,4294967295
	DD	4294967295,4294967295
	DD	1,10,100,1000,10000,100000,1000000,10000000,100000000,1000000000

EAX2BTR PROC								;This routine prints ASCII
	CLD								;decimal content of EAX register
	MOV	ESI, 400						;by binary tree digits
	MOV	EBX, EAX						;extraction.
	MOV	EAX, 5							;No specific instruction is used.
	EAX2BTR_DO1:							;Author: Andrija Radovic, ©2011
		CMP	EBX, DWORD PTR [4 * EAX + ESI + OFFSET D]
		SBB	EDX, EDX
		MOV	AL, BYTE PTR [2 * EAX + EDX + (OFFSET LB - 1)]
		TEST	AL, AL
	JNS	EAX2BTR_DO1
	AND	AX, 15
	LEA	EDI, 9 + INTRES
	SUB	EDI, EAX
	PUSH	EDI
	LEA	ESI, [EAX + 4 * EAX]
	MOV	EAX, 5
	SHL	ESI, 3
	EAX2BTR_DO3:
		CMP	EBX, DWORD PTR [4 * EAX + ESI + OFFSET D]
		SBB	EDX, EDX
		MOV	AL, BYTE PTR [2 * EAX + EDX + (OFFSET LB - 1)]
		TEST	AL, AL
	JNS	EAX2BTR_DO3
		AND	EAX, 15
		SUB	EBX, DWORD PTR [4 * EAX + ESI + OFFSET D]
		OR	AL, "0"
		STOSB
		MOV	EAX, 5
		SUB	ESI, 40
	JNC	EAX2BTR_DO3
	POP	EDX
	INVOKE	StdOut, EDX
	RET
EAX2BTR ENDP

;---------------------------------------------------------------------------------------------------------

LC	DW	0FF00H,0FF01H, 1,3, 0FF02H,4, 0FF03H,0FF04H, 2,7, 0FF05H,0FF06H, 6,8, 0FF07H,9
	DW	0FF08H,0FF09H
DC	DD	0,1,2,3,4,5,6,7,8,9
	DD	00,10,20,30,40,50,60,70,80,90
	DD	000,100,200,300,400,500,600,700,800,900
	DD	0000,1000,2000,3000,4000,5000,6000,7000,8000,9000
	DD	00000,10000,20000,30000,40000,50000,60000,70000,80000,90000
	DD	000000,100000,200000,300000,400000,500000,600000,700000,800000,900000
	DD	0000000,1000000,2000000,3000000,4000000,5000000,6000000,7000000,8000000,9000000
	DD	00000000,10000000,20000000,30000000,40000000,50000000,60000000,70000000,80000000,90000000
	DD	000000000,100000000,200000000,300000000,400000000,500000000,600000000,700000000,800000000
	DD	900000000
	DD	0000000000,1000000000,2000000000,3000000000,4000000000,4294967295,4294967295,4294967295
	DD	4294967295,4294967295
	DD	1,10,100,1000,10000,100000,1000000,10000000,100000000,1000000000

EAXCMOV PROC								;This routine prints ASCII
	CLD								;decimal content of EAX register
	MOV	ESI, 400						;by binary tree digits
	MOV	EBX, EAX						;extraction.
	MOV	EAX, 5							;CMOV instruction is used.
	EAXCMOV_DO1:							;Author: Andrija Radovic, ©2011
		CMP	EBX, DWORD PTR [4 * EAX + ESI + OFFSET DC]
		;CMOVC	 AX, WORD PTR [4 * EAX + (OFFSET LC - 4)]	 ;These two instructions
		;CMOVNC  AX, WORD PTR [4 * EAX + (OFFSET LC - 2)]	 ;work on some processors...

		CMOVC	DX, WORD PTR [4 * EAX + (OFFSET LC - 4)]	;Malfunction of x86 CMOV
		CMOVNC	DX, WORD PTR [4 * EAX + (OFFSET LC - 2)]	;requires these ones instead
		MOV	AX, DX						;of above two instructions.

		TEST	AX, AX
	JNS	EAXCMOV_DO1
	MOVZX	EAX, AL
	LEA	EDI, 9 + INTRES
	SUB	EDI, EAX
	PUSH	EDI
	LEA	ESI, [EAX + 4 * EAX]
	MOV	EAX, 5
	SHL	ESI, 3
	EAXCMOV_DO3:
		CMP	EBX, DWORD PTR [4 * EAX + ESI + OFFSET DC]
		;CMOVC	 AX, WORD PTR [4 * EAX + (OFFSET LC - 4)]	 ;These two instructions
		;CMOVNC  AX, WORD PTR [4 * EAX + (OFFSET LC - 2)]	 ;work on some processors...

		CMOVC	DX, WORD PTR [4 * EAX + (OFFSET LC - 4)]	;Malfunction of x86 CMOV
		CMOVNC	DX, WORD PTR [4 * EAX + (OFFSET LC - 2)]	;requires these ones instead
		MOV	AX, DX						;of above two instructions.

		TEST	AX, AX
	JNS	EAXCMOV_DO3
		MOVZX	EAX, AL
		SUB	EBX, DWORD PTR [4 * EAX + ESI + OFFSET DC]
		OR	AL, "0"
		STOSB
		MOV	EAX, 5
		SUB	ESI, 40
	JNC	EAXCMOV_DO3
	POP	EDX
	INVOKE	StdOut, EDX
	RET
EAXCMOV ENDP

;---------------------------------------------------------------------------------------------------------

NumFormat	DB	"%u",0
BufferW 	DB	32 DUP(0)

EAX2WIN PROC								;This routine prints ASCII EAX.
	INVOKE	wsprintf, ADDR BufferW, ADDR NumFormat, EAX		;It utilizes native Windows NT
	INVOKE	StdOut, ADDR BufferW					;subroutine.
	RET
EAX2WIN ENDP

;---------------------------------------------------------------------------------------------------------

EAX_SQR PROC								;EAX = SQR(EAX), square rooting
	XOR	ESI, ESI						;routine.
	XOR	EDX, EDX						;EDX is remainder.
	MOV	EBX, 1073741824 					;Author: Andrija Radovic, ©2011
	SQRT_DO:
		LEA	EDI, [EBX + ESI]
		ADD	EDI, EDX
		SHR	EDX, 1
		CMP	EAX, EDI
		JC	SQRT_END_IF
			MOV	ESI, EDI
			ADD	EDX, EBX
		SQRT_END_IF:
		SHR	EBX, 2
	JNZ	SQRT_DO
	SUB	EAX, ESI
	XCHG	EAX, EDX
	RET
EAX_SQR ENDP

;---------------------------------------------------------------------------------------------------------

END	ASCII

The Command Prompt windows of the program:

 

The full text is available on the link below: