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,
Thanks MichealW.
Quote
Well, one of the things you should do is preserve the contents of
EBX to do another Int 15H.
I have checked this code but I didnt see any explicit instruction for preserving ebx.

xor   ebx, ebx
  callLoop:
    mov   eax, 0e820h
    mov   edx, 'SMAP'
    mov   ecx, SIZEOF smmard
    ; Set DI to the offset address of smmard.
    mov   di, OFFSET smmard
    int   15h
    ; Preserve CF for later test.
    pushf
    .IF eax != 'SMAP'
      popf
      print NL,"Interrupt 15h Function E820h not supported or not available.",NL,NL
      jmp   callFunction88h
    .ENDIF
    ; The function may indicate that the last range
    ; has been returned by setting the carry flag
    ; or by returning zero in EBX.
    popf
    jc    finish
    test  ebx, ebx
    jz    finish

    print NL,"BASE=",hexdword$(smmard.baseLo),"h "
    print "LENGTH=",hexdword$(smmard.lengthLo),"h "
    print chr$(40),dword$(smmard.lengthLo),chr$(41)
    loc ,44
    print "TYPE="
    .IF smmard.rangeType == RT_AVAILABLE
      print "AVAILABLE"
    .ELSEIF smmard.rangeType == RT_RESERVED
      print "RESERVED"
    .ELSEIF smmard.rangeType == RT_ACPI_RECLAIM
      print "ACPI_RECLAIM"
    .ELSEIF smmard.rangeType == RT_ACPI_NVS
      print "ACPI_NVS"
    .ENDIF

    ; Update the total length.
    mov   eax,smmard.lengthLo
    add   memTotal,eax

    jmp   callLoop



In my code I have tried to preserve ebx by saving it in a variable
storeEBX and later on I am retrieving its value but its not
working. Since I have put my memory map code in a loop, its not
displaying any base address. Earlier it was printing one base address
and its length.


;//portion of memMap code from original file sect8_2.asm
;//Updated by Steve :masm forum

;"Solved the prob of backward printing of the length of region"
;Beyond memMp3: printing the base address & pause & then the offset at different locations
;               both visible
;               using arguments for print_mesg macro e.g:
; print_mesg MyArg, ScrCoord, 16;
;               Entire code of MemMap: Printing the base address and length in a loop
;-------------------------------------------------------------
;ml /c memMp4.asm
;link16 /tiny memMp4.obj,memMp4.bin;
;DEBUG btl5.BIN
;-w 100 0 0 1
;-q

;DEBUG memMp4.BIN
;-w 100 0 1 2
;-q

.MODEL  TINY
.386

print_mesg macro offsetStr, offsetScr, msgSize
       LOCAL xlat0

       mov     ax,cs
       mov     ds,ax
       push    ax
       mov     ax,xlat0
       push    ax
       retf


;display the message at B800:50h

xlat0: mov     ax,0B800h     
       mov     es,ax
       mov     di, offsetScr
       mov     si, offsetStr
       cld
       mov     ah,1Fh
       mov     cx,msgSize
endm



.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; NOT A CLK PROG
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 16 dup(0)
VAL1 db 0
VAL2 db 0
ScrCoord dw 50h ;dx stores the screen location for displaying Base address & region length
                ;<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< Macro argument
AscBuf  db      8 dup (0),' Kb Total Memory',0
mmap_ent dw ?
end_of_list db 1
MyArg   EQU     <offset arr+LoadOfs>
storeEBX  dq 0 ;<<<<<<<<<<<<<<<<<<<<------------------------------------

       
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
        mov storeEBX, ebx;<<<<<<<<<<<<<<<<<<<<<-----------------------------
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
e8201p:
        mov ebx, storeEBX;<<<<<<<<<<<<<<<<---------------------------
        mov eax, 0e820h
        mov dword ptr es:[di + 20], 1
        mov ecx, 24
        int 15h
        jc short e820f
        mov edx, 0534D4150h
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; i.e from 8 to 11
        test ecx, ecx;          ; is the qword=0????
        jne short goodent
        mov ecx, dword ptr es:[di+12];i.e from 12 to 15
        jecxz skipent
goodent:
        inc bp
        ;---------------------------    ;NOTE QW2HEX$ converts to Hex & prints using Macro
                 
        call QW2Hex$            ;Displaying the base address
       
;## 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
       
        push di
        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 
        pop di
        add di, 24
         
skipent:
test ebx, ebx ; if ebx resets to 0, list is complete
jne short e8201p
     
;-------------------------
       
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).
                        ; When called 1st DI=0. Now DI =7. So print from 7 to 0. So it pints the Base address
                        ; When called 2nd time DI=8. After adding DI=15. So it prints the length of region

        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
