RATE.BAS      

SPREADSHEET

GGA sentence in Sandpiper

Current on  April 29 2012  1315  PDT





TYPE RegType
     AX    AS INTEGER
     bx    AS INTEGER
     CX    AS INTEGER
     DX    AS INTEGER
     bp    AS INTEGER
     si    AS INTEGER
     di    AS INTEGER
     flags AS INTEGER
END TYPE

   DIM inregs AS RegType, outregs AS RegType
   DIM flag AS INTEGER
   DIM ASM$
   DECLARE SUB DiskWr (VALID$, rate$)
   DECLARE SUB InitASM (ASM$)
   DECLARE SUB SetClock (ASM$, HourMin%, Sec%)


   CONST tph = 65543.3333333333# 'tick in hour
   CONST tpm = 1092.388889#    'ticks in minute
   CONST tps# = 18.20648148148# ' tps# is ticks per second
   COMPORT = 1

   g = 0
   i# = 0
   Tsec# = 10800        '<<========================== 3 hr headstart
  PRINT "   HOURS TO RUN"
  INPUT "    1 - 24   "; HR
  RunSec# = HR * 3600

   CLS
   PRINT "Sandpiper Version April 29 2012 2011 UTC"
   CALL InitASM(ASM$)

   LOCATE 13, 15: PRINT "HIT ANY KEY to END"
   LOCATE 14, 15: PRINT HR; " hour run"
   LOCATE 6, 16: PRINT " CONNECT GPS  "
'
'  The program loops until a key is pressed
'   or time expires.
'  the NMEA string is read on each loop and
'  the PC clock is set ONCE AT THE START.
'  "Time Set" is printed to the screen when
'  the PC time is set.
'  The loop is counted by Tsec#
'  RATE is updated each second and
'  written to a file on program termination,
'  and each hour after starting.
   OPEN "COM1:4800,N,8,1,CD0,CS0,DS0,OP0,RS," FOR RANDOM AS #1
'-------------------------------begin outer loop----------------------------------------------

DO WHILE i# < RunSec#

      DO UNTIL gLL = 4
    LINE INPUT #1, A$: gLL = INSTR(A$, "PGGA")
      LOOP                        'GGA SENTENCE IN BUFFER

 
    Hour = VAL(MID$(A$, 9, 2)): Min = VAL(MID$(A$, 11, 2)): Sec = VAL(MID$(A$, 13, 2))

'       fix the GPS time
'    ----------------------
      Sec = Sec + 2
      IF (Sec >= 60) THEN
     Sec = Sec - 60
     Min = Min + 1
      END IF
      IF (Min = 60) THEN
     Min = 0
     Hour = Hour + 1
      END IF
      IF (Hour = 24) THEN
     Hour = 0
      END IF
'    ================

