Qbasicnews.com

Full Version: help with qb7.1 PDS & ASM
You're currently viewing a stripped down version of our content. View the full version with proper formatting.
Hello to all
please forgive me, my english is not so good

my problem is next:

i write a nice program in qb7.1 and is working fine, but on slow computer, PRINT is too slow
i reading data with 9k6 on serial interface and try to print this data on screen
but PRINT routine is too slow
ok, after goole+direct memory print, i find a program named display.asm
ok, display.asm is writen for qb4.5 and there is a note how to make compatible with qb7.1
after assembling and making library, thing work fine, but only in IDE
if i try to make exe, compiling and linking is done, but after i try to run EXE, program crashes, freeze or similar things
i don't understand why program work inside IDE but not after compiling
i try with 386,486,p3
dos7.1,winME,winXP

is there any usable solution for screen 0 direct memory print in qb7.1 PDS ?

thanks in advance
i did read your problem at the
http://www.qb45.com/index.php?page=forum...forum=1271
forum where it is better explained, i do not think the problem it is the PRINT function, the Quickbasics PRINT function it's not the fastest but also it is not slow.
i never have used COM1 but i would think that the problem it's about reading from the serial interface, as you said.
possibly you know there is a Basic dialect dedicated to the PIC microcontrolers that could be useful for you, just use a search machine using: "BASIC PIC microcontroler".
i you have more doubts just say, i am sure somebody will try to help you.
>do not think the problem it is the PRINT function, the Quickbasics
>PRINT function it's not the fastest but also it is not slow.

yes, it IS slow !!!!!!!

if my caracters is defined in 6(h)*7(v) matrix, and i try to print 5 digit delimited with point (999.99) then i have to print 6 char * 6(v) * 7(h) = 252

ok, data is comming in 3 byte. 1byte descriptor, 2 byte data
9600bit/s=104uS * 3 byte = 312uS

this mean, that EVERY 312uS i need to print 252 char
or 1.24uS / char

with fasprint (direct video memory write) program, named DISPLAY.ASM it is almost work fine. but, the MAIN problem is here:

i get display.asm, fixed to work with QB7.1 acordind to autor sugestion (source is from basic news)
ok, then

TASM display.asm
LIB display.lib +display.obj;
LINK /qu display.lib,,,qbxqlb

and thing work in IDE. only in IDE.
after compiling (succesful) the program crash after first call

any idea why lib does not work outside IDE ?

or any other lib for QB7.1 which contain SCREEN0 direct write ???

tnx in advance
if you put your code up, we might be able to help you so you don't even have to bother with asm.

i haven't dabbled in any asm for about 2 years, so I'm not sure how much help i'm going to be, and even when i was dabbling, i hadn't learned much

your main problem may be you are doing the math in the print statement like this:

[syntax="qbasic"]PRINT 4246.23446 / 6763.123[/syntax]

to quicken that (by just a touch)

[syntax="qbasic"] DIM ans AS DOUBLE

ans = 4246.23446 / 6763.123

PRINT ans
print using "###.##"; ans ' this will give you 5 digit output.[/syntax]

hope that helps

Oz~
>[quote="Oz"]if you put your code up, we might be able to help
>you so you don't even have to bother with asm.


ok, here is my code for bigprint

Code:
SUB bigtext (n, y)

t$ = LTRIM$(STR$(n))

FOR f = 1 TO LEN(t$)
        nr = ASC(MID$(t$, f, 1)) - 45
        t1$ = t1$ + txt(nr, 1)
        t2$ = t2$ + txt(nr, 2)
        t3$ = t3$ + txt(nr, 3)
        t4$ = t4$ + txt(nr, 4)
        t5$ = t5$ + txt(nr, 5)
        t6$ = t6$ + txt(nr, 6)
        t7$ = t7$ + txt(nr, 7)
NEXT f

LOCATE y, 1
PRINT t1$
PRINT t2$
PRINT t3$
PRINT t4$
PRINT t5$
PRINT t6$
PRINT t7$