;---------------------------Calling Macro with the screen coordinates
       
        ;print_mesg MyArg, 50h, 16;
        print_mesg MyArg, ScrCoord, 16;<------------------
        nextval: lodsb
                 stosw
        loop nextval
       
        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





Kindly help me in this regard.

Zulfi.

FORTRANS

Hi,

   The code of yours that I got working (for one entry) was from
Reply #76.  You have moved some code around since then.  The
the code that prints the results in particular.  The code in the first
posting has the "cure" for the current problem.  (I think.)  The
problem (on my machine) is currently with this code.


cmp cl, 20 ; got a 24 byte ACPI 3.X response?
jbe short skipent


   On my machine it now takes the jump (not 24 bytes).  So you
need something like this logic from the first posting.

cmp cl, 20  ; got a 24 byte ACPI 3.X response?
jbe short .notext


   That way you can process ACPI that predates the 3.x speci-
fication.

Regards,

Steve

zak100

Hi Steve,
Thanks for your help. I have added the notext code which you told me. Its now showing the 1st region and its length. But its not showing beyond that. Kindly guide me with this problem,



;ml /c memMp5.asm
;link16 /tiny memMp5.obj,memMp5.bin;
;DEBUG btl5.BIN
;-w 100 0 0 1
;-q

;DEBUG memMp5.BIN
;-w 100 0 1 2
;-q

.MODEL  TINY
.386

print_mesg macro offsetStr, offsetScr, msgSize
       LOCAL xlat0

       mov     ax,cs
       mov     ds,ax
       push    ax
       mov     ax,xlat0
       push    ax
       retf


;display the message at B800:50h

xlat0: mov     ax,0B800h     
       mov     es,ax
       mov     di, offsetScr
       mov     si, offsetStr
       cld
       mov     ah,1Fh
       mov     cx,msgSize
endm



.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; NOT A CLK PROG
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 16 dup(0)
VAL1 db 0
VAL2 db 0
ScrCoord dw 50h ;dx stores the screen location for displaying Base address & region length
                ;<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< Macro argument
AscBuf  db      8 dup (0),' Kb Total Memory',0
mmap_ent dw ?
end_of_list db 1
MyArg   EQU     <offset arr+LoadOfs>
storeEBX  dd 0   ; 32 bits

       
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
        mov storeEBX, ebx
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
e8201p:
        mov ebx, storeEBX
        mov eax, 0e820h
        mov dword ptr es:[di + 20], 1
        mov ecx, 24
        int 15h
        jc short e820f
        mov edx, 0534D4150h
jmpin:
jcxz skipent ; skip any 0 length entries
cmp cl, 20 ; got a 24 byte ACPI 3.X response?
jbe short notext
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
notext:
        mov ecx, dword ptr es:[di+8]; get lower dword of memory region length; i.e from 8 to 11
        test ecx, ecx;          ; is the qword=0????
        jne short goodent
        mov ecx, dword ptr es:[di+12];i.e from 12 to 15
        jecxz skipent
goodent:
        inc bp
        ;---------------------------    ;NOTE QW2HEX$ converts to Hex & prints using Macro
                 
        call QW2Hex$            ;Displaying the base address
       
;## 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
       
        push di
        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 
        pop di
        add di, 24
         
skipent:
test ebx, ebx ; if ebx resets to 0, list is complete
jne short e8201p
     
;-------------------------
       
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).
                        ; When called 1st DI=0. Now DI =7. So print from 7 to 0. So it pints the Base address
                        ; When called 2nd time DI=8. After adding DI=15. So it prints the length of region

        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
;---------------------------Calling Macro with the screen coordinates
       
        ;print_mesg MyArg, 50h, 16;
        print_mesg MyArg, ScrCoord, 16;<------------------
        nextval: lodsb
                 stosw
        loop nextval
       
        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,

   Okay.  I went and tried to follow what you were trying to do
and minimally fix it up.  It is (more or less) working now (for me).
I can see if you need to reboot for each change, it would take
a while to progress.  You should be able to clean things up from
here I think.  A bunch of changes were only reformatting, as I
looked at the code.  That was only to help me debug things
quicker.  Look for ## marking most of the real changes.  And
if something does not make sense to you, ask, I may have
torpedoed it.

   Tested as both a separate boot and as a DOS COM program.
If in doubt, hit a key...  Enjoy!

HTH,

Steve N.


        PAGE ,132
; DeadNDave/Zulfi/zak100 code from 26 June 2010, MASM32 forum.
; 27 June 2010, Mods by FORTRANS/Steve N. {Idiosyncratic formatting & fixes.}
; Look for ##.

;ml /c memMp5.asm
;link16 /tiny memMp5.obj,memMp5.bin;
;DEBUG btl5.BIN
;-w 100 0 0 1
;-q

;DEBUG memMp5.BIN
;-w 100 0 1 2
;-q

