News:

MASM32 SDK Description, downloads and other helpful links
MASM32.com New Forum Link
masmforum WebSite

Memory Map

Started by zak100, February 19, 2010, 06:21:07 PM

Previous topic - Next topic

zak100

Hi,
I am facing prob with DAS:


AL=AL-CF-69
AL=0-1-69
AL=0-6A
AL=96H using 2's complement

DAS:
if ((96H and 0FH) > 9 or (AUXC=1)) ----TRUE because AUXC =1

al=al-6
al= 96 -6
al=90h

At this point AL should be 30H instead of 90H.


Can somebody help me with this prob.
Zulfi.

dedndave


; if ( (al and 0Fh) > 9 or (AuxC = 1)) then
;         al := al -6
;         AuxC = 1
; endif
; if (al > 9Fh or Carry = 1) then
;         al := al - 60h
;         Carry := 1
; endif

the last section subtracts another 60h
for this code, the carry flag is always set just prior to the DAS instruction

zak100

Ok. Thanks for your reply.

Zulfi.

zak100

Hi,
I have written the code and I now understand most of it but its not printing any new stuff i.e base address and length of region.
Following is the code:


;Declarations

arr  db 10 dup(0)
VAL1 db 0
VAL2 db 0
AscBuf  db      8 dup (0),' Kb Total Memory',0
mmap_ent dw ?
end_of_list db 1
MMap_Descriptor STRUCT
  BaseAddress   DQ      ?       ; * First qword = Base address
  ByteLength    DQ      ?       ; * Second qword = Length of "region"
  RangeType     DW      ?       ; * Next dword = Region "type"
  ACPI_Attrib   DW      ?       ; * Next dword = ACPI 3.0 Extended Attri
MMap_Descriptor ENDS

Call15_1        MMap_Descriptor <>      ; Set DI to point to the first one, and
Call15_2        MMap_Descriptor <>      ; increment by 24  to point to second.
Call15_3        MMap_Descriptor <>
Call15_4        MMap_Descriptor <>
Call15_5        MMap_Descriptor <>

;Calling procedure

call do_e820_Step1

;procedure
;---------------do_e820_Step1
do_e820_Step1:
        push es
        push cs
        pop es
        mov di, offset call15_1+LoadOfs
xor ebx, ebx ; ebx must be 0 to start
xor bp, bp ; keep an entry count in bp
mov edx,0534D4150h ; Place "SMAP" into edx
mov eax, 0e820h
mov dword ptr es:[di + 20],  1 ; force a valid ACPI 3.X entry. This reqd to set last
                                ;dword to 1 before each call
mov ecx, 24 ; ask for 24 bytes
int 15h
jc short failed         ; carry set on first call means "unsupported function"
mov edx, 0534D4150h ; Some BIOSes apparently trash this register?
cmp eax, edx ; on success, eax must have been reset to "SMAP"
jne short failed
test ebx, ebx ; ebx = 0 implies list is only 1 entry long (worthless)
je short failed
;jmp short jmpin
;jmpin:
jcxz skipent ; skip any 0 length entries
cmp cl, 20 ; got a 24 byte ACPI 3.X response?
jbe short skipent
test byte ptr es:[di + 20], 1 ; if so: is the "ignore this data" bit clear?
                                ;Bit 0 of the extended Attributes indicates if the entire
                                ; entry should be ignored
je short skipent
        mov ecx, dword ptr es:[di+8]; get lower dword of memory region length
        test ecx, ecx;          ; is the qword=0????
        jne short goodent
        mov ecx, dword ptr es:[di+12];
        jecxz skipent
goodent:
        inc bp
       
         
skipent:
test ebx, ebx ; if ebx resets to 0, list is complete
je short e820f
next_call2:                     
        call QW2Hex$            ;Displaying the base address
        add di, 8               ;Length of region starts 15 bytes from current val
                                ;In the procedure we adding 7 to di
        call QW2Hex$            ;Displaying the length of region
        add di, 24
