serve JSON fron db at /points

This commit is contained in:
Daniel Barlow 2024-11-05 23:32:01 +00:00
parent 7d2b669f3f
commit 8bd67b2096
4 changed files with 46 additions and 3 deletions

View File

@ -12,7 +12,7 @@ import Data.ByteString.Lazy as BS
import Data.List as List import Data.List as List
import Database.Persist.Postgresql (ConnectionPool, ConnectionString, SqlBackend, runMigration, runSqlPool, withPostgresqlPool) import Database.Persist.Postgresql (ConnectionPool, ConnectionString, SqlBackend, runMigration, runSqlPool, withPostgresqlPool)
import Debug.Trace (traceShow) import Debug.Trace (traceShow)
import Store (migrateAll, save) import Store (fetch, migrateAll, save)
import Track (parseBS) import Track (parseBS)
import Yesod.Core import Yesod.Core
import Yesod.Form.Fields import Yesod.Form.Fields
@ -35,6 +35,7 @@ mkYesod
/timeline TimelineR GET /timeline TimelineR GET
/upload UploadR POST /upload UploadR POST
/static StaticR Static getStatic /static StaticR Static getStatic
/points PointsR GET
|] |]
getStatic :: Souplesse -> Static getStatic :: Souplesse -> Static
@ -87,6 +88,11 @@ var app = Elm.Main.init({
<p>Copyright &copy; 2024 Daniel Barlow <p>Copyright &copy; 2024 Daniel Barlow
|] |]
getPointsR :: Handler Value
getPointsR = do
points <- runDB Store.fetch
returnJson points
data FileForm = FileForm data FileForm = FileForm
{ fileInfo :: FileInfo { fileInfo :: FileInfo
} }

View File

@ -13,12 +13,13 @@
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
module Store (save, migrateAll) where module Store (save, fetch, migrateAll) where
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Reader (ReaderT) import Control.Monad.Trans.Reader (ReaderT)
import Data.Time.Clock (UTCTime) import Data.Time.Clock (UTCTime)
import Database.Persist import Database.Persist
import Database.Persist.Class
import Database.Persist.Postgresql import Database.Persist.Postgresql
( ConnectionString, ( ConnectionString,
SqlBackend, SqlBackend,
@ -29,6 +30,7 @@ import Database.Persist.Postgresql
runSqlPool, runSqlPool,
) )
import Database.Persist.TH import Database.Persist.TH
import Track (Point (..), Pos (..))
import Track as T import Track as T
connString :: ConnectionString connString :: ConnectionString
@ -52,4 +54,20 @@ fromPoint p =
let Pos lat lon ele = T.pos p let Pos lat lon ele = T.pos p
in Trkpt lat lon ele (T.time p) (T.cadence p) (T.power p) (T.heartRate p) in Trkpt lat lon ele (T.time p) (T.cadence p) (T.power p) (T.heartRate p)
toPoint :: Entity Trkpt -> Point
toPoint entity =
let tkp = (\(Entity _ tkp) -> tkp) entity
pos = Pos (trkptLat tkp) (trkptLon tkp) (trkptEle tkp)
in Point
pos
(trkptTime tkp)
Nothing
Nothing
Nothing
save p = do insert $ fromPoint p save p = do insert $ fromPoint p
fetch :: (MonadIO m) => ReaderT SqlBackend m [Point]
fetch = do
trkpts <- selectList [TrkptLat <=. 360] [] -- Asc TrkptTime]
return $ map toPoint trkpts

View File

@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Track module Track
( Track, ( Track,
@ -13,6 +14,8 @@ module Track
where where
import Control.Exception import Control.Exception
import Data.Aeson
import Data.ByteString.Lazy.Char8 qualified as L
import Data.Either import Data.Either
import Data.Functor ((<&>)) import Data.Functor ((<&>))
import Data.List as List import Data.List as List
@ -45,6 +48,19 @@ data Point = Point
} }
deriving (Show) deriving (Show)
instance ToJSON Pos where
toJSON (Pos lat lon ele) =
case ele of
Just e -> object ["lat" .= lat, "lon" .= lon, "ele" .= e]
Nothing -> object ["lat" .= lat, "lon" .= lon, "ele" .= Null]
instance ToJSON Point where
toJSON Point {..} =
object
[ "pos" .= pos,
"time" .= time
]
-- TODO do we even need this type? -- TODO do we even need this type?
type Track = [Point] type Track = [Point]

View File

@ -70,6 +70,7 @@ executable souplesse
-- Other library packages from which modules are imported. -- Other library packages from which modules are imported.
build-depends: build-depends:
base ^>=4.18.2.1 base ^>=4.18.2.1
, aeson
, souplesse-lib , souplesse-lib
, text , text
, bytestring , bytestring
@ -99,6 +100,8 @@ library souplesse-lib
lib lib
build-depends: build-depends:
base >=4.7 && <5 base >=4.7 && <5
, aeson
, bytestring
, xml-conduit , xml-conduit
, time , time
, containers , containers