.MODEL  TINY
.386

print_mesg macro offsetStr, offsetScr, msgSize
       LOCAL xlat0

       mov     ax,cs
       mov     ds,ax
;       push    ax       ; ## ??
;       mov     ax,xlat0
;       push    ax
;       retf

;display the message at B800:50h

xlat0: mov     ax,0B800h
       mov     es,ax
       mov     di, offsetScr
       mov     si, offsetStr
       cld
       mov     ah,1Fh
       mov     cx,msgSize
endm

DOSish  EQU     0       ; ## EQUate = 1 to use DEBUG in a VDM, 0 = BootLoader...

.CODE

;----------------------------------------------------------------------------------
;IF DOSish?  Okay, what was Dave doing? ##?
LoadOfs EQU     0               ;must match the value in the bootloader source file
LoadSeg EQU     1000h

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

IF DOSish               ; ## DEBUGing?
        ORG     100H    ; DOS COM file load point.
ELSE
        ORG     0       ; deadndave load point.
ENDIF

;---------------------- initialize DS segment register
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 SHORT TimerMesg
        stosw ; transfers the contents of al to mem location ptd by ES:DI
        jmp msgloop

;---------------------- done - halt; NOT A CLK PROG
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 SHORT mem
        stosw ; transfers the contents of al to mem location ptd by es:di
        jmp msgAloop

;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:
IF DOSish
        MOV     AH,04CH ; DOS 2+ Exit.
        INT     21H
ELSE
        HLT
        JMP     Halt0
ENDIF


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      16 dup(0)
VAL1    db      0
VAL2    db      0
ScrCoord dw     50h ; dx stores the screen location for displaying Base address & region length
                ; Macro argument
AscBuf  db      8 dup (0),' Kb Total Memory',0
mmap_ent dw     ?
end_of_list db  1
MyArg   EQU     <offset arr+LoadOfs>
storeEBX dd     0   ; 32 bits

MMap_Descriptor STRUC           ; Old MASM
  BaseAddress   DQ      ?       ; * First qword = Base address
  ByteLength    DQ      ?       ; * Second qword = Length of "region"
  RangeType     DD      ?       ; * Next dword = Region "type" ##
  ACPI_Attrib   DD      ?       ; * 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
        mov storeEBX, ebx
        jc 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 failed              ; ## as above, now is out of range...
        test ebx, ebx           ; ebx = 0 implies list is only 1 entry long (worthless)
        je failed               ; ## as above, now is out of range...
        jmp short jmpin
e8201p:
        CMP     BP,5            ;## Oh yeah.  Prevent buffer overflow.
        JAE     E820F

        mov ebx, storeEBX
        MOV     EDX,0534D4150H  ; ## Place "SMAP" into EDX
        mov eax, 0e820h
        mov dword ptr es:[di + 20], 1
        mov ecx, 24
        int 15h
        jc short e820f
        MOV     [storeEBX],EBX  ; ##
        mov edx, 0534D4150h
jmpin:
        jcxz skipent    ; skip any 0 length entries
        cmp cl, 20      ; got a 24 byte ACPI 3.X response?
        jbe short notext
        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
notext:
        mov ecx, dword ptr es:[di+8]; get lower dword of memory region length; i.e from 8 to 11
        test ecx, ecx;          ; is the qword=0????
        jne short goodent
        mov ecx, dword ptr es:[di+12] ; i.e from 12 to 15
        jecxz skipent
goodent:
        inc     bp
;---    ;NOTE QW2HEX$ converts to Hex & prints using Macro

        call QW2Hex$            ;Displaying the base address
        ADD     [ScrCoord],40   ; ## Move print region.

;## 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

        push di
        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
        pop di
        add di, 24
        ADD     [ScrCoord],120  ; ## Move print region.
skipent:
        test ebx, ebx ; if ebx resets to 0, list is complete
        jne short e8201p

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

e820f:
        mov mmap_ent, bp ; store the entry count
        pop es
        CLC
        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).
                        ; When called 1st DI=0.  Now DI=7.  So print from 7 to 0. So it prints the Base address
                        ; When called 2nd time DI=8.  After adding DI=15.  So it prints the length of region

        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
;--- Calling Macro with the screen coordinates

        ;print_mesg MyArg, 50h, 16;
        print_mesg MyArg, ScrCoord, 16;<------------------
nextval: lodsb
        stosw
        loop nextval

        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

zak100

Hi,
Thanks for your reply. I have not yet tested it but just to inform you that I am about to start working on it, I am writing this. I have made a quick look at it and I am not to able to digest the indirect addressing with storeEBX.
There maybe other Qs which I would ask you once I have gone through the code thoroughly.

Thanks for making it workable and signifying the changes.

Zulfi.

FORTRANS

Hi,

   It is not indirect addressing.  It is part of my idiosyncratic
