• Please review our updated Terms and Rules here

allocating RAM with int 21h

Mike Chambers

Veteran Member
Joined
Sep 2, 2006
Messages
2,621
how are you gentlemen.. i've been trying to use function 48h on int 21h to have DOS allocate 64,000 bytes for me. it always errors and reports that the largest free chunk of memory is 5 paragraphs (80 bytes)

the allocated memory MUST be contiguous. am i using the wrong function to accomplish this?

here's how i'm trying to do it:

Code:
TYPE registers
     ax AS INTEGER
     bx AS INTEGER
     cx AS INTEGER
     dx AS INTEGER
     bp AS INTEGER
     si AS INTEGER
     di AS INTEGER
     flags AS INTEGER
     ds AS INTEGER
     es AS INTEGER
END TYPE

DIM SHARED inreg AS registers
DIM SHARED outreg AS registers

inreg.ax = &H4800
inreg.bx = &H1000
CALL interrupt(&H21, inreg, outreg)

PRINT "Flags:" + STR$(outreg.flags) + " ";
IF (outreg.flags AND 1) = 0 THEN PRINT "(no error)" ELSE PRINT "(error)" 'carry flag set means error
PRINT "AX: " + RIGHT$("000" + HEX$(outreg.ax), 4)
PRINT "BX: " + RIGHT$("000" + HEX$(outreg.bx), 4)
IF (outreg.flags AND 1) = 1 THEN
 IF outreg.ax = 7 THEN
   PRINT "Error detail: memory control block destroyed."
 ELSEIF outreg.ax = 8 THEN
   PRINT "Error detail: insufficient memory."
 END IF
END IF

any ideas? when i run the code above, at least on my 486 canon notejet, it returns this:

Code:
Flags: 3 (error)
ax = 0008
bx = 0005
Error detail: insufficient memory

the goal here is to use the allocated memory as a VGA framebuffer.
 
A lot of runtime environments take all of the available DOS memory and manage it themselves. The application already owns the memory, so DOS has no more to hand out. Do you know that QB doesn't own all of the memory already?

Check the PSP (Program Segment Prefix) at runtime - the second word gives you the number of paragraphs allocated to the process. If it is huge, then you will know why DOS has to memory to give you.
 
Is it possible some other application has that memory block open? This is via the web version but I used to love the dos app "helppc" for their great guides and usually have an example. I'm not sure if the dos version might have another example of this code or if this is an exact translation, although I think your code looks ok. Have you tried that in debug to see if it gets the same result?
 
A lot of runtime environments take all of the available DOS memory and manage it themselves. The application already owns the memory, so DOS has no more to hand out. Do you know that QB doesn't own all of the memory already?

Check the PSP (Program Segment Prefix) at runtime - the second word gives you the number of paragraphs allocated to the process. If it is huge, then you will know why DOS has to memory to give you.

hm, so this function doesn't let you allocate memory outside of the range it was alloted? i wonder if a better solution would be to make a very tiny function in microsoft C to malloc what i need and return the segment:eek:ffset? if done in MS C i can just link in the OBJ.
 
Is it possible some other application has that memory block open? This is via the web version but I used to love the dos app "helppc" for their great guides and usually have an example. I'm not sure if the dos version might have another example of this code or if this is an exact translation, although I think your code looks ok. Have you tried that in debug to see if it gets the same result?

yep, same result in debug.
 
Most BASICs allocate all of available memory and then manage it according to their needs. Were they to use DOS calls to manage memory, things would slow considerably. Note also, that the smallest system-allocatable memory block is 16 bytes--and there's a 16-byte overhead for each allocated block--this can be very inefficient for languages that perform dynamic allocation of variable and temporary space.

Why not simply declare an array of the size that you need and let BASIC handle the details?

.COM programs are also automatically given all of available contiguous memory when they start. The reason for this is downward compatibility--pre DOS 2.0 systems had no memory allocation system calls for user programs.
 
Most BASICs allocate all of available memory and then manage it according to their needs. Were they to use DOS calls to manage memory, things would slow considerably. Note also, that the smallest system-allocatable memory block is 16 bytes--and there's a 16-byte overhead for each allocated block--this can be very inefficient for languages that perform dynamic allocation of variable and temporary space.

Why not simply declare an array of the size that you need and let BASIC handle the details?

.COM programs are also automatically given all of available contiguous memory when they start. The reason for this is downward compatibility--pre DOS 2.0 systems had no memory allocation system calls for user programs.