END SUB


SUB MakeChar

txt(1, 1) = "      "
txt(1, 2) = "      "
txt(1, 3) = "      "
txt(1, 4) = "      "
txt(1, 5) = "      "
txt(1, 6) = "   ** "
txt(1, 7) = "   ** "

txt(3, 1) = " **** "
txt(3, 2) = "**  **"
txt(3, 3) = "**  **"
txt(3, 4) = "**  **"
txt(3, 5) = "**  **"
txt(3, 6) = "**  **"
txt(3, 7) = " **** "

txt(4, 1) = "  *** "
txt(4, 2) = " **** "
txt(4, 3) = "*  ** "
txt(4, 4) = "   ** "
txt(4, 5) = "   ** "
txt(4, 6) = "   ** "
txt(4, 7) = "  ****"

txt(5, 1) = " **** "
txt(5, 2) = "**  **"
txt(5, 3) = "    **"
txt(5, 4) = "   ** "
txt(5, 5) = "  **  "
txt(5, 6) = " **   "
txt(5, 7) = "******"

txt(6, 1) = " **** "
txt(6, 2) = "**  **"
txt(6, 3) = "    **"
txt(6, 4) = "   ***"
txt(6, 5) = "    **"
txt(6, 6) = "**  **"
txt(6, 7) = " **** "

txt(7, 1) = "   ***"
txt(7, 2) = "  * **"
txt(7, 3) = " *  **"
txt(7, 4) = "******"
txt(7, 5) = "    **"
txt(7, 6) = "    **"
txt(7, 7) = "   ***"

txt(8, 1) = "***** "
txt(8, 2) = "**    "
txt(8, 3) = "**    "
txt(8, 4) = "***** "
txt(8, 5) = "   ** "
txt(8, 6) = "   ** "
txt(8, 7) = "***** "

txt(9, 1) = " **** "
txt(9, 2) = "**    "
txt(9, 3) = "**    "
txt(9, 4) = "******"
txt(9, 5) = "**  **"
txt(9, 6) = "**  **"
txt(9, 7) = " **** "

txt(10, 1) = "***** "
txt(10, 2) = "   ** "
txt(10, 3) = "  **  "
txt(10, 4) = " **   "
txt(10, 5) = " **   "
txt(10, 6) = " **   "
txt(10, 7) = " **   "


txt(11, 1) = " **** "
txt(11, 2) = "**  **"
txt(11, 3) = "**  **"
txt(11, 4) = " **** "
txt(11, 5) = "**  **"
txt(11, 6) = "**  **"
txt(11, 7) = " **** "

txt(12, 1) = " ****  "
txt(12, 2) = "**  ** "
txt(12, 3) = "**  ** "
txt(12, 4) = " ***** "
txt(12, 5) = "    ** "
txt(12, 6) = "    ** "
txt(12, 7) = " ****  "

END SUB

As you se, i usin start char to make a big number on display

and now, my calculation in previous post is corect
252 char in 312uS

that is why i need some fast print routine in ASM to print next sequence

111111222222333333444444555555666666
111111222222333333444444555555666666
111111222222333333444444555555666666
111111222222333333444444555555666666
111111222222333333444444555555666666
111111222222333333444444555555666666
111111222222333333444444555555666666
111111222222333333444444555555666666


where the number represent big sharacters simulated with star

i hope now is clear Smile

tnx in advance
Code:
[code][/code]

it helps :wink:
Quote:
Code:
[code][/code]

it helps :wink:


ok, second try Smile

Code:
SUB MakeChar

txt(1, 1) = "      "
txt(1, 2) = "      "
txt(1, 3) = "      "
txt(1, 4) = "      "
txt(1, 5) = "      "
txt(1, 6) = "   ** "
txt(1, 7) = "   ** "

