Saturday 23 March 2013

SUBROUTINE TO CONVERT CHARACTERS IN MEMORY TO A DECIMAL VALUE

***********************************************************************************************************
                              AUTHOR:  ANUEBUNWA VICTOR OGECHUKWU                                            

               SUBROUTINE TO CONVERT CHARACTERS IN MEMORY TO A DECIMAL VALUE                            
 Subroutine CHAR2INTR converts characters in memory to a decimal value and stores it in AX.             
 i.e '1','2','3','4' in memory ==> 1234 in AX                                                          
 .......................................................................HOW TO USE......................................................................
 (1) Load the starting address of the memory into SI register.                                          
 (2) Call CHAR2INTR.                                                                                                          ***********************************************************************************************************

;         SAMPLE PROGRAM
.MODEL SMALL
.STACK
.DATA
    AVON DB ?
.CODE
START:        MOV AX, @DATA
            MOV DS, AX
           
            MOV AH, 3FH
            LEA DX, AVON
            INT 21H                    ;Reads characters into memory, using AVON as a starting address
           
            LEA SI, AVON            ;Loads starting address into SI
            CALL CHAR2INTR            ;Calls CHAR2INTR to convert characters to a decimal value
            MOV DX, AX                ;Puts decimal value into DX
            MOV AH, 02H
            INT 21H                    ;Displays character whose ASCII code equals the decimal value
           
            MOV AH, 4CH
            INT 21H

;Subroutine CHAR2INTR
CHAR2INTR PROC
            PUSH BX
            PUSH CX
            PUSH DX
            PUSH SI
            PUSHF
           
            MOV AX, 0000H
            MOV CX, 0000H
CLOOP1:        MOV AX, [SI]            ;Loads character currently pointed to into AX
            CMP AL, '9'
            JNLE XCLOOP1            ;Exits loop if character is not less or equal to '9'
            CMP AL, '0'
            JNGE XCLOOP1            ;Exits loop if character is not greater or equal to '0'
            INC CL                    ;Else, Keeps count of the number of characters being processed
            INC SI                    ;Moves pointer to the next character
            SUB AL, 30H                ;Converts character to digit
            PUSH AX                    ;Pushes digit to stack
            JMP CLOOP1                ;continues loop

XCLOOP1:    MOV BX, 0001H
            MOV DX, 0000H
CLOOP2:        CMP CL, 0                ;Checks number of characters processed
            JE XCLOOP2                ;Exits loop if no character was processed i.e CL = 0
            POP AX                    ;Else, pops digit from stack to AX
            MUL BL                    ;Multiplies digit with it's PLACEMENT-VALUE. RECALL: unit = 1, tens = 10, hundreds = 100 ...
            ADD DX, AX                ;Adds (digit * PLACEMENT-VALUE)s together. RECALL: 234 = (4 * 1) + (3 * 10) + (2 * 100) where 1,10,100 represent their PLACEMENT-VALUES
            MOV AX, 10               
            MUL BL                    ;Multiplies current PLACEMENT-VALUE by 10 to advance to the next PLACEMENT-VALUE.
            XCHG AX, BX                ;Puts result from multiplication back to BX
            DEC CX                    ;Reduces count
            JMP CLOOP2                ;Loop continues
           
XCLOOP2:    MOV AX, DX                ;Moves converted value to AX
           
            POPF
            POP SI
            POP DX
            POP CX
            POP BX
            RET
CHAR2INTR ENDP
;End of Subroutine CHAR2INTR

END START

view in pastebin

PROCEDURE TO DISPLAY CHARACTERS IN MEMORY

********************************************************************************************************************
                       AUTHOR: ANUEBUNWA VICTOR OGECHUKWU                                                        

                    PROCEDURE TO DISPLAY CHARACTERS IN MEMORY                                                   
 Procedure DISPLAY displays characters in memory starting from a given address till it encounters CARRIAGE-RETURN.
 ............................................HOW TO USE..........................................................
 (1) Load the starting address of the memory into SI register.                                                   
 (2) Call DISPLAY.                                                                                           
;********************************************************************************************************************

;         SAMPLE PROGRAM
.MODEL SMALL
.STACK
.DATA
    AVON DB ?
