home *** CD-ROM | disk | FTP | other *** search
- ; A Tutorial for XLIB and Protected Mode
-
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; If you don't read much, then this file was made just for you. It's
- ;a lot shorter than XLIB.DOC. It also explains several protected-mode
- ;concepts, including some that are needed to understand XLIB.DOC. We work
- ;through an assembly language program which demonstrates the usage of XLIB.
- ;As we go, we are going to do a lot of talking about protected mode in
- ;general as well as protected mode under XLIB in particular.
- ; First, let's talk about what XLIB is generally designed to do: XLIB
- ;will allow you to write protected-mode procedures using your familiar
- ;language development tools (compilers, linkers, etc), and will allow you to
- ;execute code containing such procedures using DOS. XLIB is also designed
- ;to make all this as simple for you as it possibly can. That turns out to
- ;very simple indeed.
- ; XLIB has one major shortcoming: It relies on DOS to load executables
- ;and files. This means that our code must reside in the first meg because
- ;that's the only thing DOS knows how to work with. It also means that when
- ;we transfer disk files to or from extended memory, we must perform a
- ;transfer through a buffer in the first meg. In almost every other regard,
- ;we will have unlimited power. Most importantly, we will be able to access
- ;data in extended memory with extreme ease and speed.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now, let's start with a little program. We must begin with a model
- ;declaration. XLIB is a large-model library which uses PASCAL conventions.
- ;We will use the same model here; however, this is not a requirement of XLIB.
- ;We also want to tell the assembler to let us use 32-bit instructions.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- .MODEL LARGE,PASCAL
- .386P
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; The next two line are the key ingredients. We want to provide XLIB
- ;symbols to this program with XLIB.INC. We also want to link with XLIBE.LIB.
- ;XLIBE.LIB has exception trapping capabilities whereas XLIB.LIB does not.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- INCLUDE XLIB.INC
- INCLUDELIB XLIBE.LIB
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ;TASM Only:
-
- ; If you are a TASM programmer, then don't use the last two lines. Use the
- ;following lines instead. These lines include some useful macros that should
- ;have been in TASM to begin with.
- ;
- ; MASM51 ;Emulate MASM51
- ; QUIRKS ;MASM51 quirks are sometimes nice
- ;
- ;PUSHW MACRO IMMEDIATE16:REST ;PUSH 16-bit constant
- ; IF (@WordSize EQ 4)
- ; DB 66H
- ; ENDIF
- ; DB 68H
- ; DW IMMEDIATE16
- ; ENDM
- ;
- ;PUSHD MACRO IMMEDIATE32:REST ;PUSH 32-bit constant
- ; IF (@WordSize EQ 2)
- ; DB 66H
- ; ENDIF
- ; DB 68H
- ; DD IMMEDIATE32
- ; ENDM
- ;
- ; INCLUDE XLIBB.INC
- ; INCLUDELIB XLIBEB.LIB
- ;
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now we will finish our simplified segment directives.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- .STACK 1024
- .DATA
- .CODE
- .STARTUP
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now we have to deal with an annoying complication. XLIBE.LIB might need
- ;to allocate some conventional memory for its own use. The problem is that
- ;our program has likely claimed all available memory, even though it isn't
- ;going to use it. If you are a MASM programmer, then the solution is simple:
- ;Link with the CPARM:1 parameter. If you are a TASM programmer, then you
- ;must resize the memory block in which this program is contained. The
- ;following code will do the trick:
- ;
- ; MOV AX,SP ;SS:SP = end of program
- ; SHR AX,4
- ; MOV BX,SS
- ; ADD BX,AX
- ; INC BX ;BX = first para. beyond program
- ; MOV AX,ES ;ES:0000 = first para. of program
- ; SUB BX,AX ;BX = program size in para.
- ; MOV AX,4AH ;Function to resize memory block
- ; INT 21H ;Carry will be set if failure
- ; JNC STILLGOING
- ; MOV AX,4C01H ;Failed to resize so terminate
- ; INT 21H
- ;STILLGOING:
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; One more step and we will be ready to hit protected mode!!! We must
- ;initialize the library by calling INITXLIB. This procedure will return an
- ;error code in EAX. A code of zero always means success under XLIBE.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- CALL INITXLIB
- OR EAX,EAX
- JZ GOTPOWER
- MOV AX,4C01H ;DOS termination function
- INT 21H ;You will have to read after all.
- ;If you simply can't stand user
- ;manuals, then try throwing out
- ;some device drivers and TSRs.
- GOTPOWER:
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; We don't want to mess around in real mode anymore. As you will shortly
- ;see, we can do about anything in protected mode that we could do in real
- ;mode, plus a whole lot more. Moreover, XLIBE makes protected mode easier
- ;than real mode. We will spend the rest of our time working from a 32-bit
- ;protected-mode subroutine called PMMAIN. We will get there with an XLIBE
- ;procedure called CALLPM. Just push the offset of PMMAIN on the stack and
- ;call CALLPM.
- ; There is one big assumption involved here: It is assumed that PMMAIN and
- ;all other 32-bit routines are contained in a segment called TSEG. Don't
- ;worry, TSEG can be larger than 64K if you live by the rules. Read the
- ;manual if you want to know what they are.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- PUSHD OFFSET PMMAIN ;Must use a 32-bit offset
- CALL CALLPM
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; XLIBE is going to use the return address from the above call to find its
- ;way back to real mode. You can get back to real mode by using the RET
- ;instruction provided that you have maintained the stack pointer. If this is
- ;not the case, then you can still get back with no problem. More about this
- ;later. When we get back, we are just going to terminate.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- MOV AX,4C00H
- INT 21H
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now we will declare our 32-bit segment. We will later talk about
- ;protected mode segments in general and about 32-bit segments in particular.
- ;Just hang loose for now. It is all simple.
- ; When we arrive at this segment from CALLPM, our segment registers will
- ;have been loaded by XLIBE. They will be set as follows: CS will have
- ;TSEG base and a 4Gb limit (Gb = gigabyte). SS will also have TSEG base and
- ;a 4Gb limit; however, code segments and data segments are distinguished in
- ;protected mode. We will have 4096 free bytes on the stack. DS will have a
- ;zero base and 4Gb limit. This is what is called a "flat" segment. ES will
- ;have TSEG base and a 4Gb limit (same as SS). FS will have DSEG base and a
- ;64K limit. DSEG is the data segment used by XLIB. Finally, GS will have
- ;DGROUP base and a 64K limit. DGROUP is the segment group created by the
- ;.DATA directive. If you are a high-level language programmer, then DGROUP
- ;is also where your compiler probably puts all of the near data.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- TSEG SEGMENT PARA PUBLIC USE32 'CODE'
- ASSUME CS:TSEG, SS:TSEG, ES:TSEG, FS:DSEG, GS:DGROUP
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now let's look at the PMMAIN procedure below. You will see that it is a
- ;near procedure. This must be the case for all procedures called by CALLPM.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- PMMAIN PROC NEAR
-
- ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
- ; We are in 32-bit protected mode
- ;!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; By the way, you will get all registers except segment registers and ESP
- ;at the values you had in them in real mode, including status flags (carry
- ;flag, zero flag, etc) and the interrupt flag. The stack got switched on
- ;you, so don't try passing stack arguments through CALLPM. If you have
- ;arguments, then send them across in registers (e.g. load a register with a
- ;pointer to a structure containing all arguments).
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Of course, no language tool can be legitimate unless it can say "hello"
- ;to the world, so let's take care of this important business now. We will
- ;use DOS function 02H for this purpose.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- MOV EBX,OFFSET HELLOWWORLD
- MOV AH,02H
- GETCHAR: MOV DL,CS:[EBX] ;Read with CS but don't write!!!
- OR DL,DL
- JZ GOODBYEWORLD
- INT 21H ;DOS interrupt
- INC EBX
- JMP GETCHAR
-
- HELLOWWORLD DB "Hello world!",0
-
- GOODBYEWORLD:
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Did you forget that DOS is a real-mode system??? If not then you could
- ;be wondering how we got away with what we just did (i.e. INT 21H). The
- ;answer is simple. At this point, XLIBE is trapping all interrupts occurring
- ;in protected mode. It is then switching to real mode and relaying the call
- ;to the corresponding real-mode interrupt handler. Finally, it is switching
- ;back to protected mode and returning control to us. This is commonly called
- ;"reflection." We call it "deflection" in XLIB.DOC. Any interrupt will
- ;continue to be deflected until you install your own protected-mode interrupt
- ;handler for the interrupt.
- ; Therefore, we can still use our favorite software interrupts with one
- ;provision: These interrupts cannot return values in the segment registers.
- ;Such values would be overwritten with segment selectors on the way back to
- ;protected mode. More about segment selectors later.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now, let's get down to real business. Your principal interest in
- ;protected mode was likely access to extended memory. Well, it is now there
- ;for the taking. However, we must play by the rules. If you just start
- ;punching around in extended memory, then you could get a nasty thing called
- ;a "page fault." We will talk more about this later. Also, somebody else
- ;might be up there - like your disk cache or your ram drive. Mess with those
- ;and you are going to feel real bad.
- ; The safe approach is to allocate the extended memory with the PMGETMEM
- ;function. Just load EAX with the number of bytes you want and call
- ;PMGETMEM. Let's get 64K.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- MOV EAX,10000H
- CALL PMGETMEM
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; PMGETMEM will return with an error code in EAX. If EAX = 0, then the
- ;address of the allocated block will be in EDX. The actual size of the block
- ;will be in ECX, and a handle for the block will be in EBX. The allocated
- ;size will always be at least as large as your request. You will need the
- ;handle in EBX in the event that you later wanted to release the block;
- ;however, there is little need to worry about this. XLIBE will release it
- ;for you automatically when you terminate.
- ; Now, let's see if we got an error from PMGETMEM. If so, then we will
- ;return to real mode using the near RET instruction; otherwise, we will zero
- ;the entire allocated block just for fun.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- OR EAX,EAX
- JZ ZEROMEMORY
- RET ;Go back to real mode
-
- ZEROMEMORY: SUB ECX,4 ;ECX is always a multiple of 4
- MOV [EDX+ECX],EAX ;EAX = 0 from PMGETMEM
- JNZ ZEROMEMORY
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; The RET instruction is an easy way to get back home, but suppose you had
- ;pushed some stuff on the stack since the call to CALLPM. Then RET would be
- ;potentially disastrous. In this case you get back to real mode by jumping
- ;to a procedure call RETPM. The following instruction would do the trick:
- ;
- ; JMP RETPM
- ;
- ;You can use this instruction just about anywhere.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now, suppose you have a bug somewhere along here and you therefore wish
- ;to look at your register values. This is easy under XLIBE. Just use the
- ;INT 3 instruction.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- INT 3
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; INT 3 generates a breakpoint exception. XLIBE will trap this exception
- ;and print a report to the screen. This report will contain register state
- ;and other useful information. From the report screen you will be given the
- ;option to resume execution. XLIBE will attempt to trap and report all CPU
- ;exceptions in this manner. Expect to get plenty of them in protected mode.
- ;Don't worry, they are not going to crash your machine all the time like they
- ;did in the old days. XLIBE is pretty good at cleaning up your mess.
- ; See the special note below if you want to know how XLIBE is going to
- ;handle your FPU exceptions.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; OK. You already know enough about XLIBE to write some powerful code.
- ;You might not be interested in the remaining examples, so let's talk for a
- ;while about what you need to know concerning protected mode in general, and
- ;then you can get to programming if you wish.
- ; The principle difference between protected mode and real mode from the
- ;programmer's perspective is the interpretation of the segment registers. In
- ;real mode the value in the segment register is multiplied by 16 and then
- ;added to an offset to get an address. For example, consider: MOV AX,[BX].
- ;This instruction implicitly uses the DS register for the memory access.
- ;Suppose DS = 02FFH and BX = 4004H, then AX would be loaded from 6FF4H (or
- ;10H * 02FFH + 4004H). It's simple, but it is also very limiting.
- ; By the way, 4004H would be called the "effective" address while 6FF4H
- ;would be called the "linear" address. The "base" address of the segment is
- ;simply the linear address at offset zero. In this case, the base address is
- ;2FF0H.
- ; Now we will find out what stinks about real mode: The largest value
- ;you could have in DS is FFFFH (64K - 1). The largest offset you could have
- ;is also FFFFH. This means that the largest linear address you could get in
- ;real mode is 10FFEFH. That's 1 meg plus about 64K. Isn't much these days.
- ;You wouldn't be reading this if it were.
- ; In fact, you can't even get 10FFEF if you have only 20 address lines (as
- ;in the 8086). In this case you would be limited to FFFFFH, the largest
- ;number that can be expressed with 20 bits. That's where the one meg
- ;limitation came in.
- ; The addresses beyond FFFFFH and up to 10FFEFH are commonly called the
- ;"HMA" (high memory area). You get them from real mode when you have got
- ;more than 20 address lines (as in the 286 or higher). The "A20" you may
- ;have heard about is the 21st address line (the first one is numbered zero).
- ; In protected mode, the segment registers contain "selectors." Selectors
- ;index system tables called "descriptor tables." Under XLIBE, your selectors
- ;will be indexing the "local descriptor table" or LDT. The entries in these
- ;tables contain "descriptors." These are each eight bytes long. XLIBE sets
- ;them all up for you.
- ; The descriptors specify many things concerning a segment; however, two
- ;are of special importance. First, these descriptors specify the base
- ;address of the segment. Second, they specify the limit of the segment. The
- ;limit is the largest offset that can be used in conjunction with the
- ;segment. The nice thing about protected mode is that both the base and the
- ;limit can be as large as FFFFFFFFH (that's 4Gb - 1).
- ; One of the reasons that we use the term "protected mode" is the
- ;enforcement of the limits on the segments. Suppose you had DS loaded with
- ;a descriptor having FFFH limit, and suppose you tried to execute something
- ;like MOV AX,[1000H], then you will have violated protection rules and the
- ;processor will shut you down with an exception #13. Hence, memory outside
- ;of the segment is somewhat protected. Actually, there are other protection
- ;mechanisms far more important than this. More later.
- ; Observe that we could get mighty close to emulating real mode from within
- ;protected mode. We could load segment registers with base addresses less
- ;than FFFFFH and fix their limits at FFFFH. Then all we would need to do
- ;is make the processor interpret loads to the segment registers as changes
- ;to their base addresses (actually, a little more would be necessary). In
- ;fact this can be done. It's called "virtual 8086 mode." You are using it
- ;right now if you have something like EMM386, 386MAX, or QEMM386 loaded. You
- ;may be surprised to know that you have been using protected mode all along!
- ; So, the moral to the above story is: A segment register must never be
- ;loaded with anything but a selector to a valid descriptor. In real mode you
- ;could always execute MOV DS,AX. This isn't going to work in protected mode
- ;unless AX contains a selector. If it doesn't, then an exception #13 is
- ;headed your way.
- ; OK. The next major difference between the two modes has already been
- ;mentioned: In real mode, your offsets cannot be greater than FFFFH. In
- ;protected mode they can be as great as your segment limit, and that usually
- ;means 4 gig. By the way, there is nothing inherent to real mode that would
- ;logically prevent segment limits greater than FFFFH. The processor imposes
- ;this limit to enforce emulation of the 8086. If we could persuade the
- ;processor to lift this restriction, then we would find ourselves with a
- ;really powerful real mode. In fact this can be done on the data segments,
- ;and is done in some software (e.g. HIMEM.SYS).
- ; Perhaps you have heard of something called the "flat model" or
- ;"unsegmented model." This is a protected-mode model in which we set all
- ;segment base addresses to zero and set all segment limits to FFFFFFFFH.
- ;This makes life real easy, and it's probably where we are headed in the
- ;future. XLIBE tries to get you as close to this model as it can so that you
- ;won't have to be changing your code when your future finally gets here.
- ; Now let's talk about 32-bit processing as opposed to 16-bit processing.
- ;There are a few things you need to know. Notice that we have "USE32" on the
- ;TSEG segment declaration above. This is why we call TSEG a 32-bit segment.
- ;Segments you have used in times past had the USE16 attribute (the default).
- ;DSEG and DGROUP are also USE16 segments. You have probably guessed that
- ;USE16 gives you a 16-bit segment. The difference derives from a peculiarity
- ;of the processor. For most instructions, the processor has both a 16-bit
- ;version and a 32-bit version. The peculiarity is that the op codes are
- ;generally the same. Consider PUSH AX as opposed to PUSH EAX. Would you
- ;believe that they are encoded exactly the same? The op code is 50H either
- ;way.
- ; So how do we tell the difference? Well, it's done with a single bit in
- ;the code segment descriptor. If this bit is set, then the instruction will
- ;be interpreted as having a 32-bit operand. It will be interpreted as a
- ;16-bit instruction otherwise. This bit is called the "D bit" (default
- ;operand/address size).
- ; So, what if you really wanted a PUSH AX even when this curious bit is
- ;set? You do this by encoding an "operand prefix" in front of the
- ;instruction. The prefix is 66H. So if we want PUSH AX from within 32-bit
- ;mode, then we encode the instruction as 66H followed by 50H. Conversely, if
- ;we wanted PUSH EAX in 16-bit mode, then we must also encode it as 66H
- ;followed by 50H. Thus, the 66H temporarily places the processor in the
- ;opposite mode dictated by the D bit.
- ; The USE32 directive informs the assembler that we intend to execute in
- ;the declared segment with the D bit set. This information lets the
- ;assembler know that it must stick operand prefixes in front of 16-bit
- ;instructions. Accordingly, USE16 tells the assembler that we are going
- ;to execute in the declared segment with the D bit clear. Now the assembler
- ;must stick the operand prefix in front of 32-bit instructions.
- ; A somewhat different situation exists for base registers and index
- ;registers, but the conclusions are still the same. Consider MOV AL,[SI]
- ;and MOV AL,[ESP]. The first is encoded as 8AH 04H, the second is encoded
- ;as 8AH 04H 24H. When the processor sees the last sequence, how can it tell
- ;whether it reading MOV AL,[ESP], or MOV AL,[SI] plus the first byte in the
- ;next instruction? It can't, or at least not without a prefix. The prefix
- ;in this case is 67H. In a 32-bit segment, a 67H indicates that a 16-bit
- ;register is being used for a base or index. In a 16-bit segment, 67H
- ;indicates a 32-bit base or index. The USE32 and USE16 directives tell the
- ;assembler where to insert 67H.
- ; What if we had MOV AX,[BX] in a 32-bit segment? Then we must encode both
- ;prefixes (67H must be first).
- ; You have probably gathered that 16-bit instructions are bad in a 32-bit
- ;segment. They obviously require more memory. What isn't obvious is that
- ;they burn up CPU time (typically 1 clock each on the 486). So avoid 16-bit
- ;registers while in TSEG. 8 bit registers are OK in either kind of segment.
- ; Observe that the D bit has little to do with protected-mode. We could
- ;run a protected-mode program in a 16-bit segment, but then we have to pay
- ;a price for using 32-bit registers. That just isn't smart. The only
- ;association between the D bit and protected mode is that you must be in
- ;protected mode if the D bit is set. There is no such thing as 32-bit
- ;real mode, even though it is conceptually possible.
- ; OK. There is one other thing that you should perhaps understand. Its
- ;called "page mode," but the concept is a little complicated, so we have
- ;placed it at the bottom of this file. You can read it if you like, but
- ;will be OK without it.
- ; If you are ready to leave, then we can terminate our program with the
- ;following lines:
- ;
- ;
- ; RET ;Go back to real mode
- ;PMMAIN ENDP
- ;
- ;TSEG ENDS
- ; END
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Back to our discussion about XLIBE. From now on we are going to deal
- ;with you bad guys.
- ; Let's suppose you have an IO device which maps to extended memory
- ;addresses. You need to read or write to these addresses. The memory is
- ;supplied by the device and is not recognized as ordinary RAM by the
- ;operating system. The operating system may not even know that it is there.
- ;Let's suppose that the device map begins at the 16th meg boundary (1000000H)
- ;and is 64K long.
- ; It would not be wise just to start poking and peeking around 1000000H.
- ;There is a problem in that your device maps to "physical" addresses whereas
- ;your instruction code is using "logical" addresses. They may not be the
- ;same. See the discussion about page mode below if you want to understand
- ;the difference.
- ; You need to create a logical address space for accessing the device.
- ;This is very simple. Just call PMMAPIO with EDX = the physical address of
- ;the device and EAX = the size of the window.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- MOV EDX,1000000H
- MOV EAX,10000H
- CALL PMMAPIO
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; PMMAPIO returns an error code in EAX. If EAX = 0, then EDX will equal
- ;the starting address at which the device should be accessed. We will check
- ;out this error code before we continue.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- OR EAX,EAX
- JZ MOREHARDCORE
- RET ;Back to real mode
- MOREHARDCORE:
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; OK. Now let's suppose you have a great big database on disk that you
- ;have never been able to completely read into memory because of DOS
- ;limitations. We are fixing to load the whole thing. First, we must
- ;allocate memory to contain the file. Let's do that now. We are going to
- ;assume that the file will never be larger than one meg, but you could
- ;increase the assumed limit if you wanted.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- MOV EAX,100000H ;Get 1 Meg of memory for file
- CALL PMGETMEM
- OR EAX,EAX ;See if an error occurred
- JZ WAYDOWN
- RET ;Back to real mode
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Next, we need to set up a file control block (not a DOS FCB) to describe
- ;the file to XLIBE. XLIBE will expect the control block to be in the form of
- ;the structure below.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- XFILE STRUCT
- CONDCODE DWORD 0 ;Condition code from file operation
- FNAME BYTE 68 DUP(0) ;ASCII file path (zero terminated)
- FHANDLE WORD 0 ;File handle assigned by DOS
- FPTRMODE WORD 0 ;File pointer reference
- FPTR DWORD 0 ;Initial file pointer
- BLOCKADR DWORD 0 ;Memory source/destination address
- BLOCKSIZE DWORD 0 ;Size of transfer block in bytes
- BUFFERADR DWORD 0 ;Address of memory buffer in 1st meg
- BUFFERSIZE WORD 0 ;Buffer size in bytes
- CONTROL WORD 0 ;Control word
- XFILE ENDS
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ;TASM Only:
- ; If you are a TASM programmer, then don't use the structure above. Use:
- ;
- ;XFILE STRUC
- ; CONDCODE DD 0
- ; FNAME DB 68 DUP(0)
- ; FHANDLE DW 0
- ; FPTRMODE DW 0
- ; FPTR DD 0
- ; BLOCKADR DD 0
- ; BLOCKSIZE DD 0
- ; BUFFERADR DD 0
- ; BUFFERSIZE DW 0
- ; CONTROL DW 0
- ;XFILE ENDS
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ;Let's suppose that the filename is JUNK.DAT and that this file is in the
- ;current directory. If you want to run this program, then create a small
- ;text file called JUNK.DAT in the current directory. We are going to get
- ;the assembler to put our file name in the structure. The rest we will punch
- ;in ourselves. Remember that EDX is the linear address of the memory block
- ;where we are going to load this file. ECX is the size of the block. We
- ;obtained these values from PMGETMEM above. Also, remember that ES is loaded
- ;with a selector to TSEG.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ALIGN 4 ;Unaligned data will slow you down
- FCB XFILE <0,"JUNK.DAT"> ;File control block
-
- WAYDOWN: MOV ES:FCB.BLOCKADR,EDX
- MOV ES:FCB.BLOCKSIZE,ECX
- MOV ES:FCB.BUFFERSIZE,0H
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; OK. Lets get the file and talk about it later. We will need to call
- ;PMXLOAD. PMXLOAD will expect EAX to contain the linear address of the file
- ;control block. Here we go.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- MOV EAX,TSEG ;Get segment of control block
- SHL EAX,4 ;Multiply by 16 and add offset
- ADD EAX,OFFSET FCB ;EAX = linear address now
- PUSH EAX ;We will use this again
- CALL PMXLOAD
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now, we will explain what we just did. BLOCKADR is the address of the
- ;memory block where we want the file to be loaded. BLOCKSIZE is the size of
- ;this block. PMXLOAD will not load past the end of the block since that
- ;could be very dangerous to you or whoever else might be in memory. Now, DOS
- ;is going to access the disk for us, but DOS can't work with extended memory.
- ;So, we set up a buffer in conventional memory for DOS. PMXLOAD will handle
- ;the transfers from the buffer to extended memory. You could supply your
- ;own buffer address and size in BUFFERADR and BUFFERSIZE; however, if you
- ;will just set BUFFERSIZE to zero, then XLIBE will supply its own buffer.
- ; PMXLOAD will return an error code in both EAX and CONDCODE (same error
- ;code). We will check it now.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- OR EAX,EAX
- JZ GOTFILE
- JMP RETPM ;Back to real mode
- GOTFILE:
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Notice that if an error occurs, then we transfer control back to real
- ;mode with JMP RETPM rather than RET. This is because we've got some stuff
- ;on the stack now; namely, the linear address of our file control block. Of
- ;course a POP EAX followed by a RET would still work.
- ; OK. Suppose you play around with memory image of the file, perhaps
- ;making a few modifications. Now you want to save it. The file control
- ;block should be defined as before, except BLOCKSIZE and BLOCKADR should
- ;specify the address and size of the memory block you are going to save.
- ;PMXLOAD modified BLOCKSIZE in the file control block. It was set to the
- ;actual size of the file that it loaded. This means that unless you have
- ;changed the size of the memory image, then you need to make no further
- ;modifications to the file control block to perform the save. Just call
- ;PMXSAVE with the address of the control block in EAX. Here we go.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- POP EAX ;Get FCB address
- CALL PMXSAVE
- OR EAX,EAX ;See if an error occurred
- JZ FILEISSAVED
- RET
- FILEISSAVED:
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; XLIBE can also perform random reads and writes with files. See the
- ;manual if you want to know more.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; One more topic. This concerns interrupt handlers. These are real devils
- ;in any mode. Unfortunately, XLIBE can't simplify matters as much as it would
- ;like. This is because XLIBE must work in conjunction with other software
- ;(VCPI or DPMI) to give you all of this protected-mode stuff. This other
- ;software doesn't handle interrupts the same, and there isn't much that XLIBE
- ;can do to smooth out the lumps. You better read the manual on this one.
- ; Anyway, we are going to install a simple timer-tick interrupt which will
- ;print an asterisk to the screen with each timer tick. We are going to use
- ;routines in the file PMIO.INC to do the printing. You will see that we have
- ;INCLUDE PMIO.INC several lines down in the code.
- ; PMIO.INC is a very handy little file and is very simple to use. Examine
- ;the file if you want to know more. The comments in the file explain how to
- ;use the PMIO procedures. There are two things you need to know for now:
- ;PMIO.INC must be included in TSEG and its procedures should always be called
- ;with DS loaded with a flat selector (as it is at present).
- ; Let's clear the screen before we get started with our interrupt handler.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- CALL CLS
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; OK. We are going to install our own protected-mode interrupt handler for
- ;the timer tick. The timer tick is a hardware interrupt on IRQ 0. First, we
- ;need to get the current protected-mode interrupt vector so we can restore it
- ;when we are done.
- ; Now the timer tick is generally at vector eight (INT 8), but we must deal
- ;with the possibility that XLIBE has remapped interrupts. We can't assume that
- ;IRQ 0 is still assigned to INT 8. The current mapping is contained in the
- ;XLIBE data area (DSEG) in a variable called IRQ0INTNO. Let's get it now.
- ;Remember that FS contains a selector for DSEG.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- MOV AL,FS:IRQ0INTNO
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; OK. To get the current vector, we need merely to call PMGETPMIV (get
- ;protected-mode interrupt vector) with the vector number in AL. The address
- ;of the current interrupt handler will be returned in CX:EDX. Here we go.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- CALL PMGETPMIV ;No error code from this call
- PUSH ECX ;Save handler address on stack
- PUSH EDX
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now we will set our new vector. We must call PMSETPMIV with AL = the
- ;interrupt number and CX:EDX = the new handler address. CX must be a segment
- ;selector. Our new handler is called TIMERINT. It is located just a few
- ;lines down. We will get there in just a moment. PMSETPMIV will return an
- ;error code in EAX. We will check this, as always.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- PUSH CS ;Put handler address in CX:EDX
- POP ECX
- MOV EDX,OFFSET TIMERINT
- CALL PMSETPMIV
- OR EAX,EAX ;Check error code
- JZ WATCHTICKS
- JMP RETPM ;Back to real mode
- WATCHTICKS:
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Notice that we treated PUSH CS as though it put 4 bytes on the stack.
- ;It did. In 32-bit mode, the processor tries to keep the stack aligned at
- ;MOD 4. So, it padded the PUSH with a two-byte zero. It will always do
- ;this with segment registers (on far calls, on interrupts, on everything),
- ;and you would do well to remember it.
- ; OK. Now we need a little loop to delay long enough for a few timer
- ;ticks to happen. There are about 18.2 of them in a second. If you have
- ;a 486-33, then the next loop will work fine. If you have a 386, then you
- ;may be watching ticks for a while.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- MOV ECX,0FFFFFFH
- WAITAWHILE: LOOP WAITAWHILE ;Asterisks are being printed
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; That's enough. Let's put the old vector back.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- POP EDX
- POP ECX
- MOV AL,FS:IRQ0INTNO
- CALL PMSETPMIV ;Will ignore any error here.
- ;We couldn't do anything else.
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Here is where we go back to real mode for good. But keep on reading.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- RET ;Goodbye protected, ole pal
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; Now, let's look at our protected-mode handler. Comments are below.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- TIMERINT PROC FAR
- STI
- PUSH EAX
- PUSH DS
- MOV DS,CS:CSDSEGSEL ;Load DSEG selector
- MOV DS,FLATDSEL ;Load flat selector for PMIO
- MOV AL,"*"
- CALL PCH ;Print AL as ASCII
- CLI
- MOV AL,20H ;Send EOI to 8259 master
- OUT 20H,AL
- POP DS
- POP EAX
- IRETD ;Don't use IRET in 32-bit segs
- TIMERINT ENDP ;under MASM
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; As you probably know, we are not supposed to assume anything about
- ;anything in an interrupt handler, including segment register settings. Now
- ;XLIBE has recorded our selector values in DSEG (see manual). However, we
- ;have a little problem here: We need the DSEG selector to get them. The
- ;way we circumvent this dilemma is by putting a copy of the DSEG selector in
- ;your code segment where you can always read it. XLIBE has already done
- ;this for you. It placed the selector in CSDSEGSEL.
- ; After we have loaded DS with DSEGSEL, we then load it with the flat
- ;selector. This is recorded in FLATDSEL.
- ; You might be wondering why we didn't use a DOS function to do our
- ;printing. It's because you can bring a system down real hard and real fast
- ;by calling DOS in an interrupt handler. The problem occurs when DOS is
- ;itself interrupted. DOS is not generally reentrant. The print routines in
- ;PMIO are very robust. They are also fast.
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
- ; OK. You are hopefully an XLIB programmer now. Remember that XLIB is not
- ;free. You must register it once you have developed any program with it.
- ;The fee is only $40 ($60 with technical support). If you think that is bad,
- ;then you should look at the retail DOS extenders. You are talking about
- ;a lot more money and a lot more work. We appreciate your business
-
- ; TechniLib
- ;+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
-
- PMMAIN ENDP
-
- INCLUDE PMIO.INC ;Protected-mode IO routines
-
- TSEG ENDS
- END
-
- ;*****************************************************************************
- ; Special Notes
- ;*****************************************************************************
-
- ; ++++++++++++++++++++++++++++
- ; + Writing Libraries +
- ; ++++++++++++++++++++++++++++
-
-
- ; You can give high-level language programs tremendous power by linking
- ;them with protected-mode libraries developed with XLIBE. See the EASYX.ASM
- ;file for an example.
-
-
- ; ++++++++++++++++++++
- ; + Page Mode +
- ; ++++++++++++++++++++
-
-
- ; We discuss something here that's a little technical, but extremely
- ;enlightening. It's called "page mode," available only in protected mode or
- ;in virtual 8086 mode, which is of course a subset of protected mode. In
- ;page mode, memory addresses specified in instruction code undergo a little
- ;mathematical translation before they are actually applied to the physical
- ;memory. So what you ask for isn't always what you get. For example, if
- ;you write something to address 10000H, it might actually go to 20000H. This
- ;isn't bad as long as when you read from 10000H you also get 20000H, and
- ;indeed you will. Incidentally, the address you specify is called a
- ;"logical" address. The address you actually get is called the "physical"
- ;address.
- ; Now, a lot of mysteries may have just been explained to you. For
- ;example, you know that most of your programs must reside in the first meg.
- ;You also know that many of your programs consume most of the available
- ;memory in the first meg. How then do DESQview, Windows, OS/2, etc. run all
- ;of these programs at the same time??? Well, you give each program a
- ;different translation formula. Stick the first program in the first meg and
- ;give it one-to-one translation. No trickery here. Stick the second program
- ;in the second meg and then add 1 meg (100000H) to every address it tries to
- ;read and write. Remember, this program thinks it's in the first meg, so
- ;that's where it's going to be reading and writing. But, because of the
- ;translation, it's going to be getting the second meg. This program has been
- ;fooled. It has been hornswoggled by page mode.
- ; Perhaps you have wondered how your memory manager put your device drivers
- ;and TSRs in upper memory where ROM is supposed to be. The answer is page
- ;mode again. The device drivers and TSRs are actually in extended memory.
- ;The logical addresses which would otherwise belong to the ROM area have been
- ;translated to these extended memory addresses.
- ; Before explaining what all this has to do with you, let's explain the
- ;translation method. The logical address you specify is of course 32 bits
- ;wide. We are going to divide these three ways: the 10 upper bits, the
- ;next ten bits, and the lowest 12 bits. The translation runs thus: The 10
- ;highest bits are used as an index to a table which has 1024 entries. These
- ;entries are 4 bytes wide so the table consumes 4K. These entries are
- ;physical addresses to other tables which are also 4K in size. We use your
- ;upper 10 bits to pick the appropriate table. Your next 10 bits will be used
- ;as an index to the second-level table. The entries in this table supply the
- ;upper 20 bits to the physical address you are actually going to access. The
- ;lowest 12 bits of the physical address are supplied by the lowest 12 bits in
- ;your logical address. A mess isn't it. Don't worry, you are not
- ;responsible for handling this mess, but sometimes XLIBE is.
- ; Now, the second-level table supplies all but the 12 lowest bits of the
- ;physical memory address; therefore, the addresses in this table are spaced
- ;in memory at least 4096 bytes apart (2 ^ 12 = 4096). The memory is
- ;effectively divided into 4K units along 4K boundaries. These 4K units are
- ;called "pages," hence the term "page mode."
- ; The first-level table is called a "page directory." The tables at the
- ;second level are called "page tables." You typically give each program its
- ;own page directory and page tables. This is how we use a different
- ;translation method for each program.
- ; One of the most effective ways to protect a physical page from a
- ;particular program is to simply avoid placing the address of the page in the
- ;program's page tables. If the address of a physical page is not anywhere
- ;in the page tables, then there is no way that the program can access it,
- ;provided of course that we also prevent the program from playing with the
- ;page tables themselves. Hence, we could completely shield one program from
- ;another. This largely explains how OS/2 and Windows NT achieve such high
- ;degrees of protection.
- ; Now the page tables are themselves pages. That is, they are 4K in size
- ;and are situated on 4K physical address boundaries. This means that their
- ;addresses are zero in the lowest 12 bits. The pages they catalog are also
- ;zero in the lowest 12 address bits. This means that for each entry in the
- ;page directory and for each entry in the page tables we have 12 bits to play
- ;with (the lowest 12) because we never need them for address specification.
- ; An operating system can use certain of these bits to implement other
- ;protection mechanisms of the processor. For example, the operating system
- ;can use one of these bits to designate the page as read-only. Try to write
- ;to it and you are going to get a page fault (exception #14). A page can
- ;also be marked as privileged. This means that the operating system can
- ;access it but most other programs cannot.
- ; Another important bit in the page tables is the "present" bit. This bit
- ;is set if there is actually a physical page available for the implied
- ;logical address. What happens when you try to access a logical address
- ;whose page table entry is marked not present? Well, you are going to get
- ;another page fault. Under XLIBE this almost certainly means that your
- ;program is going to get terminated. Indeed, XLIBE will usually be
- ;responsible for terminating you (gently if at all possible). Which explains
- ;one of the reasons why you need to understand page mode. Page faults are
- ;going to become a major part of your protected-mode life. If your program
- ;has a wild read or write, or a bad JMP or CALL, or a RET or IRET with
- ;a mismanaged stack, then page faults are likely.
- ; Some operating systems and memory managers have "virtual memory." This
- ;is where you are using disk to emulate memory. The operating system may
- ;give you a logical address block which really doesn't have any physical
- ;memory to back it up. The page table entries for this logical address block
- ;are all marked not present. When you try to access one of these logical
- ;addresses, the resultant page fault is trapped by the operating system,
- ;which then pulls the requested page off the disk and places it in a special
- ;memory area designed for such purposes. Your page table entry is then
- ;pointed to this location and is marked present. Finally, control is
- ;returned to you. You may never know what happened.
- ; You can actually use virtual memory under XLIB. Just get a DPMI host
- ;with virtual memory capabilities.
-
-
- +++++++++++++++++++++++
- + FPU Exceptions +
- +++++++++++++++++++++++
-
-
- ; Floating point exceptions are handled a bit differently than CPU
- ;exceptions by XLIBE. Suppose you had a major goofup in your code like this:
- ;
- ; FLD1 ;Load 1.0
- ; FLDZ ;Load 0.0
- ; FDIV ;Compute 1.0/0.0 (very sinful)
- ; FSTP ST ;Pop the "quotient"
- ;
- ;The FDIV will cause a zero divide exception in the FPU. This exception will
- ;not be signalled to the CPU until the next floating point instruction. So
- ;the FSTP ST instruction is where things are going to happen.
- ; XLIBE is going to promptly throw you back into real mode when this
- ;happens. As explained above, XLIBE remembers where you left real mode (it
- ;kept the return address from the call to CALLPM), and that is where it is
- ;going to send you. When you get there, everything but EAX and EDX are going
- ;to be restored to the values they last had in real mode. AX will contain
- ;an error code. The high word of EAX will contain the FPU status word. You
- ;can examine this to determine what caused the exception. Your machine may
- ;be in an unstable state (not likely). Read the documentation for more.
-