'      LOCATE 11, 13: PRINT " GPS Time   "; Hour:  LOCATE 11, 28: PRINT Min:  LOCATE 11, 31: PRINT Sec
'
'    ------- Elapsed time comes from here ---------
'   Tsec# is total seconds
'   Ehr is elapsed hours
'   Rsec is an intermediate step, remainder seconds
'   Emin is elapsed minutes
'   Emin is NOT printed to the file
'
      Tsec# = Tsec# + 1
      Ehr = INT(Tsec# / 3600)
      Rsec = Tsec# - (Ehr * 3600)
      Emin = INT(Rsec / 60)
      LOCATE 9, 14:
      PRINT "ELAPSED     "; Ehr; Emin
'            --------begin inner loop --------- set RTC ----------
    DO WHILE g < 1          ' g = 1 , first pass
      HourMin% = Hour * 256 + Min
     Sec% = Sec * 256
       CALL SetClock(ASM$, HourMin%, Sec%)  ' set the RTC on this tick
'
'        this section gets the VALUE OF TICK into the start variable
'        and it won't run as a subroutine
'         --------------------------------------------------------
    inregs.AX = 0
    CALL INTERRUPT(&H1A, inregs, outregs)
    ticks& = outregs.CX * &H10000

    IF outregs.DX < 0 THEN
        a2& = (outregs.DX AND &H7FFF&)
        ticks& = (ticks& + a2&)
        ticks& = (ticks& OR &H8000&)
    ELSE
        ticks& = ticks& + outregs.DX
    END IF

    StartCt# = ticks&       ' write start tick value
'        ===========================================================
    g = g + 1

    LOCATE 6, 13: PRINT "     time set    "
    LOOP
'      ---------------------- end inner loop ----------------------
    VALID$ = MID$(A$, 47, 2)
    
      IF VAL(VALID$) = 0 THEN
     LOCATE 7, 16: PRINT "No GPS Fix"
    
      ELSEIF VAL(VALID$) = 3 THEN
     LOCATE 7, 16: PRINT "  2D FIX   "
    
      ELSEIF VAL(VALID$) > 3 THEN
     LOCATE 7, 16: PRINT "  3D FIX   "
      END IF

      LOCATE 2, 1
      PRINT A$

      LOCATE 10, 13:
      PRINT " PC  Time    "; TIME$

      gLL = 0                    'reset gLL so NEW PGGA in buffer next time
       i# = i# + 1              ' why is this ? debug
'--------------------------------------------------------------------------
'       this section gets the value of tick into the STOP variable
'       and it won't run as a subroutine
'
    inregs.AX = 0
    CALL INTERRUPT(&H1A, inregs, outregs)
    ticks& = outregs.CX * &H10000

    IF outregs.DX < 0 THEN
        a2& = (outregs.DX AND &H7FFF&)
        ticks& = (ticks& + a2&)
        ticks& = (ticks& OR &H8000&)
    ELSE
        ticks& = ticks& + outregs.DX
    END IF

    StopCt# = ticks& + 196652       ' ticks NOW from PC   '<<=======<<========3 hr headstart
'1 hr 65543.333333328 ( 3 hr 196629.999999984 +22 = 196652)

'==========================================================================
'      Calculate rate from ticks and seconds
'--------------------------------------------------------------------------------------
'
    IF StopCt# > StartCt# THEN
    PCcount# = StopCt# - StartCt#
    ELSE PCcount# = 1573040 - StartCt# + StopCt#
    END IF
      
    rate# = (Tsec# * tps#) / PCcount#
      
    LOCATE 16, 16
    rate$ = LEFT$(STR$(rate#), 11)
    PRINT "RATE "; rate$
    'PRINT USING "RATE  #.########"; rate#
'
    iPrint = iPrint + 1
    IF INKEY$ <> "" THEN i# = 82900
      
    DO WHILE iPrint = 1               'iPrint cannot be set to zero <<=======<<=========<<==== (1)
    CALL DiskWr(VALID$, rate$)        'in the sub so must use this
    iPrint = 0                        ' DO/LOOP structure to reset
    LOOP                              ' iPrint   3600 for every hour
LOOP
'================ end outer loop ==================
   CLOSE #1
   CALL DiskWr(VALID$, rate$)
   SLEEP 1
   OPEN "COM1:9600,N,8,1,CD0,CS0,DS0,OP0,RS," FOR RANDOM AS #1
   CLOSE #1

END
'
' variables used
'
'g              integer
'Hour           single
'i#             double
' iPrint
'gLL            integer
'Min            integer
'PCcount#               double
'rate#          double
' RunSec#
'sec#           double
'Sec%   integer
'StartCt#               double
'StartSec#              double
'StopCt#                double
't$             string
'ticks&         long
'tps#           double
'Tsec#           double
'
'%      INTEGER
'single!   .0004107 - 41070
'long&     -2147483648 - 2147483647 WHOLE NUMBERS
'double#   REALLY SMALL TO REALLY BIG, FLOATING POINT
' $   string

SUB DiskWr (VALID$, rate$)
    OPEN "RATE.TXT" FOR APPEND AS #2
    PRINT #2, VALID$; " "; TIME$; " "; rate$
    CLOSE #2
END SUB

SUB InitASM (ASM$)

'SET UP STACKFRAME
ASM$ = ""
ASM$ = ASM$ + CHR$(&H55)                            'push bp
ASM$ = ASM$ + CHR$(&H89) + CHR$(&HE5)               'mov bp,sp

ASM$ = ASM$ + CHR$(&HBA) + CHR$(&HFE) + CHR$(&H3)   'mov dx,03FE
ASM$ = ASM$ + CHR$(&HEC)                            'loop:  in al,dx
ASM$ = ASM$ + CHR$(&H24) + CHR$(&H80)               'and al,80
ASM$ = ASM$ + CHR$(&H3C) + CHR$(&H80)               'cmp al,80
ASM$ = ASM$ + CHR$(&H75) + CHR$(&HF9)               'jnz loop - loop while not 80

ASM$ = ASM$ + CHR$(&H8B) + CHR$(&H4E) + CHR$(&H8)   'mov cx,[bp+08] - HourMin
ASM$ = ASM$ + CHR$(&H8B) + CHR$(&H56) + CHR$(&H6)   'mov dx,[bp+06] - Sec
ASM$ = ASM$ + CHR$(&HB4) + CHR$(&H2D)               'mov ah,2D
ASM$ = ASM$ + CHR$(&HCD) + CHR$(&H21)               'int 21

ASM$ = ASM$ + CHR$(&H5D)                            'pop bp
ASM$ = ASM$ + CHR$(&HCA) + CHR$(&H4) + CHR$(&H0)    'retf 4

END SUB

SUB SetClock (ASM$, HourMin%, Sec%)
'----------------------------------------------------------------------
'This is an INTEL procedure to set the RTC
'From the string parameter
'-----------------------------------------------------------------------
DEF SEG = VARSEG(ASM$): CALL ABSOLUTE(BYVAL HourMin%, BYVAL Sec%, SADD(ASM$)): DEF SEG

END SUB