.CODE
START:        MOV AX, @DATA
            MOV DS, AX
           
            MOV AH, 3FH                ;Input string function
            LEA DX, AVON
            INT 21H
           
            LEA SI, AVON
            CALL DISPLAY
           
            MOV AH, 4CH
            INT 21H

;;Procedure DISPLAY
DISPLAY PROC
            PUSH AX
            PUSH DX
            PUSH SI
            PUSHF
           
            MOV AH, 02H
DLOOP1:        MOV DL, [SI]            ;Moves character at current address to DL
            CMP DL, 13
            JE XDLOOP1                ;Exits loop if DL contains CARRIAGE-RETURN
            INT 21H                    ;Else, displays character
            INC SI                    ;Moves to next address
            JMP DLOOP1                ;Continues loop
           
XDLOOP1:    POPF
            POP SI
            POP DX
            POP AX
            RET
DISPLAY ENDP
;End of procedure DISPLAY
   
END START

view in pastebin

Monday 4 March 2013

PROCEDURE TO COLLECT MULTIPLE DIGITS AS INPUT IN 8086 ASSEMBLY


;PROCEDURE TO COLLECT MULTIPLE DIGITS AS INPUT IN 8086 ASSEMBLY
;AUTHOR: ANUEBUNWA VICTOR O.
;ASSEMBLER: MASM611

;You should have the following declared in your data segment.
value DB 0000H
e1 DB "Wrong input",'$'

e2 DB 'No value entered',0AH,0DH,'Program exiting...','$'


;You may avoid using PUSHA and POPA if it gives error during assembling but be sure to backup needed values in AX,BX,CX and DX before calling this procedure.

;Beginning of procedure
read proc
PUSHA                           ;Push current values in register to stack
MOV AX, 0000H ;
MOV CX, 0000H ;
MOV BX, 0000H ;
MOV DX, 0000H ;Clears register AX,BX,CX and DX
.tryloop1:         MOV AH, 01H
INT 21H ;Calls DOS funtion to receive a character
JMP check ;Jumps to check character recieved
continue_loop: ;Where loop continues assuming character passes check
MOV BX, 0000H ;Clears BX again
MOV BL, AL ;Moves AL to BL
SUB BX, 30H ;Subtracts 30H to get the actual value of character
PUSH BX ;Push BX to stack
INC CX ;Increments CX to track the lenght of the value
CMP AL, 0DH ;Checks if character was carriage return
JNE .tryloop1 ;Jumps if not carrige return

CMP CX, 1 ;Checks if no value was entered
JE error_msg2 ;jumps if no value was entered
POP AX ;Pops out last value in stack(carrige return)
dec CX ;Decrements counter

MOV BX, 1 ;initialize multiplier
.tryloop2:          MOV AX, 0000H ;Clears AX
POP AX ;Pops data to AX
MUL BX ;Multiplies AX by BX
ADD value, AX ;Add AX to value

XCHG AX, BX ;Exchanges AX and BX
MOV BX, 10 ;Moves 10 into BX
MUL BX ;Multiplies AX by BX(containing 10)
XCHG AX, BX ;Exchanges back AX and BX
dec CX ;Decrements counter
JNE .tryloop2 ;Repeats until CX equals zero

MOV AH, 02H
MOV DL, 0aH
INT 21H ;Prints line-feed
POPA                      ;Pops values of register before procedure call from stack
RET ;returns control
read endp                                          ;End of procedure.

check: CMP AL, 0DH ;Checks if the character is carriage return
JE continue_loop ;Jumps back into loop if carriage return
CMP AL, '0' ;Checks if a non-digit was entered
JNGE error_msg
CMP AL, '9'
JNLE error_msg ;Displays error if a non-digit was entered
JMP continue_loop ;Else it jumps back into loop

error_msg: MOV AH, 02H
MOV DL, 0AH
INT 21H ;Prints line-feed
LEA DX, e1
MOV AH, 09H
INT 21H ;Prints string
JMP start ;Restarts program(assuming you have Start: as your starting label)


error_msg2: MOV AH, 02H
MOV DL, 0AH
INT 21H ;Prints line-feed
LEA DX, e2
MOV AH, 09H
INT 21H ;Prints string
JMP stp ;Stops program


Thursday 31 January 2013

PROGRAM TO DISPLAY A MULTIPLE DIGIT NUMBER IN 8086 ASSEMBLY LANGUAGE


