Announcement

Collapse
No announcement yet.

Three timers

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • Three timers

    the code following illustrates three different timers.

    peektimer is modified from an earlier pbdos message
    by hans ruegg, exact timing. it counts 256 * 18 ticks/sec.
    although it works in the test code below, it doesn't work
    in a practical program.

    newtimer is an attempt to convert the above to assembler.

    mstimer was found on the pbxtra cd, here slightly
    modified. i don't understand how it works, but it
    works. it counts approximately 1000 ticks/sec
    (more like the high 900's). part of the complexity
    of the code is due to counting 1000 ticks/sec instead
    of 4608, but only part.

    main question: what's wrong with peektimer?

    minor question: how to convert peektimer to newtimer,
    that is, assembler? the test code works most of the
    time but sometimes gives a negative number. using
    cli/sti doesn't help.

    minor question: in mstimer, are the lines marked with
    a question necessary?

    'test code

    Code:
     dim x as long
    
     print "peektimer ";
     def seg = 0
     x = peektimer
     delay 1                 'how many ticks in one second
     print peektimer - x     '4608 ticks, which is 18 * 256
    
    
     print "newtimer  ";
     x  = newtimer
     delay 1
     print newtimer - x      'usually, not always, equals above
     			
     print "mstimer   ";
     x = mstimer
     delay 1
     print mstimer - x       'approximately 1000 (a little less)
    
    
    '--------------------------------------------------
    'by hans ruegg -- see link above
    function peektimer as long    'assumes def seg = 0
     out &h43, &h34               'set timer to "mode 2"
     low? = inp(&h40)             'discard first time
     low? = inp(&h40)                                 
     a& = peekl(&h46c)
     shift left a&, 8
     function = a& + 256 - low?   '+ 256 is not necessary
    end function         
    
    
    'the above converted to assembler, except for + 256
    function newtimer as long    
     ! mov al,&h34                'set timer to "mode 2"
     ! out &h43,al                
     ! in  al,&h40                'discard first time	
     ! in  al,&h40                'low
     ! xor ah,ah
     ! mov dx,ax                  'save low in dx
     ! mov bx,&h0040              'want address &h46c
     ! mov es,bx                  
     ! mov bx,&h006c              
     ! mov ax,es:[bx]
     ! mov cl,8                   'shift left by 8
     ! shl ax,cl                  
     ! sub ax,dx                  'subtract off low
     ! mov function,ax
    end function
    
    
    'from pbxtra, more or less
    function mstimer as long
     dim saveax as word, savedx as word
     dim k1 as byte, k2 as byte
     ! mov bx,&h0040
     ! mov es,bx
     ! mov bx,&h006c
    s0101:
     ! mov al,&hc2
     ! cli
     ! out &h43,al
     ! jmp s0108            ;?
    s0108:
     ! in al,&h40
     ! jmp s010c            ;?
    s010c:
     ! shl al,1             ;? shl al doesnt affect ah
     ! in al,&h40
     ! jmp s0112            ;?
    s0112:
     ! mov cl,al
     ! in al,&h40
     ! jmp s0118            ;?
    s0118:
     ! mov ch,al
     ! jcxz s0190           ;necessary?
     ! rcr cx,1
     ! not cx
     ! mov ax,&heccc
     ! mul word ptr es:[bx]
     ! mov k1,ah            ;temporary store
     ! mov k2,al
     ! mov si,dx
     ! mov ax,&heccc
     ! mul word ptr es:[bx+02]
     ! mov di,dx
     ! add si,ax
     ! adc di,+00
     ! mov ax,&h0036
     ! mul word ptr es:[bx]
     ! add si,ax
     ! adc di,dx
     ! mov ax,&h0036
     ! mul word ptr es:[bx+02]
     ! add di,ax
     ! mov ax,&hdbb3
     ! shr cx,1
     ! shr cx,1
     ! mul cx
     ! add ah,k1            ;use temp store
     ! adc dl,k2
     ! mov ax,si
     ! adc al,dh
     ! adc ah,00
     ! mov dx,di
     ! adc dx,+00           ;below happens every 32000 ticks
     ! cmp dx,savedx        ;hi byte increased ?
     ! ja s017d
     ! cmp ax,saveax        ;lo byte increased ?
     ! jb s0189
    s017d:
     ! mov saveax,ax
     ! mov savedx,dx
     ! sti
     ! jmp short endmstimer
    s0189:
     ! cmp savedx,1318      ;almost midnight ?
     ! je s017d             ;ignore decrease in tick& if is
    s0190:                  'otherwise hangs for several secs
     ! sti
     ! jmp s0101
    endmstimer:
     function = saveax + savedx * 65536
    end function



    [this message has been edited by mark hunter (edited march 29, 2001).]
    Algorithms - interesting mathematical techniques with program code included.

  • #2
    Could be various problems here. PeekTimer may not be expecting to be interrupted
    by interrupts, and/or may be depending on default system timer settings. Come to
    that, it's using a weird combination of IN/OUT with PEEKing the BIOS heartbeat
    memory... so it's probably doing something unsavory to the timer and hoping to
    get away with it. It may well be screwing up the system clock and TIME$ function.
    PB/DOS also does its own timer manipulation for various purposes, so there may be
    room for conflicts there, also. This is "iffy" code!

    NewTimer and negative numbers: it's returning a LONG, which comes from DX,AX. It
    looks like DX is being used for some other purpose, though. The translation needs
    work.

    MSTimer: the JMPs are intended to provide a brief delay so the timer can digest
    the changed settings. Newer chips may not need this delay. On the other hand, the
    amount of delay provided by a JMP is much less these days, so it's also possible
    that you'll need a longer delay. Offhand, who knows? If MSTimer works for you, no
    need to mess with it. Otherwise, try putting in more delays where those JMPs are
    located.


    ------------------
    Tom Hanlin
    PowerBASIC Staff

    Comment


    • #3
      Mark,
      I haven't looked at the details of the code, but below are a few observations:

      The strange looking jumps are not for delay. A long jump will cause the CPU to flush the instruction queue in the CPUs pipelines so ensuring that instructions executed before the JMP are completed before executing any instruction after the JMP. It is possible (but I don't know about this particular case) for consecutive OUT/IN instructions that the OUT is held up in a pipeline waiting for the previous instruction to complete and the IN is executed in another pipeline and is not delayed and potentially could be executed before the previous OUT . The CPU can't tell because different input and output ports can appear at the same address as with the timer chip.


      Why do you say the +256 is not necessary? Have you checked? What happens if the higher bytes are all 0?
      Do you realise that the timer chip counts DOWN and not UP and that the timer interrupt occurs when the count reaches 0 and not when it rolls over to FFFF?

      "shl al doesnt affect ah"
      No, but it does set the carry flag which is tested later.


      "Peektimer is modified from an earlier"
      Why modified and who by? It's never going to be reliable if you don't disable interrupts from before the first part of the timer is read until after the last part is read (i.e.the whole function)
      Where do you tell the routine to latch the timer? The timer chip can be read during an update and will return a bad value. The chip must first be told to latch the current count before reading it by writing a 0 to port &h43.

      In newtimer the above points also apply.


      "It counts approximately 1000 ticks/sec (more like the high 900's)"

      Has it occurred to you that the DELAY 1 depends on the timer interrupt which happens every 54.925ms so the nearest it can get to a whole second is 18*.054925=0.988657s. The result expected is then always 988 or 989.

      If you try any of this in Windows then none of it will work!

      Paul.

      Comment


      • #4
        Code:
        Tom is almost certainly correct about the jumps to labels 
        immediately following the JMP instructions being intended 
        as delays.  PB's inline assembler does not provide a 
        location counter, so the old delay tactic "JMP $+2" cannot 
        be used.  Hence an effort to create the PB equivalent. 
           
        However, today's processors handle instructions in 
        sophisticated ways, and almost all of them now make relying 
        on "JMP $+2" unreliable as a method for accomplishing 
        anything.  The same is no doubt true of the tactic being 
        used in the posted code.  (I investigated this issue some 
        time back when I first discovered well-tested code no 
        longer behaving reliably under a new CPU.)
           
        Much has changed, both for software and hardware, since the 
        posted code was written.

        ------------------
        -- Greg
        [email protected]

        Comment


        • #5
          Thank you Tom Hanlin, Paul Dixon, & Greg Turgeon for your replies.

          I'll leave the jmp's in MStimer, though in tests I've run
          the code works without them.

          I'm abandoning "peektimer" and "newtimer." My goal was
          to replace MStimer with something simpler, but it looks
          like the complexity is necessary. But commenting on
          newtimer, I didn't subtract variable low from 256 because
          I'm interested in only differences from one timer
          call to the next. Since I must check for rollover (a
          negative change) anyway, there is no reason to add a
          constant. Speaking of rollover, one advantage of MStimer
          over other millisecond timers I've seen is that it returns
          a long integer rather than a short, so the rollover occurs
          less frequently.

          Regarding delay 1 actually being about .988 seconds -- yes,
          that's just what MStimer reports.

          > "shl al doesn’t affect ah" ... but it does set the carry
          > flag which is tested later.
          I don't see it being tested later before it has been changed
          by another instruction.

          > "Peektimer is modified from an earlier" ...
          The modification was trivial, and there is a "hyperlink" to
          the original.

          Regarding MStimer working in Windows -- it does work in that
          it serves my purpose, which is to keep a blkput picture on
          the screen for a certain time before replacing it with another
          picture, resulting in a movie. Although there is some
          roughness in the movie speed -- it speeds up and slows down
          a little at random -- it is acceptable. In pure DOS the movie
          is completely smooth.

          For what it's worth, here's my code for any number of
          independent millisecond timers. It uses a sub version
          of function MStimer above, and I've replaced the PB
          "temporary store" variables with a push and pop, and
          the two words to one dword conversion with a union.
          Following the code is a simple example using it.
          Code:
          declare sub GetMStime()
          declare sub resetclock(byval integer)
          declare function clock%(byval integer)
          '-------------------------------------------------------
          '  Clock is like PBXtra's MStimer except:
          '  1.  It starts at 0, and you can reset it to 0 by 
          '      command (reset must be done at least once).
          '  2.  It corrects the MStimer midnight 23 seconds 
          '      freeze problem that occurs on a 486.
          '  3.  It assumes you will be timing events lasting 
          '      less than 32 seconds.
          '-------------------------------------------------------
          %nclock = 4           'Clocks 0,1,2,3,4 - change to suit.
          dim tick0&(%nclock)   'Base of each clock.
          '-------------------------------------------------------
          ' My application, for example, uses these clocks for the 
          ' following:
          ' clock 0 - curtain open/close and fadein/fadeout
          ' clock 1 - holding movie frames during playing
          ' clock 2 - time the full first lap at beginning of playing
          ' clock 3 - time movie frames to find maximum
          ' clock 4 - time repeat mouse clicks
          '-------------------------------------------------------
          shared tick&
          '-------------------------------------------------------
          sub resetclock(byval n as integer)
           shared tick0&()
           GetMStime
           tick0&(n) = tick&
          end sub
          '-------------------------------------------------------
          function clock%(byval n as integer)
           shared tick0&()
           GetMStime
           t& = tick& - tick0&(n)
           if t& < 0 then incr t&,86399202&	'midnight, see below
           function = t&      
          end function        
          ' 24*60*60*1000 - 798 = 86400000& - 798.
          ' MStimer wrapped 798 msec before it should on a
          ' 486DX I once owned, so 798 here corrects a trivial 
          ' difference at midnight.  You could just as well 
          ' replace it with 0.
          '-------------------------------------------------------
          type TwoWords
           Lw as word
           Hw as word
          end type
          
          union WordsOrDword
           S as TwoWords
           D as dword
          end union
          '-------------------------------------------------------
          sub GetMStime static
           dim saveAX as word, saveDX as word
           dim c as WordsOrDword
           ! MOV BX,&h0040
           ! MOV ES,BX
           ! MOV BX,&h006C
          s0101:
           ! MOV AL,&hC2
           ! CLI
           ! OUT &h43,AL
           ! JMP s0108			
          s0108:
           ! IN AL,&h40
           ! JMP s010C				
          s010C:
           ! SHL AL,1             ;see Paul Dixon's message below
           ! IN  AL,&h40
           ! JMP s0112   			
          s0112:
           ! MOV CL,AL
           ! IN  AL,&h40
           ! JMP s0118				
          s0118:
           ! MOV CH,AL
           ! JCXZ s0190				
           ! RCR CX,1
           ! NOT CX
           ! MOV AX,&hECCC
           ! MUL WORD PTR es:[BX]
           ! push ax              ;save ax
           ! MOV SI,DX
           ! MOV AX,&hECCC
           ! MUL WORD PTR es:[BX+2]
           ! MOV DI,DX
           ! ADD SI,AX
           ! ADC DI,+00           ;see Paul Dixon's message below
           ! MOV AX,&h0036
           ! MUL WORD PTR es:[BX]
           ! ADD SI,AX
           ! ADC DI,DX
           ! MOV AX,&h0036
           ! MUL WORD PTR es:[BX+2]
           ! ADD DI,AX
           ! MOV AX,&hDBB3
           ! SHR CX,1
           ! SHR CX,1
           ! MUL CX
           ! pop ax               ;recover ax
           ! add ah,ah
           ! adc dl,al
           ! MOV AX,SI
           ! ADC AL,DH
           ! ADC AH,00
           ! MOV DX,DI
           ! ADC DX,+00           ;below happens only every 32000 ticks
           ! CMP DX,saveDX        ;hi byte increased ?
           ! JA  s017D
           ! CMP AX,saveAX        ;lo byte increased ?
           ! JB  s0189
          s017D:
           ! mov saveAX,ax
           ! mov saveDX,dx
           ! STI
           ! jmp short EndMStimer
          s0189:
           ! cmp saveDX,1318      ;almost midnight ?
           ! je  s017D            ;ignore decrease in tick& if is
          s0190:                  'to avoid 23 second hang
           ! STI
           ! JMP s0101
          EndMStimer:
           c.s.hw = saveDX
           c.s.lw = saveAX
           tick&  = c.d               'tick& = saveAX + saveDX*65536
          ' if tick& < oldtick& then  'test above for rollover
          '  print tick&;"     ";
          '  beep
          ' end if
          ' oldtick&=tick&
          end sub
          '-------------------------------------------------------
          
          'Simple example
          
          cls
          print "start"
          resetclock 1
          do while clock%(1) < 99 :loop     	'delay 99 milliseconds
          print "finish"



          [This message has been edited by Mark Hunter (edited October 28, 2005).]
          Algorithms - interesting mathematical techniques with program code included.

          Comment


          • #6
            Mark,
            "I'll leave the jmp's in MStimer, though in tests I've run the code works without them."

            It's dependant on the hardware you run it on so it's best to leave them in although for accessing the timer I've never found them necessary.

            "I don't see it being tested later before it has been changed by another instruction."

            ! RCR CX,1 is the next line to affect the carry flag after the shift and it uses the carry. It looks like the carry bit is used as a temporary store for the top bit of the timer which is read from the status register as the timer appears to be operating in mode 3.


            "! ADC DI,+00 ;?
            This is taking care of the potential carry resulting from the previous "! ADD SI,AX"


            Paul.

            Comment

            Working...
            X