Shop OBEX P1 Docs P2 Docs Learn Events
GPS-tracking of transportation force events — Parallax Forums

GPS-tracking of transportation force events

sandy30sandy30 Posts: 2
edited 2012-08-20 09:19 in BASIC Stamp
Hello,
Im doing my graduation project which is based upon simple 8-bit microcontroller unit (MCU) BS2p that would be used to monitor / log forces that are generated during transportation of goods / people. A working title might be "GPS-tracking of transportation force events". The MCU would be programmed to respond to events that are triggered by a signal from an accelerometer sensor and these signals would be GPS date/time/position stamped onto an externally removable storage medium (e.g. USB pen-drive) for later analysis. Possible applications include a critical assessment of whether damage is likely to be incurred upon fragile goods along selected routes, road-surface monitoring by commuter groups, cross-country terrain assessment for mountain bike events.
sensor – (28526)MMA7455 3Axis Accelerometer sensor
GPS Module – RXM-SG- GPS Module

Actually im looking for how to interface accelerometer sensor with GPS Module in breadboard series of parallax board of education BS2p microcontroller and interfacing code too…I am compleletely new to microcontroller programming..even the pbasic seems to be easy to understand but I find it very difficult as I m complete new to this..i would be glad if someone can help me to accomplish my project..

Software used is PARALLAX BASIC STAMP EDITOR 2.5.2

Coding for MMA7455 3-AXIS ACCELEROMETER MODULE

' {$STAMP BS2e}
' {$PBASIC 2.5}

'How TO Use:
' • With power initially off, connect VIN TO 5VDC (the same voltage
' powering the sTAMP). Connect GND TO Vss.
'
' • Connect P0, P1, AND P2 ON the Stamp directly TO the CS, DATA, AND CLK
' pins ON the Digital 3-Axis Accelerometer module.
'
' • Power ON the Stamp. Download AND run this code ON the Stamp.
'
' • Acceleration values will stream back TO the computer, AND can be viewed
' on the DEBUG terminal.
'
' • The offset values FOR each axis can be calibrated by placing the device
' ON a flat horizontal surface AND adjusting the corresponding constants
' UNTIL the values FOR each axis READ (WHILE in 2g mode):
' X = 0 (0g)
' Y = 0 (0g)
' Z = 63 (+1g)
' The values already present are FOR demonstration purposes AND can
' be easily modified TO fine tune your own device. Keep in mind that
' the offset values are in 1/2 Bit increments, so FOR example, TO offset
' an axis by 5 counts, the corresponding offset would need TO be increased
' by a value of 10. See the MMA7455L device datasheet FOR more
' information.

'Offset values FOR each axis:
XCal CON 25 'VAR Word
YCal CON 50 'VAR word
ZCal CON 0 'VAR Word

CLKPin PIN 0 ' Clock Pin
DATAPin PIN 1 ' Data Pin
CSPin PIN 2 ' Chip Select Pin

XOUTL CON $00 ' 10 bits output value X LSB XOUT[7] XOUT[6] XOUT[5] XOUT[4] XOUT[3] XOUT[2] XOUT[1] XOUT[0]
XOUTH CON $01 ' 10 bits output value X MSB -- -- -- -- -- -- XOUT[9] XOUT[8]
YOUTL CON $02 ' 10 bits output value Y LSB YOUT[7] YOUT[6] YOUT[5] YOUT[4] YOUT[3] YOUT[2] YOUT[1] YOUT[0]
YOUTH CON $03 ' 10 bits output value Y MSB -- -- -- -- -- -- YOUT[9] YOUT[8]
ZOUTL CON $04 ' 10 bits output value Z LSB ZOUT[7] ZOUT[6] ZOUT[5] ZOUT[4] ZOUT[3] ZOUT[2] ZOUT[1] ZOUT[0]
ZOUTH CON $05 ' 10 bits output value Z MSB -- -- -- -- -- -- ZOUT[9] ZOUT[8]
XOUT8 CON $06 ' 8 bits output value X XOUT[7] XOUT[6] XOUT[5] XOUT[4] XOUT[3] XOUT[2] XOUT[1] XOUT[0]
YOUT8 CON $07 ' 8 bits output value Y YOUT[7] YOUT[6] YOUT[5] YOUT[4] YOUT[3] YOUT[2] YOUT[1] YOUT[0]
ZOUT8 CON $08 ' 8 bits output value Z ZOUT[7] ZOUT[6] ZOUT[5] ZOUT[4] ZOUT[3] ZOUT[2] ZOUT[1] ZOUT[0]
STATUS CON $09 ' Status registers -- -- -- -- -- PERR DOVR DRDY
DETSRC CON $0A ' Detection source registers LDX LDY LDZ PDX PDY PDZ INT1 INT2
TOUT CON $0B ' "Temperature output value" (Optional) TMP[7] TMP[6] TMP[5] TMP[4] TMP[3] TMP[2] TMP[1] TMP[0]
' CON $0C ' (Reserved) -- -- -- -- -- -- -- --
I2CAD CON $0D ' I2C device address I 2CDIS DAD[6] DAD[5] DAD[4] DAD[3] DAD[2] DAD[1] DAD[0]
USRINF CON $0E ' User information (Optional) UI[7] UI[6] UI[5] UI[4] UI[3] UI[2] UI[1] UI[0]
WHOAMI CON $0F ' "Who am I" value (Optional) ID[7] ID[6] ID[5] ID[4] ID[3] ID[2] ID[1] ID[0]
XOFFL CON $10 ' Offset drift X value (LSB) XOFF[7] XOFF[6] XOFF[5] XOFF[4] XOFF[3] XOFF[2] XOFF[1] XOFF[0]
XOFFH CON $11 ' Offset drift X value (MSB) -- -- -- -- -- XOFF[10] XOFF[9] XOFF[8]
YOFFL CON $12 ' Offset drift Y value (LSB) YOFF[7] YOFF[6] YOFF[5] YOFF[4] YOFF[3] YOFF[2] YOFF[1] YOFF[0]
YOFFH CON $13 ' Offset drift Y value (MSB) -- -- -- -- -- YOFF[10] YOFF[9] YOFF[8]
ZOFFL CON $14 ' Offset drift Z value (LSB) ZOFF[7] ZOFF[6] ZOFF[5] ZOFF[4] ZOFF[3] ZOFF[2] ZOFF[1] ZOFF[0]
ZOFFH CON $15 ' Offset drift Z value (MSB) -- -- -- -- -- ZOFF[10] ZOFF[9] ZOFF[8]
MCTL CON $16 ' Mode control LPEN DRPD SPI3W STON GLVL[1] GLVL[0] MOD[1] MOD[0]
INTRST CON $17 ' Interrupt latch reset -- -- -- -- -- -- CLRINT2 CLRINT1
CTL1 CON $18 ' Control 1 -- THOPT ZDA YDA XDA INTRG[1] INTRG[0] INTPIN
CTL2 CON $19 ' Control 2 -- -- -- -- -- DRVO PDPL LDPL
LDTH CON $1A ' Level detection threshold limit value LDTH[7] LDTH[6] LDTH[5] LDTH[4] LDTH[3] LDTH[2] LDTH[1] LDTH[0]
PDTH CON $1B ' Pulse detection threshold limit value PDTH[7] PDTH[6] PDTH[5] PDTH[4] PDTH[3] PDTH[2] PDTH[1] PDTH[0]
PW CON $1C ' Pulse duration value PD[7] PD[6] PD[5] PD[4] PD[3] PD[2] PD[1] PD[0]
LT CON $1D ' Latency time value LT[7] LT[6] LT[5] LT[4] LT[3] LT[2] LT[1] LT[0]
TW CON $1E ' Time window for 2nd pulse value TW[7] TW[6] TW[5] TW[4] TW[3] TW[2] TW[1] TW[0]
' CON $1F ' (Reserved) -- -- -- -- -- -- -- --