e820f:
mov mmap_ent, bp ; store the entry count
        pop es
        ret

failed:
stc ; "function unsupported" error exit
        pop es
ret

;----other procdures
;--------------------------------- By Steve
; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;    Call with DS:SI pointing to a QWORD (eight bytes) to be
; displayed as hexadecimal. Not now. SI removed

QW2Hex$:
        PUSH    DI      ; Save registers used by routine.
        PUSH    AX
        PUSH    CX

        STD             ; String instructions decrement.

        ADD     DI,7    ; Point to last byte, (Intel big end).
        mov si ,offset arr+LoadOfs
        MOV     CX,8    ; Number of bytes to print. QWORD = 8 bytes
                        ;
QW_1:
        MOV     AL,ES:[DI]      ; Get a byte
        DEC     DI
       
        CALL TOASCII    ; Display as hex.
        mov  dl, VAL1
        mov  [si], dl   ; store the values in array and display array later
        inc si
        mov  dl, VAL2
        mov  [si], dl
        inc si
        LOOP    QW_1
;
                     ;Displaying the array contents

        mov ax,0B800h
        mov es,ax
        xor di,di
        mov di,50h
        mov cx,8       
        mov si,offset arr+LoadOfs
        mov ah,1Fh
nextval: mov al, [si]
        inc si
        stosw     ; <= You are automatically incrementing DI
        loop nextval

        CLD             ; Restore default.

        POP     CX
        POP     AX
        POP     DI

        RET
;---------------------------------------------------
; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;    This routine converts the one byte binary number in the
; AL register into its hexadecimal ASCII representation and
; prints these two bytes to the standard output or console.
; 4 March 2010,
;   Changed TOASCII routine to use AAM varient instead of MOV,
; AND, and SHR codes on nybbles.

TOASCII:
        PUSH    AX      ; Make safer for debugging.
        PUSH    DX

        XOR     AH,AH   ; Clear AH for AAM using base 16.
DB      0D4H, 10H       ; Isolates high nybble in AH and low
                        ; nybble in AL.
        PUSH    AX      ; Save low nybble.
        MOV     AL,AH   ; And process high digit first.

        CMP     AL,10   ; Convert to ASCII hex using "magic".
        SBB     AL,69H
        DAS

        MOV     DL,AL
        mov     VAL1, al
        ;CALL ConOutByte ; DOS Fn 2 or BIOS 10H Fn 0EH (or whatever).

        POP     AX      ; Retrieve low digit in AL.

        CMP     AL,10   ; Convert to ASCII hex.
        SBB     AL,69H
        DAS

        MOV     DL,AL
        mov     VAL2,al
;        CALL ConOutByte

        POP     DX
        POP     AX

        RET





Kindly some body  help me with this.

Zulf.

FORTRANS

Hi,

   What environment are you using to test your program?
I see one piece where you have a typo from where I posted
some code and edited it later to fix it.


  RangeType     DD      ?       ; * Next dword = Region "type"
  ACPI_Attrib   DD      ?       ; * Next dword = ACPI 3.0 Extended Attri


   Anyway I am using similar code to yours, and finally got it
working.  I don't see much difference in the individual routines
between your code and mine, except for printing characters.
And formatting output.

   Your posted code does not assemble for me.  So the lack of
exit code and defining an entry point are problems to check on.
And I would use more than five of those descriptor structures
as my test machine is using seven of them.


Regards,

Steve N.

zak100

Hi,
Sorry for not posting a compilable version. I have shortened my code and its able to print:
70027002.

I am printing both the base address and region length. I dont know if its the correct value.

I am using a lable 'next_call2' at which point I am displaying the values by calling your routines.

Kindly check if its correct or not. Let me know where to add your two variables.




;//portion of memMap code from original file sect8_2.asm
;//for masm forum
;ml /c memMp2.asm
;link16 /tiny memMp2.obj,memMp2.bin;
;DEBUG Btl3p_3.BIN
;-w 100 0 0 1
;-q