when i let QB handle making the array, say like DIM scanline(199) AS STRING *320 it seems like the array elements aren't contiginous in memory. i'm using an ASM routine that copies x number of bytes from one seg/offset to another. if i make that array, i works when i copy each 320 byte element individually but if i just tell it to copy 64,000 bytes starting at scanline(0) most of the screen is garbage noise.

i reason i am doing it a line at a time is that i am vertically flipping the picture, and this is the easiest/most efficient way to go about that. every little tiny drop of speed i can get out of this important, because what i'm writing is a DOS AVI player. i have Microsoft C 5.1, maybe it would be better if i offloaded the read from disk/image flip/copy to VRAM to C. on the other hand, if i can call use this memory copy routine it will be fast enough without involving C.

here's a little cut and paste of how it's reading from disk/flipping/displaying the way i have it now:

Code:
  FOR y = 199 TO 0 STEP -1
    GET #1, , scanline(y)
  NEXT y
  FOR y = 0 TO 199
    MEMWRT &HA000, 320 * y, scanline(y) 'this is of course the asm routine for memory copies. argument list: dest segment as integer, dest offset as integer, and a string to copy. the routine determines the size and location of the string's data from QB's string descriptor.
  NEXT y

that code above is getting me 10 FPS on a 486 DX2/66, and the video format is 320x200 8-bit uncompressed DIB. the plan after getting uncompressed vid play well enough, and get sound working - is to support playback of AVIs that use the old MS Video1 codec, as well as M-JPEG. i'm sure that would require at least a pentium no matter what, but i'd like to get better frame rates with uncompressed first.
 
Last edited:
Mike,

When any program in DOS gets control, it has all of memory allocated to it. You need to free the memory beyond the end of your program with INT 21h/AH=4Ah, before you can allocate anything more (other than from UMBs) with INT 21/AH=48h.

Code:
	mov	segPSP,es		; Save segment of PSP

    ....

; Free extra memory
	mov	ax,ds			; Segment of DGROUP
	lea	bx,ZTAIL+@STKSIZE+15	; Size of DGROUP, rounded up to para
        shr	bx,(4-0)		; Convert from BYTEs to PARAs
	add	bx,ax			; Segment address of end of program
	sub	bx,segPSP		; Total size of program in paras
	mov	es,segPSP		; Segment of block to modify
	assume	es:nothing
	DOSCALL @MODMEM		; Modify memory block ES to BX paras

    ...

	public	ZTAIL
ZTAIL	 label	byte


Here is the DOS call running in SYMDEB. Works as expected.

Code:
Processor is [80286]
-
-a
0F8A:0100 mov ah,48
0F8A:0102 mov bx,1000
0F8A:0105 int 21
0F8A:0107 nop
0F8A:0108
-p
AX=4800  BX=0000  CX=0000  DX=0000  SP=EF65  BP=0000  SI=0000  DI=0000
DS=0F8A  ES=0F8A  SS=0F8A  CS=0F8A  IP=0102   NV UP EI PL NZ NA PO NC
0F8A:0102 BB0010         MOV    BX,1000
-p
AX=4800  BX=1000  CX=0000  DX=0000  SP=EF65  BP=0000  SI=0000  DI=0000
DS=0F8A  ES=0F8A  SS=0F8A  CS=0F8A  IP=0105   NV UP EI PL NZ NA PO NC
0F8A:0105 CD21           INT    21  ;Allocate Memory
-p
AX=0F8A  BX=1000  CX=0000  DX=0000  SP=EF65  BP=0000  SI=0000  DI=0000
DS=0F8A  ES=0F8A  SS=0F8A  CS=0F8A  IP=0107   NV UP EI PL NZ NA PO NC
0F8A:0107 90             NOP
-

As far as calling a C OBJ to allocate memory for you in another program, that's a bigger can of worms, because you need to get the C runtime initialized. If you want to call C runtime functions from assembly code, I can send you examples of how to do that.

/Bill
 
Mike,

When any program in DOS gets control, it has all of memory allocated to it. You need to free the memory beyond the end of your program with INT 21h/AH=4Ah, before you can allocate anything more (other than from UMBs) with INT 21/AH=48h.

That applies only to .COM files. .EXE files contain the memory requirements in the header, so only what's requirested is allocated. But QB as part of its start-up code, goes ahead and requiests the kitchen sink.

There are work-arounds--take a look at the techniques here.
 
Last edited:
That applies only to .COM files. .EXE files contain the memory requirements in the header, so only what's requirested is allocated.

That would depend on how the EXE was built/linked and what's in the header, and I'm
not aware of anything that uses that scheme. Even the M$FT C runtime startup code uses
the same idea as what I've posted above.
 
Now you are:

