home *** CD-ROM | disk | FTP | other *** search
Text File | 1989-01-26 | 53.8 KB | 2,187 lines |
- ; V386.A86
- title '386 Initialization'
- pagesize 60+11
- ;********************************************************
- ;* *
- ;* XIOS INITIALIZATION ROUTINE *
- ;* CDOS 386 XIOS *
- ;* DRI OS ENGR, GMS, JW *
- ;* *
- ;********************************************************
- ;* *
- ;* RASM86 V386 $pz sz nc 286 *
- ;* *
- ;********************************************************
-
- ; Modifications :-
- ;
- ; 3.0
- ; 12 JAN 89 -- Page fault detects reset IDLE if screen I/O GMS
- ; 12 Jan 89 -- increase memory free list for systems =512 conv IJ
- ; 10 Nov 88 -- check if ROM BIOS access to port 61h on SR GMS
- ; 9 Nov 88 -- support IN/OUT AX IJ
- ; 3 NOV 88 -- make Gate A20 code MCA compatible - no bleep JW
- ; 14 Oct 88 -- Reuse 386 initialization code JW
- ; 10 Oct 88 -- Align check now handles full 64k IJ
- ; 7 OCT 88 -- do stack switch on EXCEP_HANDLER GMS
- ; 21 SEP 88 -- Include PTERM.EQU GMS
- ; 21 SEP 88 -- Include PCTERM exception handler code GMS
- ; 20 SEP 88 -- Exception handler re-written GMS
- ; 8 AUG 88 -- changed DMA error message GMS
- ; 8 AUG 88 -- keyboard interrupts always go to XIOS handler GMS
- ; 3 AUG 88 -- support dma address translation channels 1-3 GMS
- ; 29 JUL 88 -- TMP Banked window allocated in alloc_tmp@ GMS
- ; 20 JUL 88 -- change CONV_DMA to check every 4 K JW/GMS
- ; 26 MAY 88 -- SunRiver support added GMS
- ; 24 MAR 88 -- support for DMA address translation on DMA CH1 GMS
- ; 18 MAR 88 -- Added setup check for extending above A000h GMS
- ; 2 DEC 87 -- replaced ega$ with redefined video$ GMS
- ; 6.0/2.0
- ; 17 NOV 87 -- autoscan lim emulation pages and disable if failed GMS
- ; 13 NOV 87 -- force MEM to setup 22 LIM save areas GMS+JW
- ; 12 NOV 87 -- Add memory checksum test if autoscanning GMS
- ; 10 NOV 87 -- Always enable high memory on COMPAQ's between GMS
- ; E000h - EFFFh, we use EGA ROM at C000h.
- ; 7 NOV 87 -- disable hi memory scan at E000-FFFF on Model 80 JW
- ; 6 NOV 87 -- add extra ROM check to autoscan GMS
- ; 1 Nov 87 -- tell MEM it's O.K. to move SYSDAT JW
- ; 27 OCT 87 -- map out lim area from hi memory test GMS
- ; 16 OCT 87 -- add hi memory support from setup info GMS
- ; 5-Aug-87 -- add TPA at C000 or C400 for PCTmps's JW
- ; 28/JUL/87 -- Support for PS/2 model 80 hard disk DMA GMS
- ; 20/JUL/87 -- I/O bit map increased to support ports upto FFFFh JW
- ; 2/JUL/87 -- Conv_dma changed to check for linear mem on GMS
- ; transfers over 16k boundary.
- ; 22/MAY/87 -- increase memory free list for systems <640k conv GMS
- ; 15/MAY/87 -- LIM default settings read from setup area GMS
- ; 28/APR/87 -- direct DMA - check if next block contiguous GMS
- ; 3/APR/87 -- increase I/O bit map to 1000h GMS
- ; 18/FEB/87 -- increase memory free list for hercules/cga GMS
- ;
-
- eject
-
- nolist
- include CDOS.EQU
- include XIOS.EQU
- include PCHW.EQU
- include ASCII.EQU
- include ROSDATA.EQU
- include PTERM.EQU
- list
- ; These have been included:
- ; include CDOS.EQU
- ; include XIOS.EQU
- ; include PCHW.EQU
- ; include ASCII.EQU
- ; include ROSDATA.EQU
- ; include PTERM.EQU
- eject
-
- ; Global Descriptor Table Selectors
-
- DESC_LEN equ 08h ; length of GDT descriptor
- GDT_GDT_SEL equ 1*DESC_LEN ; GDT itself
- GDT_SYSDAT_SEL equ 4*DESC_LEN ; SYSDAT descriptor
- GDT_SS_SEL equ 7*DESC_LEN ; SS descriptor
- GDT_INT_SEL equ 8*DESC_LEN ; 8086 interrupt vectors
- GDT_PTBL_SEL equ 9*DESC_LEN ; PTBL descriptor
- GDT_XIOSC_SEL equ 3*DESC_LEN ; XIOS code seg descriptor
-
-
- ; Page size used for allocation
-
- MBLK_SIZE equ 16*1024 ;16 Kbytes
- MBLK_PARA equ MBLK_SIZE/16 ;page size in paragraphs
- MBLK_MASK equ MBLK_PARA-1 ;mask all but page select bits
- MBLK_SHIFT equ 10 ;log2(MBLK_PARA)
-
- ; Descriptor table sizes
- PAGE_SHIFT equ 12 ; 386 uses 2**12 bits per page (4 Kb)
- IDT_SIZE equ 128*8 ; we only use vectors 00h-77h
- TSS_SIZE equ (68h+(2000h)+1)
- PAGE_SIZE equ (1 shl PAGE_SHIFT)
-
- ; I/O permission bit map equates
- DMA_INIT_BIT equ 0000010000000000b ; dma initialise
- DMA_80_INIT equ 0000000100000000b ; dma initialise
-
- DMA equ 0
- DMA_INIT equ DMA+10 ; dma init port address
-
- ; Descriptor table definitions
- DATA_ACCESS equ 092h ; data type descriptor
- INT_GATE equ 08eh ; 386 interrupt gate
-
- MAX_HI_PAGES equ 14 ; max number of 16k blocks to check
-
- ; Hardware interrupt stack frame
-
- EX_BP equ word ptr 0[bp]
- EX_INT equ word ptr 4[bp] ; interrupt vector * 4
- EX_IP equ word ptr 6[bp]
- EX_CS equ word ptr 10[bp]
- EX_EFLAGS equ word ptr 14[bp]
- EX_SP equ word ptr 18[bp]
- EX_SS equ word ptr 22[bp]
- EX_ES equ word ptr 26[bp]
- EX_DS equ word ptr 30[bp]
- EX_FS equ word ptr 34[bp]
- EX_GS equ word ptr 38[bp]
-
-
- ; Exception interrupt handler stack frame
-
- EXCEP_AL equ byte ptr 4[bp]
- EXCEP_AH equ byte ptr 5[bp]
- EXCEP_AX equ word ptr 4[bp]
- EXCEP_IP equ word ptr 6[bp]
- EXCEP_CS equ word ptr 8[bp]
- EXCEP_FLAGS equ word ptr 10[bp]
-
- ; Codemacro for 80386 instruction:
-
-
- CodeMacro OP_32
- DB 66h
- EndM
-
- eject
-
-
- CGROUP group V386_CODE
- DGROUP group V386_DATA
-
-
-
- V386_CODE cseg
-
- extrn sysdat$:word ; in HEADER.A86
-
- extrn mem_alloc_i@ :near ; in INIT.A86
- extrn io_mem_alloc@:near
- extrn init_reuse@:near
- extrn io_conout@ :near
- extrn fatal_int@ :near ; in ISRS.A86
- extrn proc_abort@:near ; in WINDOWS1.A86
- extrn i_keyboard@:near ; in KEYBOARD.A86
- extrn point_vs@:near, point_cursor@:near ; in WINDOWS2.A86
-
- public init_386@ ; for INIT.A86
- public vxm_dma@ ; for FLOPPY.A86
- public alloc_tmp@ ; for INIT.A86
-
- if not SR
- extrn point_vc@:near ; in PCTERM.A86
- extrn pc_point_curs@:near
- endif
-
- dseg
- public vm_flag$ ; we're in virtual mode
-
- public hi_xmem_addr$, hi_xmem_size$ ; shadowed RAM from A000-E000
- public num_pages$
-
- extrn dma_low16$:word ; in FLOPPY.A86
- extrn dma_high4$:byte ;
- extrn pc_at$:byte
- extrn fatal_prot$:byte ; in ISRS.A86
- extrn active_vc$:byte ; in PCTERM.A86
- extrn fatal_page$:byte
-
- extrn hi_on$:word, hi_off$:word ; in INIT.A86
- extrn kbd_imhere$: byte ; in KEYBOARD.A86
- extrn video$:byte ; in WINDOWS1.A86
- extrn su_check$:word, su_lim_flag$:byte ; in HEADER.A86
- extrn su_lim_base$:word, su_lim_maxsize$:word
- extrn su_hi_enable$:word, su_hi_auto$:word
- extrn su_flag_bits$:word
- extrn num_mmkb$:word ; in PUBDATA.A86
- extrn ccb_list$:word
- if SR
- extrn io_basead$:word ; in SRTERM.A86
- extrn switch_seg$:word
- endif
-
- V386_CODE cseg
-
- INITCODE_START equ offset $ ; start of reusable code
-
- ;---------
- init_386@: ; test for the 80386
- ;---------
-
- ;; 386 Machine - setup
- ;; -------------------
- mov vm_flag$,0ffh ; internal XIOS flag
- mov bx,v386_ptr$ ; load BX -> to V386 specific table
- ; see if SETUP been run
- cmp su_check$,0DDB2h ; check for secret code
- jnz no_setup ; no, do not change defaults
- mov ax,su_lim_base$ ; get setup values
- mov lim_pfba$,ax ; and save in v386 table
- mov al,su_lim_flag$
- mov lim_flag$,al
- mov ax,su_lim_maxsize$
- mov lim_maxpag$,ax
- no_setup:
- test lim_flag$,0ffh ; lim emulation enabled ?
- jz no_check
- mov dx,lim_pfba$ ; get lim base address
- mov cx,4 ; number of 16 kb pages to test
- check_lim:
- call auto_extra ; scan LIM area for use as ROM or RAM
- or al,al
- jnz dis_limemu ; if page unavailable disable emulation
- call auto_scan
- or al,al
- jnz dis_limemu
- add dx,MBLK_PARA
- loop check_lim
- jmps no_check ; All 4 pages o.k
- dis_limemu:
- mov lim_flag$,00h ; disable lim emulation
-
- no_check:
- call mem_init ; initialise for paged memory
- call build_idt ; build the interrupt descriptor table
- call build_tss ; build task state segment descriptor
-
- cli ;; lock out interrupts for a while
- mov bx,5070h
- call reprog_pic ;; reprogram PIC for protected mode
- mov di,50h*4 ;; start vector
- mov si,offset dummy_int_50 ;; start offset of isr
- mov cx,8 ;; count
- call do_int_vecs ;; setup some dummy int vectors at 50h
- call gate_a20_on ;; enable A20 for 1meg wrap
-
- mov bx,v386_ptr$ ;; get pointer to vxm table in SYSDAT
- mov ax,offset excep_handler
- mov excep_off,ax ; put our exception handler address
- mov excep_seg,cs ; into SYSDAT.
- mov keyboard_isr + 2,cs ; also store for keyboard isr address
- mov ax,offset pfault_handler
- mov pfault_off,ax ; put page fault handler into SYSDAT
- mov pfault_seg,cs
-
- mov nvcons$,NUM_VIR_CONS+2*NUM_AUX_PORTS
- ; force memory manager to allocate
- ; LIM save areas for the maximum
- ; # of virtual consoles that we support
- ; (two VC's per serial port)
- ; actual values set in ALLOC_SER_RSPS
- ; in INIT.A86
-
- or v386_flag,80h ; O.K. to move SYSDAT (if possible)
- ; this can only be turned on if
- ; there are no MFL/MWD entries
- ; below SYSDAT, memory at the low
- ; end of the TPA is contiguous,
- ; no segment allocations have been
- ; made yet and no pointers to SYSDAT
- ; are stored anywhere in the
- ; operating system yet (except
- ; XIOS CS:6, SUP CS:6 and NDOS CS:6)
- mov si,INITCODE_START
- mov di,INITCODE_END
- call init_reuse@ ; reuse initialization code
-
- ret
-
- eject
- mem_init: ; initialise for paged memory
- ;-------- ; BX -> V386 table
- mov ah,88h
- int 15h ; get extended memory size above 1024k
- mov emem,ax ; addressing range AX=size in 1k blocks
- push ax
- or ax,ax ; is there any extended memory
- jnz grow_mem
- jmp dont_grow ; no - silly system
- grow_mem:
- mov ax,num_mmkb$ ; AX = conventional memory size in K
- cmp ax,512 ; is it already full window?
- jne is_640 ; yes..
- mov cx,128/16 ; else grow mfl from 512k to 640k
- mov ax,8000h
- call increase_mfl
- is_640:
- test video$,EGA+VGA ; test if EGA/VGA installed
- jnz is_ega ; EGA attached - EXIT
- test su_flag_bits$,A000_VIDEO ; is non ega video ram at A000h
- jnz is_ega ; yes, don't extend TPA
- mov ax,0A000h ; increase no. memory partitions by 4
- mov cx,4
- call increase_mfl
- is_ega:
-
- ; Lets grow the free high memory
- ; if SETUP options enabled
- push bx ; save v386_ptr
-
- test lim_flag,0ffh ; lets find if LIM enabled
- jz no_lim ; and mask out LIM region from hi mem
- mov dx,lim_pfba ; get lim base address
- mov cx,MAX_HI_PAGES
- mov ax,0001h ; mask regs
- xor bx,bx
- sub dx,(0C000h-MBLK_PARA)
- lim_loop:
- sub dx,MBLK_PARA ; 16k block
- jz found_lim
- shl ax,1
- loop lim_loop
- found_lim:
- or bx,ax ; mask out
- mov dx,1000h ; 64k in paragraphs
- lim_loop2:
- sub dx,MBLK_PARA
- jz found_lim2
- shl ax,1 ; shift mask
- or bx,ax ; and set
- loop lim_loop2 ; keep going for length of LIM
- found_lim2:
- not bx
- and su_hi_enable$,bx ; mask enable setup bits
- and su_hi_auto$,bx ; and autoscan bits
-
- no_lim:
- test word ptr su_hi_auto$, 0ffffh ; any auto-scanning enabled
- jz no_auto
- call autoscan_all ; find free memory and set enable flags
- no_auto:
- mov ax,hi_off$
- and su_hi_enable$,ax ; on COMPAQ: and 0FFFh: nothing >= F000
- mov ax,hi_on$
- or su_hi_enable$,ax ; on COMPAQ: or 0F00h: use E000-EFFF
-
- mov bx,su_hi_enable$
- test bx, bx ; any high mem pages enabled?
- jz no_hi_mem
- ; build high MFL
- mov cx,MAX_HI_PAGES ; max pages to enable
- mov di,offset hi_mfl ; high memory free list
- mov si,di
- mov dx,0C000h ; start search address
- search_loop:
- shr bx,1 ; get setup bits
- jnc next_scan
- test hi_on$,1 ; known-good memory?
- jnz enable1 ; skip the test (COMPAQ/Sprite)
- call auto_scan ; check for ROM/RAM
- or al,al
- jz enable1 ; enable bit
- disable_loop:
- dec al ; count of bad 16k blocks
- jz next_scan
- shr hi_on$,1 ; skip next bit in "forced-on" mask
- shr bx,1 ; skip next bit in mask
- add dx,MBLK_PARA ; next 16k block
- jmps disable_loop
-
- enable1:
- mov MD_START[di],dx ; else build memory descriptor
- mov MD_LENGTH[di],MBLK_PARA ; 16k block
- mov si,di ; current MD
- add di,MD_SIZE ; next descriptor
- mov MD_LINK[si],di ; link to next
- next_scan:
- shr hi_on$,1 ; shift enforced on bits
- add dx,MBLK_PARA ; next 16k block
- loop search_loop
-
- mov MD_LINK[si],0000h ; terminate link
- cmp MD_START[si],0000h
- jz no_hi_mem ; none allocated
-
- mov si,offset hi_mfl
- mov bx,v386_ptr
- mov hi_mfl_root,si ; start of hi_mfl into 386 table
- no_hi_mem:
-
- ; Group together all contiguous memory allocations from auto scan
- mov bx,v386_ptr
- mov di,hi_mfl_root ; start of hi_mfl from 386 table
- test di,di ; did scan find any memory
- jz end_trim ; no hi mem allocs
- not_contig:
- mov bx,di ; move to next item
- trim_next:
- mov di,MD_LINK[bx] ; link to next
- or di,di
- jz end_trim ; end of linked list
- mov ax,MD_START[bx] ; start seg
- add ax,MD_LENGTH[bx] ; + length of partition
- cmp ax,MD_START[di]
- jne not_contig ; not contiguous
- mov ax,MD_LENGTH[di] ; else fold two partitions together
- add MD_LENGTH[bx],ax
- mov ax,mdul
- xchg ax,MD_LINK[di] ; release entry into MDUL
- mov mdul,di
- mov MD_LINK[bx],ax ; skip now unused entry
- jmps trim_next
-
- end_trim:
- pop bx ; restore v386_ptr
-
- dont_grow:
- pop ax ; get conventional memory size in K
- add ax,1024 ; add in 1st megabyte
- shr ax,4 ; AX = # of 16 K pages
- cmp hi_xmem_size$,0 ; is there RAM above extended memory?
- je no_hi_xmem ; skip if regular extended memory only
- mov ax,hi_xmem_addr$ ; AX = A16..A31 of extra high memory
- shl ax,2 ; convert to 16 K block #
- add ax,hi_xmem_size$ ; add in the size in 16 K blocks
- and ax,(0-8) ; make sure it's paragraph alignable
- no_hi_xmem:
- mov npages$,ax ; # of words in free space map
- shr ax,3 ; 8 words per paragraph
- xchg ax,dx ; DX = # of paragraphs
- call mem_alloc_i@ ; allocate free space map segment
- mov mp_table$,ax ; AX = map segment - insert in SYSDAT
- mov es,ax ; ES -> map segment
-
- mov cx,npages$ ; CX = word count
- mov ax,0FFFFh ; AX <> 0: not available for allocation
- sub di,di
- rep stosw ; mark all pages as used
-
- mov ax,num_mmkb$ ; get normal memory
- shr ax,4 ; available in 16k blocks
- mov cx,ax ; mark as available - either 512/640
- sub ax,ax ; 0000 means available
- sub di,di
- rep stosw ; mark conventional RAM as usable
-
- mov di,(1024/16)*WORD ; base of extended memory in mp_table$
- mov cx,emem ; get extended memory size in Kb
- shr cx,4 ; convert to 16 Kb blocks
- rep stosw ; mark extended memory as available
-
- mov di,hi_xmem_addr$ ; base of extra high memory
- shl di,3 ; convert to offset in mp_table$
- mov cx,hi_xmem_size$ ; get # of good pages up there
- rep stosw ; mark hi extended as available
-
- ; Now print a short summary:
-
- sub dx,dx
- mov cx,npages$ ; count all available pages
- sub si,si
- mov es,mp_table$
- count_pages:
- lods es:ax
- test ax,ax
- jnz count_pag1
- add dx,MBLK_SIZE/1024
- count_pag1:
- loop count_pages
- xchg ax,dx ; AX = # of kilobytes
- mov num_pages$,ax
- ret
-
- ; Scan hi memory regions from C000h-F7FFh
- ; for ROM or RAM if "su_hi_auto$" bit set
- ; and set corresponding bits in "su_hi_enable$"
- autoscan_all:
- mov bx,su_hi_auto$ ; get autoscan enable bits
- mov cx,MAX_HI_PAGES ; max pages to enable
- mov dx,0C000h ; start search address
- mov si,0001h ; setup enable bit mask
- autoscan_loop:
- shr bx,1 ; autoscan enabled
- jnc next_autoscan ; no..
- call auto_extra ; extra scan for autoscanning
- or al,al
- jnz dis_loop ; found something so disable
- ; else do more tests
- push si
- call auto_scan ; test region
- or al,al
- pop si
- jz ena ; enable bit
- dis_loop:
- dec al ; count of bad 16k blocks
- jz next_autoscan
- shr bx,1 ; update autoscan bits
- shl si,1 ; update mask
- add dx,MBLK_PARA ; next 16k block
- jmps dis_loop
- ena:
- or su_hi_enable$,si ; set setup enable bit
- next_autoscan:
- shl si,1 ; update mask
- add dx,MBLK_PARA ; next 16k block
- loop autoscan_loop ; scan all
-
- ret
-
- ; Extra scan routine for Autoscanning modes
- ; Entry : DX = scan segment
- ; Exit:
- ; AL = 0 no valid info
- ; else AL = count of unavailable pages
- auto_extra:
- push bx ! push cx ! push dx ! push si ! push di
- push ds
- mov ds,dx ; scan segment
- mov es,dx
- xor di,di
- mov cx,256
- xor ax,ax
- repe scasw ; if all zeroes
- jz end_test ; then exit (test invalid)
-
- xor di,di
- mov cx,256
- mov ax,0ffffh
- repe scasw ; if all bytes FFh
- jz end_test ; then exit (test invalid)
-
- call chk_test ; get checksum of area
- mov dx,bx ; and store
- mov cx,10h ; loop count
- do_chk_loop:
- push cx
- call chk_test ; get checksum again
- pop cx
- cmp bx,dx ; compare new checksum with original
- loope do_chk_loop ; retry if still the same
- mov al,1 ; ready for error exit
- je not_avail ; if data remains constant then segment
- ; probably contains ROM or RAM
- ; so mark as unavailable
- end_test:
- xor al,al ; test proved inadequate
- not_avail:
- pop ds
- pop di ! pop si ! pop dx ! pop cx ! pop bx
- ret
-
- chk_test:
- xor si,si
- xor ah,ah
- xor bx,bx
- mov cx,512
- chk_loop:
- lodsb
- add bx,ax ; compute simple checksum
- loop chk_loop
- ret
-
- ; Scan region for presence of ROM or RAM
- ; Entry : DX = scan segment address
- ; Exit:
- ; AL = 0 if available
- ; else AL = count of unavailable pages
- auto_scan:
- push di ! push cx
- mov ax,0ffffh ; find start of ROM segment
- mov es,ax ; reset vector address
- mov ax,es:.01h ; get offset
- and ax,0C000h ; round down to
- shr ax,4
- add ax,es:.03h ; + segment of reset code
- cmp dx,ax
- mov al,1
- jae scan_ret ; exit AL = unavailable count
-
- mov es,dx
- xor di,di
- mov ax,0AA55h ; IBM ROM ID
- scasw ; check for ROM ID, DI += 2
- jne test_ram ; no ROM so test RAM
- mov al,es:[di] ; get # of 512 byte pages in ROM
- add al,((16384/512)-1)
- mov cl,5
- shr al,cl ; AL = # of 16 Kb pages
- ;; inc al ; ##JW## this seems wrong
- jmps scan_ret ; exit AL = unavailable count
-
- test_ram:
- xor di,di ; check for RAM
- mov cx,10
- mov al,80h
- out CMOS_ADDR,al ; disable NMI
- jmps $+2
- in al,CMOS_DATA ; dummy read
- ram_check:
- mov al,es:[di] ; read a byte
- push ax ; and preserve
- not al
- mov es:[di],al ; write a differnt pattern
- jmps $+2 ; use the data bus
- cmp al,es:[di] ; read back the value
- pop ax
- mov es:[di],al ; write back original byte
- mov ah,0 ; for good return
- jnz map_ok ; no RAM up there so available
- inc di ! inc di ; even boundary read/write check
- loop ram_check
- inc ah ; bad return
- map_ok: ; return ZF reset
- mov al,0
- out CMOS_ADDR,al ; re-enable NMI
- jmps $+2
- in al,CMOS_DATA ; dummy read
- mov al,ah ; return code
- scan_ret:
- pop cx ! pop di
- ret
-
-
- print_num:
- ; entry: AX = number to print
-
- sub dx,dx
- mov cx,10
- div cx ; AX = result, DX = remainder
- push dx
- test ax,ax
- jz print_num1
- call print_num ; print result if non-zero
- print_num1:
- pop cx ; remainder is last digit in binary
- add cl,'0' ; convert to ASCII digit
- sub dx,dx ; ouput to master console
- jmp io_conout@ ; print the last character
-
-
- print_msg:
- lodsb ; fetch a character
- pr_msg_loop:
- push si
- call print_char ; print just one
- pop si
- lodsb ; fetch another
- test al,al
- jnz pr_msg_loop ; when char = 0, done
- ret
-
-
- print_char:
- mov cl,al ; char to cl
- mov dl,0
- jmp io_conout@ ; print it
-
-
- ; Build interrupt descriptor table
- ; must be at least 256 bytes in size for 80386 ints
- ; Enter BX = -> V386 table in SYSDAT
- build_idt:
- push bx
- mov dx,(IDT_SIZE+15)/16
- call mem_alloc_i@
- mov idt_seg$,ax ; insert in SYSDAT
- mov idt_limit$,IDT_SIZE-1
- mov es,ax ; IDT destination seg
- xor di,di
- xor ax,ax ; clear whole table
- mov cx,IDT_SIZE/2 ; words
- rep stosw
-
- mov bx,GDT_XIOSC_SEL ; XIOS code segment selector
- mov dh,INT_GATE ; interrupt gate type
- xor dl,dl
- ; build 8 descriptors in IDT for Master PIC ints
- ; PIC ints 50h -> 57h
- mov si,offset idt_m_pic_offs
- mov di,50h*8 ; offset 50h in IDT
- mov cx,8
- call idt_loop ; insert in IDT
-
- ; build 8 descriptors in IDT for Slave PIC ints
- ; PIC ints 70h -> 77h
- mov si,offset idt_s_pic_offs
- mov di,70h*8 ; offset 70h in IDT
- mov cx,8
- call idt_loop ; insert in IDT
- pop bx
- ret
-
-
- ; setup IDT params
- idt_loop:
- movsw ; get routine entry offset
- mov ax,bx ; IDT code segment selector
- stosw ; store in IDT
- mov ax,dx ; interrupt gate type
- stosw
- mov ax,0 ; high bits of offset
- stosw
- loop idt_loop
- ret
-
-
- ; build task state segment
- ; and I/O permission bit map:
- ; Enter BX = -> V386 table in SYSDAT
- build_tss:
- mov dx,(TSS_SIZE+15)/16
- call mem_alloc_i@
- mov tss_seg$,ax ; insert in SYSDAT
- mov tss_limit$,TSS_SIZE
- mov es,ax
- sub di,di
- mov cx,TSS_SIZE/2 ; size of TSS including I/O map
- sub ax,ax
- rep stosw ; initilaise TSS + I/O map
- mov di,66h ; insert offset of BIT_MAP_OFFSET
- lea ax,2[di] ; start bit map after offset
- stosw
- or es:word ptr[di],DMA_INIT_BIT ; set bit in I/O map - port 0Ah
- test pc_at$,02h ; is it model 80
- jz not_80
- or es:word ptr 2[di],DMA_80_INIT ; set bit in I/O map - port 18h
- not_80:
- ret ; trap on access to DMA initialise
-
-
-
- reprog_pic:
- ;----------
- ; entry: BH = master PIC vector
- ; BL = slave PIC vector
-
- in al,MAST_PIC1 ; read old interrupt mask
- push ax
- mov al,11h ; get ICW1 (edge triggered, master)
- out MAST_PIC0,al
- jmps $+2
- mov al,bh ; get master's base address
- out MAST_PIC1,al ; (ICW2 = vector #)
- jmps $+2
- mov al,04h ; ICW3: slave hooked up to #2
- out MAST_PIC1,al
- jmps $+2
- mov al,01h ; ICW4: master PIC, 8086 mode
- out MAST_PIC1,al
- jmps $+2
- pop ax
- out MAST_PIC1,al ; restore interrupt mask
-
- jmps $+2
-
- in al,SLAVE_PIC1 ; read old interrupt mask
- push ax
- mov al,11h ; get ICW1 (edge triggered, master)
- out SLAVE_PIC0,al
- jmps $+2
- mov al,bl ; get slave's base address
- out SLAVE_PIC1,al ; (ICW2 = vector #)
- jmps $+2
- mov al,02h ; ICW3: slave hooked up to #2
- out SLAVE_PIC1,al
- jmps $+2
- mov al,01h ; ICW4: master PIC, 8086 mode
- out SLAVE_PIC1,al
- jmps $+2
- pop ax
- out SLAVE_PIC1,al ; restore interrupt mask
- ret
-
- ; Set up some dummy interrupt vectors
- ; in case we have an interrupt from the PIC
- ; before protected mode is enabled..
- ; Entry : DI = int vector offset
- ; SI = start isr offsets
- ; CX = count
- do_int_vecs:
- xor ax,ax
- mov es,ax
- mov ax,cs
- do_all_ints:
- mov es:[di],si ; store offset
- add si,3 ; next offset address
- inc di ! inc di
- stosw ; store segment
- loop do_all_ints
- ret
-
- eject
- ; Routine to enable or disable A20 for 1meg wrap
- gate_a20_on:
- test pc_at$,2 ; MCA based machine?
- jz pcat_a20_on ; skip if "classic bus" machine
- in al,MCA_SYSCTLA
- or al,SYSCTLA_A20 ; enable the A20 line
- out MCA_SYSCTLA,al
- ret
-
- pcat_a20_on:
- mov ah,0dfh
- cli
- call wait_8042 ; ensure the keyboard buffer is empty
- jnz gate_ret
- mov al,0d1h ; command to write output port
- out AT_KBD_STATUS,al
- call wait_8042
- jnz gate_ret
- mov al,ah
- out KBD_DATA,al
- gate_ret:
- ret
-
- wait_8042: ; wait for the 8042 input buff empty
- sub cx,cx
- wait_loop:
- in al,AT_KBD_STATUS
- and al,IN_BUF_FULL ; test input buffer flag
- loopnz wait_loop
- ret
-
- INITCODE_END equ offset $ ; end of reusable initialization code
-
- eject
-
- dummy_int_50:
- int 08h ; go to 8086 interrupt service routine
- iret
-
- dummy_int_51:
- int 09h
- iret
-
- dummy_int_52:
- int 0ah
- iret
-
- dummy_int_53:
- int 0bh
- iret
-
- dummy_int_54:
- int 0ch
- iret
-
- dummy_int_55:
- int 0dh
- iret
-
- dummy_int_56:
- int 0eh
- iret
-
- dummy_int_57:
- int 0fh
- iret
-
- eject
-
- ; Allocate 16k banked window for TMP allocation
- ; at top of TPA - uses best fit by calling io_mem_alloc
- ; Called from io_protect.
- alloc_tmp@:
- mov cx,(PAGE_SIZE)/16 -1 ; align on 4k boundary
- mov dx,1024*16/16 ; allocate 16k window
- call io_mem_alloc@ ; return AX = start segment address
- mov cx,16/16 ; enf of mwd for TMP allocation
- ;; call increase_mwd
- ;; ret ;;; fall through
- increase_mwd:
- lea si,mwdr$ ; memory window list root
- jmps find_next
-
- ; increase memory free list
- ; Entry : CX = number of 16k blocks
- ; AX = start segment address
- increase_mfl:
- lea si,mfl$ ; memory free list root
- find_next:
- mov di,si ; save previous link
- mov si,MD_LINK[di] ; link to next
- test si,si ; find end of MFL
- jnz find_next ; 0 => end of list
-
- mov si,mdul$
- mov MD_LINK[di],si ; insert start into end of MFL
- add_mem:
- mov dx,MBLK_PARA ; starting at A000h length 400h
- mov di,si ; save previous
- mov MD_START[si],ax
- mov MD_LENGTH[si],dx
- add ax,dx
- mov si,MD_LINK[si] ; link to next partition
- loop add_mem
- mov MD_LINK[di],0000 ; end new MFL
- mov mdul$,si ; new start of MDUL
- ret
-
-
- eject
-
- ; Exception handler interrupt service routine
- ; arrives here as per normal 8086 interrupt except CS:IP return address
- ; on stack actually points to the violating instruction.
- ; Before returning update IP on stack to point to next
- ; instruction and execute IRET.
- ;
- ; Note: before executing any I/O instruction
- ; reset relevent BIT in I/O map, else
- ; another exception interrupt will occur
- ; and you will be here for the rest of time.
-
- excep_handler:
- cli
- cld
- push ax
- push bp
- push ds
- mov bp,sp ; stack frame pointer
- mov ds,sysdat$
- mov excep_ss,ss ; save the registers
- mov excep_sp,sp
- mov ss,sysdat$
- mov sp,offset excep_stack_top
-
- pusha
- push es
-
- mov es,excep_ss ; get original stack seg
-
- mov cx,ax ; DX , AX = params for OUT DX,AX
- mov ds,es:EXCEP_CS
- mov si,es:EXCEP_IP ; DS:SI = violating instruction
- lodsb ; get 8086 opcode
- cmp al,0EEh ; check if "OUT DX,AL"
- je em_out_dx_al
- cmp al,0E6h ; check if "OUT port,AL"
- je em_out_al
- cmp al,0EFh ; check if "OUT DX,AX"
- jmpz em_out_dx_ax
- cmp al,0E7H ; check if "OUT port,AX"
- jmpz em_out_ax
-
- cmp al,0ECh ; check if "IN AL,DX"
- je em_in_dx_al
- cmp al,0E4h ; check if "IN AL,port"
- je em_in_al
- cmp al,0EDh ; check if "IN AX,DX"
- jmpz em_in_dx_ax
- cmp al,0E5h ; check if "IN AX,port"
- jmpz em_in_ax
-
- em_illegal:
- mov ds,sysdat$
- pop es
- popa
- mov ss,excep_ss
- mov sp,excep_sp
- pop ds
- pop bp
- pop ax
- mov si,offset fatal_prot$ ; 'Protection interrupt'
- jmp fatal_int@ ; display error message and terminate
-
- ; Emulate OUT instruction
- em_out_al:
- lodsb ; get port address byte
- xor dh,dh
- mov dl,al ; port address in DX
- em_out_dx_al:
- mov es:EXCEP_IP,si ; update IP for 1 or 2-byte opcode
- mov ds,sysdat$ ; get sysdat seg
- mov outbyte,cl ; save output byte
-
- push cs
- pop es
- mov di,offset port_addr
- mov ax,dx ; port address
- mov cx,num_ports
- repne scasw
- jmpnz em_illegal ; not supported
- sub di,offset port_addr
- sub di,2
- call es:out_table[di] ; execute "OUT" instruction CL=AL on entry
- jmp ret_excep
-
- ; Emulate "IN" instruction
- em_in_al:
- lodsb ; get port address byte
- xor dh,dh
- mov dl,al ; port address in DX
- em_in_dx_al:
- mov es:EXCEP_IP,si ; update IP for 1 or 2-byte opcode
- mov ds,sysdat$ ; get sysdat seg
-
- push cs
- pop es
- mov di,offset port_addr
- mov ax,dx ; port address
- mov cx,num_ports
- repne scasw
- jmpnz em_illegal ; not supported
- sub di,offset port_addr
- sub di,2
- call es:in_table[di] ; execute "IN" instruction
- ; AL on stack for exit
- jmp ret_excep
-
- ; Emulate OUT AX
- em_out_ax:
- lodsb ; get port address byte
- xor dh,dh
- mov dl,al ; port address in DX
- em_out_dx_ax:
- mov es:EXCEP_IP,si ; update IP for 1 or 2-byte opcode
- mov ds,sysdat$ ; get sysdat seg
-
- push cx ; save the word we are to output
- push dx ; and the port
-
- mov outbyte,cl ; save output byte
- push cs
- pop es
- mov di,offset port_addr
- mov ax,dx ; port address
- mov cx,num_ports
- repne scasw
- jmpnz em_illegal ; not supported
- sub di,offset port_addr
- sub di,2
- call es:out_table[di] ; execute "OUT" CL=AL on entry
-
- pop dx ; recover output port
- pop cx ; and the word
- inc dx ; point to next port
- mov cl,ch ; and output the hi byte
-
- mov outbyte,cl ; save output byte
- push cs
- pop es
- mov di,offset port_addr
- mov ax,dx ; port address
- mov cx,num_ports
- repne scasw
- jmpnz em_illegal ; not supported
- sub di,offset port_addr
- sub di,2
- call es:out_table[di] ; execute "OUT" CL=AH on entry
-
- jmp ret_excep
-
- ; emulate in AX
- em_in_ax:
- lodsb ; get port address byte
- xor dh,dh
- mov dl,al ; port address in DX
- em_in_dx_ax:
- mov es:EXCEP_IP,si ; update IP for 1 or 2-byte opcode
- mov ds,sysdat$ ; get sysdat seg
-
- push dx ; save the port
-
- push cs
- pop es
- mov di,offset port_addr
- mov ax,dx ; port address
- mov cx,num_ports
- repne scasw
- jmpnz em_illegal ; not supported
- sub di,offset port_addr
- sub di,2
- call es:in_table[di] ; execute "IN" instruction
- ; AL on stack for exit
- pop dx ; recover the port number
- inc dx ; and point to the next port
- mov es,excep_ss ; get original stack seg
- mov al,es:EXCEP_AL
- push ax ; save lo byte of IN
-
- push cs
- pop es
- mov di,offset port_addr
- mov ax,dx ; port address
- mov cx,num_ports
- repne scasw
- jmpnz em_illegal ; not supported
- sub di,offset port_addr
- sub di,2
- call es:in_table[di] ; execute "IN" instruction
- ; AL on stack for exit
- pop ax ; recover lo byte of IN
- mov es,excep_ss ; get original stack seg
- mov ah,es:EXCEP_AL ; get hi byte of IN
- mov es:EXCEP_AX,ax ; and save the word away
-
- ; jmp ret_excep
-
- ret_excep:
- pop es
- popa
- mov ss,excep_ss
- mov sp,excep_sp
- pop ds
- pop bp
- pop ax
- iret
-
- port_addr dw DMA_BMSK_REG ; dma command port
- dw DMA_FUNC_REG ; model 80 hard disk dma
- dw TIMER_2_REG ; counter timer port (beeper)
- dw TIMER_CMND_REG ; counter timer (beeper)
- dw PORT_B
- dw CRT_INDEX ; b&w CRT index registers
- dw CRT_DATA
- dw CRT_CTRL
- dw CRT_STATUS
- dw CRT_CONF
- dw COL_CRT_INDEX ; color CRT index registers
- dw COL_CRT_DATA
- dw COL_CRT_CTRL
- dw COL_CRT_STATUS
- dw COL_CRT_CONF
-
- num_ports equ (offset $ - offset port_addr)/2
-
- out_table dw offset out_dma
- dw offset out_dma_80
- dw offset out_timer2
- dw offset out_timer
- dw offset out_port_b
- dw offset out_crt_index
- dw offset out_crt_data
- dw offset out_crt_ctrl
- dw offset out_crt_status
- dw offset out_crt_conf
- dw offset out_col_index
- dw offset out_col_data
- dw offset out_col_ctrl
- dw offset out_col_status
- dw offset out_col_conf
-
- in_table dw offset in_dma
- dw offset in_dma_80
- dw offset in_timer2
- dw offset in_timer
- dw offset in_port_b
- dw offset in_crt_index
- dw offset in_crt_data
- dw offset in_crt_ctrl
- dw offset in_crt_status
- dw offset in_crt_conf
- dw offset in_col_index
- dw offset in_col_data
- dw offset in_col_ctrl
- dw offset in_col_status
- dw offset in_col_conf
-
- ; Set bit in I/O permission bit map
- ; Enter DX = port address
- set_trap:
- call get_mask
- or es:[bx],al ; set I/O bit
- ret
-
- ; Reset bit in I/O permission bit map
- ; Enter DX = port address
- reset_trap:
- call get_mask
- not al
- and es:[bx],al ; reset I/O bit
- ret
-
- get_mask:
- mov bx,v386_ptr
- mov es,tss_seg ; point ES to TSS SEGMENT
- push dx
- mov ax,dx
- mov bx,8
- xor dx,dx
- div bx
- mov bx,ax ; BX = byte to set
- add bx,68h ; offset of I/O bit map
- mov al,1
- mov cl,dl
- shl al,cl ; AL = bit position
- pop dx
- ret
-
-
- ; output byte to port
- ; Enter: DX=port
- ; outbyte=byte to output
- do_out:
- call reset_trap ; reset I/O bit
- mov al,outbyte ; output byte
- out dx,al
- call set_trap ; set I/O bit
- ret
-
- ; input byte from port
- ; Enter: DX=port
- ; byte on stack for exit
- do_in:
- call reset_trap ; reset I/O bit
- in al,dx
- mov es,excep_ss ; get original stack seg
- mov es:EXCEP_AL,al
- call set_trap ; set I/O bit
- ret
-
- eject
-
- ; DMA transfer
- in_dma:
- ;------
- jmp do_in ; just get input byte
- out_dma:
- ;-------
- mov es,excep_ss ; get original stack seg
- mov bx,es:EXCEP_CS
- mov ax,cs
- cmp bx,ax ; does it come from XIOS
- jne out_dma1
- jmp do_out ; yes it must be our floppy driver
- ; so just do OUT instructon
- out_dma1:
- call reset_trap ; reset bit in I/O map
- push dx
- call emu_dma ; emulate DMA
- pop dx
- call set_trap
- ret
-
- ; Model 80 hard disk DMA
- in_dma_80:
- ;---------
- jmp do_in ; just do input byte
-
- out_dma_80:
- ;----------
- call reset_trap ; reset bit in I/O map to
- push dx
- call do_emu_80 ; emulate OUT DX,AL
- pop dx
- call set_trap
- ret
-
- ; Used by Sunriver stations and PCTERMS
- out_timer2:
- out_timer:
- out_port_b:
- ;----------
- if SR
- cmp kbd_imhere$,0 ; in keyboard ISR ?
- jne out_sr1 ; yes - do not emulate on SunRiver
- mov es,excep_ss ; get original stack seg
- mov bx,es:EXCEP_CS
- cmp bx,0e000h ; from ROS
- jb out_sr ; no emulate
- out_sr1:
- jmp do_out ; else must be for main console
- out_sr:
- mov es,io_basead$
- mov bx,dx
- mov cl,outbyte
- mov es:[bx],cl ; do memory mapped i/o for station
- ret
- else
-
- mov es,excep_ss ; get original stack seg
- mov bx,es:EXCEP_CS ; handle beeper on PCTERMS
- mov ax,cs
- cmp bx,ax ; does it come from XIOS
- je port_b1 ; yes..
- cmp kbd_imhere$,0 ; in keyboard ISR ?
- jne port_b1 ; yes..
- cmp bx,0e000h ; or from ROS
- jb emu_beep
- port_b1:
- jmp do_out ; then do OUT DX,AL
- emu_beep:
- test byte ptr outbyte,02h ; beeper bit on??
- jz no_beep ; no trash it
- mov dl,active_vc$ ; get active virtual console
- call point_vc@ ; point to VC_ structure
- or VC_MODE,BEL_BIT ; get flush to output bell code
- no_beep:
- ret
-
- endif
-
- ; Used by Sunriver stations
- in_timer2:
- in_timer:
- ;--------
- jmp do_in ; just do IN instruction
-
- ; Used by Sunriver stations and PCTERMS
- in_port_b:
- ;---------
- if SR
- cmp kbd_imhere$,0 ; in keyboard ISR ?
- jne do_in ; yes - must be for main console
- mov es,excep_ss ; get original stack seg
- mov bx,es:EXCEP_CS
- cmp bx,0e000h ; from ROS
- jae do_in
- mov es,io_basead$
- mov bx,dx
- mov al,es:[bx] ; do memory mapped i/o for station
- mov es,excep_ss ; get original stack seg
- mov es:EXCEP_AL,al ; put on stack for exit
- ret
- endif
- jmp do_in ; PCTERM
-
- ; B&W and Color CRT index registers
- out_crt_index:
- out_col_index:
- ;-------------
- mov dl,active_vc$ ; get active virtual console
- if not SR
- cmp dl,NUM_VIR_CONS
- jb video1
- call point_vc@
- mov al,outbyte
- mov VC_CRT_IDX,al ; set virtual CRT index register
- ret ; in VC_ structure
- endif
- video1:
- call point_vs@
- mov al,outbyte
- mov VS_CRT_IDX,al ; set virtual CRT index register
- ret ; in VC_ structure
-
- out_crt_data:
- out_col_data:
- ;------------
- mov dl,active_vc$ ; get active virtual console
- if not SR
- cmp dl,NUM_VIR_CONS
- jb video2
- call point_vc@
- mov dl,VC_CRT_IDX ; get data register index
- cmp dl,13h ; range check it
- ja out_crt1
- mov dh,0 ; make it a word
- lea di,VC_CRT_DATA ; get VC_ data area
- add di,dx ; add index
- mov al,outbyte
- mov [di],al ; save value written in VC_CRT_DATA
- cmp dl,10
- je cur_hide
- cmp dl,11
- je cur_hide ; cursor start/end regs
- cmp dl,15 ; was it cursor address?
- jne out_crt1 ; skip if not
- dec di
- mov ax,[di] ; get our cursor address
- xchg al,ah ; swap high/low for 6845
- and ah,3fh ; cursor location register is 14 bit
- mov dl,CRT_COLS
- div dl ; AL = row, AH = col
- mov dh,al ; DH = row
- mov dl,ah ; DL = column
- cmp dh,VC_ROWSB ; check if in legal range
- jae out_crt1 ; no, skip cursor update
- call pc_point_curs@
- mov VC_OFFSET,ax
- mov VC_CURSOR,dx ; set cursor position
- out_crt1:
- ret
-
- cur_hide:
- lea di,VC_CRT_DATA ; get VC_ data area
- mov cx,10[di] ; get cursor start/end
- xchg cl,ch
- test ch,60h ; setting bits 5 or 6 turns cursor off
- jnz c_off
- and ch,0fh ; mask start cursor line
- and cl,0fh ; and end
- cmp ch,cl ; if start > end
- ja c_off ; then turn cursor off
- or VC_MODE,CURSOR_BIT
- jmps c_ret ; turn on
- c_off:
- and VC_MODE,not CURSOR_BIT
- c_ret:
- or VC_MODE,UPDATE_BIT ; flag flush to turn on/off
- ret
- endif
- video2:
- call point_vs@
- mov dl,VS_CRT_IDX ; get data register index
- cmp dl,18h ; range check it
- ja out_crt2
- mov dh,0 ; make it a word
- lea di,VS_CRT_DATA ; get VC_ data area
- add di,dx ; add index
- mov al,outbyte
- mov [di],al ; save value written in VC_CRT_DATA
- cmp dl,10
- je cur_hide1
- cmp dl,11
- je cur_hide1 ; cursor start/end regs
- cmp dl,15 ; was it cursor address?
- jne out_crt2 ; skip if not
- dec di
- mov ax,[di] ; get our cursor address
- xchg al,ah ; swap high/low for 6845
- and ah,3fh ; cursor location register is 14 bit
- mov dl,CRT_COLS
- div dl ; AL = row, AH = col
- mov dh,al ; DH = row
- mov dl,ah ; DL = column
- cmp dh,VS_ROWSB ; check if in legal range
- jae out_crt2 ; no, skip cursor update
- call point_cursor@
- mov VS_OFFSET,ax
- mov VS_CURSOR,dx ; set cursor position
- out_crt2:
- ret
-
- cur_hide1:
- lea di,VS_CRT_DATA ; get VC_ data area
- mov cx,10[di] ; get cursor start/end
- xchg cl,ch
- test ch,60h ; setting bits 5 or 6 turns cursor off
- jnz c_off1
- and ch,0fh ; mask start cursor line
- and cl,0fh ; and end
- cmp ch,cl ; if start > end
- ja c_off1 ; then turn cursor off
- or VS_MODE,CURSOR_BIT
- jmps c_ret1 ; turn on
- c_off1:
- and VS_MODE,not CURSOR_BIT
- c_ret1:
- or VS_MODE,UPDATE_BIT ; flag flush to turn on/off
- ret
-
-
- out_crt_ctrl:
- out_col_ctrl:
- ;------------
- mov dl,active_vc$ ; get active virtual console
- if not SR
- cmp dl,NUM_VIR_CONS
- jb video3
- call point_vc@
- mov al,outbyte
- mov VC_BLINK,al ; enable/disable blink attribute
- ret
- endif
- video3:
- call point_vs@
- mov al,outbyte
- ; mov VS_BLINK,al ; enable/disable blink attribute
- ret
-
- out_crt_status:
- out_col_status:
- ;------------
- out_crt_conf:
- out_col_conf:
- ;------------
- ret ; ignore writing to configuration port
-
-
- in_crt_index:
- in_col_index:
- ;-----------
- mov dl,active_vc$ ; get active virtual console
- if not SR
- cmp dl,NUM_VIR_CONS
- jb video4
- call point_vc@
- mov al,VC_CRT_IDX ; else read back virtual index register
- mov es,excep_ss ; get original stack seg
- mov es:EXCEP_AL,al ; and put on stack for exit
- ret
- endif
- video4:
- call point_vs@
- mov al,VS_CRT_IDX ; else read back virtual index register
- mov es,excep_ss ; get original stack seg
- mov es:EXCEP_AL,al ; and put on stack for exit
- ret
-
- in_crt_data:
- in_col_data:
- ;-----------
- mov dl,active_vc$ ; get active virtual console
- if not SR
- cmp dl,NUM_VIR_CONS
- jb video5
- call point_vc@
- mov dl,VC_CRT_IDX ; get data register index
- mov dh,0 ; make it a word
- lea di,VC_CRT_DATA
- add di,dx
- mov al,[di] ; get value written
- mov es,excep_ss ; get original stack seg
- mov es:EXCEP_AL,al ; and put on stack for exit
- ret
- endif
- video5:
- call point_vs@
- mov dl,VS_CRT_IDX ; get data register index
- mov dh,0 ; make it a word
- lea di,VS_CRT_DATA
- add di,dx
- mov al,[di] ; get value written
- mov es,excep_ss ; get original stack seg
- mov es:EXCEP_AL,al ; and put on stack for exit
- ret
-
- in_crt_status:
- in_col_status:
- ;-------------
- mov dl,active_vc$ ; get active virtual console
- if not SR
- cmp dl,NUM_VIR_CONS
- jb video6
- call point_vc@
- inc VC_CRT_STAT
- mov al,VC_CRT_STAT
- or al,0F0h ; these bits always 1 on MDA
- mov es,excep_ss ; get original stack seg
- mov es:EXCEP_AL,al ; and put on stack for exit
- ret
- endif
- video6:
- call point_vs@
- inc VS_CRT_STAT
- mov al,VS_CRT_STAT
- or al,0F0h ; these bits always 1 on MDA
- mov es,excep_ss ; get original stack seg
- mov es:EXCEP_AL,al ; and put on stack for exit
- ret
-
- in_crt_ctrl:
- in_col_ctrl:
- ;-----------
- in_crt_conf:
- in_col_conf:
- ;-----------
- jmp do_in ; just do "IN"
-
- eject
-
- ; Arrives here when all DMA transfer params are setup
- ; either from ROS int 13h or application programming
- ; DMA directly.
- ; If we arrived here from ROS int 13h then the XIOS
- ; has already deblocked over 16K page boundary.
- ; If not from ROS then we can only allow DMA to
- ; continue if the transfer will fit inside the 16K page.
-
- ; first translate dma address to 32 bit address
- emu_dma:
- OP_32! push bx ; save EBX - used in conv_dma
- mov emu_dma_outport,dx ; in case we have aligment abort...
- mov cl,outbyte ; get output byte
- ; check if channel 3, 2 (fdc) or channel 1 or DISABLE
- test cl,DMA_BMSK_DISABLE ; is it DISABLE
- jz test_dma
- jmp init_dma
- test_dma:
- and cl,DMA_BMSK_C3 ; channels 0-3
- xor ch,ch
- mov di,cx ; channel number to di
- dec di ; make channels 1-3 zero relative
- mov al,0
- out DMA_CBPF,al ; reset flip/flop
- jmps $+2 ! jmps $+2 ; wait
- xor dh,dh
- mov dl,dma_page[di]
- in al,dx ; get the high 4 bits of address
- mov ch,al
- mov dl,dma_address[di]
- in al,dx ; get low address
- mov ah,al
- in al,dx ; get high address
- xchg al,ah ; AX
-
- mov bx,v386_ptr$ ; get v386 table pointer
- mov es,ptbl_seg$ ; ES -> page table seg from sysdat
- ; push di
- call conv_dma ; convert address in CH, AX
- ; pop di ; to address in BL, DX
- ; bytes remaining in page in EAX
- mov cx,dx
- OP_32! push ax ; save count
- mov al,0
- out DMA_CBPF,al ; reset flip/flop
- jmps $+2 ! jmps $+2 ; wait
-
- mov al,cl ; get low address
- xor dh,dh
- mov dl,dma_address[di]
- out dx,al
- jmps $+2 ! jmps $+2 ; wait
- mov al,ch ; and high address
- out dx,al
- jmps $+2 ! jmps $+2 ; wait
- mov al,bl ; get high four bits
- mov dl,dma_page[di]
- out dx,al ; to page register
- jmps $+2 ! jmps $+2 ; wait
-
- OP_32! pop cx ; restore remaining byte count
-
- mov ax,EXCEP_CS
- cmp ax,0f000h ; does it come from ROS
- je init_dma ; yes .. no need for further tests
-
- mov bx,v386_ptr$ ; lets look at the global state
- test v386_flag,VXF_ALIGN ; if alignment is on
- jnz init_dma ; then the world is wonderful
-
- ; get DMA transfer count
- out DMA_CBPF,al ; reset flip/flop
- jmps $+2 ! jmps $+2 ; wait
- OP_32! xor ax,ax
- mov dl,dma_count[di]
- in al,dx ; low byte of dma transfer count
- mov ah,al
- in al,dx ; high byte of dma transfer count
- xchg ah,al ; ax = count in bytes
- OP_32! cmp ax,cx ; enough contiguous memory to fit ?
-
- ja illegal_dma ; no .. do not allow dma transfer as
- ; DMA count will take transfer
- ; over 16k page boundary
- init_dma:
- ; else start dma transfer
- mov al,outbyte ; recover value to be output to port
- out DMA_BMSK_REG,al ; initialise disk channel
-
- init_dma_exit:
- OP_32! pop bx ; restore EBX
- ret
-
-
- illegal_dma:
- ; we have detected a potentially illegal DMA condition. We now give
- ; things one last chance - if the current process has been loaded
- ; into aligned memory then we assume it knows what it is doing.
- ; (We are catering for the case where ALIGN=OFF, but the EXE has been
- ; pifed'd).
- ;
- ; nb. Some programs (eg. Everex Tape Streamer) have been known to program
- ; the DMA from an interrupt context. This can be damaging to your health
- ; as you could attempt to terminate in any (or even no) context.
- ; Roll on banked interrupts!
- ;
- mov bx,rlr$ ; get the current process
- mov bx,P_MPAR[bx] ; get the root of the MPAD's
- test MPAD_FLAGS[bx],MPADF_ALIGNED
- jnz init_dma ; if aligned then trust it...
-
- mov dx,emu_dma_outport ; we must reprotect the port
- call set_trap ; before we abort the process
-
- mov ax,offset fatal_dma_msg ; let's abort the process
- mov cx,fatal_dma_msg_len ; with relevant message
- jmp proc_abort@
-
-
-
- ; Model 80 DMA transfers from int 13h function
- ; arrives here when all DMA transfer params are setup.
-
- ; first translate dma address to 32 bit address
- ; Entry : DX = port address
- ; outbyte = value to write to port
- do_emu_80:
- mov al,outbyte
- and al,0f0h ; mask top nibble - function command
- cmp al,0a0h ; is it initialise command
- je do_80
- call do_out ; no execute out instruction
- ret
-
- do_80:
- OP_32! push bx ; save EBX - used in conv_dma
- mov al,outbyte
- and al,0fh ; mask channel number
- or al,RESET_PTR ; clear byte pointer command
- out DMA_FUNC_REG,al ; output command
- jmps $+2 ! jmps $+2 ; wait
-
- in al,DMA_EXEC_REG ; get low address
- mov bl,al
- in al,DMA_EXEC_REG ; get mid address
- mov bh,al
- in al,DMA_EXEC_REG ; get page table address
- mov ch,al
- mov ax,bx
-
- mov bx,v386_ptr$ ; get v386 table pointer
- mov es,ptbl_seg$ ; ES -> page table seg from sysdat
- call conv_dma ; convert address in CH, AX
- ; to address in BL, DX
- ; bytes remaining in page in AX
- mov al,outbyte
- and al,0fh ; mask channel number
- or al,RESET_PTR ; clear byte pointer command
- out DMA_FUNC_REG,al ; output command
- jmps $+2 ! jmps $+2 ; wait
-
- mov al,dl ; get low address
- out DMA_EXEC_REG,al
- jmps $+2 ! jmps $+2 ; wait
- mov al,dh ; and high address
- out DMA_EXEC_REG,al
- jmps $+2 ! jmps $+2 ; wait
- mov al,bl ; page table address
- out DMA_EXEC_REG,al ; to page register
- jmps $+2 ! jmps $+2 ; wait
-
- mov al,outbyte
- out DMA_FUNC_REG,al ; initialise disk channel
-
- OP_32! pop bx ; restore EBX
- ret
-
- eject
- ; *****************************************
- ; Page fault handler for IDLE detection
- ; set IDLE bit in CCB if read/write
- ; to/from screen memory A000-C000h
- ; Reset write protect attribute before
- ; returning to process.....
- ; Entry :
- ; stack = 32bit address of page fault
- ; Exit :
- ; IRET if screen write
- ; else display PAGE FAULT
- ; *****************************************
- pfault_handler:
- cli
- cld
- OP_32! mov cs:save_eax,ax ; save EAX
- OP_32! pop ax ; get linear address into EAX
- OP_32! mov cs:address_eax,ax ; save linear address
-
- push ds ! push es
- push bx
- push cx
- push dx
- OP_32! push di
- OP_32! push si
- mov ds,sysdat$
- mov di,rlr$ ; get running proc
- mov dl,P_CONS[di] ; get process's console number
-
- ;;; mov dl,active_vc$ ; get process's console number
- cmp dl,NUM_VIR_CONS
- jb is_main
-
- ; must be PC Terminal
- OP_32! mov ax,cs:address_eax ; get linear address
- OP_32! and ax,0ffffh
- dw 7fffh ; remove top bit of address
- OP_32! xor di,di
- mov di,MONO_SEG
- OP_32! shl di,4
- OP_32! cmp ax,di
- jae test_top
- fatal_error1:
- jmp fatal_error
- test_top:
- OP_32! add di,1000h ; next 4k
- dw 0000h
- OP_32! cmp ax,di
- jae fatal_error1
- mov di,MONO_SEG ; restore base
- jmps reset_idle
-
- ; main Video terminal
- is_main:
- mov cx,NUM_VIR_CONS
- mov dl,0
- test_all_vcs:
- push dx
- push cx
- call point_vs@
- OP_32! xor si,si
- OP_32! xor di,di
- mov si,VS_CRT_SEG
- mov di,VS_VC_SEG
-
- OP_32! shl di,4
- OP_32! shl si,4
- OP_32! mov ax,cs:address_eax ; get linear address
- OP_32! and ax,0ffffh
- dw 7fffh ; remove top bit of address
-
- OP_32! cmp ax,di
- jb test_si
- OP_32! add di,1000h ; next 4k
- dw 0000h
- OP_32! cmp ax,di
- jae test_si
- mov di,VS_VC_SEG ; restore base
- jmps reset_idle1
-
- test_si:
- OP_32! cmp ax,si
- jb test_all
- OP_32! add si,1000h ; next 4k
- dw 0000h
- OP_32! cmp ax,si
- jae test_all
- mov di,VS_CRT_SEG ; base to DI
- jmps reset_idle1
-
- test_all:
- pop cx
- pop dx
- inc dl
- loop test_all_vcs
- jmps fatal_error
-
-
- reset_idle1:
- pop cx
- pop dx
- reset_idle:
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg ; and page table
- shr di,6 ; / 100h *4 = page table entry
- or es:byte ptr [di],07h ; reset write attribute
- xor dh,dh
- mov di,dx
- shl di,1
- mov di,ccb_list$[di] ; get ccb pointer for VC
- or C_STATE[di],CSM_IDLE ; set IDLE bit
-
- OP_32! pop si
- OP_32! pop di
- pop dx
- pop cx
- pop bx
- pop es ! pop ds
-
- OP_32! mov ax,cs:save_eax ; restore EAX
- iret
-
- fatal_error:
- mov di,VS_CRT_SEG ; screen to DI
- mov si,VS_VC_SEG
- mov bx,v386_ptr$ ; get pointer to 386 specific table
- mov es,ptbl_seg ; and page table
- shr di,6 ; / 100h *4 = page table entry
- shr si,6 ; / 100h *4 = page table entry
- mov al,67h ; reset write attribute
- stosb
- mov es:[si],al
- OP_32! pop si
- OP_32! pop di
- pop dx
- pop cx
- pop bx
- pop es ! pop ds
-
- OP_32! mov ax,cs:address_eax ; saved EAX
- mov si,offset fatal_page$ ; 'Memory protection interrupt'
- jmp fatal_int@ ; display error message and terminate
-
- save_eax dw 0 ; save EAX area
- dw 0
- address_eax dw 0 ; save EAX area
- dw 0
-
-
- ; hardware interrupt handlers (master PIC):
- ; entered in protected mode
-
- int50:
- ;-----
- push 08h*4
- jmps i_common
- int51:
- ;-----
- push 09h*4
- jmps i_common
- int52:
- ;-----
- push 0ah*4
- jmps i_common
- int53:
- ;-----
- push 0bh*4
- jmps i_common
- int54:
- ;-----
- push 0ch*4
- jmps i_common
- int55:
- ;-----
- push 0dh*4
- jmps i_common
- int56:
- ;-----
- push 0eh*4
- jmps i_common
- int57:
- ;-----
- push 0fh*4
- jmps i_common
-
- ; hardware interrupt handlers (slave PIC):
-
- int70:
- ;-----
- push 70h*4
- jmps i_common
- int71:
- ;-----
- push 71h*4
- jmps i_common
- int72:
- ;-----
- push 72h*4
- jmps i_common
- int73:
- ;-----
- push 73h*4
- jmps i_common
- int74:
- ;-----
- push 74h*4
- jmps i_common
- int75:
- ;-----
- push 75h*4
- jmps i_common
- int76:
- ;-----
- push 76h*4
- jmps i_common
- int77:
- ;-----
- push 77h*4
- jmps i_common
-
- ;--------
- i_common:
- ;--------
- OP_32! push bp ; push EBP
- OP_32! mov bp,sp ; point at stack frame
- OP_32! push bx
- OP_32! push si
- push ds
-
- cld
- mov bx,GDT_GDT_SEL
- mov ds,bx
-
- ; Build user stack alias:
-
- OP_32! sub bx,bx
- mov bx,EX_SS
- OP_32! shl bx,4
- OP_32! or bx,0
- dw DATA_ACCESS shl 8
- mov si,GDT_SS_SEL
- OP_32! mov 2[si],bx
-
- ; emulate the 8086 interrupt:
-
- mov ds,si ; DS -> 8086 stack segment
- sub EX_SP,6 ; make space for CS,IP,FLAGS
- mov si,EX_SP ; DS:SI = user stack
- mov bx,EX_IP
- mov [si],bx ; push IP on user stack
- mov bx,EX_CS
- mov 2[si],bx ; push CS on user stack
- mov bx,EX_EFLAGS
- mov 4[si],bx ; push FLAGS on user stack
- and bx,not 0300h ; clear IF and TF
- mov EX_EFLAGS,bx ; update flags for IRET
-
- mov si,EX_INT ; get vector # * 4
- cmp si,9*4 ; keyboard interrupt
- jne i_common1 ; no..
- mov bx,GDT_SYSDAT_SEL
- mov ds,bx ; DS -> SYSDAT seg
- ; ALWAYS jump to our keyboard handler
- ;; cmp active_vc$,NUM_VIR_CONS ; are we on main console
- ;; jb i_common1 ; yes..
- mov si,offset keyboard_isr ; get offset location of keyboard isr address
- jmps i_common2
- i_common1:
- mov bx,GDT_INT_SEL
- mov ds,bx ; DS -> 8086 int vectors
- i_common2:
- mov bx,[si] ; get offset from interrupt vector
- mov EX_IP,bx ; and store on system stack
- mov bx,2[si] ; get segment from interrupt vector
- mov EX_CS,bx ; and store on system stack
-
- pop ds
- OP_32! pop si
- OP_32! pop bx
- OP_32! pop bp
- add sp,2 ; remove int vector from stack
- OP_32! iret ; continue at handler address
-
-
- eject
-
-
- ; entry from Floppy module for converting
- ; DMA transfer address.
- ; Entry: AX = bottom 16 bits of address
- ; CH = highest 4 bits of address, always less then 16 -
- ; no megabyte wrap around
- ; Exit: AX = number of bytes remaining in page
-
- vxm_dma@:
- push bx ! push dx ! push es ; save scratch registers
- mov bx,v386_ptr$ ; get pointer to V386 table
- mov es,ptbl_seg$
- call conv_dma
- mov dma_low16$,dx ; store for dma controller
- mov dma_high4$,bl ; store top 4 bits for dma controller
-
- pop es ! pop dx ! pop bx ; restore scratch registers
- ret
-
- ; Translate virtual to physical address for DMA transfers
- ; in virtual address mode and compute # of bytes transferable
- ; in this page until memory becomes noncontiguous.
- ;
- ; Entry: AX = A0-A15 of virtual address
- ; CH = A16-A19 of virtual address
- ; Exit: DX = A0-A15 of physical address
- ; BL = A16-A23 of physical address
- ; EAX = # of linear bytes in this page
- ;
- ; SI preserved
-
- conv_dma:
- OP_32! sub bx,bx ;; clear EBX
- mov bl,ch
- mov cl,16
-
- OP_32! shl bx,cl
- mov bx,ax ;; EBX = 32 bit address
- OP_32! shr bx,PAGE_SHIFT ;; make byte address into page index
- shl bx,2 ; byte offset in page table of
- ; our page
- mov dx,es:[bx] ; lower 16 bits of physical address
- mov ch,es:2[bx] ; get A16-A23
- and dx,0 - PAGE_SIZE ; mask top nibble
- ; AX = offset within 64k
- OP_32! and ax,PAGE_SIZE - 1 ; make offset within 4k page
- dw 0
- or dx,ax ; combine 16 bit offset
-
- OP_32! sub ax,PAGE_SIZE
- dw 0
- OP_32! neg ax ; AX = # of bytes left in page
-
- push si
- mov si,bx ; ES:SI -> page table entry
-
- conv_dma1:
- mov bl,es:1[si] ; get A12-A16 (4 Kb block)
- and bl,not (PAGE_SIZE/256-1); zero A0-A11
- add si,4 ; point to next page
- conv_dma2:
- cmp ch,es:2[si] ; next page in same 64 Kb block?
- jne conv_dma3 ; skip if not in same 64 K page
- mov bh,es:1[si] ; get next A12-A16
- and bh,not (PAGE_SIZE/256-1); zero next A0-A11
- sub bh,bl ; BH = distance between pages
- cmp bh,PAGE_SIZE/256 ; are they contiguous?
- jne conv_dma3 ; no, stop scanning
- OP_32! add ax,PAGE_SIZE ; add in size of next page
- dw 0
- OP_32! cmp ax,0 ; is block getting too large?
- dw 1 ; ie. >= 64k
- jb conv_dma1 ; no, keep on scanning
- conv_dma3:
- pop si ; restore SI
- mov bl,ch ; get A16 - A23
- ret
-
-
-
- eject
-
- V386_DATA dseg PARA ; paragraph align for 32-bit stack
-
-
- ; Master PIC isr offsets
- idt_m_pic_offs dw offset int50
- dw offset int51
- dw offset int52
- dw offset int53
- dw offset int54
- dw offset int55
- dw offset int56
- dw offset int57
-
-
- ; Slave PIC isr offsets
- idt_s_pic_offs dw offset int70
- dw offset int71
- dw offset int72
- dw offset int73
- dw offset int74
- dw offset int75
- dw offset int76
- dw offset int77
-
- ; DMA channel parameters
- dma_page db DMA_PAGE_C1 ; a16 to a20 for channel 1
- db DMA_PAGE_FDC ; ditto for channel 2
- db DMA_PAGE_C3 ; ditto for channel 3 (hd)
-
- dma_address db DMA_C1_ADDRESS ; 8237 channel 1 address
- db DMA_C2_ADDRESS ; 8237 channel 2 address
- db DMA_C3_ADDRESS ; 8237 channel 3 address (hd)
-
- dma_count db DMA_C1_COUNT ; 8237 channel 1 transfer count
- db DMA_C2_COUNT ; 8237 channel 2 transfer count
- db DMA_C3_COUNT ; 8237 channel 3 transfer count
-
- ; High memory free list (re-uses following tables)
- hi_mfl rw 160
-
- vm_flag$ db 0 ; 0FFh if we're in virtual mode
- rb 1
-
- emem rw 1 ; extended memory size - 1k blocks
-
- hi_xmem_addr$ dw 0 ; extra RAM base (A16..A31)
- hi_xmem_size$ dw 0 ; extra RAM size (# of 16K blocks)
-
- error_code rw 2 ; pop error code into here
-
- keyboard_isr dw offset i_keyboard@ ; pointer to keyboard ISR
- dw 0000 ; XIOS cseg set up at init
-
- num_pages$ dw 0000 ; for INIT display
-
- fatal_dma_msg db 0dh,0ah
- db 'DMA transfer error: Use ALIGN option in CCONFIG.SYS.'
- fatal_dma_msg_len equ offset $ - offset fatal_dma_msg$
- outbyte rb 1 ; temp storage
- emu_dma_outport rw 1 ; temp storage
-
- dw 0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch
- dw 0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch
- dw 0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch
- dw 0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch
- dw 0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch
- dw 0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch,0cccch
- dw 0cccch,0cccch
-
- excep_stack_top rw 1
- excep_ss rw 1
- excep_sp rw 1
-
-
- end
-