[alt.msdos.programmer] Vertical Beam Interrupt on VGA

bcf@ccadfa.adfa.oz.au (- Chem.) (12/11/90)

I am sending this code for a friend. He can get it to work on
an XT with EGA but not with an AT with VGA. He would appreciate
any suggestions.


;
;   The following code works fine on and IBM XT clone with a Paradise EGA
;           card
;   It does not work on an IBM AT clone with and Ultra VGA card
;
;   Can anyone tell me what else I must do for the AT
;
;   Also I want similar code to work in EGA 320x200, VGA MCGA 320x200
;
        extrn   xDoAnimation:near

NL_TEXT         segment byte public 'CODE'
        assume  cs:NL_TEXT

Include     mwasm.h

        extrn       xg_mode:word
        extrn       xg_currPort:dword
        extrn       xg_cursorShield:word
        extrn       xg_originX:word
        extrn       xg_originY:word
        extrn       xg_theWorld:dword
        extrn       xg_EGA_regs:word

EOI     equ     020h
IC      equ     021h
ICMASK  equ     11111011b
VI      equ     0Ah

animStackSeg        dw      0           ; save stack seg
animStackPtr        dw      0           ; save stack pointer
animStack           dw      1022 dup (?)
animStackEnd        dw      0           ;
msg     db  "message",0dh,0ah,"$"

start   proc    far
        push    cs                      ;
        pop     ds                      ;

        mov     animStackSeg,ss         ; setup our own stack
        mov     animStackPtr,sp         ;

        push    cs                      ;
        pop     ss                      ;

        mov     sp,offset animStackEnd  ;

        mov     ax,0010h                ;
        int     10h                     ;

        call    far ptr _xInitVR        ;

        mov     cx,010h
s010:
        push    cx
        mov     cx,07FFFh
s020:
        inc     bx
        loop    s020
        pop     cx
        loop    s010

        call    far ptr _xStopVR        ;

        mov     ax,40h                  ;
        mov     es,ax                   ;
        and     byte ptr es:[10h],11001111b ; zero bits 4 and 5 of equip-flag
        or      byte ptr es:[10h],00100000b ; set to
                                        ;   11 - monchrome
                                        ;   10 - colour (25x80)
                                        ;   01 - colour (40x25)
                                        ;
        mov     ax,3                    ;
        int     10h                     ;

        mov     dx,offset msg
        mov     ah,9
        int     21h
        mov     ss,animStackSeg         ; reset stack
        mov     sp,animStackPtr         ;
        mov     ah,4Ch
        int     21h                     ;

start   endp

;*********************************************************************
;
;   function    VRInt
;
;   caller      called when vertical retrace interrupt occurs
;
;   regs        none, must preserve whole environment
;
        public      xg_vSync
xg_vSync    dw  0                       ; set to 1 when vert sync occurred

egaMode     db  2Bh,2Bh,2Bh,2Bh,24h,24h,23h,2Eh
            db  00h,00h,00h,00h,00h,24h,23h,2Eh
            db  2Bh
egaVRDefault    db      0               ;
PrevISROA       dd      0               ;

;
delayClock      dw      0               ;
skipTick        dw      0               ;

VRInt       proc    far
        pushStack                       ;
        push    dx                      ;
        push    ax                      ;
        mov     ah,00
        mov     msg,ah

        mov     dx,3C2h                 ; see if vertical interrupt occured
        in      al,dx                   ;
        test    al,80h                  ; test bit 7 of status reg
        jnz     vri010                  ; yes

        pushf                           ; no, simulate interrupt
        call    PrevISROA               ; to original interrupt

vriExit:
        pop     ax                      ;
        pop     dx                      ;
        popStack                        ;
        iret                            ;

vri010:                                 ; handle interrupt
        mov     dx,ega_CRTC             ;
        in      al,dx                   ; preserve CRTC

        mov     ah,egaVRDefault         ; default VR end reg

        and     ah,11101111b            ; clear bits 4 (interrupt latch)

        mov     al,11h                  ;
        out     dx,al                   ;
        mov     al,ah                   ;
        inc     dx                      ;
        out     dx,al                   ;
        dec     dx                      ;

        jmp     $+2                     ; delay

        mov     al,20h                  ; send EOI
        out     EOI,al                  ;
        jmp     $+2                     ;
        sti                             ; enable system interrupts other than VR

        mov     xg_vSync,1              ;
        dec     delayClock              ; decrement delay clock, if any set
        dec     skipTick                ; decrement skip clock, if any set

;       call    xDoAnimation            ;

vri015:

        cli                             ; enable another VR interrupt
        mov     dx,ega_CRTC             ;
        mov     ah,egaVRDefault         ; default VR end reg

        and     ah,11001111b            ; enable interrupts
        or      ah,00010000b            ;

        mov     al,11h                  ;
        out     dx,al                   ;
        mov     al,ah                   ;
        inc     dx                      ;
        out     dx,al                   ;
        dec     dx                      ;

        jmp     $+2                     ; delay

        pop     ax                      ;
        out     dx,al                   ; restore previous address reg value

        jmp     vriExit                 ;

VRInt       endp