;DEBUG memMp2.BIN
;-w 100 0 1 1
;-q
;DISPLAYING real Time using int 1AH
.MODEL  TINY
.386
.CODE

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

LoadOfs EQU     0               ;must match the value in the bootloader source file
LoadSeg EQU     1000h

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

;---------------------- initialize ES segment register

        ORG     0

Start:  push    cs
        pop     ds
       
;-----------clear screen
mov ax, 3
int 10h

   
;---------------------- writing a message on screen at startup, character by character- we can't use int 21h
overdata:
       
        xor di, di
        mov ax, 0B800h
        mov es, ax
        mov si, offset msg0+LoadOfs
       mov ah, 41h; attribute byte
       cld;
msgloop:
        lodsb; loads al with a byte of data pted by ds:si
        or al, al
        jz TimerMesg
        stosw; transfers the contents of al to mem location ptd by es:di
        jmp msgloop
       
;---------------------- done - halt
TimerMesg:

        xor di, di
        mov ax, 0B820h
        mov es, ax
        mov si, offset msgA+LoadOfs
       mov ah, 41h; attribute byte
       cld;
msgAloop:
        lodsb; loads al with a byte of data pted by ds:si
        or al, al
        ;jz RTime
        jz mem
        stosw; transfers the contents of al to mem location ptd by es:di
        jmp msgAloop
        mov cx, 1000
;DISPLAY_TIMER:
;-------------Find Total Memory
mem:        cld
        ;call    FindTotalMem    ;calculate total memory (sets the SI register)
        mov     ah,7            ;display attribute
        mov     di,0            ;display position
        ;call    Dsply           ;display total memory
        call do_e820_Step1
        ;call Qw2Hex by Dave (instead using code provided by Fortran or Steve)

Halt0: hlt
jmp     Halt0


Msg0    db      "We be bootin234!",0
msgA db 'Total minutes elapsed since Kernel start is',0
clkcounter db 0
secs db 0
mins db 0
hrs  db 0
cnt  db 0; Its value represents the digits of Timer
s    db 0; selector for secs minutes and hrs used in displayCnt
arr  db 10 dup(0)
VAL1 db 0
VAL2 db 0
AscBuf  db      8 dup (0),' Kb Total Memory',0
mmap_ent dw ?
end_of_list db 1
MMap_Descriptor STRUCT
  BaseAddress   DQ      ?       ; * First qword = Base address
  ByteLength    DQ      ?       ; * Second qword = Length of "region"
  RangeType     DW      ?       ; * Next dword = Region "type"
  ACPI_Attrib   DW      ?       ; * Next dword = ACPI 3.0 Extended Attri
MMap_Descriptor ENDS

Call15_1        MMap_Descriptor <>      ; Set DI to point to the first one, and
Call15_2        MMap_Descriptor <>      ; increment by 24  to point to second.
Call15_3        MMap_Descriptor <>
Call15_4        MMap_Descriptor <>
Call15_5        MMap_Descriptor <>


;---------------do_e820_Step1
do_e820_Step1:
        push es
        push cs
        pop es
        mov di, offset call15_1+LoadOfs
xor ebx, ebx ; ebx must be 0 to start
xor bp, bp ; keep an entry count in bp
mov edx,0534D4150h ; Place "SMAP" into edx
mov eax, 0e820h
mov dword ptr es:[di + 20],  1 ; force a valid ACPI 3.X entry. This reqd to set last
                                ;dword to 1 before each call
mov ecx, 24 ; ask for 24 bytes
int 15h
jc short failed         ; carry set on first call means "unsupported function"
mov edx, 0534D4150h ; Some BIOSes apparently trash this register?
cmp eax, edx ; on success, eax must have been reset to "SMAP"
jne short failed
test ebx, ebx ; ebx = 0 implies list is only 1 entry long (worthless)
je short failed
;jmp short jmpin
;jmpin:
jcxz skipent ; skip any 0 length entries
cmp cl, 20 ; got a 24 byte ACPI 3.X response?
jbe short skipent
test byte ptr es:[di + 20], 1 ; if so: is the "ignore this data" bit clear?
                                ;Bit 0 of the extended Attributes indicates if the entire
                                ; entry should be ignored
je short skipent
        mov ecx, dword ptr es:[di+8]; get lower dword of memory region length
        test ecx, ecx;          ; is the qword=0????
        jne short goodent
        mov ecx, dword ptr es:[di+12];
        jecxz skipent
goodent:
        inc bp
       
         
skipent:
test ebx, ebx ; if ebx resets to 0, list is complete
je short e820f
next_call2:                     
        call QW2Hex$            ;Displaying the base address   <---------------
        add di, 8               ;Length of region starts 15 bytes from current val
                                ;In the procedure we adding 7 to di <-----------
        call QW2Hex$            ;Displaying the length of region
        add di, 24
e820f:
mov mmap_ent, bp ; store the entry count
        pop es
        ret

failed:
stc ; "function unsupported" error exit
        pop es
ret

QW2Hex$:
        PUSH    DI      ; Save registers used by routine.
        PUSH    AX
        PUSH    CX

        STD             ; String instructions decrement.

        ADD     DI,7    ; Point to last byte, (Intel big end).
        mov si ,offset arr+LoadOfs
        MOV     CX,8    ; Number of bytes to print. QWORD = 8 bytes
                        ;
QW_1:
        MOV     AL,ES:[DI]      ; Get a byte
        DEC     DI
       
        CALL TOASCII    ; Display as hex.
        mov  dl, VAL1
        mov  [si], dl   ; store the values in array and display array later
        inc si
        mov  dl, VAL2
        mov  [si], dl
        inc si
        LOOP    QW_1
;
                     ;Displaying the array contents

        mov ax,0B800h
        mov es,ax
        xor di,di
        mov di,50h
        mov cx,8       
        mov si,offset arr+LoadOfs
        mov ah,1Fh
nextval: mov al, [si]
        inc si
        stosw     ; <= You are automatically incrementing DI
        loop nextval

        CLD             ; Restore default.

        POP     CX
        POP     AX
        POP     DI

        RET
;---------------------------------------------------
; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;    This routine converts the one byte binary number in the
; AL register into its hexadecimal ASCII representation and
; prints these two bytes to the standard output or console.
; 4 March 2010,
;   Changed TOASCII routine to use AAM varient instead of MOV,
; AND, and SHR codes on nybbles.

TOASCII:
        PUSH    AX      ; Make safer for debugging.
        PUSH    DX

        XOR     AH,AH   ; Clear AH for AAM using base 16.
DB      0D4H, 10H       ; Isolates high nybble in AH and low
                        ; nybble in AL.
        PUSH    AX      ; Save low nybble.
        MOV     AL,AH   ; And process high digit first.

        CMP     AL,10   ; Convert to ASCII hex using "magic".
        SBB     AL,69H
        DAS

        MOV     DL,AL
        mov     VAL1, al
        ;CALL ConOutByte ; DOS Fn 2 or BIOS 10H Fn 0EH (or whatever).

        POP     AX      ; Retrieve low digit in AL.

        CMP     AL,10   ; Convert to ASCII hex.
        SBB     AL,69H
        DAS

        MOV     DL,AL
        mov     VAL2,al
;        CALL ConOutByte

        POP     DX
        POP     AX

        RET

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



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

        END     Start






Zulfi.


FORTRANS

Hi Zulfi,

   Okay, I got it to work.  I sure hope your machine boots
faster than mine if you need to reboot each time.  I used
DEBUG to walk through the program.  Anyway, some minimal
changes to your code.


       PAGE ,132    ;## Added for better listing.