txt(3, 1) = " **** "
txt(3, 2) = "**  **"
txt(3, 3) = "**  **"
txt(3, 4) = "**  **"
txt(3, 5) = "**  **"
txt(3, 6) = "**  **"
txt(3, 7) = " **** "

txt(4, 1) = "  *** "
txt(4, 2) = " **** "
txt(4, 3) = "*  ** "
txt(4, 4) = "   ** "
txt(4, 5) = "   ** "
txt(4, 6) = "   ** "
txt(4, 7) = "  ****"

txt(5, 1) = " **** "
txt(5, 2) = "**  **"
txt(5, 3) = "    **"
txt(5, 4) = "   ** "
txt(5, 5) = "  **  "
txt(5, 6) = " **   "
txt(5, 7) = "******"

txt(6, 1) = " **** "
txt(6, 2) = "**  **"
txt(6, 3) = "    **"
txt(6, 4) = "   ***"
txt(6, 5) = "    **"
txt(6, 6) = "**  **"
txt(6, 7) = " **** "

txt(7, 1) = "   ***"
txt(7, 2) = "  * **"
txt(7, 3) = " *  **"
txt(7, 4) = "******"
txt(7, 5) = "    **"
txt(7, 6) = "    **"
txt(7, 7) = "   ***"

txt(8, 1) = "***** "
txt(8, 2) = "**    "
txt(8, 3) = "**    "
txt(8, 4) = "***** "
txt(8, 5) = "   ** "
txt(8, 6) = "   ** "
txt(8, 7) = "***** "

txt(9, 1) = " **** "
txt(9, 2) = "**    "
txt(9, 3) = "**    "
txt(9, 4) = "******"
txt(9, 5) = "**  **"
txt(9, 6) = "**  **"
txt(9, 7) = " **** "

txt(10, 1) = "***** "
txt(10, 2) = "   ** "
txt(10, 3) = "  **  "
txt(10, 4) = " **   "
txt(10, 5) = " **   "
txt(10, 6) = " **   "
txt(10, 7) = " **   "


txt(11, 1) = " **** "
txt(11, 2) = "**  **"
txt(11, 3) = "**  **"
txt(11, 4) = " **** "
txt(11, 5) = "**  **"
txt(11, 6) = "**  **"
txt(11, 7) = " **** "

txt(12, 1) = " ****  "
txt(12, 2) = "**  ** "
txt(12, 3) = "**  ** "
txt(12, 4) = " ***** "
txt(12, 5) = "    ** "
txt(12, 6) = "    ** "
txt(12, 7) = " ****  "

END SUB

ah, yeah. this time it is almost perfect Smile

tnx mr.match
and now, THE END Smile

i ask same question on www.qb45.com and guy named PLASMA is helped me
ok, the corrected ASM is here



Code:
; DISPLAY.ASM - contains a collection of video-related procedures and
;               functions for use with Microsoft high-level languages.
;
;   Author:     Christy Gemmell
;   For:        Assembly-Language Toolbox for QuickBASIC
;   Version:    4.07
;   Date:       22/9/1990 (fixed 10/9/2005 by Plasma)
;
;   Compatible with the BASIC/PDS 7.x compilers
;   Assembled using Microsoft Macro Assembler, MASM version 5.1
;
;   Global symbols and procedures.
;
                .model  medium

                extrn   StringAddress: proc

                public  ScreenAddress, ScreenWrite
                public  VideoType, FastPrint

                .code

;   Data Division.
;
;   Video parameters - default to monochrome screen display
;
SnowFlag        db      0               ; Snow prevention flag
VideoRam        dw      0B000h          ; Current video segment
VideoPort       dw      03BAh           ; Current video status port
Param1          label   word
Mode            db      7               ; Current screen mode
Columns         db      80              ; Current screen width
Param2          label   word
Rows            db      25              ; Current screen length
ActivePage      db      0               ; Current video page

;Listing 1.1     Collect video information