formatting that I warned about.


        MOV     [storeEBX],EBX
        mov storeEBX, ebx


   These produce the exact same code.  I like using the brackets
to indicate storage to a variable.  Some assemblers do produce
different code for the above (i.e. NASM).  But not MASM.  Just
my habit.

Regards,

Steve N.

zak100

Hi Steve,
Thanks for this explanation.

Zulfi.

zak100

Hi,
Thanks Steve. Its working now. I got following 5 regions with base addresses and lengths:
0000 0000 0000 0000         0000 0000 0009 F400
0000 0000 0009 F400         0000 0000 0000 0C00   
0000 0000 000F 0000         0000 0000 0001 0000   
0000 0000 0010 0000         0000 0000 1F5E 0000   
0000 0000 1F6E 0000         0000 0000 0000 3000   


Thanks for formatting.
Let me know about the correctness of this result.
Zulfi.

FORTRANS

Hi,

   Glad it works for you.  Your results look good as well.  But
when I compare that to some of my computers, it looks as
if you should alter the program to print out more memory
blocks.  If you look at the six or seven regions in Reply #102,
you will see a region starting at FFFF 0000 and the same
length as the block at 000F 0000.  Those should be the
computer's BIOS regions.  You are not showing both of
those regions yet.  You could look at the results there
to see what else you mayl want your program to print out

Cheers,

Steve N.

zak100

Hi,
Thanks Steve for guiding me upto this point and for pointing out the regions not being printed. I would try to look at this problem first before going into the details of other stuff shown in those sample printouts (reply#102). Right now I have no clue why those regions were left out.

Zulfi.

FORTRANS

Hi,

   They were left out as you only defined five buffers for
the data returned by the interrupt.  If you call that
interrupt more than that, you crash the program as you
overwrite the executing progam.  (Quick guess how I
found that out.)  I then put in a test to prevent that
from happening.


        CMP     BP,5            ;## Oh yeah.  Prevent buffer overflow.
        JAE     E820F


Regards,

Steve N.

zak100

Hi Steve,
I am now getting following 9 regions:
0000 0000 0000 0000         0000 0000 0009 F400
0000 0000 0009 F400         0000 0000 0000 0C00   
0000 0000 000F 0000         0000 0000 0001 0000   
0000 0000 0010 0000         0000 0000 1F5E 0000   
0000 0000 1F6E 0000         0000 0000 0000 3000   
0000 0000 1F6E 3000         0000 0000 0000 D000
0000 0000 1F6F 0000         0000 0000 0001 0000
0000 0000 E000 0000         0000 0000 0800 0000
0000 0000 FEC0 0000                      0000 0000 0140 0000


I cant see the BIOS region.
I tried with 12 buffers:

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 <>
call15_6        MMap_Descriptor <>
call15_7        MMap_Descriptor <>
call15_8        MMap_Descriptor <>
call15_9        MMap_Descriptor <>
call15_0        MMap_Descriptor <>
call15_A        MMap_Descriptor <>
call15_B        MMap_Descriptor <>


and the comparison code is given below:



CMP     BP,12           ;## Oh yeah.  Prevent buffer overflow.
                               ;Total buffers=8, last one is:   
                               ;call15_8        MMap_Descriptor <>
        JAE     E820F


But its not going beyond 9. Is it the maximum number of regions??
My other prob. is non-printing of BIOS regions.
Kindly guide me in this regard. I appreciate your help and guidance.

Zulfi.

MichaelW

I have not been keeping up with this thread, but on some (probably older) systems the BIOS is duplicated in E block and F block, for example:

BASE=00000000H LENGTH=0009F800 (653312)    TYPE=AVAILABLE
BASE=0009F800H LENGTH=00000800 (2048)      TYPE=RESERVED
BASE=000E0000H LENGTH=00020000 (131072)    TYPE=RESERVED
BASE=00100000H LENGTH=0FF00000 (267386880) TYPE=AVAILABLE


Also, if the goal is to assemble the entire map in memory, it should be possible to count the number of blocks in the first pass, allocate the required memory, then make another pass to read the information into the allocated memory.


eschew obfuscation

FORTRANS

Hi,

QuoteI cant see the BIOS region.

   Well, you got the one at 000F 000.  All the machines I have
tested have had one at FFFF 0000.  Most of those were older
machines though.  You could put in some checks to see if it
was skipped by the code as it does make some checks.


        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


   That seems unlikely, but you could comment out the JE line
and see what happens.

   I have heard of some BIOS'es hiding parts of the BIOS after
it boots up, but have no further information about that.  So if
that is all that are reported, that is probably all there is.

Cheers

Steve

FORTRANS

Hi,

   Modifying the code to increase the number of records, I got
same seven regions on my machine.  So I think things are
working okay on my machine.

Steve N.