...
MMap_Descriptor STRUC    ;## changed for older MASM, you can ignore.
  BaseAddress   DQ      ?       ; * First qword = Base address
  ByteLength    DQ      ?       ; * Second qword = Length of "region"
  RangeType     DD      ?       ; * Next dword = Region "type"  ## change typo.
  ACPI_Attrib   DD      ?       ; * Next dword = ACPI 3.0 Extended Attri  ## change typo.
MMap_Descriptor ENDS
...
        call QW2Hex$            ;Displaying the base address   <---------------
        add di, 8               ;Length of region starts 15 bytes from current val
;## You are not pausing after showing the first value before showing the second.
;## And they both print at the same location on screen.
        MOV     AX,0    ;## Pause?
        INT     16H
                                ;In the procedure we adding 7 to di <-----------
        call QW2Hex$            ;Displaying the length of region
...
QW2Hex$:
        PUSH    DI      ; Save registers used by routine.
        PUSH    AX
        PUSH    CX
        PUSH    ES      ;## You are using ES then changing it to display the characters.
...
        mov di,50h
        mov cx,16      ;## 8 bytes will be 16 characters.  And it comes out backwards...
        mov si,offset arr+LoadOfs
...
        POP     ES      ;##
        POP     CX
        POP     AX
        POP     DI


   This got me the same values as MichaelW's and my code gave
on my computer.  I may have missed something, but that was
most of what I did.

HTH,

Steve N.

zak100

Thanks Steve. I am little bit slow. I am interested in this. I am impressed by quick response from you people. I would try to get back on this as early as possible.

Zulfi.

zak100

Hi,
I am getting 16 0s as base address and following value as length of region:
7002700270027002

What does it mean??

Thanks for your help. I am still trying to print it using base:length of Region format (style).

Zulfi.

FORTRANS

Hi,

   When I got that value it meant that the ES register was
pointing to the wrong segment.  It was pointing to the video
segment and not your data area.  20 hex is a space and
07H is the default background attribute.

Regards,

Steve

zak100

Hi,
Thanks for your attention. By wrong you mean that there is a technical error in my code ??

Quote
<<20 hex is a space and
07H is the default background attribute.>>


This means that the value printed is not the length of region.

Zulfi.

FORTRANS

Hi,

QuoteBy wrong you mean that there is a technical error in my code ??

   My post in reply 51 has eight pieces of code marked with ##.
Did you make all of those changes to your code?  More changes
are _still_ needed, but that was the minimum to show the region
length data in some form.  Actually two of the ## marked pieces
are sort of extra, but the rest are needed.

QuoteThis means that the value printed is not the length of region.

   Exactly.  The length of the region is stored in your program's data
by the BIOS.  The 20072007H is in the video display memory.  On my
computer the length printed out as 000000000009FC00, after reformatting
it.  You should see something similar for the length on your computer.

Steve

zak100

Thanks for your reply. I am checking what I missed.

Zulfi.

zak100

Hi,
I checked and I found that I forgot PUSH and POP ES.

But I am getting 0's for base but for length of region I am getting:
004f000000000000

I am also showing you my code:


;//portion of memMap code from original file sect8_2.asm
;//Updated by Steve :masm forum
;ml /c memMp3.asm
;link16 /tiny memMp3.obj,memMp3.bin;
;DEBUG Btl3p_3.BIN
;-w 100 0 0 1
;-q

;DEBUG memMp3.BIN
;-w 100 0 1 1
;-q
;DISPLAYING real Time using int 1AH
.MODEL  TINY
.386
.CODE

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

LoadOfs EQU     0               ;must match the value in the bootloader source file
LoadSeg EQU     1000h

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

;---------------------- initialize ES segment register

        ORG     0

Start:  push    cs
        pop     ds
       
;-----------clear screen
mov ax, 3
int 10h

   
;---------------------- writing a message on screen at startup, character by character- we can't use int 21h
overdata:
       
        xor di, di
        mov ax, 0B800h
        mov es, ax
        mov si, offset msg0+LoadOfs
       mov ah, 41h; attribute byte
       cld;
