home *** CD-ROM | disk | FTP | other *** search
-
- title LISTING 3 ;DETERMINING CPU TYPE
-
- ; Cputest.asm is the Lattice C-callable assembly language routine that determines
- ; the machine's processor type.
-
- ; Copyright (c) 1986 Dan Jacobs and Joel Rosenblum
-
- name cputest ;determine CPU type
-
- include dos.mac ; Lattice C memory model configuration macro
- ; In this case it is a copy of dm8086.mac
-
- ; processor type equates
- CPU_88 equ 01H ; Intel 8088 - 8086
- CPU_186 equ 02H ; Intel 80188 - 80186
- CPU_286 equ 04H ; Intel 80286
- CPU_V20 equ 08H ; NEC V20 - V30
-
- PSEG
-
- comment\**********************************************************************
-
- NAME
- cputest
-
- SYNOPSIS
-
- unsigned int cputest (features)
- unsigned int features; see definition of machine type
-
- DESCRIPTION
-
- returns features with the proper active CPU type or'ed in
-
- *****************************************************************************\
-
- public cputest
- cputest proc near
-
- push BP ; save the frame pointer (if called from C)
- mov BP, SP
-
- ; next, save the passed existing features
-
- mov AX, 4[BP]
- push AX
-
- ; check for 8088 or 8086 by using the SHR instruction since the
- ; 8088 and 8086 do not mask cl with 07H before executing the shift.
-
- mov CL, 20H
- mov AX, 1
- shr AX, CL
- test AX, AX ; if after the shift AX is the same
- ; as before, it's a 8088 - 8086 or V20 - V30
- jnz check_80186 ; else, continue checking other Intel CPUs
-
- ; check for V20 or V30 by detecting if PUSHA is a valid instruction
- ; on the NEC CPUs
-
- mov BX, SP ; save SP
- pusha
- cmp BX, SP ; if SP has not been decremented, then
- je is_88 ; it's an 8088 - 8086
- popa ; else, we restore registers
- mov AX, CPU_V20
- jmp return
-
- is_88: mov AX, CPU_88
- jmp return
-
- check_80186:
-
- ; check for the 80188 or 80186 by detecting if SP is updated
- ; before or after it is pushed.
-
- push SP
- pop BX
- cmp BX, SP
- je is_286 ; if updated after, it's a 80286
-
- mov AX, CPU_186 ; else, it's a 80186 or 80188
- jmp short return
-
- is_286: mov AX, CPU_286
-
- return: pop BX ; recall saved features
- or AX, BX ; and or cputype into other features bits
- pop BP
- ret
-
- cputest endp
-
- ENDPS
- end
-
- -------------------------------------------------------------------------------
-
- title LISTING 4 ;DETECTING MATH CO-PROCESSOR
-
- ; testndp.asm is the Lattice C-callable assembly language routine that
- ; determines the presence of an 8087 or 80287 math co-processer chip.
-
- ; assembeled using Microsoft MASM v4.0
-
- ; Copyright (c) 1986 Dan Jacobs and Joel Rosenblum
-
- ; portions copyrighted by MicroWay, Inc.
-
- name test_ndp
-
- include dos.mac ; Lattice C memory model configuration macro
- ; In this case it is a copy of dm8086.mac
-
- ; We have to code the instructions for the NDP as dbs as the assembler
- ; generates an unwanted WAIT instruction
-
- FINIT_MAC MACRO
- db 0DBH, 0E3H
- ENDM
-
- FSTCW_MAC MACRO address
- db 0D9H, 03EH
- dw offset DGROUP:address
- ENDM
-
-
-
- ; bit mask for coprocessor in FEATURES
- NDP equ 0010H ; a coprocessor is present
-
- DSEG
- ndp_word dw 0 ; a storage location for the ndp to use for test
- ENDDS
-
- PSEG
-
- comment\**********************************************************************
-
- NAME
- testndp
-
- SYNOPSIS
- Check to see if a 8087 or 80287 numeric data processor is
- present in the machine. Here, we present two methods which
- you may select based upon how you set CHOOSE in the code:
- First, IBM's recommended procedure which does an int 11
- (equipment determination) BIOS call. The problem with this
- method is that it only works on IBMs and 100% compatibles.
- Note that in the PC and XT the returned value is determined
- by reading the switch setting. Unfortunately, all of the
- early "guide to operations" manuals informed you to set the
- switch the coprocessor the wrong way, rendering it usless.
- Second, MicroWay's recommended procedure checks for the
- coprocessor directly. We believe that this method should be
- used since it is more universal. We leave the choice to you
- depending how you set the equ for CHOOSE below:
-
- 1 to use int 11
- or
- 0 for direct check
-
- SYNOPSIS
- unsigned int test_ndp (features);
- unsigned features; see definition of machine type
-
- RETURN VALUE
- the passed features variable with the NDP bit or'ed in
-
- *****************************************************************************\
-
- CHOOSE equ 0 ; 0 = direct ndp check, 1 = IBM int 11 bios call
-
- public test_ndp
-
- test_ndp proc near
-
- assume ds:DGROUP
-
- push bp ; save the frame pointer (if called from C)
- mov bp, sp
-
- ; next, save the passed existing features
- mov ax, 4[bp]
- push ax
-
- if CHOOSE ; use bios int check
- int 11H ; equipment determination call
- and ax, 2 ; coprocessor present
- jz no_ndp
- else ; use direct ndp check ala MicroWay
- FINIT_MAC ; initilize the coprocessor
- mov ndp_word, 0
- FSTCW_MAC <ndp_word> ; fstcw ndp_word
- ; move control word to ndp_word
- mov cx, 064H ; count for wait loop
- l1: push dx
- pop dx
- loop l1
- and ndp_word, 03BFH ; mask to bits we want
- cmp ndp_word, 03BFH ; all the correct bits set
- jne no_ndp
-
- mov ndp_word, 0
- FSTCW_MAC <ndp_word> ; fstcw ndp_word
- ; move control word to ndp_word
- mov cx, 064H ; count for wait loop
- l2: push dx
- pop dx
- loop l2
- and ndp_word, 1F3FH ; mask to bits we want
- cmp ndp_word, 033FH ; all the correct bits set
- jne no_ndp
-
- endif
- mov bx, NDP ; mask to turn on coprocessor bit
- jmp short ndp_exit
-
- no_ndp: mov bx, 0 ; nothing to mask in
-
- ndp_exit:
- pop ax ; get saved passed features
- or ax, bx ; and or in bit for ndp
-
- pop bp ; restore frame pointer to return to C caller
-
- ret
-
- test_ndp endp
-
- ENDPS
- end
-
- _______________________________________________________________________________
-
- title Listing 5a ;Calculating Timing Loops
-
- ; Cal.asm is an assembly language routine that provides a standard
- ; delay independent of clock speed. It may be called from a C
- ; routine in your software as illustrated in listing 5b.
-
- ; Note: The PC's timer interrupt is assumed set to the standard ~18.2Hz
-
- ; Copyright (c) 1986 Howie Marshall, Applied Reasoning Corp.
-
- pgroup group prog
- dgroup group data
-
- bios_data segment at 40H
- org 06cH
- low_time dw ?
- bios_data ends
-
- data segment public 'data'
- extrn us500:word, ms2:word
- dummy dw 0 ; a dummy to compare against
- data ends
-
- prog segment byte public 'prog'
- ;
- ; delaycal - calibrate the delay loop
- ;
- ; temp = delaycal(delay_time) from C. Returns delay_count
- ;
- assume cs:pgroup
- public delaycal
- delaycal proc near
- assume ds:dgroup
- push bp
- push ds
- mov bp,sp
- mov ax,bios_data
- mov ds,ax
- assume ds:bios_data
- ;
- ; wait for the timer to tick over
- ;
- mov di,low_time
- timwait:
- cmp di,low_time
- je timwait
- ;
- xor ax,ax
- xor dx,dx
- add di,6 ; wait for 5 more ticks
- ;*************************************************************
- timloop:
- add ax,1
- adc dx,0
- cmp di,low_time ; have 5 ticks occurred yet?
- ja timloop ; no, continue looping
- ;*************************************************************
- ;
- ; 5 ticks @ 18.2 ticks/sec => 270272 microseconds in 5 ticks
- ;
- ; 270272 = 16 * 16892
- ;
- mov bx,16
- div bx ; cut down to single word
- mov bx,6[bp] ; get desired delay time
- mul bx
- mov bx,16892
- div bx ; finish divide-by-270272
- or ax,ax
- jnz timok
- inc ax ; do at least one loop
- timok:
- mov sp,bp
- pop ds
- assume ds:dgroup
- pop bp
- ret
- delaycal endp
- ;
- ; DELAY SUBROUTINES:
- ;
- ; This routine delays for 500 microseconds.
- ;
- public del500u
- del500u proc near
- assume ds:dgroup
- mov ax,us500
- neg ax
- ;
- ; This loop contains the same instructions as the calibration loop
- ; in delaycal above, but in a different order. The first two are
- ; do not actually affect the loop, other than taking the same number
- ; of cycles as the corresponding portion of the loop in delaycal.
- ;
- ; Note that both loops consist of:
- ; ADD, ADC, CMP, Jcond
- ;
- ;*************************************************************
- loop1:
- adc dx,0 ; kill some time
- cmp dx,dummy ; and some more
- add ax,1 ; increment our count
- jnz loop1 ; no, continue looping
- ;*************************************************************
- ret
- del500u endp
- ;
- ; This is essentially the same as del500u, except that a different
- ; count value is used to delay for 2 milliseconds.
- ;
- public del2m
- del2m proc near
- assume ds:dgroup
- mov ax,ms2
- neg ax
- ;*************************************************************
- loop2:
- adc dx,0 ; kill some time
- cmp dx,dummy ; and some more
- add ax,1 ; increment our count
- jnz loop2 ; no, continue looping
- ;*************************************************************
- ret
- del2m endp
- prog ends
- end
-
- -------------------------------------------------------------------------------
-
- title LISTING 6 ;DETECTING VIDEO TYPE
-
- ; Video.asm is the Lattice C-callable assembly language routine that determines
- ; the presence of video screen adapter cards and displays in an IBM compatible
- ; system.
- ; *NOTE* The timing loops have only been validated on 6 Mhz. AT
-
- ; Copyright (c) 1986 Dan Jacobs and Joel Rosenblum
-
- ; portions copyrighted by Hercules Corp. and International Business Machines Corp.
-
- ; For a more complete test of the EGA adapter card see IBM Seminar Proceedings
- ; Vol. 2, No. 11-1
-
- name video_test ;determine video adapter card
-
- include dos.mac ; Lattice C memory model configuration macro
- ; In this case it is a copy of dm8086.mac
-
- ; *NOTE* all the below equates must be the same as list1.c
-
- ; video mode equates
- CGA equ 01H ; IBM Color graphics adapter (CGA)
- MONO equ 02H ; IBM Monochrome card
- HERCULES equ 04H ; Hercules monochrome graphics card
- PGA equ 08H ; Professional graphics controller (PGA)
- EGA_MONO equ 10H ; IBM Enhanced graphics adapter (EGA) w/monochrome display
- EGA_COLOR equ 20H ; EGA w/color display
- EGA_HIGH equ 40H ; EGA w/high resolution color display
- UNKNOWN equ 80H ; Unknown board type
-
- ; machine type equates
- IBMCOMPAT equ 0100H
- IBMPC equ 0200H
- IBMPCAT equ 0400H
- IBM_CONVERT equ 0800H
-
- ; global equates
- VIDEO_IO equ 10H ; BIOS video i/o interrupt number
- GET_MODE equ 0FH ; video i/o get mode function
-
- DSEG
-
- video_type db ? ; place to accumulate the video type
- t_features dw ? ; machine discriptor passed to function
-
- ENDDS
-
- PSEG
-
- comment\**********************************************************************
-
- NAME
- Video_test - checks to see which video adapter and display are used
-
- SYNOPSIS
- unsigned int Video_test (features);
- unsigned features; see definition of machine type
-
- RETURN VALUE
- type of video board used
- 01H = Color graphics adapter
- 02H = Monochrome card
- 04H = Hercules card
- 08H = Professional graphics adapter
- 10H = EGA w/monocrome display
- 20H = EGA w/color display
- 40H = EGA w/high resolution color display
- 80H = Unknown video card
-
- *****************************************************************************\
-
- public video_test
-
- video_test proc near
-
- push bp ; save the frame pointer (if called from C)
- mov bp, sp
-
- ; next, save the passed existing features
- mov ax, 4[bp]
- mov t_features, ax
-
- check_ega:
- ; Unfortunately this method of checking the EGA requires the use of
- ; BIOS routines. Therefore, it can only be used on compatible
- ; machines. We first, however, determine if we can make the BIOS call.
-
- ; We use FEATURES to check if the BIOS int 10
- ; is available for use.
-
- test t_features, IBMCOMPAT + IBMPC + IBMPCAT
- jz ega_done ; can only do this test on compatible
-
- mov ax, 1200H ; video alternate select
- mov bl, 10H ; return EGA info
- mov bh, 0FFH ; invalid data for test
- mov cl, 0FH ; reserved switch setting
- int VIDEO_IO ; returns with bh = color or mono mode
- ; bl = memory value
- ; ch = feature bits
- ; cl = switch setting
-
- cmp cl, 0CH ; test switch setting
- jge ega_done ; above max setting
- cmp bh, 01H ; test range 0 - 1
- jg ega_done ; above range
- cmp bl, 03H ; check memory value for 0 - 3 range
- jg ega_done ; above range
-
- ; if it gets here, there is a EGA card present
- ; now test for the attached monitor
-
- and cl, 0EH ; trim the switch to the bits we need
- cmp cl, 1010B ; monochrome monitor attached ?
- je is_m
- cmp cl, 0100B ; secondary mono setting ?
- jne color ; nope check color display
- is_m: or video_type, EGA_MONO ; set EGA card with monochrome display
- jmp short ega_done
- color: cmp cl, 1000B ; primary color display ?
- je is_c
- cmp cl, 1110B ; secondary color ?
- jne enh_d ; check for high resolution display
- is_c: or video_type, EGA_COLOR ; EGA card with color display
- jmp short ega_done
- enh_d: cmp cl, 1100B ; primary high resolution display ?
- je is_enh
- cmp cl, 0110B ; secondary high resolution display ?
- jne ega_done
- is_enh: or video_type, EGA_HIGH ; EGA card with high resolution color display
-
- ega_done:
-
- ; check for Hercules card is present by checking the status port
- ; at 3BAH for the vertical retrace bit.
- ; **NOTE** you can also tell the mode the card is in and set the card
- ; mode. For more information, contact Hercules technical support.
-
- mov dx,3BAH ; address of status port
- in al,dx
- and al,80h ; vertical retrace bit
- mov ah,al ; Save bit 7 for test
-
- mov cx,8000h ; count for delay loop
- examine:
- in al,dx ; Take another reading
- and al,80h ; Isolate bit 7
- cmp al,ah
- jne is_hercules ; If bit 7 changes then it
- loop examine ; is a Hercules Graphics Card
-
- jmp check_color ; After this long, it must be
- ; something else.
- is_hercules:
- or video_type, HERCULES
- jmp short check_pga ; don't check for mono or color
- ; board if Hercules present
-
- check_color:
- test video_type, EGA_COLOR + EGA_HIGH
- jnz check_mono ; can't have a color card with
- ; EGA in color mode
-
- ; next check for a Color Graphics Adapter by the checking for the
- ; presence of the cursor register at 0x3D4
- mov dx, 03D4H
- call cursor_reg ; carry flag set if not there
- jc check_mono
- or video_type, CGA ; there is a color graphics adapter
-
- check_mono:
- test video_type, EGA_MONO ; can't have mono card in machine
- jnz check_pga ; with EGA in mono
-
- ; first check for a monochrome board by checking for the
- ; presence of the cursor register at 0x3B4
- mov dx, 03B4H
- call cursor_reg ; carry flag set if not there
- jc check_pga
- or video_type, MONO ; there is a monochrome adapter card
-
- check_pga:
- ; now test for a Professional Graphics Adapter by checking the cursor
- ; status register which is memory mapped to address C600:03DB
-
- push es
- mov ax, 0C600H ; load segment
- mov es, ax
- mov di, 03DBH ; load offset
- mov ah, es:[di] ; save the original value
- mov byte ptr es:[di], 5AH ; test value
- mov al, byte ptr es:[di] ; read it back
- mov byte ptr es:[di], ah ; restore original
- cmp al, 5AH
- pop es ; clear stack
- jne check_done ; no PGA adapter
- or video_type, PGA ; yes, it's there
-
- check_done:
- cmp video_type, 0 ; When all else fails...
- jne exit ; can't recognize any card
- mov video_type, UNKNOWN
-
- exit: xor ax, ax ; clear ah
- mov al, video_type
-
- pop bp ; restore frame pointer to return to C caller
-
- ret
-
- video_test endp
-
-
- comment\**********************************************************************
-
- NAME
- cursor_reg
-
- SYNOPSIS
- checks to see if there is a cursor register at the
- address passed in dx
-
- RETURN VALUE
- carry clear - if cursor register present
- carry set - no cursor register here
-
- *****************************************************************************\
- cursor_reg proc near
-
- mov al, 0FH ; set the index to the cursor register
- out dx, al
- inc dx ; increment to data register
- in al, dx ; get the original value
- xchg al, ah ; save it for later
- mov al, 5AH ; test value
- out dx, al ; set cursor control register
- jmp $+2 ; waste some time
- jmp $+2
- jmp $+2
- in al, dx
- cmp al, 5AH ; same as written ?
- xchg al, ah ; restore saved value
- out dx, al
- je yup ; it was the control register
- stc ; no cursor return code
- ret
- yup: clc ; is there return code
- ret
-
- cursor_reg endp
-
- ENDPS
- end
-