save points to postgres in upload handler

This commit is contained in:
Daniel Barlow 2024-11-05 19:35:34 +00:00
parent 81fa7346d3
commit 798ded7541
3 changed files with 37 additions and 16 deletions

View File

@ -66,13 +66,21 @@ _Do not look below this line_
a singly-linked list a singly-linked list
* need a web server in haskell that * need a web server in haskell that
- accepts file upload and parses the gpx file - [done] accepts file upload and parses the gpx file
- serves the data points in some format elm can digest easily - serves the data points in some format elm can digest easily
* need a database of some kind so the data can be saved * [done] need a database of some kind so the data can be saved
* and boring stuff like auth[zn] * and boring stuff like auth[zn]
* frontend can get data from backend * frontend can get data from backend
* for DX, backend can serve the js files needed by frontend * [done] for DX, backend can serve the js files needed by frontend
* we only have yesod-core, may need other parts as well * [ad hoc] we only have yesod-core, may need other parts as well
## Postgres
I run the postgresql devel server using Docker instead of changing my
global NixOS configuration, so that it's self-contained and I can
start and stop it when I want to
``` ```
docker run -p 5432:5432 --name souplesse-postgres -e POSTGRES_USER=souplesse -e POSTGRES_PASSWORD=secret -d postgres docker run -p 5432:5432 --name souplesse-postgres -e POSTGRES_USER=souplesse -e POSTGRES_PASSWORD=secret -d postgres
nix-shell -p postgresql --run "psql -h localhost -U souplesse -p 5432" nix-shell -p postgresql --run "psql -h localhost -U souplesse -p 5432"

View File

@ -7,24 +7,24 @@
module Main where module Main where
import Control.Monad.Logger (runStderrLoggingT) import Control.Monad.Logger (runStderrLoggingT)
import Control.Monad.Trans.Resource (runResourceT)
import Data.ByteString.Lazy as BS import Data.ByteString.Lazy as BS
import Data.List as List import Data.List as List
import Database.Persist.Postgresql (ConnectionString, runMigration, runSqlPersistMPool, 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 (migrateAll, save)
import Track (parseBS, parseFile) import Track (parseBS)
import Yesod.Core import Yesod.Core
import Yesod.Form.Fields import Yesod.Form.Fields
import Yesod.Form.Functions import Yesod.Form.Functions
import Yesod.Form.Types import Yesod.Form.Types
import Yesod.Persist
-- https://github.com/yesodweb/yesod-cookbook/blob/master/cookbook/Static-file-subsite-Hello-World.md -- https://github.com/yesodweb/yesod-cookbook/blob/master/cookbook/Static-file-subsite-Hello-World.md
import Yesod.Static import Yesod.Static
staticFiles "frontend" -- this param appears to be a pathname staticFiles "frontend" -- this param appears to be a pathname
data Souplesse = Souplesse data Souplesse = Souplesse ConnectionPool Static
{ getStatic :: Static
}
-- ref https://www.yesodweb.com/book/routing-and-handlers -- ref https://www.yesodweb.com/book/routing-and-handlers
-- for adding params (start/end) to the timeline route -- for adding params (start/end) to the timeline route
@ -37,8 +37,20 @@ mkYesod
/static StaticR Static getStatic /static StaticR Static getStatic
|] |]
getStatic :: Souplesse -> Static
getStatic y =
let Souplesse _ s = y
in s
instance Yesod Souplesse instance Yesod Souplesse
instance YesodPersist Souplesse where
type YesodPersistBackend Souplesse = SqlBackend
runDB action = do
Souplesse pool _ <- getYesod
runSqlPool action pool
getCalendarR :: Handler Html getCalendarR :: Handler Html
getCalendarR = do getCalendarR = do
(formWidget, _) <- generateFormPost uploadForm (formWidget, _) <- generateFormPost uploadForm
@ -93,17 +105,19 @@ instance RenderMessage Souplesse FormMessage where
postUploadR :: Handler Html postUploadR :: Handler Html
postUploadR = do postUploadR = do
((result, _), _) <- runFormPost uploadForm ((result, _), _) <- runFormPost uploadForm
case result of case result of
FormSuccess upload -> do FormSuccess upload -> do
bs <- fileSourceByteString $ fileInfo upload bs <- fileSourceByteString $ fileInfo upload
case Track.parseBS (fromStrict bs) of case Track.parseBS (fromStrict bs) of
Right points -> Right points -> do
runDB $ mapM_ Store.save points
defaultLayout [whamlet|<p>#{List.length points} points - thanks!|] defaultLayout [whamlet|<p>#{List.length points} points - thanks!|]
Left _ -> Left _ ->
defaultLayout defaultLayout
[whamlet|<p>parse error |] [whamlet|<p>parse error |]
FormMissing -> FormMissing ->
defaultLayout [whamlet|<p>FormMissing (?)|] defaultLayout [whamlet|<p>FormMissing (?)|]
FormFailure errors -> FormFailure errors ->
defaultLayout defaultLayout
[whamlet| [whamlet|
@ -119,10 +133,7 @@ connStr = "host=127.0.0.1 port=5432 user=souplesse dbname=souplesse password=sec
main :: IO () main :: IO ()
main = runStderrLoggingT $ withPostgresqlPool connStr 10 $ \pool -> liftIO $ do main = runStderrLoggingT $ withPostgresqlPool connStr 10 $ \pool -> liftIO $ do
flip runSqlPersistMPool pool $ do runResourceT $ flip runSqlPool pool $ do
runMigration migrateAll runMigration migrateAll
p1 : _ <- liftIO $ Track.parseFile "track.gpx"
Store.save p1
static' <- static "frontend" static' <- static "frontend"
warp 3000 $ Souplesse static' warp 3000 $ Souplesse pool static'

View File

@ -75,10 +75,12 @@ executable souplesse
, bytestring , bytestring
, persistent , persistent
, persistent-postgresql , persistent-postgresql
, resourcet
, monad-logger , monad-logger
, yesod-core == 1.6.25.1 , yesod-core == 1.6.25.1
, yesod-static , yesod-static
, yesod-form , yesod-form
, yesod-persistent
-- Directories containing source files. -- Directories containing source files.
hs-source-dirs: app hs-source-dirs: app