Compare commits
6 Commits
7860a189b3
...
dcaa38e5fe
Author | SHA1 | Date | |
---|---|---|---|
dcaa38e5fe | |||
a15346ae7a | |||
b572e353b4 | |||
6e4073ca7a | |||
ff4451cb6f | |||
c3c31e52b4 |
@ -55,9 +55,8 @@ _Do not look below this line_
|
||||
|
||||
## WIP, Puzzles and TODO
|
||||
|
||||
* [done] Pos can't include elevation if it's sometimes unknown
|
||||
* do we even need Track? will it ever be anything more than a collection
|
||||
of Points?
|
||||
* [done] need a real gpx file with namespace decls before we can parse power and stuff
|
||||
* [done] tests seem to pass without <gpx> element?
|
||||
* [done] stop returning bogus data when missing required elements (e.g. time)
|
||||
* can we lose this "if isJust lat && isJust lon && isJust ts" wart?
|
||||
* probably we should store points in a more efficient form than
|
||||
a singly-linked list
|
||||
|
@ -1,4 +1,10 @@
|
||||
module Main where
|
||||
|
||||
import Control.Exception
|
||||
import Track(parseFile)
|
||||
import Data.List as List
|
||||
|
||||
main :: IO ()
|
||||
main = putStrLn "Hello, Haskell!"
|
||||
main = do
|
||||
points <- Track.parseFile "track.gpx"
|
||||
putStrLn ("loaded " ++ (show (List.length points)))
|
||||
|
75
lib/Track.hs
75
lib/Track.hs
@ -10,6 +10,7 @@ module Track
|
||||
heartRate,
|
||||
time,
|
||||
parse,
|
||||
parseFile,
|
||||
Track.length,
|
||||
)
|
||||
where
|
||||
@ -20,14 +21,16 @@ import Data.List as List
|
||||
import Data.List qualified
|
||||
import Data.Map as Map
|
||||
import Data.Maybe
|
||||
import Data.Either
|
||||
import Data.Text qualified
|
||||
import Data.Text.Lazy as T
|
||||
import Data.Time
|
||||
import Data.Time.ISO8601 qualified
|
||||
import Debug.Trace (trace, traceShow)
|
||||
import Text.Read (readMaybe)
|
||||
import Text.XML
|
||||
import Text.XML.Cursor as Cursor
|
||||
import Text.Read (readMaybe)
|
||||
|
||||
data Pos = Pos Float Float (Maybe Float) deriving (Show, Eq)
|
||||
|
||||
type Power = Maybe Int
|
||||
@ -60,40 +63,37 @@ instance Exception BadFile
|
||||
|
||||
elToPoint :: Cursor -> Either SomeException Point
|
||||
elToPoint c =
|
||||
case node c of
|
||||
NodeElement (Element _ attrs _) ->
|
||||
let lat = (listToMaybe $ attribute "lat" c ) >>= asFloat
|
||||
lon = (listToMaybe $ attribute "lon" c ) >>= asFloat
|
||||
ele = listToMaybe $ child c >>= element (gpxNS "ele") >>= child >>= content
|
||||
ts =
|
||||
listToMaybe (child c >>= element (gpxNS "time") >>= child >>= content)
|
||||
>>= (Data.Time.ISO8601.parseISO8601 . Data.Text.unpack)
|
||||
gpxtpx =
|
||||
child c
|
||||
>>= element (gpxNS "extensions")
|
||||
>>= child
|
||||
>>= element (tpxNS "TrackPointExtension")
|
||||
>>= child
|
||||
extn n =
|
||||
gpxtpx >>= element n >>= child >>= content
|
||||
let lat = listToMaybe (attribute "lat" c) >>= asFloat
|
||||
lon = listToMaybe (attribute "lon" c) >>= asFloat
|
||||
ts =
|
||||
listToMaybe (child c >>= element (gpxNS "time") >>= child >>= content)
|
||||
>>= (Data.Time.ISO8601.parseISO8601 . Data.Text.unpack)
|
||||
ele = listToMaybe (child c >>= element (gpxNS "ele") >>= child >>= content) >>= asFloat
|
||||
gpxtpx =
|
||||
child c
|
||||
>>= element (gpxNS "extensions")
|
||||
>>= child
|
||||
>>= element (tpxNS "TrackPointExtension")
|
||||
>>= child
|
||||
extn n =
|
||||
gpxtpx >>= element n >>= child >>= content
|
||||
|
||||
cadence = extn (tpxNS "cad")
|
||||
hr = extn (tpxNS "hr")
|
||||
power = extn "{http://www.garmin.com/xmlschemas/PowerExtension/v1}PowerInWatts"
|
||||
in if isJust lat && isJust lon && isJust ts
|
||||
then
|
||||
Right $
|
||||
Point
|
||||
(Pos (fromJust lat) (fromJust lon) (ele >>= asFloat))
|
||||
(fromJust ts)
|
||||
(listToMaybe cadence >>= asInt)
|
||||
(listToMaybe power >>= asInt)
|
||||
(listToMaybe hr >>= asInt)
|
||||
else Left (toException (BadFile "missing a required attribute"))
|
||||
where
|
||||
asFloat v = return (Data.Text.unpack v) >>= (readMaybe :: String -> Maybe Float)
|
||||
asInt v = return (Data.Text.unpack v) >>= (readMaybe :: String -> Maybe Int)
|
||||
_ -> Left (toException (BadFile "did not find trkpt"))
|
||||
cadence = extn (tpxNS "cad")
|
||||
hr = extn (tpxNS "hr")
|
||||
power = extn "{http://www.garmin.com/xmlschemas/PowerExtension/v1}PowerInWatts"
|
||||
in if isJust lat && isJust lon && isJust ts
|
||||
then
|
||||
Right $
|
||||
Point
|
||||
(Pos (fromJust lat) (fromJust lon) ele)
|
||||
(fromJust ts)
|
||||
(listToMaybe cadence >>= asInt)
|
||||
(listToMaybe power >>= asInt)
|
||||
(listToMaybe hr >>= asInt)
|
||||
else Left (toException (BadFile "missing a required attribute"))
|
||||
where
|
||||
asFloat v = (readMaybe :: String -> Maybe Float) (Data.Text.unpack v)
|
||||
asInt v = (readMaybe :: String -> Maybe Int) (Data.Text.unpack v)
|
||||
|
||||
getPoints :: Cursor -> Either SomeException [Point]
|
||||
getPoints c =
|
||||
@ -112,3 +112,10 @@ parse str = do
|
||||
|
||||
length :: Track -> Int
|
||||
length = Data.List.length
|
||||
|
||||
-- parseFile :: FilePath -> IO [Point]
|
||||
parseFile name = do
|
||||
gpx <- Text.XML.readFile def name
|
||||
return $ case getPoints (fromDocument gpx) of
|
||||
Left err -> []
|
||||
Right points -> points
|
||||
|
@ -68,7 +68,9 @@ executable souplesse
|
||||
-- other-extensions:
|
||||
|
||||
-- Other library packages from which modules are imported.
|
||||
build-depends: base ^>=4.18.2.1
|
||||
build-depends:
|
||||
base ^>=4.18.2.1
|
||||
, souplesse-lib
|
||||
|
||||
-- Directories containing source files.
|
||||
hs-source-dirs: app
|
||||
|
@ -4,8 +4,8 @@ module Main where
|
||||
|
||||
import Control.Exception
|
||||
import Data.Either
|
||||
import Data.Time qualified
|
||||
import Data.List as List
|
||||
import Data.Time qualified
|
||||
import Debug.Trace (trace, traceShow)
|
||||
import System.Exit qualified as Exit
|
||||
import Test.HUnit
|
||||
@ -33,7 +33,7 @@ wrap x = preamble ++ x ++ "</gpx>"
|
||||
|
||||
wrapPoint x =
|
||||
let trk = "<trk><trkseg>" ++ x ++ "</trkseg></trk>"
|
||||
in wrap trk
|
||||
in wrap trk
|
||||
|
||||
onepoint =
|
||||
wrap
|
||||
@ -84,56 +84,51 @@ testMalformed =
|
||||
in assertBool "catches syntax error" (isLeft trk)
|
||||
|
||||
testMissingAttrs =
|
||||
let els = [
|
||||
[r|
|
||||
let els =
|
||||
[ [r|
|
||||
<trkpt lon="2" latsdf="51">
|
||||
<time>2024-10-23T08:34:59.779+01:00</time>
|
||||
</trkpt>
|
||||
|],
|
||||
[r|
|
||||
[r|
|
||||
<trkpt lon="dsfgsdfg" lat="51">
|
||||
<time>2024-10-23T08:34:59.779+01:00</time>
|
||||
</trkpt>
|
||||
|],
|
||||
[r|
|
||||
[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))
|
||||
|
||||
in TestCase $
|
||||
assertBool
|
||||
"failed to catch missing/malformed attribute"
|
||||
(List.all (isLeft . Track.parse . wrapPoint) els)
|
||||
|
||||
test2 =
|
||||
TestList [
|
||||
TestCase $
|
||||
either
|
||||
(assertFailure . displayException)
|
||||
( \(p : _) ->
|
||||
assertEqual
|
||||
"matches lat/lon"
|
||||
(Track.Pos 51.0 (-0.1) Nothing)
|
||||
(Track.pos p)
|
||||
)
|
||||
(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)
|
||||
]
|
||||
|
||||
TestList
|
||||
[ TestCase $
|
||||
either
|
||||
(assertFailure . displayException)
|
||||
( \(p : _) ->
|
||||
assertEqual
|
||||
"matches lat/lon"
|
||||
(Track.Pos 51.0 (-0.1) Nothing)
|
||||
(Track.pos p)
|
||||
)
|
||||
(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 =
|
||||
TestCase $
|
||||
|
Loading…
Reference in New Issue
Block a user