souplesse/lib/Track.hs

97 lines
2.0 KiB
Haskell
Raw Normal View History

2024-10-28 23:35:36 +00:00
{-# LANGUAGE OverloadedStrings #-}
2024-10-29 19:21:25 +00:00
module Track (
Track,
Pos(..),
pos,
elevation,
2024-10-29 19:21:25 +00:00
parse,
Track.length
) where
2024-10-27 23:13:39 +00:00
import Data.Time
import qualified Data.List
2024-10-28 23:35:36 +00:00
import Text.XML
import Text.XML.Cursor as Cursor
import qualified Data.Text
import Data.Text.Lazy as T
import Debug.Trace (trace, traceShow)
import Data.List as List
import Data.Map as Map
import Control.Exception
data Pos = Pos Float Float deriving (Show, Eq)
2024-10-28 23:35:36 +00:00
type Power = Maybe Int
type Cadence = Maybe Int
type HeartRate = Maybe Int
data Point = Point {
pos :: Pos,
elevation :: Maybe Float,
2024-10-28 23:35:36 +00:00
time :: UTCTime,
power :: Power,
cadence :: Cadence,
heartRate :: HeartRate
} deriving (Show)
2024-10-27 23:13:39 +00:00
2024-10-29 19:35:17 +00:00
-- TODO do we even need this type?
2024-10-27 23:13:39 +00:00
type Track = [Point]
2024-10-28 23:35:36 +00:00
mkPoint pos =
Point
pos
2024-10-29 21:22:49 +00:00
Nothing
2024-10-28 23:35:36 +00:00
(UTCTime (toEnum 60631) 43200)
(Just 0)
(Just 0)
(Just 0)
elToPoint :: Cursor -> Point
2024-10-29 21:22:49 +00:00
elToPoint c =
case node c of
2024-10-28 23:35:36 +00:00
NodeElement (Element _ attrs _) ->
let
2024-10-29 19:35:17 +00:00
lat = getAttr "lat"
2024-10-28 23:35:36 +00:00
lon = getAttr "lon"
2024-10-29 21:22:49 +00:00
ele = child c >>= element "ele" >>= child >>= content
in Point (Pos lat lon)
(case ele of
e:[] -> Just $ asFloat e
_ -> Nothing)
(UTCTime (toEnum 60631) 43200)
(Just 0)
(Just 0)
(Just 0)
where
asFloat v = (read (Data.Text.unpack v) :: Float)
getAttr name =
case (Map.lookup name attrs) of
Just v -> asFloat v
_ -> 0
_ -> mkPoint (Pos 0 0)
2024-10-28 23:35:36 +00:00
getPoints :: Cursor -> [Point]
getPoints c =
let
trkpts =
child c >>=
element "trk" >>= descendant >>=
element "trkpt"
in
List.map elToPoint trkpts
-- TODO am sure we could use some amazing monad thing to reduce
-- the amount of pattern matching here
parse :: String -> Either SomeException [Point]
2024-10-28 23:35:36 +00:00
parse str =
case parseText def (T.pack str) of
Right gpx ->
let
points = getPoints $ fromDocument gpx
2024-10-29 19:35:17 +00:00
in Right points
2024-10-28 23:35:36 +00:00
Left err ->
Left err
2024-10-27 23:13:39 +00:00
length :: Track -> Int
length trk = Data.List.length trk