Code:
        .model  small,c
        .stack

        .data

Message db      "Hello world!",10,13,'$

        .code

StartHere:
        mov     ax,seg @Data
        mov     ds,ax
        lea      dx,Message
        mov     ah,9
        int     21h
        mov     ax,4c00h
        int     21h

        end     StartHere

And so it shows:

Code:
D:\DEVELO~1\CATWEA~1\sydex\pci>exehdr samp.exe

Microsoft (R) EXE File Header Utility  Version 3.20
Copyright (C) Microsoft Corp 1985-1993.  All rights reserved.

.EXE size (bytes)         221
Magic number:             5a4d
Bytes on last page:       0021
Pages in file:            0002
Relocations:              0001
Paragraphs in header:     0020
Extra paragraphs needed:  0041
Extra paragraphs wanted:  ffff
Initial stack location:   0003:0400
Word checksum:            0000
Entry point:              0000:0000
Relocation table address: 001e
Memory needed:            2K
 
Change your code to try to allocate something with function 48 and run
it in debug. See what you get back.

(or not)
 
Code:
	.model	small,c
	.stack

	.data

SignOn	 db	 "DOS function 48H returns $"
Failed	 db	"flop$"

	.code

StartHere:
	mov	ax,seg @Data
	mov	ds,ax
	lea	dx,SignOn
	mov	ah,9
	int	21h
	mov	ah,48h
	mov	bx,16
	int	21h
	jc	NoSoap
	call	ShowWord
AllDone:
	mov	ax,4c00h
	int	21h

NoSoap:
	mov	ah,9
	lea	dx,Failed
	int	21h
	jmp	AllDone


;*	ShowWord - Output hex word in (ax).
;
;	All registers preserved.
;

ShowWord	proc	near
	push	ax
	mov	al,ah
	call	ShowByte
	pop	ax
	call	ShowByte
	ret
ShowWord	endp

;*	ShowByte - Show a Byte in hex.
;
;	(al) = byte.
;

ShowByte	proc	near
	push	ax
	shr	al,1
	shr	al,1
	shr	al,1
	shr	al,1
	call	ShowNib
	pop	ax
	push	ax
	call	ShowNib
	pop	ax
	ret
ShowByte	endp

ShowNib	   proc	   near		     ; convert and display a nibble
	and	al,15
	add	al,'0'
	cmp	al,'9'
	jbe	ShowNib2
	add	al,'a'-'9'-1
ShowNib2:
	push	dx
	push	cx
	mov	dl,al
	mov	ah,2
	int	21h
	pop	cx
	pop	dx
	ret
ShowNib	   endp






	end	StartHere

And i get:

Code:
DOS function 48H returns 0f49

Try it yourself.
 

Attachments

  • SAMP.ZIP
    278 bytes · Views: 1
Chuck, I was amazed that I could be that wrong (since I tested it myself before spouting off).
So I tried your example code myself.

But, since the original poster was trying to allocate 64k, I made one change.
I changed your:

Code:
    mov    ah,48h
    mov    bx,16
    int    21h

to:

Code:
    mov    ah,48h
    mov    bx,1000h
    int    21h

Results - the allocation fails...

Code:
C:\junk>vi chuck.asm

C:\junk>ml chuck.asm
Microsoft (R) Macro Assembler Version 6.15.8803
Copyright (C) Microsoft Corp 1981-2000.  All rights reserved.

 Assembling: chuck.asm

Microsoft (R) Segmented Executable Linker  Version 5.60.339 Dec  5 1994
Copyright (C) Microsoft Corp 1984-1993.  All rights reserved.

Object Modules [.obj]: chuck.obj
Run File [chuck.exe]: "chuck.exe"
List File [nul.map]: NUL
Libraries [.lib]:
Definitions File [nul.def]:

C:\junk>chuck
DOS function 48H returns flop
C:\junk>

If you use something along the lines of the code I posted before, it'll work.

Your example works because the DOS arena is normally fragmented enough there's a small piece available below your pgm to satisfy the request. The 4th entry in the display below would handle it.

Code:
Name        Arena  Owner      Size
             0210    DOS   0313  ( 12592)
COMMAND.COM  0524   0525   00A2  (  2592)
             05C7   Free   0007  (   112)
             05CF   0525   005E  (  1504)
-Available-  062E   0681   0051  (  1296)
-Available-  0680   0681   997E  (628704)

Bill
 
Nope. I can change the amount to 1000h and I get the following:

Code:
DOS function 48H returns 0e88