XAccel VAR Word ' Variables to store incoming RAW data from the accelerometer
YAccel VAR Word
ZAccel VAR Word

Address VAR Word ' Variables for reading and writing data to the acclerometer
SendData VAR Byte
ReceiveData VAR Byte

'
' MCTL - Mode control register
' +
+
' ¦ D7 ¦ D6 ¦ D5 ¦ D4 ¦ D3 ¦ D2 ¦ D1 ¦ D0 ¦
' +----+----+----+----+----+----+----+----¦
' ¦ -- ¦DRPD¦SPI3¦STON¦GLVL¦GLVL¦MODE¦MODE¦
' +
+
'
'
' D7 - don't care 0
'
' D6(DRPD) - DATA ready status 0 - OUTPUT TO INT1 PIN
' 1 - is NOT OUTPUT TO INT1 PIN
'
' D5(SPI3W)- Wire Mode 0 - SPI is 4-wire mode
' 1 - SPI is 3-wire mode
'
' D4(STON) - Self Test 0 - NOT enabled
' 1 - enabled
'
' D3(GLVL[1]) - g-SELECT 00 - 8g ; 16 LSB/g in 8-Bit format
' D2(GLVL[0]) - g-SELECT 10 - 4g ; 32 LSB/g in 8-Bit format
' 01 - 2g ; 64 LSB/g in 8-Bit format
'
' ; Note: When reading g in 10-Bit
' ; format, resolution is fixed
' ; at 64 LSB/g
' 10-Bit g register
' +
+
' ¦ D9 ¦ D8 ¦ D7 ¦ D6 ¦ D5 ¦ D4 ¦ D3 ¦ D2 ¦ D1 ¦ D0 ¦
' +
+
' ¦<
>¦ ; These 8 bits are READ in 8g mode
' ¦<
>¦ ; These 8 bits are READ in 4g mode
' ¦<
>¦ ; These 8 bits are READ in 2g mode
'
' D1(MODE[1]) - Mode SELECT 00 - Standby
' D0(MODE[0]) - Mode SELECT 01 - Measurement
' 10 - Level Detection
' 11 - Pulse Detection

Main:
Address = MCTL: SendData = 100101: GOSUB DataOut 'Set the Mode control register
'DATA ready status is NOT OUTPUT TO INT1 PIN
'3-wire SPI mode
'Self Test NOT enabled
'+/-2g sensitivity mode
'Measurement mode

Address = XOFFL: SendData = XCal& $FF: GOSUB DataOut 'Write X-Axis Calibration Value ; LOWBYTE
Address = XOFFH: SendData = XCal >> 8: GOSUB DataOut ' ; HIGHBYTE

Address = YOFFL: SendData = YCal& $FF: GOSUB DataOut 'Write Y-Axis Calibration Value ; LOWBYTE
Address = YOFFH: SendData = YCal >> 8: GOSUB DataOut ' ; HIGHBYTE

Address = ZOFFL: SendData = ZCal& $FF: GOSUB DataOut 'Write Z-Axis Calibration Value ; LOWBYTE
Address = ZOFFH: SendData = ZCal >> 8: GOSUB DataOut ' ; HIGHBYTE

DEBUG CLS 'Clear Display
GOSUB TextField 'Draw TEXT field (stationary TEXT that does not get updated)

ReadDataLoop:
Address = XOUT8:GOSUB DataIn 'Read in X-Axis Acceleration Value
XAccel = ReceiveData|($FF00*ReceiveData.BIT7) 'Sign extend the two's complement byte so
'negative numbers can be properly displayed

Address = YOUT8:GOSUB DataIn 'Read in Y-Axis Acceleration Value
YAccel = ReceiveData|($FF00*ReceiveData.BIT7) 'Sign extend the two's complement byte so
'negative numbers can be properly displayed

Address = ZOUT8:GOSUB DataIn 'Read in Z-Axis Acceleration Value
ZAccel = ReceiveData|($FF00*ReceiveData.BIT7) 'Sign extend the two's complement byte so
'negative numbers can be properly displayed

DEBUG CRSRXY,50,3, SDEC XAccel, " ", 'Display the RAW X, Y, and Z Accelerometer values
CRSRXY,50,4, SDEC YAccel, " ",
CRSRXY,50,5, SDEC ZAccel, " "

GOTO ReadDataLoop

DataOut:
LOW CSPin 'Pull chip select pin low to start transmission
SHIFTOUT DATAPin, CLKPin, MSBFIRST, [(Address|00000)<<1] 'Select register Address
SHIFTOUT DATAPin, CLKPin, MSBFIRST, [SendData] 'Write value to Address
HIGH CSPin 'End transmission
RETURN

DataIn:
LOW CSPin 'Pull chip select pin low to start transmission
SHIFTOUT DATAPin, CLKPin, MSBFIRST, [Address<<1] 'Select register Address
SHIFTIN DATAPin, CLKPin, MSBPRE, [ReceiveData] 'Read value from Address
HIGH CSPin 'End transmission
RETURN

TextField:
DEBUG CRSRXY,40,0,"MMA7455 3-Axis Accelerometer BS2 DEMO #1", 'Display all stationary TEXT that does not get updated
CRSRXY,48,2,"8-Bit 2g Mode ; 64 LSB/g",
CRSRXY,48,3, "X=",
CRSRXY,48,4, "Y=",
CRSRXY,48,5, "Z="
RETURN

'
[ Title ]
'
' File...... RXM-SG GPS Demo V1.0.bsp
' Purpose... Demonstrate Decoding Data From RXM-SG GPS Module
' Author.... Parallax, Inc.
' E-mail.... support@parallax.com
' Started... 08-16-2010
' Updated...
'
' {$STAMP BS2p}
' {$PBASIC 2.5}


'
[ Program Description ]

' 1) Connect the TX output of the Parallax RXM-SG GPS Module to P0 of the
' BS2p module.
' 2) Provide common ground and a regulated 5V for the GPS Module. If
' using the Board of Education you can get 5V from VDD.
' 3) Download this program to the BS2p module and watch the debug screen.

' NOTE: Be sure the battery and antenna are installed before powering up
' the GPS Module.

' This code is NOT compatible with the PMB-648 & PMB-688 by default.
' Unlike the PMB-648 & PMB-688, the RXM-SG GPS Module runs at 9600 bps by
' default.

' Reads NMEA data string from GPS receiver and parses data. GPS string is
' buffered into scratchpad RAM with SPSTR modifier. Once in SPRAM, data is
' parsed out based on its position.
'
' $GPRMC,POS_UTC,POS_STAT,LAT,LAT_D,LON,LON_D,SPD,HDG,DATE,MAG_VAR,MAG_REF,*CC
'
' POS_UTC - UTC of position. Hours, minutes and seconds. (hhmmss)
' POS_STAT - Position status. (A = Data valid, V = Data invalid)
' LAT - Latitude (ddmm.ffff)
' LAT_D - Latitude direction. (N = North, S = South)
' LON - Longitude (dddmm.ffff)
' LON_D - Longitude direction (E = East, W = West)
' SPD - Speed over ground. (knots) (0.0 - 999.9)
' HDG - Heading/track made good (degrees True) (x.x)
' DATE - Date (ddmmyy)
' MAG_VAR - Magnetic variation (degrees) (x.x)
' MAG_REF - Magnetic variation (E = East, W = West)
' *CC - Checksum

' This program also reads the $GPGGA string and parses it for altitude.


'
[ Revision History ]



'
[ I/O Definitions ]

GPSpin PIN 0 ' GPS serial input


'
[ Constants ]

T9600 CON 240 ' Baud rate for GPS (typical)

MoveTo CON 2 ' DEBUG positioning command
ClrRt CON 11 ' Clear line right of cursor

EST CON -5 ' Eastern Standard Time
CST CON -6 ' Central Standard Time
MST CON -7 ' Mountain Standard Time
PST CON -8 ' Pacific Standard Time

EDT CON -4 ' Eastern Daylight Time
CDT CON -5 ' Central Daylight Time
MDT CON -6 ' Mountain Daylight Time
PDT CON -7 ' Pacific Daylight Time

UTCfix CON PDT ' For Rocklin, CA
Comma CON "," ' Comma
DegSym CON 176 ' Degrees symbol for report
MinSym CON 39 ' Minutes symbol
SecSym CON 34 ' Seconds symbol


'
[ Variables ]

index VAR Byte ' Index into GPS data in SPRAM
flags VAR Byte ' Holds bit values
valid VAR Flags.BIT3 ' Is data valid?
numSats VAR Byte ' Number of satellites

tmHrs VAR Byte ' Time fields
tmMins VAR Byte
tmSecs VAR Byte

latDeg VAR Byte ' Latitude
latMin VAR Byte
latSec VAR Word
latNS VAR flags.BIT0 ' 0 = N

longDeg VAR Byte ' Longitude
longMin VAR Byte
longSec VAR Word
longEW VAR flags.BIT1 ' 0 = E

speed VAR Word ' In tenths of mph***************
altitude VAR Word ' In feet************************

day VAR Byte ' Day of month, 1 - 31
month VAR flags.NIB1 ' Month, 1 - 12
year VAR Byte ' Year, 00 - 99

char VAR Byte ' Byte pulled from SPRAM
workVal VAR Word ' For numeric conversions
eeAddr VAR workVal ' Pointer to EE data

field VAR Nib ' Field #
fldWidth VAR field ' Width of field


'
[ EEPROM Data ]

NotValid DATA "No", 0
IsValid DATA "Yes", 0
DaysInMon DATA 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31
MonNames DATA "JAN",0,"FEB",0,"MAR",0,"APR",0,"MAY",0,"JUN",0
DATA "JUL",0,"AUG",0,"SEP",0,"OCT",0,"NOV",0,"DEC",0


