extract Session module
This commit is contained in:
parent
617feef051
commit
886089fbcd
@ -13,6 +13,7 @@ import Data.List as List
|
|||||||
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
|
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
|
||||||
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 Session
|
||||||
import Store
|
import Store
|
||||||
import Track (parseBS)
|
import Track (parseBS)
|
||||||
import Yesod.Core
|
import Yesod.Core
|
||||||
@ -56,7 +57,7 @@ instance YesodPersist Souplesse where
|
|||||||
getCalendarR :: Handler Html
|
getCalendarR :: Handler Html
|
||||||
getCalendarR = do
|
getCalendarR = do
|
||||||
(formWidget, _) <- generateFormPost uploadForm
|
(formWidget, _) <- generateFormPost uploadForm
|
||||||
sessions' <- runDB Store.sessions
|
sessions' <- runDB Session.recents
|
||||||
defaultLayout
|
defaultLayout
|
||||||
[whamlet|
|
[whamlet|
|
||||||
<h1>Calendar
|
<h1>Calendar
|
||||||
|
69
lib/Session.hs
Normal file
69
lib/Session.hs
Normal file
@ -0,0 +1,69 @@
|
|||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE DerivingStrategies #-}
|
||||||
|
{-# LANGUAGE EmptyDataDecls #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
{-# LANGUAGE GADTs #-}
|
||||||
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
|
{-# LANGUAGE StandaloneDeriving #-}
|
||||||
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
|
||||||
|
module Session
|
||||||
|
( Session(..)
|
||||||
|
, recents
|
||||||
|
, updateSessions
|
||||||
|
, migrateSession
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.Text
|
||||||
|
import Text.RawString.QQ (r)
|
||||||
|
import Data.Time.Clock (
|
||||||
|
UTCTime,
|
||||||
|
)
|
||||||
|
|
||||||
|
import Database.Persist
|
||||||
|
-- import Database.Persist.Class
|
||||||
|
import Database.Persist.TH
|
||||||
|
import Database.Persist.Postgresql
|
||||||
|
( SqlBackend,
|
||||||
|
PgInterval
|
||||||
|
)
|
||||||
|
import Control.Monad.IO.Class (MonadIO)
|
||||||
|
import Control.Monad.Trans.Reader (ReaderT)
|
||||||
|
|
||||||
|
|
||||||
|
share
|
||||||
|
[mkPersist sqlSettings, mkMigrate "migrateSession"]
|
||||||
|
[persistLowerCase|
|
||||||
|
Session
|
||||||
|
startTime UTCTime
|
||||||
|
duration PgInterval
|
||||||
|
draft Bool default=True
|
||||||
|
notes String Maybe
|
||||||
|
|]
|
||||||
|
|
||||||
|
updateSessions :: Text
|
||||||
|
updateSessions = [r|
|
||||||
|
-- delete existing drafts as new data may extend one of them
|
||||||
|
delete from session where draft;
|
||||||
|
-- find all potential start points in the new data
|
||||||
|
insert into session(start_time, duration, draft) (select time as start_time, make_interval(0) as duration, true as draft from trkpt as p where not exists (select id from session where start_time <= p.time and (start_time + duration) > p.time) and not exists(select * from trkpt as p1 where time > p.time - '600 seconds'::interval and time < p.time));
|
||||||
|
-- reset durations
|
||||||
|
update session s1
|
||||||
|
set duration =
|
||||||
|
coalesce(
|
||||||
|
(select max(time) from trkpt t1
|
||||||
|
where t1.time < coalesce((select min(start_time) from session s2 where s2.start_time > s1.start_time), now())) - s1.start_time
|
||||||
|
, make_interval())
|
||||||
|
where draft;
|
||||||
|
|]
|
||||||
|
|
||||||
|
recents :: (MonadIO m) => ReaderT SqlBackend m [Session]
|
||||||
|
recents = do
|
||||||
|
s <- selectList [SessionDraft !=. True] [Desc SessionStartTime, LimitTo 10]
|
||||||
|
return $ Prelude.map (\(Entity _ x) -> x) s
|
49
lib/Store.hs
49
lib/Store.hs
@ -13,9 +13,13 @@
|
|||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
|
||||||
module Store (save, fetch, sessions, sessionStartTime,
|
module Store
|
||||||
sessionDuration, migrateSession, migrateTrkpt
|
( save,
|
||||||
) where
|
fetch,
|
||||||
|
migrateTrkpt,
|
||||||
|
module Session,
|
||||||
|
)
|
||||||
|
where
|
||||||
|
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad.IO.Class (MonadIO, liftIO)
|
import Control.Monad.IO.Class (MonadIO, liftIO)
|
||||||
@ -30,30 +34,19 @@ import Database.Persist.Postgresql
|
|||||||
createPostgresqlPool,
|
createPostgresqlPool,
|
||||||
pgConnStr,
|
pgConnStr,
|
||||||
pgPoolSize,
|
pgPoolSize,
|
||||||
|
rawExecute,
|
||||||
runMigration,
|
runMigration,
|
||||||
runSqlPool,
|
runSqlPool,
|
||||||
rawExecute,
|
|
||||||
PgInterval
|
|
||||||
)
|
)
|
||||||
import Database.Persist.TH
|
import Database.Persist.TH
|
||||||
|
import Session
|
||||||
import Text.Read (readMaybe)
|
import Text.Read (readMaybe)
|
||||||
import Track (Point (..), Pos (..))
|
import Track (Point (..), Pos (..))
|
||||||
import Track as T
|
import Track as T
|
||||||
import Text.RawString.QQ (r)
|
|
||||||
|
|
||||||
connString :: ConnectionString
|
connString :: ConnectionString
|
||||||
connString = "host=127.0.0.1 port=5432 user=souplesse dbname=souplesse password=secret"
|
connString = "host=127.0.0.1 port=5432 user=souplesse dbname=souplesse password=secret"
|
||||||
|
|
||||||
share
|
|
||||||
[mkPersist sqlSettings, mkMigrate "migrateSession"]
|
|
||||||
[persistLowerCase|
|
|
||||||
Session
|
|
||||||
startTime UTCTime
|
|
||||||
duration PgInterval
|
|
||||||
draft Bool default=True
|
|
||||||
notes String Maybe
|
|
||||||
|]
|
|
||||||
|
|
||||||
share
|
share
|
||||||
[mkPersist sqlSettings, mkMigrate "migrateTrkpt"]
|
[mkPersist sqlSettings, mkMigrate "migrateTrkpt"]
|
||||||
[persistLowerCase|
|
[persistLowerCase|
|
||||||
@ -67,7 +60,6 @@ Trkpt
|
|||||||
heartRate Int Maybe
|
heartRate Int Maybe
|
||||||
|]
|
|]
|
||||||
|
|
||||||
|
|
||||||
fromPoint :: Point -> Trkpt
|
fromPoint :: Point -> Trkpt
|
||||||
fromPoint p =
|
fromPoint p =
|
||||||
let Pos lat lon ele = T.pos p
|
let Pos lat lon ele = T.pos p
|
||||||
@ -84,31 +76,10 @@ toPoint entity =
|
|||||||
(trkptPower tkp)
|
(trkptPower tkp)
|
||||||
(trkptHeartRate tkp)
|
(trkptHeartRate tkp)
|
||||||
|
|
||||||
updateSessions = [r|
|
|
||||||
-- delete existing drafts as new data may extend one of them
|
|
||||||
delete from session where draft;
|
|
||||||
-- find all potential start points in the new data
|
|
||||||
insert into session(start_time, duration, draft) (select time as start_time, make_interval(0) as duration, true as draft from trkpt as p where not exists (select id from session where start_time <= p.time and (start_time + duration) > p.time) and not exists(select * from trkpt as p1 where time > p.time - '600 seconds'::interval and time < p.time));
|
|
||||||
-- reset durations
|
|
||||||
update session s1
|
|
||||||
set duration =
|
|
||||||
coalesce(
|
|
||||||
(select max(time) from trkpt t1
|
|
||||||
where t1.time < coalesce((select min(start_time) from session s2 where s2.start_time > s1.start_time), now())) - s1.start_time
|
|
||||||
, make_interval())
|
|
||||||
where draft;
|
|
||||||
|]
|
|
||||||
|
|
||||||
data OverlapExists = OverlapExists String deriving (Show)
|
data OverlapExists = OverlapExists String deriving (Show)
|
||||||
|
|
||||||
instance Exception OverlapExists
|
instance Exception OverlapExists
|
||||||
|
|
||||||
sessions :: (MonadIO m) => ReaderT SqlBackend m [Session]
|
|
||||||
sessions = do
|
|
||||||
s <- selectList [SessionDraft !=. True] [Desc SessionStartTime, LimitTo 10]
|
|
||||||
return $ map (\(Entity _ x) -> x) s
|
|
||||||
|
|
||||||
|
|
||||||
save :: (MonadIO m) => Track -> ReaderT SqlBackend m (Either OverlapExists Track)
|
save :: (MonadIO m) => Track -> ReaderT SqlBackend m (Either OverlapExists Track)
|
||||||
save track = do
|
save track = do
|
||||||
let start = startTime track
|
let start = startTime track
|
||||||
@ -118,7 +89,7 @@ save track = do
|
|||||||
then return $ Left (OverlapExists "track overlaps with existing data")
|
then return $ Left (OverlapExists "track overlaps with existing data")
|
||||||
else do
|
else do
|
||||||
mapM_ (insert . fromPoint) track
|
mapM_ (insert . fromPoint) track
|
||||||
rawExecute updateSessions []
|
rawExecute Session.updateSessions []
|
||||||
return $ Right track
|
return $ Right track
|
||||||
|
|
||||||
fetch :: (MonadIO m) => UTCTime -> NominalDiffTime -> ReaderT SqlBackend m [Point]
|
fetch :: (MonadIO m) => UTCTime -> NominalDiffTime -> ReaderT SqlBackend m [Point]
|
||||||
|
@ -99,6 +99,7 @@ library souplesse-lib
|
|||||||
Track
|
Track
|
||||||
Store
|
Store
|
||||||
Point
|
Point
|
||||||
|
Session
|
||||||
hs-source-dirs:
|
hs-source-dirs:
|
||||||
lib
|
lib
|
||||||
build-depends:
|
build-depends:
|
||||||
|
Loading…
Reference in New Issue
Block a user