;*********************************************************************
;
;   xInitVR(void)
;
;   enable vertical retrace interrupts for animation handler and
;   page flipping

            public  _xInitVR
_xInitVR        proc    far
        pushStack                       ;

        mov     ax,40h                  ;
        mov     es,ax                   ;

        mov     dx,ega_CRTC             ;
        mov     ax,1A00h                ;
        int     10h                     ;

        cmp     al,1Ah                  ; if VGA, al left intact
        je      ev010                   ; yes

        mov     al,es:[49h]             ; video BIOS mode number
        mov     bx,offset egaMode       ;
        push    cs                      ;
        pop     ds                      ;
        xlat                            ; al = default VR end reg
        jmp     short ev020             ;

ev010:                                  ; VGA mode
        mov     al,11h                  ;
        cli
        out     dx,al                   ; read register
        jmp     $+2
        inc     dx                      ;
        in      al,dx                   ;
        sti                             ;
ev020:
        mov     egaVRDefault,al         ; save VR end reg

        mov     ax,350Ah                ; save old interrupt vector
        mov     al,VI
        int     21h                     ;
        mov     word ptr PrevISROA,bx   ;
        mov     word ptr PrevISROA+2,es ;
                                        ; set new handler
        push    ds                      ; save ds
        mov     dx,offset VRInt         ;
        push    cs                      ;
        pop     ds                      ;

        mov     ax,250Ah                ;
        mov     al,VI
        int     21h                     ;

        pop     ds                      ; restore ds

        cli                             ; clear interrupts
        in      al,IC                   ;
        and     al,ICMASK               ; mask reg, reset bit 2
        out     IC,al                   ;

        mov     dx,ega_CRTC             ; enable vertical interrupts
        mov     ah,egaVRDefault         ; default VR end reg

        and     ah,11001111b            ; clear bits 4 and 5 of VR end reg
        mov     al,11h                  ;
        out     dx,ax                   ;

        jmp     $+2                     ; delay

        or      ah,00010000b            ; set ready to accept interrupt
        out     dx,ax                   ;

        jmp     $+2                     ; delay

        sti                             ;

        popStack                        ;
        ret                             ;

_xInitVR            endp                ;

;*********************************************************************
;
;   xStopVR(void)
;
;   disable vertical retrace interrupts

            public  _xStopVR
_xStopVR        proc    far
        pushStack                       ;

        cli                             ; stop interrupts
        mov     dx,ega_CRTC             ; enable vertical interrupts
        mov     ah,egaVRDefault         ; default VR end reg

        mov     al,11h                  ;
        out     dx,al                   ;
        mov     al,ah                   ;
        inc     dx                      ;
        out     dx,al                   ;
        dec     dx                      ;

        jmp     $+2                     ; delay

        lds     dx,PrevISROA            ; restore old interrupt handler
        mov     ax,250Ah                ;
        mov     al,VI
        int     21h                     ;

        popStack                        ;
        ret                             ;

_xStopVR        endp

;*********************************************************************
;
;       void        xDelay(p_time)
;
;           short       p_time      - in 50th of a second
;
dlp_time            equ     [bp+6]

        public      _xDelay
_xDelay     proc    far
        pushStack                       ;

        mov     ax,dlp_time             ;
        mov     delayClock,ax           ; wait till this time
dl010:
        cmp     delayClock,0            ; delayTick updated by timer routine
        jg      dl010                   ;

        popStack                        ;
        ret
_xDelay     endp

;*********************************************************************
;
;       void        xSkip(p_time)
;
;           short       p_time      - in 60th of a second (max 16K)
;
skp_time            equ     [bp+6]

        public      _xSkip
_xSkip      proc    far
        pushStack                       ;

        mov     ax,skp_time             ;
        mov     skipTick,ax             ;
        popStack                        ;
        ret                             ;
_xSkip      endp

;*********************************************************************
;
;       short       xSkipDone()
;
;       returns non-zero when skip count dropped below zero
;
        public      _xSkipDone
_xSkipDone      proc far

        xor     ax,ax                   ;
        cmp     skipTick,0              ;
        jg      skd010                  ; not done
        mov     ax,0FFFFh               ; done
skd010:
        ret                             ;

_xSkipDone      endp



NL_TEXT     ends
            end     start

Thanks,

Ben Freasier

nn86302@tut.fi (Niilo Neuvo) (12/12/90)

The code is 100% ok. It is just the fact that most of the current
VGA card don't support the horizontal retrace interrupt. When IBM
made it's original VGA card for the AT it didn't support interrupts,
so most vendors decided that they don't have to support it either.
(I read this from a book called programming IBM EGA/VGA, can't
 remember the author(s) nor the publisher.)

The IBM PS/2 series supports the interrupt as fasr as I have tested
(and read).

You have to work around this problem by polling the CRT interrupt bit.
I have never tried syncing the timer to the raster, but I guess
that it could be done rather easily with a bit of programming.

--
      NN   NN  NN   NN  NNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNN
    NNNN    N  NN    N  NNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNN
  NNNNNN  N    NN  N    NNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNN
NNNNNNNN  NN   NN  NN   NNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNNN