Compare commits

...

4 Commits

Author SHA1 Message Date
7860a189b3 make elevation part of Position
this reverses the change made in 64470309 when it hadn't occured to
me that the members of a tuple can have different types
2024-10-31 17:09:59 +00:00
5b827ed6ed handle missing lat/lon/time data 2024-10-31 16:18:40 +00:00
10c7d68f31 extract function for gpxtpx extensions 2024-10-31 13:20:16 +00:00
63f54a9355 read heart rate 2024-10-31 13:00:01 +00:00
2 changed files with 81 additions and 42 deletions

View File

@ -3,10 +3,11 @@
module Track module Track
( Track, ( Track,
Pos (..), Pos (..),
BadFile,
pos, pos,
elevation,
cadence, cadence,
power, power,
heartRate,
time, time,
parse, parse,
Track.length, Track.length,
@ -14,6 +15,7 @@ module Track
where where
import Control.Exception import Control.Exception
import Data.Functor ((<&>))
import Data.List as List import Data.List as List
import Data.List qualified import Data.List qualified
import Data.Map as Map import Data.Map as Map
@ -25,9 +27,8 @@ import Data.Time.ISO8601 qualified
import Debug.Trace (trace, traceShow) import Debug.Trace (trace, traceShow)
import Text.XML import Text.XML
import Text.XML.Cursor as Cursor import Text.XML.Cursor as Cursor
import Data.Functor((<&>)) import Text.Read (readMaybe)
data Pos = Pos Float Float (Maybe Float) deriving (Show, Eq)
data Pos = Pos Float Float deriving (Show, Eq)
type Power = Maybe Int type Power = Maybe Int
@ -37,7 +38,6 @@ type HeartRate = Maybe Int
data Point = Point data Point = Point
{ pos :: Pos, { pos :: Pos,
elevation :: Maybe Float,
time :: UTCTime, time :: UTCTime,
cadence :: Cadence, cadence :: Cadence,
power :: Power, power :: Power,
@ -54,8 +54,7 @@ gpxNS localName =
tpxNS localName = tpxNS localName =
Name localName (Just "http://www.garmin.com/xmlschemas/TrackPointExtension/v2") Nothing Name localName (Just "http://www.garmin.com/xmlschemas/TrackPointExtension/v2") Nothing
data BadFile = BadFile String deriving (Show)
data BadFile = BadFile deriving (Show)
instance Exception BadFile instance Exception BadFile
@ -63,45 +62,38 @@ elToPoint :: Cursor -> Either SomeException Point
elToPoint c = elToPoint c =
case node c of case node c of
NodeElement (Element _ attrs _) -> NodeElement (Element _ attrs _) ->
let lat = getAttr "lat" let lat = (listToMaybe $ attribute "lat" c ) >>= asFloat
lon = getAttr "lon" lon = (listToMaybe $ attribute "lon" c ) >>= asFloat
ele = child c >>= element (gpxNS "ele") >>= child >>= content ele = listToMaybe $ child c >>= element (gpxNS "ele") >>= child >>= content
ts = child c >>= element (gpxNS "time") >>= child >>= content ts =
listToMaybe (child c >>= element (gpxNS "time") >>= child >>= content)
>>= (Data.Time.ISO8601.parseISO8601 . Data.Text.unpack)
gpxtpx = gpxtpx =
child c child c
>>= element (gpxNS "extensions") >>= element (gpxNS "extensions")
>>= child >>= child
>>= element (tpxNS "TrackPointExtension") >>= element (tpxNS "TrackPointExtension")
>>= child >>= child
cadence = extn n =
gpxtpx gpxtpx >>= element n >>= child >>= content
>>= element (tpxNS "cad")
>>= child cadence = extn (tpxNS "cad")
>>= content hr = extn (tpxNS "hr")
power = power = extn "{http://www.garmin.com/xmlschemas/PowerExtension/v1}PowerInWatts"
gpxtpx in if isJust lat && isJust lon && isJust ts
>>= element (Name "PowerInWatts" (Just "http://www.garmin.com/xmlschemas/PowerExtension/v1") Nothing) then
>>= child
>>= content
parsedTime =
listToMaybe ts
>>= (Data.Time.ISO8601.parseISO8601 . Data.Text.unpack)
in case parsedTime of
Nothing -> Left (toException BadFile)
Just utime ->
Right $ Right $
Point Point
(Pos lat lon) (Pos (fromJust lat) (fromJust lon) (ele >>= asFloat))
(listToMaybe ele <&> asFloat) (fromJust ts)
utime (listToMaybe cadence >>= asInt)
(listToMaybe cadence <&> asInt) (listToMaybe power >>= asInt)
(listToMaybe power <&> asInt) (listToMaybe hr >>= asInt)
Nothing else Left (toException (BadFile "missing a required attribute"))
where where
asFloat v = (read (Data.Text.unpack v) :: Float) asFloat v = return (Data.Text.unpack v) >>= (readMaybe :: String -> Maybe Float)
asInt v = (read (Data.Text.unpack v) :: Int) asInt v = return (Data.Text.unpack v) >>= (readMaybe :: String -> Maybe Int)
getAttr name = maybe 0 asFloat (Map.lookup name attrs) _ -> Left (toException (BadFile "did not find trkpt"))
_ -> Left (toException BadFile)
getPoints :: Cursor -> Either SomeException [Point] getPoints :: Cursor -> Either SomeException [Point]
getPoints c = getPoints c =

View File

@ -5,6 +5,7 @@ module Main where
import Control.Exception import Control.Exception
import Data.Either import Data.Either
import Data.Time qualified import Data.Time qualified
import Data.List as List
import Debug.Trace (trace, traceShow) import Debug.Trace (trace, traceShow)
import System.Exit qualified as Exit import System.Exit qualified as Exit
import Test.HUnit import Test.HUnit
@ -30,6 +31,10 @@ xsi:schemaLocation="http://www.topografix.com/GPX/1/1 http://www.topografix.com/
wrap x = preamble ++ x ++ "</gpx>" wrap x = preamble ++ x ++ "</gpx>"
wrapPoint x =
let trk = "<trk><trkseg>" ++ x ++ "</trkseg></trk>"
in wrap trk
onepoint = onepoint =
wrap wrap
[r| [r|
@ -51,6 +56,7 @@ onepointWithAttrs =
<extensions><gpxtpx:TrackPointExtension> <extensions><gpxtpx:TrackPointExtension>
<gpxtpx:speed>2.4</gpxtpx:speed> <gpxtpx:speed>2.4</gpxtpx:speed>
<gpxtpx:cad>128</gpxtpx:cad> <gpxtpx:cad>128</gpxtpx:cad>
<gpxtpx:hr>160</gpxtpx:hr>
<pwr:PowerInWatts>55</pwr:PowerInWatts> <pwr:PowerInWatts>55</pwr:PowerInWatts>
<opentracks:accuracy_horizontal>3.216</opentracks:accuracy_horizontal><opentracks:distance>10.675</opentracks:distance> <opentracks:accuracy_horizontal>3.216</opentracks:accuracy_horizontal><opentracks:distance>10.675</opentracks:distance>
<cluetrust:distance>32.025</cluetrust:distance> <cluetrust:distance>32.025</cluetrust:distance>
@ -77,17 +83,57 @@ testMalformed =
let trk = Track.parse (wrap "<dgdsfg>>") let trk = Track.parse (wrap "<dgdsfg>>")
in assertBool "catches syntax error" (isLeft trk) in assertBool "catches syntax error" (isLeft trk)
testMissingAttrs =
let els = [
[r|
<trkpt lon="2" latsdf="51">
<time>2024-10-23T08:34:59.779+01:00</time>
</trkpt>
|],
[r|
<trkpt lon="dsfgsdfg" lat="51">
<time>2024-10-23T08:34:59.779+01:00</time>
</trkpt>
|],
[r|
<trkpt lon="2" lat="51">
<time>2024-10-23G87sdCfdfgsdfhg</time>
</trkpt>
|]
]
in
TestCase $
assertBool
"failed to catch missing/malformed attribute"
(List.all isLeft
(List.map (\ text -> Track.parse (wrapPoint text))
els))
test2 = test2 =
TestList [
TestCase $ TestCase $
either either
(assertFailure . displayException) (assertFailure . displayException)
( \(p : _) -> ( \(p : _) ->
assertEqual assertEqual
"matches lat/lon" "matches lat/lon"
(Track.Pos 51.0 (-0.1)) (Track.Pos 51.0 (-0.1) Nothing)
(Track.pos p) (Track.pos p)
) )
(Track.parse onepoint) (Track.parse onepoint),
TestCase $
either
(assertFailure . displayException)
( \(p : _) ->
assertEqual
"matches lat/lon"
(Track.Pos 51.0 (-0.1) (Just 25.2))
(Track.pos p)
)
(Track.parse onepointWithAttrs)
]
test3 = test3 =
TestCase $ TestCase $
@ -97,7 +143,7 @@ test3 =
assertEqual assertEqual
"handles missing attributes" "handles missing attributes"
(Nothing, Nothing) (Nothing, Nothing)
(Track.elevation p, Track.cadence p) (Track.power p, Track.cadence p)
) )
(Track.parse onepoint) (Track.parse onepoint)
@ -108,8 +154,8 @@ test4 =
( \(p : _) -> ( \(p : _) ->
assertEqual assertEqual
"handles attributes" "handles attributes"
(Just 25.2, Just 128, Just 55, Data.Time.UTCTime (toEnum 60606) 27299.779) (Just 128, Just 55, Data.Time.UTCTime (toEnum 60606) 27299.779, Just 160)
(Track.elevation p, Track.cadence p, Track.power p, Track.time p) (Track.cadence p, Track.power p, Track.time p, Track.heartRate p)
) )
(Track.parse onepointWithAttrs) (Track.parse onepointWithAttrs)
@ -118,6 +164,7 @@ tests =
TestList TestList
[ test1, [ test1,
testMalformed, testMalformed,
testMissingAttrs,
test2, test2,
test3, test3,
test4 test4