diff --git a/lib/Track.hs b/lib/Track.hs
index 320f730..25aad83 100644
--- a/lib/Track.hs
+++ b/lib/Track.hs
@@ -25,9 +25,10 @@ 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
@@ -62,8 +63,8 @@ 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
+ 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)
diff --git a/tests/UnitTest.hs b/tests/UnitTest.hs
index a2a2bd6..5d5f9e9 100644
--- a/tests/UnitTest.hs
+++ b/tests/UnitTest.hs
@@ -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 ++ ""
wrapPoint x =
let trk = "" ++ x ++ ""
- in wrap trk
+ in wrap trk
onepoint =
wrap
@@ -84,56 +84,57 @@ testMalformed =
in assertBool "catches syntax error" (isLeft trk)
testMissingAttrs =
- let els = [
- [r|
+ let els =
+ [ [r|
|],
- [r|
+ [r|
|],
- [r|
+ [r|
|]
]
- 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
+ ( List.map
+ (\text -> Track.parse (wrapPoint text))
+ 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 $