souplesse/lib/Session.hs

91 lines
2.5 KiB
Haskell
Raw Normal View History

2024-11-10 16:18:18 +00:00
{-# 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
2024-11-10 22:17:18 +00:00
( Session (..),
recents,
refreshDrafts,
2024-11-11 21:13:32 +00:00
migration,
2024-11-10 22:17:18 +00:00
)
where
2024-11-10 16:18:18 +00:00
2024-11-10 22:17:18 +00:00
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.Trans.Reader (ReaderT)
2024-11-10 16:18:18 +00:00
import Data.Text
2024-11-10 22:17:18 +00:00
import Data.Time.Clock
( NominalDiffTime,
UTCTime,
2024-11-10 16:18:18 +00:00
)
import Database.Persist
import Database.Persist.Postgresql
2024-11-10 22:17:18 +00:00
( PgInterval,
SqlBackend,
getPgInterval,
rawExecute,
2024-11-10 16:18:18 +00:00
)
2024-11-10 22:17:18 +00:00
import Database.Persist.TH
import Text.RawString.QQ (r)
2024-11-10 16:18:18 +00:00
share
2024-11-11 21:13:32 +00:00
[mkPersist sqlSettings, mkMigrate "migration"]
2024-11-10 16:18:18 +00:00
[persistLowerCase|
SessionRow sql=session
2024-11-10 16:18:18 +00:00
startTime UTCTime
duration PgInterval
draft Bool default=True
notes String Maybe
|]
data Session = Session
{ startTime :: UTCTime,
duration :: NominalDiffTime,
draft :: Bool,
notes :: Maybe String
}
fromEntity :: Entity SessionRow -> Session
fromEntity (Entity _ row) =
Session
(sessionRowStartTime row)
(getPgInterval (sessionRowDuration row))
(sessionRowDraft row)
(sessionRowNotes row)
updateSql :: Text
updateSql =
2024-11-10 22:17:18 +00:00
[r|
2024-11-10 16:18:18 +00:00
-- 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;
|]
refreshDrafts :: (MonadIO m) => ReaderT SqlBackend m ()
refreshDrafts =
rawExecute updateSql []
2024-11-10 22:17:18 +00:00
recents :: (MonadIO m) => ReaderT SqlBackend m [Session]
2024-11-10 16:18:18 +00:00
recents = do
s <- selectList [SessionRowDraft !=. True] [Desc SessionRowStartTime, LimitTo 10]
return $ Prelude.map fromEntity s