;  Collect information about the current video display.
;
;   Returns:    AL =    Current display mode
;               AH =    Screen width in columns
;               BL =    Screen height in rows
;               BH =    Active display page
;
;  The correct video display segment and CRT status port addresses are
;  determined for the current system and, if necessary, the internal
;  'snow' prevention flag is set.
;
VideoType       proc    far
                push    cx                      ; Preserve these
                push    dx                      ;    registers
                push    es                      ;
                push    bp                      ;Added this [DEC]
                mov     ah,0Fh                  ; ROM-BIOS Service 16
                int     10h                     ; - Check video mode
                cmp     al,7                    ; Monochrome display?
                je      Type_02                 ; Yes, use defaults
                mov     cs:VideoRam,0B800h      ; Otherwise set up
                mov     cs:VideoPort,03DAh      ;    for colour
Type_01:
                mov     cs:Param1,ax            ; Save display mode
                                                ;    and width
                push    bx                      ; Save active display
                xor     bh,bh                   ;    page
                mov     dl,24                   ; Default to 25 rows
                mov     ax,1130h                ; ROM-BIOS Service 16
                int     10h                     ;  - get font
                pop     bx                      ;    information
                mov     bl,dl                   ; DL = rows - 1
                inc     bl                      ; Save video page    
                mov     cs:Param2,bx            ;    and height
                mov     bl,10h                  ; Test for presence
                mov     ah,12h                  ;    of an EGA or VGA
                int     10h                     ;      display adaptor
                cmp     bl,10h                  ; Any response?
                jne     Type_02                 ; Yes, can't be a CGA
                mov     cs:SnowFlag,1           ; Set snow prevention
Type_02:                                        ;    flag
                mov     bx,cs:Param2            ; Recover page and
                                                ;    screen height
                mov     ax,cs:Param1            ; Recover screen mode
                                                ;    and width
                pop     bp                      ;added [DEC]
                pop     es                      ; Clean up the stack
                pop     dx
                pop     cx
                ret                             ; Return to caller
VideoType       endp

;Listing 1.2     Convert row/column co-ordinates to an address

;   Calculate address from a pair of row/column co-ordinates.
;
;   Given the row/column column co-ordinate of a character on the
;   screen, this function returns the segment:offset address of that
;   character in video memory. The address is correctly adjusted to
;   the start of the the currently active display page, but no check
;   is made to ensure that the co-ordinates supplied are within the
;   actual screen bounds.
;
;   Input:     AL      = Row co-ordinate of character (base zero).
;              AH      = Column co-ordinate of character (base zero).
;   Output:    ES:DI==>  Address in video display buffer of the
;                         character cell specified.
;              DX      = CRT status register port address.
;
;   It is assumed that a previous call has been made to the VideoType
;   function to determine the screen width, the port address of the
;   CRT status register and the correct video display segment.
;
ScreenAddress  proc    far
               push    ax               ; Save working registers
               push    bx
               mov     bh,ah            ; Column to BH
               mov     bl,cs:Columns    ; Get current screen width
               shl     bl,1             ; Add in attribute bytes
               mul     bl               ; Multiply by row number
               xor     bl,bl            ; Calculate
               xchg    bh,bl            ;    column offset
               shl     bl,1             ;      in BX
               add     ax,bx            ; Add it to the row offset
               mov     di,ax            ;    and copy to DI
               xor     ax,ax            ; Index to ROM-BIOS
               mov     es,ax            ;    data in low memory
               mov     ax,es:[44Eh]     ; Get offset of current page
               add     di,ax            ; Adjust target pointer
               mov     es,cs:VideoRam   ; Return segment of video RAM
               mov     dx,cs:VideoPort  ; Return CRT status port
               pop     bx               ; Clean up the stack
               pop     ax
               ret                      ;    and return to caller
ScreenAddress  endp

