{-# LANGUAGE QuasiQuotes #-}
module Main where
import Control.Exception
import Data.Either
import Data.List as List
import Data.Time qualified
import Debug.Trace (trace, traceShow)
import System.Exit qualified as Exit
import Test.HUnit
import Text.RawString.QQ (r)
import Track qualified
preamble =
[r|
|]
wrap x = preamble ++ x ++ ""
wrapPoint x =
let trk = "" ++ x ++ ""
in wrap trk
onepoint =
wrap
[r|
|]
onepointWithAttrs =
wrap
[r|
25.2
2.4
128
160
55
3.21610.675
32.025
|]
test1 =
TestCase $
either
(assertFailure . displayException)
( assertEqual
"empty track has no elements"
0
. Track.length
)
(Track.parse (wrap ""))
testMalformed =
TestCase $
let trk = Track.parse (wrap ">")
in assertBool "catches syntax error" (isLeft trk)
testMissingAttrs =
let els =
[ [r|
|],
[r|
|],
[r|
|]
]
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)
]
test3 =
TestCase $
either
(assertFailure . displayException)
( \(p : _) ->
assertEqual
"handles missing attributes"
(Nothing, Nothing)
(Track.power p, Track.cadence p)
)
(Track.parse onepoint)
test4 =
TestCase $
either
(assertFailure . displayException)
( \(p : _) ->
assertEqual
"handles attributes"
(Just 128, Just 55, Data.Time.UTCTime (toEnum 60606) 27299.779, Just 160)
(Track.cadence p, Track.power p, Track.time p, Track.heartRate p)
)
(Track.parse onepointWithAttrs)
tests :: Test
tests =
TestList
[ test1,
testMalformed,
testMissingAttrs,
test2,
test3,
test4
]
main :: IO ()
main = do
result <- runTestTT tests
if (failures result > 0) || (errors result > 0)
then Exit.exitFailure
else Exit.exitSuccess