;AUTHOR: ANUEBUNWA VICTOR O.
;PROGRAM TO DISPLAY A MULTIPLE DIGIT NUMBER IN 8086 ASSEMBLY ;LANGUAGE
;ASSEMBLER: MASM611

.MODEL SMALL
.STACK
.DATA
MSG DB 'The multiple digit number is: ','$'
.CODE

START: MOV AX, @DATA
        MOV DS, AX

       MOV AH, 09H
       LEA DX, MSG
       INT 21H         ;Calls MS DOS to display message

       MOV AX, 1234 ;Number to be displayed
       CALL display            ;Calls procedure display to display number

       MOV AH, 4CH
       INT 21H

;Display procedure from previous post should appear here.

END START

;OUTPUT
;The multiple digit number is: 1234

PROCEDURE TO DISPLAY A MULTIPLE DIGIT NUMBER IN 8086 ASSEMBLY LANGUAGE


Good day, Today we will improve on our program from previous post which calculates the average of two numbers in 8086 assembly language to calculate for n numbers, also, you would have noticed that our previous program collects, calculates and displays the average of numbers with a single digit and that doesn't qualify a good program.
Therefore, We will want our program to accept, calculate and display average for numbers with multiple digits.
First we modify our display procedure, making it able to display multiple digits numbers like 10, 80, 345 etc. instead of single characters.
Well, What our new procedure basically does is to split the provided value(in AX) to single digits(i.e by continually dividing it by 10 till it turns 0), change them to their ASCII code equivalence and display them using a loop.

Here is the sample code.
;ASSEMBLER: MASM611
display proc ;Beginning of procedure
MOV BX, 10 ;Initializes divisor
MOV DX, 0000H ;Clears DX
MOV CX, 0000H ;Clears CX

;Splitting process starts here
.Dloop1: MOV DX, 0000H ;Clears DX during jump
div BX ;Divides AX by BX
PUSH DX ;Pushes DX(remainder) to stack
INC CX ;Increments counter to track the number of digits
CMP AX, 0 ;Checks if there is still something in AX to divide
JNE .Dloop1 ;Jumps if AX is not zero

.Dloop2: POP DX ;Pops from stack to DX
ADD DX, 30H ;Converts to it's ASCII equivalent
MOV AH, 02H
INT 21H ;calls DOS to display character
LOOP .Dloop2 ;Loops till CX equals zero
RET ;returns control
display ENDP

Thursday 17 January 2013

PROGRAM TO CALCULATE AVERAGE OF TWO NUMBERS IN 8086 ASSEMBLY LANGUAGE


;AUTHOR: ANUEBUNWA VICTOR O
;PROGRAM TO CALCULATE AVERAGE OF TWO NUMBERS
;USING MASM ASSEMBLER

.MODEL SMALL
.STACK
DATA SEGMENT ; Beginning of data segment
num1 DB 10 ;Declaration of first value
num2 DB 3 ;Declaration of second value
average DB ?         ;Empty slot to store average
remainder DB " remainder ",'$'
rem DB ?         ;Empty slot to store remainder
DATA ENDS ;End of data segment
CODE SEGMENT ; Beginning of code segment
ASSUME CS: CODE, DS: DATA
Start: ;Starting address
MOV AX, DATA
MOV DS, AX ;Initializes the DS(Data segment) register

MOV AL, num1
ADD AL, num2
MOV AH, 00 ; Clears AH Register(Because this is where our remainder will be)
MOV BL, 02 ; Loads divisor into BL register
DIV BL ; DIV : divide AX by BL. Remainder in AH and result in AL

ADD AL, 48
MOV average, AL ;stores average
ADD AH, 48
MOV rem, AH ;stores remainder

CALL display          ;call procedure "display"

MOV AX, 4C00H ;Returns control to MS-DOS
INT 21H

display proc         ;Procedure "display"
MOV AH, 02H
MOV DL, average
INT 21H ;Displays average

MOV AH, 09H
LEA DX, remainder
INT 21H ;Displays message "remainder"

MOV AH, 02H
MOV DL, rem
INT 21H ;Displays remainder
ret ;returns control back to the point this procedure was called
display endp         ;End of procedure



CODE ENDS ;End of code segment
END Start ;End of program

;......................**********.......................................
;OUTPUT>:
;6 remainder 1