Try it yourself. (Hint: It's a matter of knowing the standard Microsoft toolset.. Look at page 974 in the big gray DOS Encyclopedia.)
 

Attachments

  • SAMP2.ZIP
    280 bytes · Views: 2
The original poster wanted to know why his memory allocations failed and I've explained that.
You're making use of MZ header params that M$FT C itself doesn't even use.

You win! -- I'm done.
 
wow.... what a thread lol. thanks for the infos and links, gents. i ended up going about it a different (and better) way. i found some info on the details of passing arguments to an asm routine from QB, so i was able to put this together and compile it in MASM 5.1:

Code:
.8086
.MODEL medium, BASIC
.CODE
MemCopy PROC USES si di ds es, FromSeg:PTR WORD, FromOfs:PTR WORD, \
   ToSeg:PTR WORD, ToOfs:PTR WORD, Count:PTR WORD

    mov bx,FromOfs ;where we load ds:si with the source location
    mov si,[bx]
    mov bx,ToSeg
    mov es,[bx] ;and then es:di with the destination
    mov bx,ToOfs
    mov di,[bx]
    mov bx,Count ;the count is how many bytes to copy, divided by 2 because
    mov cx,[bx]  ;we'll use movsw instead of movsb to copy 2 bytes at a time

    mov bx,FromSeg
    mov ds,[bx]

    cld ;begin the data copy!
    rep movsw
    ret
MemCopy  ENDP
END

and here is the copy/paste of the code that reads and displays the frames now.. quad() is a 4-element array, each being 16,000 bytes. n is the current frame number to display. idxv() is an array generated from the AVI's index chunks giving offsets of each frame within the file.

Code:
  SEEK #1, idxv(n).dwchunkoffset + offsmovi + 8
  GET #1, , quad(0)
  GET #1, , quad(1)
  GET #1, , quad(2)
  GET #1, , quad(3)

  destseg% = &HAF8C
  FOR q = 0 TO 3
    srcstartseg% = VARSEG(quad(q))
    srcstartptr% = VARPTR(quad(q))
    FOR n2 = 0 TO 49
      MemCopy srcstartseg%, srcstartptr%, destseg%, 0, 160
      destseg% = destseg% - 20
      srcstartptr% = srcstartptr% + 320
    NEXT n2
  NEXT q

this has been a nice learning experience. ;-0

and if you guys want to see how my QB+ASM AVI player is working currently, here is a vid i capped of a 486 DX/25 playing a 320x200 uncompressed DIB AVI:

http://www.youtube.com/watch?v=r14JXsQ93Is

i'm working on sound support right now, which i've had experience with in the past. should be any problem. pretty damn smooth, eh? :)

that is probably mostly thanks to the (relatively) modern 4 GB WD hard drive in that system, though. i doubt there's any way most actual 486-era drives could pull this fast of a transfer rate off. anyway, yeah... working on sound now, and then i'm going to see about implementing Video1, MJPEG, and RLE compressed streams too. fun!


EDIT: alright... really, i couldn't help myself. here is the same build of the player and the same AVI file as in that video with the 486 playing it, but on my 12 MHz 286 laptop.. :)

http://www.youtube.com/watch?v=jphgMJZRrk4

i had to.
 
Last edited:
That's !@%#%@# awesome, Mike! I can't believe you managed that. A 25mhz box, too! Power of ASM..

I will totally watch much of my downloaded media on a 486 (133mhz, though, so it will cope a tad better ;D) if you complete this - I swear it - lol.

Wow.. I'm surprised the 286 managed as quickly as it did. With a video half that resolution it could be watchable even on there..

Once you get sound, you must release this beast.
 
That's !@%#%@# awesome, Mike! I can't believe you managed that. A 25mhz box, too! Power of ASM..

I will totally watch much of my downloaded media on a 486 (133mhz, though, so it will cope a tad better ;D) if you complete this - I swear it - lol.

Wow.. I'm surprised the 286 managed as quickly as it did. With a video half that resolution it could be watchable even on there..

Once you get sound, you must release this beast.

muaahahaha thanks. i will release it for sure. the only problem with watching most of your downloaded video with it is you'll have to convert it all to use codecs this player will understand. most DVD rips, etc, out there aren't compressed with Video1, MJPEG or RLE lol. :)

only uncompressed could ever hope to be full speed like that on a 486. MAYBE a very very fast 486 like yours will have usable frame rates with compression. definitely a really slow pentium will be able to do it. i still havent completed sound, as i've had a lot of work to do at my shop lately but i hope to work on it more tonight! you might want to give QuickView Pro a try on your 486.

http://www.multimediaware.com/qv/

^ it even plays DiVX, although i've never tried that on a 486. ;)
 
Back
Top