;Listing 1.3     Output a character and attribute to the screen.
;
;   Output a character and attribute to the video display.
;
;   If the 'snow prevention' flag is set, this routine waits until the
;   beginning of the next CRT horizontal retrace period before writing
;   data to the display. This is necessary only on computers fitted
;   with Colour Graphics Adaptor (CGA) which may suffer from glitches
;   or screen snow if data is written to the screen while the video
;   buffer is being refreshed.
;
;   Input:      ES:DI==>    Address in the video display buffer where
;                           the data is to be written.
;               DX =        Port address of CRT status register.
;               AL =        Character to output.
;               AH =        Display attribute of character.
;
;   Output:     DI          Updated to point to next output address.
;
ScreenWrite     proc    far
                push    bx              ; Preserve BX
                cmp     cs:SnowFlag,0   ; Snow prevention needed?
                cli                     ; Don't interrupt!
                jz      Write_3         ; No, don't bother
                mov     bx,ax           ; Save byte and attribute
Write_1:
                in      al,dx           ; Read video port
                test    al,1            ; Test bit zero
                jnz     Write_1         ; Wait until it's reset
Write_2:
                in      al,dx           ; Read port again
                test    al,1            ; Test bit zero
                jz      Write_2         ; Wait until it's set
                mov    ax,bx            ; Recover data
Write_3:
                stosw                   ; Write data to screen
                sti                     ; Restore interrupts
                pop     bx              ; Restore BX
                ret
ScreenWrite     endp

;Listing 1.4     Main program module.

;   Fast screen printing.
;
;   This procedure outputs text directly to the video display without
;   going through DOS or ROM-BIOS services.
;
FastPrint       proc    far
                push    bp              ; Save Base pointer
                mov     bp,sp           ; Establish stack frame
                push    ds
                push    es              ; Save Extra Segment
                push    si              ;    and index pointers
                push    di
                call    VideoType       ; Get video parameters
                mov     dh,ah           ; Load screen dimensions
                mov     dl,bl           ;    into DX
                mov     ax,[bp+12]      ; Get row number
                dec     al              ; Convert to base zero
                cmp     al,0            ; Top screen row?
                jae     Fast_01         ; Jump if not below
                xor     al,al           ; Don't go over the top!
Fast_01:
                cmp     al,dl           ; Bottom row?
                jb      Fast_02         ; Go no further
                mov     al,dl
                dec     al
Fast_02:
                mov     bx,[bp+10]      ; Get column number
                mov     ah,bl           ;    into AH
                dec     ah              ; Convert to base zero
                cmp     ah,0            ; Leftmost column?
                jae     Fast_03         ; Jump if not below
                xor     ah,ah           ; Don't go off the screen
Fast_03:
                cmp     ah,dh           ; Rightmost column?
                jb      Fast_04         ; Go no further
                mov     ah,dh           ; Don't go off the screen
                dec     ah              ; Base zero, remember?
Fast_04:
                push    ax              ; Save display co-ordinates
                mov     ax,[bp+8]       ; Index to string descriptor
                push    ax              ; Call BASIC for
                call    StringAddress   ;    string parameters
                pop     bx              ; Recover co-ordinates
                jcxz    Fast_08         ; Abort if a null string
                mov     ds,dx           ; String segment to DS
                mov     si,ax           ; DS:SI==> string data
                mov     ax,bx           ; Co-ordinates to AX
                call    ScreenAddress   ; Calculate target address
                mov     ax,[bp+6]       ; Get display attribute
                xchg    ah,al           ;    into AH
                cld                     ; Clear direction flag
Fast_06:
                lodsb                   ; Get a byte from the string
                call    ScreenWrite     ; Write byte and attribute
                loop    Fast_06         ; For length of string
                xor     ax,ax           ; Report success
Fast_07:
                pop     di              ; Clean up the stack
                pop     si
                pop     es
                pop    ds
                pop     bp
                ret     8               ; Return to QuickBASIC
Fast_08:
                mov     ax, 1           ; Report error
                jmp     short Fast_07

FastPrint       endp

end

code is working fine in IDE and as standalone LIB

ok, tnx for help
bye