'
[ Initialization ]

Initialize:
PAUSE 250 ' Let DEBUG open
DEBUG CLS ' Clear the screen
DEBUG "RXM-SG GPS Demo V1.0", CR
DEBUG "======================="

Draw_Ruler:
FOR index = 0 TO 65
IF (index = 0) THEN Print_Ones
IF (index // 10) > 0 THEN Print_Ones
DEBUG MoveTo, (7 + index), 3, DEC1 (index / 10)
Print_Ones:
DEBUG MoveTo, (7 + index), 4, DEC1 (index // 10)
Print_Ticks:
IF (index // 10) > 0 THEN Next_Digit
DEBUG MoveTo, (7 + index), 5, "|"
Next_Digit:
NEXT

Draw_Data_Labels:

DEBUG MoveTo, 0, 9, "Signal Valid: "
DEBUG MoveTo, 0, 11, " Local Time: "
DEBUG MoveTo, 0, 12, " Local Date: "
DEBUG MoveTo, 0, 14, " Latitude: "
DEBUG MoveTo, 0, 15, " Longitude: "
DEBUG MoveTo, 0, 16, " Altitude: "
DEBUG MoveTo, 0, 17, " Speed: "


'
[ Program Code ]

Main:
' Wait for $GPRMC string and store data in SPRAM
SERIN GPSpin, T9600, 3000, No_GPS_Data, [WAIT("GPRMC,"), SPSTR 65]
GOSUB Parse_GPS_Data ' Extract data from SPRAM

Show_GPMRC_String:
DEBUG MoveTo, 0, 6, "$GPRMC," ' Print header
index = 0 ' Start at position UTC

Print_GPRMC_Char: ' Print the $GPRMC data string
GET index, char ' Get char from SPRAM
DEBUG char ' Display it
IF char = "*" THEN Print_Checksum ' Look for checksum indicator
index = index + 1 ' Point to next char
GOTO Print_GPRMC_Char

Print_Checksum:
GET (index + 1), char ' Get first checksum char
DEBUG char ' Display
GET (index + 2), char ' Get second checksum char
DEBUG char, ClrRt ' Display, clear to end of line

Show_Report:
DEBUG MoveTo, 14, 9 ' Was the signal valid?
LOOKUP valid, [NotValid, IsValid], eeAddr' Get answer from EE
GOSUB Print_Z_String ' Print it

DEBUG " (", DEC numSats, " Satellites)"

DEBUG ClrRt ' Clear end of line
IF (valid = 0) THEN Signal_Not_Valid

Get_Altitude:
SERIN GPSpin, T9600, 2000, Signal_Is_Valid, [WAIT("GPGGA,"), SPSTR 75]

index = 45 ' Altitude
GOSUB Mixed_To_Tenths ' Convert "xxx.x" To number
altitude = workVal

index = 38 : fldWidth = 2 ' Number of sats
GOSUB String_To_Value
numSats = workVal

Show_GPGGA_String:
DEBUG MoveTo, 0, 7, "$GPGGA," ' Print header
index = 0 ' Start at position UTC

Print_GPGGA_Char: ' Print the $GPRMC data string
GET index, char ' Get char from SPRAM
DEBUG char ' Display it
IF char = "*" THEN Print_Chexum ' Look for checksum indicator
index = index + 1 ' Point to next char
GOTO Print_GPGGA_Char

Print_Chexum:
GET (index + 1), char ' Get first checksum char
DEBUG char ' Display
GET (index + 2), char ' Get second checksum char
DEBUG char, ClrRt ' Display, clear to end of line

Signal_Is_Valid:
DEBUG MoveTo, 14, 11, DEC2 tmHrs, ":", DEC2 tmMins, ":", DEC2 tmSecs

DEBUG MoveTo, 14, 12, DEC2 day, " "
eeAddr = (month - 1) * 4 + MonNames ' get address of month name
GOSUB Print_Z_String ' print it
DEBUG " 20", DEC2 year

DEBUG MoveTo, 14, 14, " ", DEC2 latDeg, DegSym, " ", DEC2 latMin, MinSym, " "
DEBUG DEC2 (latSec / 10), ".", DEC1 (latSec // 10), SecSym, " "
DEBUG "N" + (latNS * 5)

DEBUG MoveTo, 14, 15, DEC3 longDeg, DegSym, " ", DEC2 longMin, MinSym, " "
DEBUG DEC2 (longSec / 10), ".", DEC1 (longSec // 10), SecSym, " "
DEBUG "E" + (longEW * 18)

DEBUG MoveTo, 14, 16, DEC (altitude / 10), ".", DEC1 (altitude //10), " Meters", ClrRt
DEBUG MoveTo, 14, 17, DEC (speed / 10), ".", DEC1 (speed // 10), " MPH "
GOTO Main

Signal_Not_Valid:
DEBUG MoveTo, 14, 11, "?", ClrRt ' Clear all fields
DEBUG MoveTo, 14, 12, "?", ClrRt
DEBUG MoveTo, 14, 14, "?", ClrRt
DEBUG MoveTo, 14, 15, "?", ClrRt
DEBUG MoveTo, 14, 16, "?", ClrRt
DEBUG MoveTo, 14, 17, "?", ClrRt
GOTO Main


'
[ Subroutines ]

No_GPS_Data:
DEBUG CLS, "Error: No GPS data detected"
PAUSE 2500
GOTO Initialize ' Try again


Parse_GPS_Data:
index = 0 : fldWidth = 2 ' UTC hours
GOSUB String_To_Value
tmHrs = workVal

index = 2 : fldWidth = 2 ' UTC minutes
GOSUB String_To_Value
tmMins = workVal

index = 4 : fldWidth = 2 ' UTC seconds
GOSUB String_To_Value
tmSecs = workVal

index = 13 : fldWidth = 2 ' Latitude degrees
GOSUB String_To_Value
latDeg = workVal

index = 15 : fldWidth = 2 ' Latitude minutes
GOSUB String_To_Value
latMin = workVal

index = 18 : fldWidth = 4 ' Latitude fractional minutes
GOSUB String_To_Value
latSec = workVal ** $0F5C ' x 0.06 --> tenths of seconds

index = 25 : fldWidth = 3 ' Longitude degrees
GOSUB String_To_Value
longDeg = workVal

index = 28 : fldWidth = 2 ' Longitude minutes
GOSUB String_To_Value
longMin = workVal

index = 31 : fldWidth = 4 ' Longitude fractional minutes
GOSUB String_To_Value
longSec = workVal ** $0F5C ' x 0.06 --> tenths of seconds

' Get non-numeric data

Get_Valid:
GET 11, char
valid = 1 ' Assume valid
IF (char = "A") THEN Get_Lat_Dir ' It is, so skip
valid = 0 ' Set to 0 if not valid

Get_Lat_Dir:
latNS = 0 ' Assume North
GET 19, char ' Check it
IF (char = "N") THEN Get_Long_Dir ' Confirm
latNS = 1 ' Set to 1 if South

Get_Long_Dir:
longEW = 0 ' Assume East
GET 33, char ' Check it
IF (char = "E") THEN Get_Speed ' Confirm
longEW = 1 ' Set to 1 if West

' Get variable length data

Get_Speed:
index = 38
GOSUB Mixed_To_Tenths ' Convert "xxx.x" To number
' speed = workVal ' Speed in knots (tenths)
speed = workVal + (workVal ** $2699) ' x 1.1507771555 for mph

' Get date
' -- past variable data, so we need to use field search

Get_Date:
field = 8 ' Set field to find
GOSUB Move_To_Field ' Go get position
PUT 125, index ' Save date position

fldWidth = 2
GOSUB String_To_Value
day = workVal ' UTC day, 1 - 31

GET 125, index ' Get stored position
index = index + 2 : fldWidth = 2
GOSUB String_To_Value
month = workVal ' UTC month, 1 - 12

GET 125, index ' Get stored position
index = index + 4 : fldWidth = 2
GOSUB String_To_Value
year = workVal ' UTC year, 0 - 99

' Adjust date for local position

Correct_Local_Time_Date:
workVal = tmHrs + UTCfix ' Add UTC offset
IF (workVal < 24) THEN Adjust_Time ' Midnight crossed?
workVal = UTCfix ' Yes, so adjust date
BRANCH workVal.BIT15, [Location_Leads, Location_Lags]

Location_Leads: ' East of Greenwich
day = day + 1 ' No, move to next day
eeAddr = DaysInMon * (month - 1) ' Get days in month
READ eeAddr, char
IF (day <= char) THEN Adjust_Time ' In same month?
month = month + 1 ' No, move to next month
day = 1 ' First day
IF (month < 13) THEN Adjust_Time ' In same year?
month = 1 ' No, set to January
year = year + 1 // 100 ' Add one to year
GOTO Adjust_Time

Location_Lags: ' West of Greenwich
day = day - 1 ' Adjust day
IF (day > 0) THEN Adjust_Time ' Same month?
month = month - 1
IF (month > 0) THEN Adjust_Time ' Same year?
month = 1 ' No, set to January
eeAddr = DaysInMon * (month - 1)
READ eeAddr, day ' Get new day
year = year + 99 // 100 ' Set to previous year

Adjust_Time:
tmHrs = tmHrs + (24 + UTCfix) // 24 ' Localize hours
RETURN

' *********************************************
' Convert string data (nnnn) to numeric value
' -- index - location of first digit in data
' -- fldWidth - width of data field (1 to 5)
' -- workVal - returns numeric value of field
' *********************************************

String_To_Value:
workVal = 0
IF (fldWidth = 0) OR (fldWidth > 5) THEN String_To_Value_Done

Get_Field_Digit:
GET index, char ' Get digit from field
workVal = workVal + (char - "0") ' Convert, add into value
fldWidth = fldWidth - 1 ' Decrement field width
IF (fldWidth = 0) THEN String_To_Value_Done
workVal = workVal * 10 ' Shift result digits left
index = index + 1 ' Point to next digit
GOTO Get_Field_Digit

String_To_Value_Done:
RETURN

' *****************************************************
' Convert string data (nnn.n) to numeric value (tenths)
' -- index - location of first digit in data
' -- workVal - returns numeric value of field
' *****************************************************

Mixed_To_Tenths:
workVal = 0

Get_Mixed_Digit:
GET index, char ' Read digit from speed field
IF (char = ".") THEN Get_Mixed_Last ' Skip decimal point
workVal = (workVal + (char - "0")) * 10' Add digit, move data left
index = index + 1 ' Point to next digit
GOTO Get_Mixed_Digit

Get_Mixed_Last:
GET (index + 1), char
workVal = workVal + (char - "0") ' Speed in knots
RETURN

' ************************************************************
' Find field location after variable-length data (i.e., speed)
' -- field - field number
' -- index - returns position of first digit in field
' ************************************************************

Move_To_Field:
index = 0
IF (field = 0) THEN Move_To_Field_Done' If zero, we're there

Get_Char:
GET index, char ' Get char from SPRAM
IF (char = Comma) THEN Found_Comma ' Is it a comma?
index = index + 1 ' No, move to next char
GOTO Get_Char

Found_Comma:
field = field - 1 ' Was comma, dec field coutner
index = index + 1 ' Point to next char
IF (field = 0) THEN Move_To_Field_Done' If field = 0, we're there
GOTO Get_Char

Move_To_Field_Done:
RETURN

' *********************************************
' Print Zero-terminated string stored in EEPROM
' -- eeAddr - starting character of string
' *********************************************

Print_Z_String:
READ eeAddr, char ' Get char from EE
IF (char = 0) THEN Print_Z_String_Done' If zero, we're done
DEBUG char ' Print the char
eeAddr = eeAddr + 1 ' Point to the next one
GOTO Print_Z_String

Print_Z_String_Done:
RETURN








































GPS tracking code of RXM-SG-GPS Module

'
[ Title ]
'
' File...... RXM-SG GPS Demo V1.0.bsp
' Purpose... Demonstrate Decoding Data From RXM-SG GPS Module
' Author.... Parallax, Inc.
' E-mail.... support@parallax.com
' Started... 08-16-2010
' Updated...
'
' {$STAMP BS2p}
' {$PBASIC 2.5}


'
[ Program Description ]

' 1) Connect the TX output of the Parallax RXM-SG GPS Module to P0 of the
' BS2p module.
' 2) Provide common ground and a regulated 5V for the GPS Module. If
' using the Board of Education you can get 5V from VDD.
' 3) Download this program to the BS2p module and watch the debug screen.

' NOTE: Be sure the battery and antenna are installed before powering up
' the GPS Module.

' This code is NOT compatible with the PMB-648 & PMB-688 by default.
' Unlike the PMB-648 & PMB-688, the RXM-SG GPS Module runs at 9600 bps by
' default.

' Reads NMEA data string from GPS receiver and parses data. GPS string is
' buffered into scratchpad RAM with SPSTR modifier. Once in SPRAM, data is
' parsed out based on its position.
'
' $GPRMC,POS_UTC,POS_STAT,LAT,LAT_D,LON,LON_D,SPD,HDG,DATE,MAG_VAR,MAG_REF,*CC
'
' POS_UTC - UTC of position. Hours, minutes and seconds. (hhmmss)
' POS_STAT - Position status. (A = Data valid, V = Data invalid)
' LAT - Latitude (ddmm.ffff)
' LAT_D - Latitude direction. (N = North, S = South)
' LON - Longitude (dddmm.ffff)
' LON_D - Longitude direction (E = East, W = West)
' SPD - Speed over ground. (knots) (0.0 - 999.9)
' HDG - Heading/track made good (degrees True) (x.x)
' DATE - Date (ddmmyy)
' MAG_VAR - Magnetic variation (degrees) (x.x)
' MAG_REF - Magnetic variation (E = East, W = West)
' *CC - Checksum

' This program also reads the $GPGGA string and parses it for altitude.


'
[ Revision History ]



'
[ I/O Definitions ]

GPSpin PIN 0 ' GPS serial input


'
[ Constants ]

T9600 CON 240 ' Baud rate for GPS (typical)

MoveTo CON 2 ' DEBUG positioning command
ClrRt CON 11 ' Clear line right of cursor

EST CON -5 ' Eastern Standard Time
CST CON -6 ' Central Standard Time
MST CON -7 ' Mountain Standard Time
PST CON -8 ' Pacific Standard Time

EDT CON -4 ' Eastern Daylight Time
CDT CON -5 ' Central Daylight Time
MDT CON -6 ' Mountain Daylight Time
PDT CON -7 ' Pacific Daylight Time

UTCfix CON PDT ' For Rocklin, CA
Comma CON "," ' Comma
DegSym CON 176 ' Degrees symbol for report
MinSym CON 39 ' Minutes symbol
SecSym CON 34 ' Seconds symbol


'
[ Variables ]

index VAR Byte ' Index into GPS data in SPRAM
flags VAR Byte ' Holds bit values
valid VAR Flags.BIT3 ' Is data valid?
numSats VAR Byte ' Number of satellites

tmHrs VAR Byte ' Time fields
tmMins VAR Byte
tmSecs VAR Byte

latDeg VAR Byte ' Latitude
latMin VAR Byte
latSec VAR Word
latNS VAR flags.BIT0 ' 0 = N

longDeg VAR Byte ' Longitude
longMin VAR Byte
longSec VAR Word
longEW VAR flags.BIT1 ' 0 = E

speed VAR Word ' In tenths of mph***************
altitude VAR Word ' In feet************************

day VAR Byte ' Day of month, 1 - 31
month VAR flags.NIB1 ' Month, 1 - 12
year VAR Byte ' Year, 00 - 99

char VAR Byte ' Byte pulled from SPRAM
workVal VAR Word ' For numeric conversions
eeAddr VAR workVal ' Pointer to EE data

field VAR Nib ' Field #
fldWidth VAR field ' Width of field


'
[ EEPROM Data ]

NotValid DATA "No", 0
IsValid DATA "Yes", 0
DaysInMon DATA 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31
MonNames DATA "JAN",0,"FEB",0,"MAR",0,"APR",0,"MAY",0,"JUN",0
DATA "JUL",0,"AUG",0,"SEP",0,"OCT",0,"NOV",0,"DEC",0


'
[ Initialization ]

Initialize:
PAUSE 250 ' Let DEBUG open
DEBUG CLS ' Clear the screen
DEBUG "RXM-SG GPS Demo V1.0", CR
DEBUG "======================="

Draw_Ruler:
FOR index = 0 TO 65
IF (index = 0) THEN Print_Ones
IF (index // 10) > 0 THEN Print_Ones
DEBUG MoveTo, (7 + index), 3, DEC1 (index / 10)
Print_Ones:
DEBUG MoveTo, (7 + index), 4, DEC1 (index // 10)
Print_Ticks:
IF (index // 10) > 0 THEN Next_Digit
DEBUG MoveTo, (7 + index), 5, "|"
Next_Digit:
NEXT

Draw_Data_Labels:
DEBUG MoveTo, 0, 9, "Signal Valid: "
DEBUG MoveTo, 0, 11, " Local Time: "
DEBUG MoveTo, 0, 12, " Local Date: "
DEBUG MoveTo, 0, 14, " Latitude: "
DEBUG MoveTo, 0, 15, " Longitude: "
DEBUG MoveTo, 0, 16, " Altitude: "
DEBUG MoveTo, 0, 17, " Speed: "


'
[ Program Code ]

Main:
' Wait for $GPRMC string and store data in SPRAM
SERIN GPSpin, T9600, 3000, No_GPS_Data, [WAIT("GPRMC,"), SPSTR 65]
GOSUB Parse_GPS_Data ' Extract data from SPRAM

Show_GPMRC_String:
DEBUG MoveTo, 0, 6, "$GPRMC," ' Print header
index = 0 ' Start at position UTC

Print_GPRMC_Char: ' Print the $GPRMC data string
GET index, char ' Get char from SPRAM
DEBUG char ' Display it
IF char = "*" THEN Print_Checksum ' Look for checksum indicator
index = index + 1 ' Point to next char
GOTO Print_GPRMC_Char

Print_Checksum:
GET (index + 1), char ' Get first checksum char
DEBUG char ' Display
GET (index + 2), char ' Get second checksum char
DEBUG char, ClrRt ' Display, clear to end of line

Show_Report:
DEBUG MoveTo, 14, 9 ' Was the signal valid?
LOOKUP valid, [NotValid, IsValid], eeAddr' Get answer from EE
GOSUB Print_Z_String ' Print it

DEBUG " (", DEC numSats, " Satellites)"

DEBUG ClrRt ' Clear end of line
IF (valid = 0) THEN Signal_Not_Valid

Get_Altitude:
SERIN GPSpin, T9600, 2000, Signal_Is_Valid, [WAIT("GPGGA,"), SPSTR 75]

index = 45 ' Altitude
GOSUB Mixed_To_Tenths ' Convert "xxx.x" To number
altitude = workVal

index = 38 : fldWidth = 2 ' Number of sats
GOSUB String_To_Value
numSats = workVal

Show_GPGGA_String:
DEBUG MoveTo, 0, 7, "$GPGGA," ' Print header
index = 0 ' Start at position UTC

Print_GPGGA_Char: ' Print the $GPRMC data string
GET index, char ' Get char from SPRAM
DEBUG char ' Display it
IF char = "*" THEN Print_Chexum ' Look for checksum indicator
index = index + 1 ' Point to next char
GOTO Print_GPGGA_Char

Print_Chexum:
GET (index + 1), char ' Get first checksum char
DEBUG char ' Display
GET (index + 2), char ' Get second checksum char
DEBUG char, ClrRt ' Display, clear to end of line

Signal_Is_Valid:
DEBUG MoveTo, 14, 11, DEC2 tmHrs, ":", DEC2 tmMins, ":", DEC2 tmSecs

DEBUG MoveTo, 14, 12, DEC2 day, " "
eeAddr = (month - 1) * 4 + MonNames ' get address of month name
GOSUB Print_Z_String ' print it
DEBUG " 20", DEC2 year

DEBUG MoveTo, 14, 14, " ", DEC2 latDeg, DegSym, " ", DEC2 latMin, MinSym, " "
DEBUG DEC2 (latSec / 10), ".", DEC1 (latSec // 10), SecSym, " "
DEBUG "N" + (latNS * 5)

DEBUG MoveTo, 14, 15, DEC3 longDeg, DegSym, " ", DEC2 longMin, MinSym, " "
DEBUG DEC2 (longSec / 10), ".", DEC1 (longSec // 10), SecSym, " "
DEBUG "E" + (longEW * 18)

DEBUG MoveTo, 14, 16, DEC (altitude / 10), ".", DEC1 (altitude //10), " Meters", ClrRt
DEBUG MoveTo, 14, 17, DEC (speed / 10), ".", DEC1 (speed // 10), " MPH "
GOTO Main

Signal_Not_Valid:
DEBUG MoveTo, 14, 11, "?", ClrRt ' Clear all fields
DEBUG MoveTo, 14, 12, "?", ClrRt
DEBUG MoveTo, 14, 14, "?", ClrRt
DEBUG MoveTo, 14, 15, "?", ClrRt
DEBUG MoveTo, 14, 16, "?", ClrRt
DEBUG MoveTo, 14, 17, "?", ClrRt
GOTO Main


'
[ Subroutines ]

No_GPS_Data:
DEBUG CLS, "Error: No GPS data detected"
PAUSE 2500
GOTO Initialize ' Try again


Parse_GPS_Data:
index = 0 : fldWidth = 2 ' UTC hours
GOSUB String_To_Value
tmHrs = workVal

index = 2 : fldWidth = 2 ' UTC minutes
GOSUB String_To_Value
tmMins = workVal

index = 4 : fldWidth = 2 ' UTC seconds
GOSUB String_To_Value
tmSecs = workVal

index = 13 : fldWidth = 2 ' Latitude degrees
GOSUB String_To_Value
latDeg = workVal

index = 15 : fldWidth = 2 ' Latitude minutes
GOSUB String_To_Value
latMin = workVal

index = 18 : fldWidth = 4 ' Latitude fractional minutes
GOSUB String_To_Value
latSec = workVal ** $0F5C ' x 0.06 --> tenths of seconds

index = 25 : fldWidth = 3 ' Longitude degrees
GOSUB String_To_Value
longDeg = workVal

index = 28 : fldWidth = 2 ' Longitude minutes
GOSUB String_To_Value
longMin = workVal

index = 31 : fldWidth = 4 ' Longitude fractional minutes
GOSUB String_To_Value
longSec = workVal ** $0F5C ' x 0.06 --> tenths of seconds

' Get non-numeric data

Get_Valid:
GET 11, char
valid = 1 ' Assume valid
IF (char = "A") THEN Get_Lat_Dir ' It is, so skip
valid = 0 ' Set to 0 if not valid

Get_Lat_Dir:
latNS = 0 ' Assume North
GET 19, char ' Check it
IF (char = "N") THEN Get_Long_Dir ' Confirm
latNS = 1 ' Set to 1 if South

Get_Long_Dir:
longEW = 0 ' Assume East
GET 33, char ' Check it
IF (char = "E") THEN Get_Speed ' Confirm
longEW = 1 ' Set to 1 if West

' Get variable length data

Get_Speed:
index = 38
GOSUB Mixed_To_Tenths ' Convert "xxx.x" To number
' speed = workVal ' Speed in knots (tenths)
speed = workVal + (workVal ** $2699) ' x 1.1507771555 for mph

' Get date
' -- past variable data, so we need to use field search

Get_Date:
field = 8 ' Set field to find
GOSUB Move_To_Field ' Go get position
PUT 125, index ' Save date position

fldWidth = 2
GOSUB String_To_Value
day = workVal ' UTC day, 1 - 31

GET 125, index ' Get stored position
index = index + 2 : fldWidth = 2
GOSUB String_To_Value
month = workVal ' UTC month, 1 - 12

GET 125, index ' Get stored position
index = index + 4 : fldWidth = 2
GOSUB String_To_Value
year = workVal ' UTC year, 0 - 99

' Adjust date for local position

Correct_Local_Time_Date:
workVal = tmHrs + UTCfix ' Add UTC offset
IF (workVal < 24) THEN Adjust_Time ' Midnight crossed?
workVal = UTCfix ' Yes, so adjust date
BRANCH workVal.BIT15, [Location_Leads, Location_Lags]

Location_Leads: ' East of Greenwich
day = day + 1 ' No, move to next day
eeAddr = DaysInMon * (month - 1) ' Get days in month
READ eeAddr, char
IF (day <= char) THEN Adjust_Time ' In same month?
month = month + 1 ' No, move to next month
day = 1 ' First day
IF (month < 13) THEN Adjust_Time ' In same year?
month = 1 ' No, set to January
year = year + 1 // 100 ' Add one to year
GOTO Adjust_Time

Location_Lags: ' West of Greenwich
day = day - 1 ' Adjust day
IF (day > 0) THEN Adjust_Time ' Same month?
month = month - 1
IF (month > 0) THEN Adjust_Time ' Same year?
month = 1 ' No, set to January
eeAddr = DaysInMon * (month - 1)
READ eeAddr, day ' Get new day
year = year + 99 // 100 ' Set to previous year

Adjust_Time:
tmHrs = tmHrs + (24 + UTCfix) // 24 ' Localize hours
RETURN

' *********************************************
' Convert string data (nnnn) to numeric value
' -- index - location of first digit in data
' -- fldWidth - width of data field (1 to 5)
' -- workVal - returns numeric value of field
' *********************************************

String_To_Value:
workVal = 0
IF (fldWidth = 0) OR (fldWidth > 5) THEN String_To_Value_Done

Get_Field_Digit:
GET index, char ' Get digit from field
workVal = workVal + (char - "0") ' Convert, add into value
fldWidth = fldWidth - 1 ' Decrement field width
IF (fldWidth = 0) THEN String_To_Value_Done
workVal = workVal * 10 ' Shift result digits left
index = index + 1 ' Point to next digit
GOTO Get_Field_Digit

String_To_Value_Done:
RETURN

' *****************************************************
' Convert string data (nnn.n) to numeric value (tenths)
' -- index - location of first digit in data
' -- workVal - returns numeric value of field
' *****************************************************

Mixed_To_Tenths:
workVal = 0

Get_Mixed_Digit:
GET index, char ' Read digit from speed field
IF (char = ".") THEN Get_Mixed_Last ' Skip decimal point
workVal = (workVal + (char - "0")) * 10' Add digit, move data left
index = index + 1 ' Point to next digit
GOTO Get_Mixed_Digit

Get_Mixed_Last:
GET (index + 1), char
workVal = workVal + (char - "0") ' Speed in knots
RETURN

' ************************************************************
' Find field location after variable-length data (i.e., speed)
' -- field - field number
' -- index - returns position of first digit in field
' ************************************************************

Move_To_Field:
index = 0
IF (field = 0) THEN Move_To_Field_Done' If zero, we're there

Get_Char:
GET index, char ' Get char from SPRAM
IF (char = Comma) THEN Found_Comma ' Is it a comma?
index = index + 1 ' No, move to next char
GOTO Get_Char

Found_Comma:
field = field - 1 ' Was comma, dec field coutner
index = index + 1 ' Point to next char
IF (field = 0) THEN Move_To_Field_Done' If field = 0, we're there
GOTO Get_Char

Move_To_Field_Done:
RETURN

' *********************************************
' Print Zero-terminated string stored in EEPROM
' -- eeAddr - starting character of string
' *********************************************

Print_Z_String:
READ eeAddr, char ' Get char from EE
IF (char = 0) THEN Print_Z_String_Done' If zero, we're done
DEBUG char ' Print the char
eeAddr = eeAddr + 1 ' Point to the next one
GOTO Print_Z_String

Print_Z_String_Done:
RETURN


Thank you

Comments

  • Mike GreenMike Green Posts: 23,101
    edited 2012-08-20 09:19
    This forum works best if you ask specific questions. Just posting a bunch of code and a rough description of what you want to accomplish will not get much interest. In addition, posting large pieces of code using cut and paste will turn off most viewers.

    1) When posting large pieces of code, post them as attachments to your messages. If you're going to use cut and paste, use the [ code ] and [ /code ] brackets around the code. This will preserve any formatting.

    2) Ask specific questions. No one here is going to write your programs for you or even try to put together large disparate hunks of code. You will have to learn about the various devices you plan to use, look at the existing sample code, and adapt it yourself. There are plenty of guides to Stamp programming. Browse through the Parallax Downloads page. The Educational Tutorials and Translations button is useful as well as the Stamp Documentation button. The "What's a Microcontroller?" tutorial and the "Basic Stamp Syntax and Reference Manual" are good starting points.

    3) Start with the demonstration programs you've copied. See how they operate. See what the data from the GPS receiver and the accelerometer look like. Think about how you'd use the Memory Stick Datalogger. Start making a plan (design) for what you'd do with the data, how you'd want to process it and log it to one or more files.
Sign In or Register to comment.