diff --git a/messages/uniworx/de.msg b/messages/uniworx/de.msg index e77dd2055..7873810fe 100644 --- a/messages/uniworx/de.msg +++ b/messages/uniworx/de.msg @@ -221,6 +221,7 @@ MaterialInvisible: Dieses Material ist für Teilnehmer momentan unsichtbar! MaterialInvisibleUntil date@Text: Dieses Material ist für Teilnehmer momentan unsichtbar bis #{date}! MaterialFiles: Dateien MaterialHeading materialName@MaterialName: Material #{materialName} +MaterialListHeading: Materialien MaterialNewHeading: Neues Material veröffentlichen MaterialNewTitle: Neues Material MaterialEditHeading materialName@MaterialName: Material "#{materialName}" editieren diff --git a/src/Database/Esqueleto/Utils.hs b/src/Database/Esqueleto/Utils.hs index 6c89e6c96..32eed0a58 100644 --- a/src/Database/Esqueleto/Utils.hs +++ b/src/Database/Esqueleto/Utils.hs @@ -18,9 +18,9 @@ import Database.Esqueleto.Utils.TH -- --- Description : Convenience for using @Esqueleto@, +-- Description : Convenience for using `Esqueleto`, -- intended to be imported qualified --- just like Esqueleto +-- just like @Esqueleto@ -- ezero = E.val (0 :: Int64) @@ -43,13 +43,13 @@ hasInfix :: (E.Esqueleto query expr backend, E.SqlString s2) => hasInfix = flip isInfixOf -- | Given a test and a set of values, check whether anyone succeeds the test --- WARNING: SQL leaves it explicitely unspecified whether || is short curcuited (i.e. lazily evaluated) +-- WARNING: SQL leaves it explicitely unspecified whether `||` is short curcuited (i.e. lazily evaluated) any :: Foldable f => (a -> E.SqlExpr (E.Value Bool)) -> f a -> E.SqlExpr (E.Value Bool) any test = F.foldr (\needle acc -> acc E.||. test needle) false -- | Given a test and a set of values, check whether all succeeds the test --- WARNING: SQL leaves it explicitely unspecified whether && is short curcuited (i.e. lazily evaluated) +-- WARNING: SQL leaves it explicitely unspecified whether `&&` is short curcuited (i.e. lazily evaluated) all :: Foldable f => (a -> E.SqlExpr (E.Value Bool)) -> f a -> E.SqlExpr (E.Value Bool) all test = F.foldr (\needle acc -> acc E.&&. test needle) true @@ -81,7 +81,7 @@ mkExactFilter :: (PersistField a) -> E.SqlExpr (E.Value Bool) mkExactFilter = mkExactFilterWith id --- | like @mkExactFiler@ but allows for conversion; convenient in conjunction with @anyFilter@ and @allFilter@ +-- | like `mkExactFiler` but allows for conversion; convenient in conjunction with `anyFilter` and `allFilter` mkExactFilterWith :: (PersistField b) => (a -> b) -- ^ type conversion -> (t -> E.SqlExpr (E.Value b)) -- ^ getter from query to searched element diff --git a/src/Handler/Material.hs b/src/Handler/Material.hs index e7ce5134c..29b3a0792 100644 --- a/src/Handler/Material.hs +++ b/src/Handler/Material.hs @@ -79,7 +79,16 @@ fetchMaterial tid ssh csh mnm = do getMaterialListR :: TermId -> SchoolId -> CourseShorthand -> Handler Html -getMaterialListR = error "unimplemented" -- TODO +getMaterialListR _tid _ssh _csh = do + -- muid <- maybeAuthId + -- cid <- runDB . getKeyBy404 $ TermSchoolCourseShort tid ssh csh + -- table <- return $ error "unimplemented" -- TODO + -- let headingLong = prependCourseTitle tid ssh csh $ MsgMaterialListHeading + -- headingShort = prependCourseTitle tid ssh csh $ MsgMaterialListHeading + -- siteLayoutMsg headingLong $ do + -- setTitleI headingShort + -- $(widgetFile "material-list") + error "unimplemented" -- TODO getMFileR :: TermId -> SchoolId -> CourseShorthand -> MaterialName -> FilePath -> Handler TypedContent getMFileR tid ssh csh mnm title = serveOneFile fileQuery @@ -116,7 +125,8 @@ getMShowR tid ssh csh mnm = do return (file E.^. FileTitle, file E.^. FileModified) , dbtRowKey = \(_ `E.InnerJoin` file) -> file E.^. FileId , dbtColonnade = widgetColonnade $ mconcat - [ colFilePathSimple (view _1) matLink + [ -- dbRowIndicator -- important: contains writer to indicate that the tables is not empty + colFilePathSimple (view _1) matLink , colFileModification (view _2) ] , dbtProj = \row -> @@ -135,16 +145,15 @@ getMShowR tid ssh csh mnm = do } return (matEnt,fileTable') + let matVisFro = materialVisibleFrom material now <- liftIO $ getCurrentTime materialLastEdit <- formatTime SelFormatDateTime $ materialLastEdit material - let matVisFro = materialVisibleFrom material materialVisibleFrom <- traverse (formatTime SelFormatDateTime) matVisFro when (NTop matVisFro >= NTop (Just now)) $ addMessageI Warning $ maybe MsgMaterialInvisible MsgMaterialInvisibleUntil materialVisibleFrom let headingLong = prependCourseTitle tid ssh csh $ MsgMaterialHeading mnm headingShort = prependCourseTitle tid ssh csh $ SomeMessage mnm - siteLayoutMsg headingLong $ do setTitleI headingShort $(widgetFile "material-show") diff --git a/src/Handler/Sheet.hs b/src/Handler/Sheet.hs index 5d8d7c634..449c906c2 100644 --- a/src/Handler/Sheet.hs +++ b/src/Handler/Sheet.hs @@ -154,7 +154,7 @@ getSheetOldUnassigned tid ssh csh = runDB $ do getSheetListR :: TermId -> SchoolId -> CourseShorthand -> Handler Html getSheetListR tid ssh csh = do muid <- maybeAuthId - Entity cid _ <- runDB . getBy404 $ TermSchoolCourseShort tid ssh csh + cid <- runDB . getKeyBy404 $ TermSchoolCourseShort tid ssh csh let lastSheetEdit sheet = E.sub_select . E.from $ \sheetEdit -> do E.where_ $ sheetEdit E.^. SheetEditSheet E.==. sheet E.^. SheetId diff --git a/src/Handler/Utils/Table/Cells.hs b/src/Handler/Utils/Table/Cells.hs index 28b3df6b2..e01f9115a 100644 --- a/src/Handler/Utils/Table/Cells.hs +++ b/src/Handler/Utils/Table/Cells.hs @@ -49,6 +49,7 @@ pathPieceCell = cell . toWidget . toPathPiece sqlCell :: (IsDBTable (YesodDB UniWorX) a) => YesodDB UniWorX Widget -> DBCell (YesodDB UniWorX) a sqlCell act = mempty & cellContents .~ lift act +-- Recfor line numbers, use dbRow --------------------- -- Icon cells diff --git a/src/Handler/Utils/Table/Columns.hs b/src/Handler/Utils/Table/Columns.hs index 30d2e6a4a..d31f6365f 100644 --- a/src/Handler/Utils/Table/Columns.hs +++ b/src/Handler/Utils/Table/Columns.hs @@ -11,6 +11,7 @@ import Import -- import Text.Blaze (ToMarkup(..)) +import Data.Monoid (Any(..)) import qualified Database.Esqueleto as E import Database.Esqueleto.Utils as E @@ -34,6 +35,14 @@ import Handler.Utils.Table.Cells -- * additional helper, such as default sorting +----------------------- +-- Numbers and Indices + +-- | Simple index column, also indicating whether there is a row at all +-- For a version without indication, use `Handler.Utils.Pagination.dbRow` instead. +dbRowIndicator :: IsDBTable m Any => Colonnade Sortable (DBRow r) (DBCell m Any) +dbRowIndicator = sortable Nothing (i18nCell MsgNrColumn) $ \DBRow{ dbrIndex } -> tellCell (Any True) $ textCell $ tshow dbrIndex + --------------- -- Files @@ -48,7 +57,7 @@ colFilePath row2path row2link = sortable (Just "path") (i18nCell MsgFileTitle) m in anchorCell link $ str2widget filePath -- | Generic column for links to FilePaths, where the link only depends on the FilePath itself -colFilePathSimple :: (IsDBTable m c) => (t -> E.Value FilePath) -> (FilePath -> Route UniWorX) -> Colonnade Sortable t (DBCell m c) +colFilePathSimple :: (IsDBTable m c) => (t -> E.Value FilePath) -> (FilePath -> Route UniWorX) -> Colonnade Sortable t (DBCell m c) colFilePathSimple row2path row2link = sortable (Just "path") (i18nCell MsgFileTitle) makeCell where makeCell row = @@ -57,7 +66,7 @@ colFilePathSimple row2path row2link = sortable (Just "path") (i18nCell MsgFileTi in anchorCell link $ str2widget filePath -- | Generic column for File Modification -colFileModification :: (IsDBTable m c) => (t -> E.Value UTCTime) -> Colonnade Sortable t (DBCell m c) +colFileModification :: (IsDBTable m c) => (t -> E.Value UTCTime) -> Colonnade Sortable t (DBCell m c) colFileModification row2time = sortable (Just "time") (i18nCell MsgFileModified) (timeCell . E.unValue . row2time) sortFilePath :: IsString s => (r -> E.SqlExpr (Entity File)) -> (s, SortColumn r) diff --git a/src/Handler/Utils/Table/Pagination.hs b/src/Handler/Utils/Table/Pagination.hs index ce39f6300..6caaebca0 100644 --- a/src/Handler/Utils/Table/Pagination.hs +++ b/src/Handler/Utils/Table/Pagination.hs @@ -910,7 +910,7 @@ formCell formCellLens genIndex genForm input@(DBRow{dbrKey}) = FormCell -- Predefined colonnades ---Number column? +-- | Simple number column, also see Handler.Utils.Table.Columns.dbRowIndicator dbRow :: forall h r m a. (Headedness h, IsDBTable m a) => Colonnade h (DBRow r) (DBCell m a) dbRow = Colonnade.singleton (headednessPure $ i18nCell MsgNrColumn) $ \DBRow{ dbrIndex } -> textCell $ tshow dbrIndex diff --git a/templates/material-list.hamlet b/templates/material-list.hamlet new file mode 100644 index 000000000..503a88d43 --- /dev/null +++ b/templates/material-list.hamlet @@ -0,0 +1,2 @@ +
+ ^{table} diff --git a/templates/material-show.hamlet b/templates/material-show.hamlet index cd8daa63c..92dba855e 100644 --- a/templates/material-show.hamlet +++ b/templates/material-show.hamlet @@ -16,7 +16,7 @@ $maybe descr <- materialDescription
_{MsgFileModified}
#{materialLastEdit} -$if hasFiles +$if hasFiles || True

_{MsgMaterialFiles} ^{fileTable}