msgloop:
        lodsb; loads al with a byte of data pted by ds:si
        or al, al
        jz TimerMesg
        stosw; transfers the contents of al to mem location ptd by es:di
        jmp msgloop
       
;---------------------- done - halt
TimerMesg:

        xor di, di
        mov ax, 0B820h
        mov es, ax
        mov si, offset msgA+LoadOfs
       mov ah, 41h; attribute byte
       cld;
msgAloop:
        lodsb; loads al with a byte of data pted by ds:si
        or al, al
        ;jz RTime
        jz mem
        stosw; transfers the contents of al to mem location ptd by es:di
        jmp msgAloop
        mov cx, 1000
;DISPLAY_TIMER:
;-------------Find Total Memory
mem:        cld
        ;call    FindTotalMem    ;calculate total memory (sets the SI register)
        mov     ah,7            ;display attribute
        mov     di,0            ;display position
        ;call    Dsply           ;display total memory
        call do_e820_Step1
        ;call Qw2Hex by Dave (instead using code provided by Fortran or Steve)

Halt0: hlt
jmp     Halt0


Msg0    db      "We be bootin234!",0
msgA db 'Total minutes elapsed since Kernel start is',0
clkcounter db 0
secs db 0
mins db 0
hrs  db 0
cnt  db 0; Its value represents the digits of Timer
s    db 0; selector for secs minutes and hrs used in displayCnt
arr  db 10 dup(0)
VAL1 db 0
VAL2 db 0
AscBuf  db      8 dup (0),' Kb Total Memory',0
mmap_ent dw ?
end_of_list db 1
MMap_Descriptor STRUCT
  BaseAddress   DQ      ?       ; * First qword = Base address
  ByteLength    DQ      ?       ; * Second qword = Length of "region"
  RangeType     DW      ?       ; * Next dword = Region "type"
  ACPI_Attrib   DW      ?       ; * Next dword = ACPI 3.0 Extended Attri
MMap_Descriptor ENDS

Call15_1        MMap_Descriptor <>      ; Set DI to point to the first one, and
Call15_2        MMap_Descriptor <>      ; increment by 24  to point to second.
Call15_3        MMap_Descriptor <>
Call15_4        MMap_Descriptor <>
Call15_5        MMap_Descriptor <>


;---------------do_e820_Step1
do_e820_Step1:
        push es
        push cs
        pop es
        mov di, offset call15_1+LoadOfs
xor ebx, ebx ; ebx must be 0 to start
xor bp, bp ; keep an entry count in bp
mov edx,0534D4150h ; Place "SMAP" into edx
mov eax, 0e820h
mov dword ptr es:[di + 20],  1 ; force a valid ACPI 3.X entry. This reqd to set last
                                ;dword to 1 before each call
mov ecx, 24 ; ask for 24 bytes
int 15h
jc short failed         ; carry set on first call means "unsupported function"
mov edx, 0534D4150h ; Some BIOSes apparently trash this register?
cmp eax, edx ; on success, eax must have been reset to "SMAP"
jne short failed
test ebx, ebx ; ebx = 0 implies list is only 1 entry long (worthless)
je short failed
;jmp short jmpin
;jmpin:
jcxz skipent ; skip any 0 length entries
cmp cl, 20 ; got a 24 byte ACPI 3.X response?
jbe short skipent
test byte ptr es:[di + 20], 1 ; if so: is the "ignore this data" bit clear?
                                ;Bit 0 of the extended Attributes indicates if the entire
                                ; entry should be ignored
je short skipent
        mov ecx, dword ptr es:[di+8]; get lower dword of memory region length
        test ecx, ecx;          ; is the qword=0????
        jne short goodent
        mov ecx, dword ptr es:[di+12];
        jecxz skipent
goodent:
        inc bp
       
         
skipent:
test ebx, ebx ; if ebx resets to 0, list is complete
je short e820f
next_call2:                     
        call QW2Hex$            ;Displaying the base address   <---------------
        add di, 8               ;Length of region starts 15 bytes from current val
                                ;In the procedure we adding 7 to di <-----------
