Snapshot list

This commit is contained in:
Michael Snoyman 2015-05-14 17:02:05 +03:00
parent ff6a3c6877
commit 69d65594a5
4 changed files with 30 additions and 28 deletions

View File

@ -3,10 +3,10 @@
module Handler.Snapshots where module Handler.Snapshots where
import Data.Time.Clock import Data.Time.Clock
import qualified Database.Esqueleto as E
import Formatting import Formatting
import Formatting.Time import Formatting.Time
import Import import Import
import Stackage.Database
snapshotsPerPage :: Integral a => a snapshotsPerPage :: Integral a => a
snapshotsPerPage = 50 snapshotsPerPage = 50
@ -20,27 +20,14 @@ snapshotsPerPage = 50
-- inclined, or create a single monolithic file. -- inclined, or create a single monolithic file.
getAllSnapshotsR :: Handler Html getAllSnapshotsR :: Handler Html
getAllSnapshotsR = do getAllSnapshotsR = do
error "getAllSnapshotsR"
{-
now' <- liftIO getCurrentTime now' <- liftIO getCurrentTime
currentPageMay <- lookupGetParam "page" currentPageMay <- lookupGetParam "page"
let currentPage :: Int let currentPage :: Int
currentPage = fromMaybe 1 (currentPageMay >>= readMay) currentPage = fromMaybe 1 (currentPageMay >>= readMay)
(totalCount, groups) <- fmap (groupUp now') $ runDB $ do (totalCount, snapshots) <- getSnapshots
c <- count ([] :: [Filter Stackage]) snapshotsPerPage
rs <- E.select $ E.from $ \(stackage `E.InnerJoin` user) -> do ((fromIntegral currentPage - 1) * snapshotsPerPage)
E.on (stackage E.^. StackageUser E.==. user E.^. UserId) let groups = groupUp now' snapshots
E.orderBy [E.desc $ stackage E.^. StackageUploaded]
E.limit snapshotsPerPage
E.offset ((fromIntegral currentPage - 1) * snapshotsPerPage)
return
( stackage E.^. StackageSlug
, stackage E.^. StackageTitle
, stackage E.^. StackageUploaded
, user E.^. UserDisplay
, user E.^. UserHandle
)
return (c, rs)
let isFirstPage = currentPage == 1 let isFirstPage = currentPage == 1
isLastPage = currentPage * snapshotsPerPage >= totalCount isLastPage = currentPage * snapshotsPerPage >= totalCount
@ -49,8 +36,13 @@ getAllSnapshotsR = do
setTitle "Stackage Server" setTitle "Stackage Server"
let snapshotsNav = $(widgetFile "snapshots-nav") let snapshotsNav = $(widgetFile "snapshots-nav")
$(widgetFile "all-snapshots") $(widgetFile "all-snapshots")
where uncrapify now' c = where uncrapify now' snapshot =
let (E.Value ident, E.Value title, E.Value uploaded, E.Value display, E.Value handle') = c ( snapshotName snapshot
in (ident,title,format (diff True) (diffUTCTime uploaded now'),display,handle') , snapshotTitle snapshot
groupUp now' (c, rs) = (c, (groupBy (on (==) (\(_,_,uploaded,_,_) -> uploaded)) . map (uncrapify now')) rs) , format (diff True)
-} $ diffUTCTime
(UTCTime (snapshotCreated snapshot) 0)
now'
)
groupUp now' = groupBy (on (==) (\(_,_,uploaded) -> uploaded))
. map (uncrapify now')

View File

@ -27,6 +27,7 @@ module Stackage.Database
, getPackage , getPackage
, prettyName , prettyName
, getSnapshotsForPackage , getSnapshotsForPackage
, getSnapshots
) where ) where
import Database.Sqlite (SqliteException) import Database.Sqlite (SqliteException)
@ -588,3 +589,14 @@ getSnapshotsForPackage pname = run $ do
return $ case ms of return $ case ms of
Nothing -> Nothing Nothing -> Nothing
Just s -> Just (s, snapshotPackageVersion sp) Just s -> Just (s, snapshotPackageVersion sp)
getSnapshots
:: GetStackageDatabase m
=> Int -- ^ limit
-> Int -- ^ offset
-> m (Int, [Snapshot])
getSnapshots l o = run $ (,)
<$> count ([] :: [Filter Snapshot])
<*> fmap (map entityVal) (selectList
[]
[LimitTo l, OffsetBy o, Desc SnapshotCreated])

View File

@ -3,15 +3,13 @@
<h1>Snapshots <h1>Snapshots
^{snapshotsNav} ^{snapshotsNav}
$forall stackages <- groups $forall stackages <- groups
$forall (_, _, uploaded, _, _) <- take 1 stackages $forall (_, _, uploaded) <- take 1 stackages
<h3> <h3>
#{uploaded} #{uploaded}
<ul .snapshots> <ul .snapshots>
$forall (ident, title, _uploaded, display, handle) <- stackages $forall (ident, title, _uploaded) <- stackages
<li> <li>
<strong> <strong>
<a href=@{SnapshotR ident StackageHomeR}> <a href=@{SnapshotR ident StackageHomeR}>
#{title} #{title}
<p>
#{display} (#{handle})
^{snapshotsNav} ^{snapshotsNav}

View File

@ -61,4 +61,4 @@ $newline never
#{pliName pli} #{pliName pli}
-#{pliVersion pli} -#{pliVersion pli}
<td> <td>
#{pliSynopsis pli} #{strip $ pliSynopsis pli}