souplesse/app/Main.hs

177 lines
4.9 KiB
Haskell
Raw Normal View History

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module Main where
2024-11-04 23:37:48 +00:00
import Control.Monad.Logger (runStderrLoggingT)
import Control.Monad.Trans.Resource (runResourceT)
import Data.ByteString.Lazy as BS
import Data.List as List
2024-11-10 17:30:28 +00:00
import Data.Text as T
2024-11-10 22:47:35 +00:00
import Data.Text.Lazy qualified as T (toStrict)
import Data.Text.Lazy.Builder qualified as B
import Data.Text.Lazy.Builder.Int qualified as B
2024-11-10 17:30:28 +00:00
import Data.Time.Clock (nominalDiffTimeToSeconds)
2024-11-10 22:17:18 +00:00
import Data.Time.Clock.POSIX (posixSecondsToUTCTime, utcTimeToPOSIXSeconds)
import Database.Persist.Postgresql (ConnectionPool, ConnectionString, SqlBackend, runMigration, runSqlPool, withPostgresqlPool)
import Debug.Trace (traceShow)
2024-11-11 21:13:32 +00:00
import Point qualified (fetch, migration, save)
import Session qualified
import Track (parseBS)
import Yesod.Core
import Yesod.Form.Fields
import Yesod.Form.Functions
import Yesod.Form.Input
import Yesod.Form.Types
import Yesod.Persist
import Yesod.Static
staticFiles "frontend" -- this param appears to be a pathname
data Souplesse = Souplesse ConnectionPool Static
-- ref https://www.yesodweb.com/book/routing-and-handlers
-- for adding params (start/end) to the timeline route
mkYesod
"Souplesse"
[parseRoutes|
/ CalendarR GET
/timeline TimelineR GET
/upload UploadR POST
/static StaticR Static getStatic
2024-11-05 23:32:01 +00:00
/points PointsR GET
|]
getStatic :: Souplesse -> Static
getStatic y =
let Souplesse _ s = y
in s
instance Yesod Souplesse
instance YesodPersist Souplesse where
type YesodPersistBackend Souplesse = SqlBackend
runDB action = do
Souplesse pool _ <- getYesod
runSqlPool action pool
intToText :: (Integral a) => a -> T.Text
2024-11-10 22:47:35 +00:00
intToText = T.toStrict . B.toLazyText . B.decimal
getCalendarR :: Handler Html
getCalendarR = do
2024-11-10 22:47:35 +00:00
let fTime = intToText . floor . utcTimeToPOSIXSeconds
fDur = intToText . ceiling . nominalDiffTimeToSeconds
2024-11-04 23:36:10 +00:00
(formWidget, _) <- generateFormPost uploadForm
2024-11-10 16:18:18 +00:00
sessions' <- runDB Session.recents
defaultLayout
[whamlet|
<h1>Calendar
<p>A calendar view goes here
<ul>
$forall s <- sessions'
2024-11-10 17:30:28 +00:00
<li>
<a href=@?{(TimelineR, [("start", fTime $ Session.startTime s), ("duration", fDur $ Session.duration s)])} > #{show $ Session.startTime s} #{show (Session.duration s)}
<form action="/upload" method=post enctype="multipart/form-data">
^{formWidget}
<input type="submit" name="send" value="send">
<a href="/timeline">timeline
&copy; 2024 Daniel Barlow
|]
getTimelineR :: Handler Html
-- what's this about? <img src=@{StaticR image_png}/>|]
getTimelineR = defaultLayout $ do
setTitle "timeline"
addScriptRemote "/static/frontend.js"
toWidgetBody
[julius|
window.addEventListener("load", function(){
var app = Elm.Main.init({
node: document.getElementById("elm")
});
})
|]
toWidget
[hamlet|
<pre id="elm">
<p>Copyright &copy; 2024 Daniel Barlow
|]
type Form x = Html -> MForm (HandlerFor Souplesse) (FormResult x, Widget)
data Timerange = Timerange {start :: Int, duration :: Int} deriving (Show)
2024-11-05 23:32:01 +00:00
getPointsR :: Handler Value
getPointsR = do
tr <-
runInputGet $
Timerange
<$> ireq intField "start"
<*> ireq intField "duration"
let start' = posixSecondsToUTCTime $ fromInteger $ toInteger $ start tr
duration' = fromInteger $ toInteger $ duration tr
2024-11-11 21:13:32 +00:00
points <- runDB $ Point.fetch start' duration'
returnJson (traceShow tr points)
2024-11-05 23:32:01 +00:00
data FileForm = FileForm
{ fileInfo :: FileInfo
}
uploadForm :: Form FileForm
uploadForm =
renderDivs $
FileForm
<$> fileAFormReq "choose file"
instance RenderMessage Souplesse FormMessage where
renderMessage _ _ = defaultFormMessage
postUploadR :: Handler Html
postUploadR = do
2024-11-07 18:59:56 +00:00
((result, _), _) <- runFormPostNoToken uploadForm
case result of
FormSuccess upload -> do
bs <- fileSourceByteString $ fileInfo upload
case Track.parseBS (fromStrict bs) of
Right points -> do
2024-11-11 21:13:32 +00:00
eitherPoints <- runDB $ Point.save points
2024-11-07 18:59:56 +00:00
case eitherPoints of
Right points' ->
defaultLayout [whamlet|<p>#{List.length points'} points - thanks!|]
Left _ ->
defaultLayout [whamlet|<p>overlap error |]
2024-11-04 23:36:10 +00:00
Left _ ->
defaultLayout
2024-11-05 18:57:52 +00:00
[whamlet|<p>parse error |]
FormMissing ->
defaultLayout [whamlet|<p>FormMissing (?)|]
FormFailure errors ->
defaultLayout
[whamlet|
<h1>Error uploading
<ul>
$forall err <- errors
<li>#{err}
|]
2024-11-04 23:37:48 +00:00
connStr :: ConnectionString
connStr = "host=127.0.0.1 port=5432 user=souplesse dbname=souplesse password=secret"
main :: IO ()
2024-11-04 23:37:48 +00:00
main = runStderrLoggingT $ withPostgresqlPool connStr 10 $ \pool -> liftIO $ do
runResourceT $ flip runSqlPool pool $ do
2024-11-11 21:13:32 +00:00
runMigration Session.migration
runMigration Point.migration
2024-11-05 18:56:12 +00:00
static' <- static "frontend"
warp 3000 $ Souplesse pool static'