;## You are not pausing after showing the first value before showing the second.
;## And they both print at the same location on screen.
        MOV     AX,0    ;## Pause?
        INT     16H
        call QW2Hex$            ;Displaying the length of region
        add di, 24
e820f:
mov mmap_ent, bp ; store the entry count
        pop es
        ret

failed:
stc ; "function unsupported" error exit
        pop es
ret

QW2Hex$:
        PUSH    DI      ; Save registers used by routine.
        PUSH    AX
        PUSH    CX
        PUSH    ES

        STD             ; String instructions decrement.

        ADD     DI,7    ; Point to last byte, (Intel big end).
        mov si ,offset arr+LoadOfs
        MOV     CX,8    ; Number of bytes to print. QWORD = 8 bytes
                        ;
QW_1:
        MOV     AL,ES:[DI]      ; Get a byte
        DEC     DI
       
        CALL TOASCII    ; Display as hex.
        mov  dl, VAL1
        mov  [si], dl   ; store the values in array and display array later
        inc si
        mov  dl, VAL2
        mov  [si], dl
        inc si
        LOOP    QW_1
;
                     ;Displaying the array contents

        mov ax,0B800h
        mov es,ax
        xor di,di
        mov di,50h
        mov cx,16        ;## 8 bytes will be 16 characters.  And it comes out backwards...
        mov si,offset arr+LoadOfs
        mov ah,1Fh
nextval: mov al, [si]
        inc si
        stosw     ; <= You are automatically incrementing DI
        loop nextval

        CLD             ; Restore default.

        POP     ES
        POP     CX
        POP     AX
        POP     DI

        RET
;---------------------------------------------------
; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;    This routine converts the one byte binary number in the
; AL register into its hexadecimal ASCII representation and
; prints these two bytes to the standard output or console.
; 4 March 2010,
;   Changed TOASCII routine to use AAM varient instead of MOV,
; AND, and SHR codes on nybbles.

TOASCII:
        PUSH    AX      ; Make safer for debugging.
        PUSH    DX

        XOR     AH,AH   ; Clear AH for AAM using base 16.
DB      0D4H, 10H       ; Isolates high nybble in AH and low
                        ; nybble in AL.
        PUSH    AX      ; Save low nybble.
        MOV     AL,AH   ; And process high digit first.

        CMP     AL,10   ; Convert to ASCII hex using "magic".
        SBB     AL,69H
        DAS

        MOV     DL,AL
        mov     VAL1, al
        ;CALL ConOutByte ; DOS Fn 2 or BIOS 10H Fn 0EH (or whatever).

        POP     AX      ; Retrieve low digit in AL.

        CMP     AL,10   ; Convert to ASCII hex.
        SBB     AL,69H
        DAS

        MOV     DL,AL
        mov     VAL2,al
;        CALL ConOutByte

        POP     DX
        POP     AX

        RET

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



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

        END     Start




Zulfi.

FORTRANS

Hi Zulfi,

Quote
I checked and I found that I forgot PUSH and POP ES.

   Right.  Fits the symptoms.

QuoteBut I am getting 0's for base but for length of region I am getting:
004f000000000000

   Except for being backwards that looks okay.  To "unbackwards"
the number change the code something like.

   Either pull this out and make it a separate routine.  That
would be a start to change where the number prints out later on.


                     ;Displaying the array contents

        mov ax,0B800h
        mov es,ax
        xor di,di
        mov di,50h          ; <= You will want to make this changable to print in different places.
        mov cx,16        ;## 8 bytes will be 16 characters.  And it comes out backwards...
        mov si,offset arr+LoadOfs
        mov ah,1Fh
nextval: mov al, [si]
        inc si
        stosw     ; <= You are automatically incrementing DI
        loop nextval


   Or move it to be after this line for a quick fix.


        CLD             ; Restore string instruction direction default.


   Tricky.

Regards,

Steve N.