From 72b2b72f0396b157ada9f29f168042d4b700ad69 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 4 Apr 2018 12:54:00 +0200 Subject: [PATCH 001/108] Implement table sorting --- src/Handler/Term.hs | 36 +++++++++++++++++++-------- src/Handler/Utils/Table/Pagination.hs | 25 +++++++++++-------- 2 files changed, 39 insertions(+), 22 deletions(-) diff --git a/src/Handler/Term.hs b/src/Handler/Term.hs index 9d85edbee..5deecac7e 100644 --- a/src/Handler/Term.hs +++ b/src/Handler/Term.hs @@ -1,11 +1,13 @@ -{-# LANGUAGE NoImplicitPrelude #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE QuasiQuotes #-} -{-# LANGUAGE MultiParamTypeClasses #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE NoImplicitPrelude + , OverloadedStrings + , OverloadedLists + , RecordWildCards + , TemplateHaskell + , QuasiQuotes + , MultiParamTypeClasses + , TypeFamilies + , FlexibleContexts + #-} module Handler.Term where @@ -29,7 +31,7 @@ getTermShowR = do -- return term -- let - termData = E.from $ \term -> do + termData term = do -- E.orderBy [E.desc $ term E.^. TermStart ] let courseCount :: E.SqlExpr (E.Value Int) courseCount = E.sub_select . E.from $ \course -> do @@ -37,7 +39,7 @@ getTermShowR = do return E.countRows return (term, courseCount) selectRep $ do - provideRep $ toJSON . map fst <$> runDB (E.select termData) + provideRep $ toJSON . map fst <$> runDB (E.select $ E.from termData) provideRep $ do let colonnadeTerms = mconcat [ headed "Kürzel" $ \(Entity tid Term{..},_) -> cell $ do @@ -71,7 +73,19 @@ getTermShowR = do table <- dbTable def $ DBTable { dbtSQLQuery = termData , dbtColonnade = colonnadeTerms - , dbtSorting = mempty + , dbtSorting = [ ( "start" + , SortColumn $ \term -> term E.^. TermStart + ) + , ( "end" + , SortColumn $ \term -> term E.^. TermEnd + ) + , ( "lecture-start" + , SortColumn $ \term -> term E.^. TermLectureStart + ) + , ( "lecture-end" + , SortColumn $ \term -> term E.^. TermLectureEnd + ) + ] , dbtAttrs = tableDefault , dbtIdent = "terms" :: Text } diff --git a/src/Handler/Utils/Table/Pagination.hs b/src/Handler/Utils/Table/Pagination.hs index 28fcb1073..23f0b6608 100644 --- a/src/Handler/Utils/Table/Pagination.hs +++ b/src/Handler/Utils/Table/Pagination.hs @@ -6,6 +6,7 @@ , QuasiQuotes , LambdaCase , ViewPatterns + , FlexibleContexts #-} module Handler.Utils.Table.Pagination @@ -19,6 +20,7 @@ module Handler.Utils.Table.Pagination import Import import qualified Database.Esqueleto as E import qualified Database.Esqueleto.Internal.Sql as E (SqlSelect) +import qualified Database.Esqueleto.Internal.Language as E (From) import Text.Blaze (Attribute) import qualified Text.Blaze.Html5.Attributes as Html5 @@ -37,7 +39,7 @@ import Text.Hamlet (hamletFile) import Data.Ratio ((%)) -data SortColumn = forall a. PersistField a => SortColumn { getSortColumn :: E.SqlExpr (E.Value a) } +data SortColumn t = forall a. PersistField a => SortColumn { getSortColumn :: t -> E.SqlExpr (E.Value a) } data SortDirection = SortAsc | SortDesc deriving (Eq, Ord, Enum, Show, Read) @@ -49,18 +51,19 @@ instance PathPiece SortDirection where | t == "desc" = Just SortDesc | otherwise = Nothing -sqlSortDirection :: (SortColumn, SortDirection) -> E.SqlExpr E.OrderBy -sqlSortDirection (SortColumn e, SortAsc ) = E.asc e -sqlSortDirection (SortColumn e, SortDesc) = E.desc e +sqlSortDirection :: t -> (SortColumn t, SortDirection) -> E.SqlExpr E.OrderBy +sqlSortDirection t (SortColumn e, SortAsc ) = E.asc $ e t +sqlSortDirection t (SortColumn e, SortDesc) = E.desc $ e t -data DBTable = forall a r h i. +data DBTable = forall a r h i t. ( Headedness h , E.SqlSelect a r , PathPiece i + , E.From E.SqlQuery E.SqlExpr E.SqlBackend t ) => DBTable - { dbtSQLQuery :: E.SqlQuery a + { dbtSQLQuery :: t -> E.SqlQuery a , dbtColonnade :: Colonnade h r (Cell UniWorX) - , dbtSorting :: Map Text SortColumn + , dbtSorting :: Map Text (SortColumn t) , dbtAttrs :: Attribute , dbtIdent :: i } @@ -109,7 +112,7 @@ dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do | otherwise = dbtAttrs psResult <- runInputGetResult $ PaginationSettings - <$> ireq (multiSelectField $ return sortingOptions) (wIdent "sorting") + <$> (fromMaybe [] <$> iopt (multiSelectField $ return sortingOptions) (wIdent "sorting")) <*> (fromMaybe (psLimit defPS) <$> iopt intField (wIdent "pagesize")) <*> (fromMaybe (psPage defPS) <$> iopt intField (wIdent "page")) <*> ireq checkBoxField (wIdent "table-only") @@ -125,14 +128,14 @@ dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do FormFailure errs -> first (map SomeMessage errs <>) $ runPSValidator Nothing FormMissing -> runPSValidator Nothing psSorting' = map (first (dbtSorting !)) psSorting - sqlQuery' = dbtSQLQuery - <* E.orderBy (map sqlSortDirection psSorting') + sqlQuery' = E.from $ \t -> dbtSQLQuery t + <* E.orderBy (map (sqlSortDirection t) psSorting') <* E.limit psLimit <* E.offset (psPage * psLimit) mapM_ (addMessageI "warning") errs - (rows, [E.Value rowCount]) <- runDB $ (,) <$> E.select sqlQuery' <*> E.select (E.countRows <$ dbtSQLQuery :: E.SqlQuery (E.SqlExpr (E.Value Int64))) + (rows, [E.Value rowCount]) <- runDB $ (,) <$> E.select sqlQuery' <*> E.select (E.countRows <$ E.from dbtSQLQuery :: E.SqlQuery (E.SqlExpr (E.Value Int64))) bool return (sendResponse <=< tblLayout) psShortcircuit $ do let table = encodeCellTable dbtAttrs' dbtColonnade rows From e71864368c7a5530b1ef17457c40f9ef977893e3 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 4 Apr 2018 14:35:11 +0200 Subject: [PATCH 002/108] Implement links to toggle table sorting --- src/Handler/Term.hs | 16 +++---- src/Handler/Utils/Table/Pagination.hs | 48 +++++++++++++++++-- src/Handler/Utils/Table/Pagination/Types.hs | 40 ++++++++++++++++ .../layout-wrapper.hamlet} | 0 .../layout.hamlet} | 0 templates/table/sortable-header.hamlet | 7 +++ templates/table/table.hamlet | 12 +++++ 7 files changed, 111 insertions(+), 12 deletions(-) create mode 100644 src/Handler/Utils/Table/Pagination/Types.hs rename templates/{table-layout-wrapper.hamlet => table/layout-wrapper.hamlet} (100%) rename templates/{table-layout.hamlet => table/layout.hamlet} (100%) create mode 100644 templates/table/sortable-header.hamlet create mode 100644 templates/table/table.hamlet diff --git a/src/Handler/Term.hs b/src/Handler/Term.hs index 5deecac7e..2461a05fc 100644 --- a/src/Handler/Term.hs +++ b/src/Handler/Term.hs @@ -42,7 +42,7 @@ getTermShowR = do provideRep $ toJSON . map fst <$> runDB (E.select $ E.from termData) provideRep $ do let colonnadeTerms = mconcat - [ headed "Kürzel" $ \(Entity tid Term{..},_) -> cell $ do + [ sortable Nothing "Kürzel" $ \(Entity tid Term{..},_) -> cell $ do -- Scrap this if to slow, create term edit page instead adminLink <- handlerToWidget $ isAuthorized (TermEditExistR tid) False [whamlet| @@ -52,22 +52,22 @@ getTermShowR = do $else #{termToText termName} |] - , headed "Beginn Vorlesungen" $ \(Entity _ Term{..},_) -> + , sortable (Just "lecture-start") "Beginn Vorlesungen" $ \(Entity _ Term{..},_) -> stringCell $ formatTimeGerWD termLectureStart - , headed "Ende Vorlesungen" $ \(Entity _ Term{..},_) -> + , sortable (Just "lecture-end") "Ende Vorlesungen" $ \(Entity _ Term{..},_) -> stringCell $ formatTimeGerWD termLectureEnd - , headed "Aktiv" $ \(Entity _ Term{..},_) -> + , sortable Nothing "Aktiv" $ \(Entity _ Term{..},_) -> textCell $ bool "" tickmark termActive - , headed "Kursliste" $ \(Entity tid Term{..}, E.Value numCourses) -> + , sortable Nothing "Kursliste" $ \(Entity tid Term{..}, E.Value numCourses) -> cell [whamlet| #{show numCourses} Kurse |] - , headed "Semesteranfang" $ \(Entity _ Term{..},_) -> + , sortable (Just "start") "Semesteranfang" $ \(Entity _ Term{..},_) -> stringCell $ formatTimeGerWD termStart - , headed "Semesterende" $ \(Entity _ Term{..},_) -> + , sortable (Just "end") "Semesterende" $ \(Entity _ Term{..},_) -> stringCell $ formatTimeGerWD termEnd - , headed "Feiertage im Semester" $ \(Entity _ Term{..},_) -> + , sortable Nothing "Feiertage im Semester" $ \(Entity _ Term{..},_) -> stringCell $ (intercalate ", ") $ map formatTimeGerWD termHolidays ] table <- dbTable def $ DBTable diff --git a/src/Handler/Utils/Table/Pagination.hs b/src/Handler/Utils/Table/Pagination.hs index 23f0b6608..6f0c1d4c5 100644 --- a/src/Handler/Utils/Table/Pagination.hs +++ b/src/Handler/Utils/Table/Pagination.hs @@ -14,15 +14,24 @@ module Handler.Utils.Table.Pagination , DBTable(..) , PaginationSettings(..) , PSValidator(..) + , Sortable(..), sortable , dbTable ) where +import Handler.Utils.Table.Pagination.Types + import Import import qualified Database.Esqueleto as E import qualified Database.Esqueleto.Internal.Sql as E (SqlSelect) import qualified Database.Esqueleto.Internal.Language as E (From) import Text.Blaze (Attribute) import qualified Text.Blaze.Html5.Attributes as Html5 +import qualified Text.Blaze.Html5 as Html5 +import Yesod.Core.Types (Body(..),GWData(..),WidgetT(..)) + +import qualified Data.Binary.Builder as Builder + +import qualified Network.Wai as Wai import Data.CaseInsensitive (CI) import qualified Data.CaseInsensitive as CI @@ -32,6 +41,7 @@ import Control.Monad.RWS hiding ((<>), Foldable(..), mapM_) import Data.Map (Map, (!)) import Colonnade hiding (bool, fromMaybe) +import Colonnade.Encode import Yesod.Colonnade import Text.Hamlet (hamletFile) @@ -56,7 +66,7 @@ sqlSortDirection t (SortColumn e, SortAsc ) = E.asc $ e t sqlSortDirection t (SortColumn e, SortDesc) = E.desc $ e t data DBTable = forall a r h i t. - ( Headedness h + ( ToSortable h , E.SqlSelect a r , PathPiece i , E.From E.SqlQuery E.SqlExpr E.SqlBackend t @@ -94,6 +104,7 @@ instance Default PSValidator where modify $ \ps -> ps { psLimit = psLimit def } tell . pure $ SomeMessage MsgPSLimitNonPositive + dbTable :: PSValidator -> DBTable -> Handler Widget dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do let @@ -138,11 +149,40 @@ dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do (rows, [E.Value rowCount]) <- runDB $ (,) <$> E.select sqlQuery' <*> E.select (E.countRows <$ E.from dbtSQLQuery :: E.SqlQuery (E.SqlExpr (E.Value Int64))) bool return (sendResponse <=< tblLayout) psShortcircuit $ do - let table = encodeCellTable dbtAttrs' dbtColonnade rows + getParams <- handlerToWidget $ queryToQueryText . Wai.queryString . reqWaiRequest <$> getRequest + let table = $(widgetFile "table/table") pageCount = max 1 . ceiling $ rowCount % psLimit - $(widgetFile "table-layout") + tblLink f = decodeUtf8 . Builder.toLazyByteString . renderQueryText True $ f getParams + withSortLinks Sortable{ sortableContent = Cell{..}, .. } = Cell + { cellContents = $(widgetFile "table/sortable-header") + , .. + } + $(widgetFile "table/layout") where tblLayout :: Widget -> Handler Html tblLayout tbl' = do tbl <- widgetToPageContent tbl' - withUrlRenderer $(hamletFile "templates/table-layout-wrapper.hamlet") + withUrlRenderer $(hamletFile "templates/table/layout-wrapper.hamlet") + + setParam :: Text -> Maybe Text -> QueryText -> QueryText + setParam key v qt = (key, v) : [ i | i@(key', _) <- qt, key' /= key ] + +widgetFromCell :: + (Attribute -> WidgetT site IO () -> WidgetT site IO ()) + -> Cell site + -> WidgetT site IO () +widgetFromCell f (Cell attrs contents) = + f attrs contents +td,th :: + Attribute -> WidgetT site IO () -> WidgetT site IO () + +td = liftParent Html5.td +th = liftParent Html5.th + +liftParent :: (Html -> Html) -> Attribute -> WidgetT site IO a -> WidgetT site IO a +liftParent el attrs (WidgetT f) = WidgetT $ \hdata -> do + (a,gwd) <- f hdata + let Body bodyFunc = gwdBody gwd + newBodyFunc render = + el Html5.! attrs $ (bodyFunc render) + return (a,gwd { gwdBody = Body newBodyFunc }) diff --git a/src/Handler/Utils/Table/Pagination/Types.hs b/src/Handler/Utils/Table/Pagination/Types.hs new file mode 100644 index 000000000..c2038c4d0 --- /dev/null +++ b/src/Handler/Utils/Table/Pagination/Types.hs @@ -0,0 +1,40 @@ +{-# LANGUAGE NoImplicitPrelude + , ExistentialQuantification + , RankNTypes + , RecordWildCards + #-} + +module Handler.Utils.Table.Pagination.Types where + +import Import hiding (singleton) + +import Colonnade +import Colonnade.Encode + +data Sortable a = Sortable + { sortableKey :: (Maybe Text) + , sortableContent :: a + } + +sortable :: Maybe Text -> c -> (a -> c) -> Colonnade Sortable a c +sortable k h = singleton (Sortable k h) + +instance Headedness Sortable where + headednessPure = Sortable Nothing + headednessExtract = Just $ \(Sortable _ x) -> x + headednessExtractForall = Just $ ExtractForall (\(Sortable _ x) -> x) + +newtype SortableP s = SortableP { toSortable :: forall a. s a -> Sortable a} + +class Headedness s => ToSortable s where + pSortable :: Maybe (SortableP s) + +instance ToSortable Sortable where + pSortable = Just $ SortableP id + +instance ToSortable Headed where + pSortable = Just $ SortableP (\(Headed x) -> Sortable Nothing x) + +instance ToSortable Headless where + pSortable = Nothing + diff --git a/templates/table-layout-wrapper.hamlet b/templates/table/layout-wrapper.hamlet similarity index 100% rename from templates/table-layout-wrapper.hamlet rename to templates/table/layout-wrapper.hamlet diff --git a/templates/table-layout.hamlet b/templates/table/layout.hamlet similarity index 100% rename from templates/table-layout.hamlet rename to templates/table/layout.hamlet diff --git a/templates/table/sortable-header.hamlet b/templates/table/sortable-header.hamlet new file mode 100644 index 000000000..1054b1ce0 --- /dev/null +++ b/templates/table/sortable-header.hamlet @@ -0,0 +1,7 @@ +^{cellContents} +$maybe flag <- sortableKey +
+
"-asc")}>asc + / + "-desc")}>desc +$nothing diff --git a/templates/table/table.hamlet b/templates/table/table.hamlet new file mode 100644 index 000000000..b1de810bf --- /dev/null +++ b/templates/table/table.hamlet @@ -0,0 +1,12 @@ + + $maybe sortableP <- pSortable + $with toSortable <- toSortable sortableP + + $forall OneColonnade{..} <- getColonnade dbtColonnade + ^{widgetFromCell th $ withSortLinks $ toSortable oneColonnadeHead} + $nothing + + $forall row <- rows + + $forall OneColonnade{..} <- getColonnade dbtColonnade + ^{widgetFromCell td $ oneColonnadeEncode row} From c2174161c502bc1c395a09f74e665e2dfaef57a3 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 4 Apr 2018 15:28:55 +0200 Subject: [PATCH 003/108] Better name for templates/table/table --- src/Handler/Utils/Table/Pagination.hs | 2 +- templates/table/{table.hamlet => colonnade.hamlet} | 0 2 files changed, 1 insertion(+), 1 deletion(-) rename templates/table/{table.hamlet => colonnade.hamlet} (100%) diff --git a/src/Handler/Utils/Table/Pagination.hs b/src/Handler/Utils/Table/Pagination.hs index 6f0c1d4c5..ef3ab45ec 100644 --- a/src/Handler/Utils/Table/Pagination.hs +++ b/src/Handler/Utils/Table/Pagination.hs @@ -150,7 +150,7 @@ dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do bool return (sendResponse <=< tblLayout) psShortcircuit $ do getParams <- handlerToWidget $ queryToQueryText . Wai.queryString . reqWaiRequest <$> getRequest - let table = $(widgetFile "table/table") + let table = $(widgetFile "table/colonnade") pageCount = max 1 . ceiling $ rowCount % psLimit tblLink f = decodeUtf8 . Builder.toLazyByteString . renderQueryText True $ f getParams withSortLinks Sortable{ sortableContent = Cell{..}, .. } = Cell diff --git a/templates/table/table.hamlet b/templates/table/colonnade.hamlet similarity index 100% rename from templates/table/table.hamlet rename to templates/table/colonnade.hamlet From dc45702f32c02eda6fab784cb7d8381310032b70 Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Mon, 9 Apr 2018 22:22:38 +0200 Subject: [PATCH 004/108] added JS and CSS for sortable tables --- src/Foundation.hs | 2 + static/js/featureChecker.js | 3 - static/js/fetchPolyfill.js | 466 +++++++++++++++++++++++++++++++ static/js/urlPolyfill.js | 348 +++++++++++++++++++++++ templates/table/colonnade.julius | 78 ++++++ templates/table/colonnade.lucius | 31 ++ templates/table/layout.hamlet | 6 +- 7 files changed, 929 insertions(+), 5 deletions(-) create mode 100644 static/js/fetchPolyfill.js create mode 100644 static/js/urlPolyfill.js create mode 100644 templates/table/colonnade.julius create mode 100644 templates/table/colonnade.lucius diff --git a/src/Foundation.hs b/src/Foundation.hs index 647dc34a9..b5121435d 100644 --- a/src/Foundation.hs +++ b/src/Foundation.hs @@ -438,6 +438,8 @@ defaultMenuLayout menu widget = do pc <- widgetToPageContent $ do addStylesheetRemote "https://fonts.googleapis.com/css?family=Source+Sans+Pro:300,400,600,800,900" addScript $ StaticR js_featureChecker_js + addScript $ StaticR js_fetchPolyfill_js + addScript $ StaticR js_urlPolyfill_js addStylesheet $ StaticR css_fonts_css addStylesheet $ StaticR css_icons_css $(widgetFile "default-layout") diff --git a/static/js/featureChecker.js b/static/js/featureChecker.js index a3a21e663..ad8e26303 100644 --- a/static/js/featureChecker.js +++ b/static/js/featureChecker.js @@ -1,7 +1,4 @@ window.addEventListener('touchstart', function onFirstTouch() { - // we could use a class document.body.classList.add('touch-supported'); - - // we only need to know once that a human touched the screen, so we can stop listening now window.removeEventListener('touchstart', onFirstTouch, false); }, false); diff --git a/static/js/fetchPolyfill.js b/static/js/fetchPolyfill.js new file mode 100644 index 000000000..ac9a4fd87 --- /dev/null +++ b/static/js/fetchPolyfill.js @@ -0,0 +1,466 @@ +(function(self) { + 'use strict'; + + if (self.fetch) { + return + } + + var support = { + searchParams: 'URLSearchParams' in self, + iterable: 'Symbol' in self && 'iterator' in Symbol, + blob: 'FileReader' in self && 'Blob' in self && (function() { + try { + new Blob() + return true + } catch(e) { + return false + } + })(), + formData: 'FormData' in self, + arrayBuffer: 'ArrayBuffer' in self + } + + if (support.arrayBuffer) { + var viewClasses = [ + '[object Int8Array]', + '[object Uint8Array]', + '[object Uint8ClampedArray]', + '[object Int16Array]', + '[object Uint16Array]', + '[object Int32Array]', + '[object Uint32Array]', + '[object Float32Array]', + '[object Float64Array]' + ] + + var isDataView = function(obj) { + return obj && DataView.prototype.isPrototypeOf(obj) + } + + var isArrayBufferView = ArrayBuffer.isView || function(obj) { + return obj && viewClasses.indexOf(Object.prototype.toString.call(obj)) > -1 + } + } + + function normalizeName(name) { + if (typeof name !== 'string') { + name = String(name) + } + if (/[^a-z0-9\-#$%&'*+.\^_`|~]/i.test(name)) { + throw new TypeError('Invalid character in header field name') + } + return name.toLowerCase() + } + + function normalizeValue(value) { + if (typeof value !== 'string') { + value = String(value) + } + return value + } + + // Build a destructive iterator for the value list + function iteratorFor(items) { + var iterator = { + next: function() { + var value = items.shift() + return {done: value === undefined, value: value} + } + } + + if (support.iterable) { + iterator[Symbol.iterator] = function() { + return iterator + } + } + + return iterator + } + + function Headers(headers) { + this.map = {} + + if (headers instanceof Headers) { + headers.forEach(function(value, name) { + this.append(name, value) + }, this) + } else if (Array.isArray(headers)) { + headers.forEach(function(header) { + this.append(header[0], header[1]) + }, this) + } else if (headers) { + Object.getOwnPropertyNames(headers).forEach(function(name) { + this.append(name, headers[name]) + }, this) + } + } + + Headers.prototype.append = function(name, value) { + name = normalizeName(name) + value = normalizeValue(value) + var oldValue = this.map[name] + this.map[name] = oldValue ? oldValue+','+value : value + } + + Headers.prototype['delete'] = function(name) { + delete this.map[normalizeName(name)] + } + + Headers.prototype.get = function(name) { + name = normalizeName(name) + return this.has(name) ? this.map[name] : null + } + + Headers.prototype.has = function(name) { + return this.map.hasOwnProperty(normalizeName(name)) + } + + Headers.prototype.set = function(name, value) { + this.map[normalizeName(name)] = normalizeValue(value) + } + + Headers.prototype.forEach = function(callback, thisArg) { + for (var name in this.map) { + if (this.map.hasOwnProperty(name)) { + callback.call(thisArg, this.map[name], name, this) + } + } + } + + Headers.prototype.keys = function() { + var items = [] + this.forEach(function(value, name) { items.push(name) }) + return iteratorFor(items) + } + + Headers.prototype.values = function() { + var items = [] + this.forEach(function(value) { items.push(value) }) + return iteratorFor(items) + } + + Headers.prototype.entries = function() { + var items = [] + this.forEach(function(value, name) { items.push([name, value]) }) + return iteratorFor(items) + } + + if (support.iterable) { + Headers.prototype[Symbol.iterator] = Headers.prototype.entries + } + + function consumed(body) { + if (body.bodyUsed) { + return Promise.reject(new TypeError('Already read')) + } + body.bodyUsed = true + } + + function fileReaderReady(reader) { + return new Promise(function(resolve, reject) { + reader.onload = function() { + resolve(reader.result) + } + reader.onerror = function() { + reject(reader.error) + } + }) + } + + function readBlobAsArrayBuffer(blob) { + var reader = new FileReader() + var promise = fileReaderReady(reader) + reader.readAsArrayBuffer(blob) + return promise + } + + function readBlobAsText(blob) { + var reader = new FileReader() + var promise = fileReaderReady(reader) + reader.readAsText(blob) + return promise + } + + function readArrayBufferAsText(buf) { + var view = new Uint8Array(buf) + var chars = new Array(view.length) + + for (var i = 0; i < view.length; i++) { + chars[i] = String.fromCharCode(view[i]) + } + return chars.join('') + } + + function bufferClone(buf) { + if (buf.slice) { + return buf.slice(0) + } else { + var view = new Uint8Array(buf.byteLength) + view.set(new Uint8Array(buf)) + return view.buffer + } + } + + function Body() { + this.bodyUsed = false + + this._initBody = function(body) { + this._bodyInit = body + if (!body) { + this._bodyText = '' + } else if (typeof body === 'string') { + this._bodyText = body + } else if (support.blob && Blob.prototype.isPrototypeOf(body)) { + this._bodyBlob = body + } else if (support.formData && FormData.prototype.isPrototypeOf(body)) { + this._bodyFormData = body + } else if (support.searchParams && URLSearchParams.prototype.isPrototypeOf(body)) { + this._bodyText = body.toString() + } else if (support.arrayBuffer && support.blob && isDataView(body)) { + this._bodyArrayBuffer = bufferClone(body.buffer) + // IE 10-11 can't handle a DataView body. + this._bodyInit = new Blob([this._bodyArrayBuffer]) + } else if (support.arrayBuffer && (ArrayBuffer.prototype.isPrototypeOf(body) || isArrayBufferView(body))) { + this._bodyArrayBuffer = bufferClone(body) + } else { + throw new Error('unsupported BodyInit type') + } + + if (!this.headers.get('content-type')) { + if (typeof body === 'string') { + this.headers.set('content-type', 'text/plain;charset=UTF-8') + } else if (this._bodyBlob && this._bodyBlob.type) { + this.headers.set('content-type', this._bodyBlob.type) + } else if (support.searchParams && URLSearchParams.prototype.isPrototypeOf(body)) { + this.headers.set('content-type', 'application/x-www-form-urlencoded;charset=UTF-8') + } + } + } + + if (support.blob) { + this.blob = function() { + var rejected = consumed(this) + if (rejected) { + return rejected + } + + if (this._bodyBlob) { + return Promise.resolve(this._bodyBlob) + } else if (this._bodyArrayBuffer) { + return Promise.resolve(new Blob([this._bodyArrayBuffer])) + } else if (this._bodyFormData) { + throw new Error('could not read FormData body as blob') + } else { + return Promise.resolve(new Blob([this._bodyText])) + } + } + + this.arrayBuffer = function() { + if (this._bodyArrayBuffer) { + return consumed(this) || Promise.resolve(this._bodyArrayBuffer) + } else { + return this.blob().then(readBlobAsArrayBuffer) + } + } + } + + this.text = function() { + var rejected = consumed(this) + if (rejected) { + return rejected + } + + if (this._bodyBlob) { + return readBlobAsText(this._bodyBlob) + } else if (this._bodyArrayBuffer) { + return Promise.resolve(readArrayBufferAsText(this._bodyArrayBuffer)) + } else if (this._bodyFormData) { + throw new Error('could not read FormData body as text') + } else { + return Promise.resolve(this._bodyText) + } + } + + if (support.formData) { + this.formData = function() { + return this.text().then(decode) + } + } + + this.json = function() { + return this.text().then(JSON.parse) + } + + return this + } + + // HTTP methods whose capitalization should be normalized + var methods = ['DELETE', 'GET', 'HEAD', 'OPTIONS', 'POST', 'PUT'] + + function normalizeMethod(method) { + var upcased = method.toUpperCase() + return (methods.indexOf(upcased) > -1) ? upcased : method + } + + function Request(input, options) { + options = options || {} + var body = options.body + + if (input instanceof Request) { + if (input.bodyUsed) { + throw new TypeError('Already read') + } + this.url = input.url + this.credentials = input.credentials + if (!options.headers) { + this.headers = new Headers(input.headers) + } + this.method = input.method + this.mode = input.mode + if (!body && input._bodyInit != null) { + body = input._bodyInit + input.bodyUsed = true + } + } else { + this.url = String(input) + } + + this.credentials = options.credentials || this.credentials || 'omit' + if (options.headers || !this.headers) { + this.headers = new Headers(options.headers) + } + this.method = normalizeMethod(options.method || this.method || 'GET') + this.mode = options.mode || this.mode || null + this.referrer = null + + if ((this.method === 'GET' || this.method === 'HEAD') && body) { + throw new TypeError('Body not allowed for GET or HEAD requests') + } + this._initBody(body) + } + + Request.prototype.clone = function() { + return new Request(this, { body: this._bodyInit }) + } + + function decode(body) { + var form = new FormData() + body.trim().split('&').forEach(function(bytes) { + if (bytes) { + var split = bytes.split('=') + var name = split.shift().replace(/\+/g, ' ') + var value = split.join('=').replace(/\+/g, ' ') + form.append(decodeURIComponent(name), decodeURIComponent(value)) + } + }) + return form + } + + function parseHeaders(rawHeaders) { + var headers = new Headers() + // Replace instances of \r\n and \n followed by at least one space or horizontal tab with a space + // https://tools.ietf.org/html/rfc7230#section-3.2 + var preProcessedHeaders = rawHeaders.replace(/\r?\n[\t ]+/g, ' ') + preProcessedHeaders.split(/\r?\n/).forEach(function(line) { + var parts = line.split(':') + var key = parts.shift().trim() + if (key) { + var value = parts.join(':').trim() + headers.append(key, value) + } + }) + return headers + } + + Body.call(Request.prototype) + + function Response(bodyInit, options) { + if (!options) { + options = {} + } + + this.type = 'default' + this.status = options.status === undefined ? 200 : options.status + this.ok = this.status >= 200 && this.status < 300 + this.statusText = 'statusText' in options ? options.statusText : 'OK' + this.headers = new Headers(options.headers) + this.url = options.url || '' + this._initBody(bodyInit) + } + + Body.call(Response.prototype) + + Response.prototype.clone = function() { + return new Response(this._bodyInit, { + status: this.status, + statusText: this.statusText, + headers: new Headers(this.headers), + url: this.url + }) + } + + Response.error = function() { + var response = new Response(null, {status: 0, statusText: ''}) + response.type = 'error' + return response + } + + var redirectStatuses = [301, 302, 303, 307, 308] + + Response.redirect = function(url, status) { + if (redirectStatuses.indexOf(status) === -1) { + throw new RangeError('Invalid status code') + } + + return new Response(null, {status: status, headers: {location: url}}) + } + + self.Headers = Headers + self.Request = Request + self.Response = Response + + self.fetch = function(input, init) { + return new Promise(function(resolve, reject) { + var request = new Request(input, init) + var xhr = new XMLHttpRequest() + + xhr.onload = function() { + var options = { + status: xhr.status, + statusText: xhr.statusText, + headers: parseHeaders(xhr.getAllResponseHeaders() || '') + } + options.url = 'responseURL' in xhr ? xhr.responseURL : options.headers.get('X-Request-URL') + var body = 'response' in xhr ? xhr.response : xhr.responseText + resolve(new Response(body, options)) + } + + xhr.onerror = function() { + reject(new TypeError('Network request failed')) + } + + xhr.ontimeout = function() { + reject(new TypeError('Network request failed')) + } + + xhr.open(request.method, request.url, true) + + if (request.credentials === 'include') { + xhr.withCredentials = true + } else if (request.credentials === 'omit') { + xhr.withCredentials = false + } + + if ('responseType' in xhr && support.blob) { + xhr.responseType = 'blob' + } + + request.headers.forEach(function(value, name) { + xhr.setRequestHeader(name, value) + }) + + xhr.send(typeof request._bodyInit === 'undefined' ? null : request._bodyInit) + }) + } + self.fetch.polyfill = true +})(typeof self !== 'undefined' ? self : this); \ No newline at end of file diff --git a/static/js/urlPolyfill.js b/static/js/urlPolyfill.js new file mode 100644 index 000000000..e38c12021 --- /dev/null +++ b/static/js/urlPolyfill.js @@ -0,0 +1,348 @@ +(function(global) { + /** + * Polyfill URLSearchParams + * + * Inspired from : https://github.com/WebReflection/url-search-params/blob/master/src/url-search-params.js + */ + + var checkIfIteratorIsSupported = function() { + try { + return !!Symbol.iterator; + } catch(error) { + return false; + } + }; + + + var iteratorSupported = checkIfIteratorIsSupported(); + + var createIterator = function(items) { + var iterator = { + next: function() { + var value = items.shift(); + return { done: value === void 0, value: value }; + } + }; + + if(iteratorSupported) { + iterator[Symbol.iterator] = function() { + return iterator; + }; + } + + return iterator; + }; + + /** + * Search param name and values should be encoded according to https://url.spec.whatwg.org/#urlencoded-serializing + * encodeURIComponent() produces the same result except encoding spaces as `%20` instead of `+`. + */ + var serializeParam = function(value) { + return encodeURIComponent(value).replace(/%20/g, '+'); + }; + + var deserializeParam = function(value) { + return decodeURIComponent(value).replace(/\+/g, ' '); + }; + + var polyfillURLSearchParams= function() { + + var URLSearchParams = function(searchString) { + Object.defineProperty(this, '_entries', { value: {} }); + + if(typeof searchString === 'string') { + if(searchString !== '') { + searchString = searchString.replace(/^\?/, ''); + var attributes = searchString.split('&'); + var attribute; + for(var i = 0; i < attributes.length; i++) { + attribute = attributes[i].split('='); + this.append( + deserializeParam(attribute[0]), + (attribute.length > 1) ? deserializeParam(attribute[1]) : '' + ); + } + } + } else if(searchString instanceof URLSearchParams) { + var _this = this; + searchString.forEach(function(value, name) { + _this.append(value, name); + }); + } + }; + + var proto = URLSearchParams.prototype; + + proto.append = function(name, value) { + if(name in this._entries) { + this._entries[name].push(value.toString()); + } else { + this._entries[name] = [value.toString()]; + } + }; + + proto.delete = function(name) { + delete this._entries[name]; + }; + + proto.get = function(name) { + return (name in this._entries) ? this._entries[name][0] : null; + }; + + proto.getAll = function(name) { + return (name in this._entries) ? this._entries[name].slice(0) : []; + }; + + proto.has = function(name) { + return (name in this._entries); + }; + + proto.set = function(name, value) { + this._entries[name] = [value.toString()]; + }; + + proto.forEach = function(callback, thisArg) { + var entries; + for(var name in this._entries) { + if(this._entries.hasOwnProperty(name)) { + entries = this._entries[name]; + for(var i = 0; i < entries.length; i++) { + callback.call(thisArg, entries[i], name, this); + } + } + } + }; + + proto.keys = function() { + var items = []; + this.forEach(function(value, name) { items.push(name); }); + return createIterator(items); + }; + + proto.values = function() { + var items = []; + this.forEach(function(value) { items.push(value); }); + return createIterator(items); + }; + + proto.entries = function() { + var items = []; + this.forEach(function(value, name) { items.push([name, value]); }); + return createIterator(items); + }; + + if(iteratorSupported) { + proto[Symbol.iterator] = proto.entries; + } + + proto.toString = function() { + var searchString = ''; + this.forEach(function(value, name) { + if(searchString.length > 0) searchString+= '&'; + searchString += serializeParam(name) + '=' + serializeParam(value); + }); + return searchString; + }; + + global.URLSearchParams = URLSearchParams; + }; + + if(!('URLSearchParams' in global) || (new URLSearchParams('?a=1').toString() !== 'a=1')) { + polyfillURLSearchParams(); + } + + // HTMLAnchorElement + +})( + (typeof global !== 'undefined') ? global + : ((typeof window !== 'undefined') ? window + : ((typeof self !== 'undefined') ? self : this)) +); + +(function(global) { + /** + * Polyfill URL + * + * Inspired from : https://github.com/arv/DOM-URL-Polyfill/blob/master/src/url.js + */ + + var checkIfURLIsSupported = function() { + try { + var u = new URL('b', 'http://a'); + u.pathname = 'c%20d'; + return (u.href === 'http://a/c%20d') && u.searchParams; + } catch(e) { + return false; + } + }; + + + var polyfillURL = function() { + var _URL = global.URL; + + var URL = function(url, base) { + if(typeof url !== 'string') url = String(url); + + var doc = document.implementation.createHTMLDocument(''); + window.doc = doc; + if(base) { + var baseElement = doc.createElement('base'); + baseElement.href = base; + doc.head.appendChild(baseElement); + } + + var anchorElement = doc.createElement('a'); + anchorElement.href = url; + doc.body.appendChild(anchorElement); + anchorElement.href = anchorElement.href; // force href to refresh + + if(anchorElement.protocol === ':' || !/:/.test(anchorElement.href)) { + throw new TypeError('Invalid URL'); + } + + Object.defineProperty(this, '_anchorElement', { + value: anchorElement + }); + }; + + var proto = URL.prototype; + + var linkURLWithAnchorAttribute = function(attributeName) { + Object.defineProperty(proto, attributeName, { + get: function() { + return this._anchorElement[attributeName]; + }, + set: function(value) { + this._anchorElement[attributeName] = value; + }, + enumerable: true + }); + }; + + ['hash', 'host', 'hostname', 'port', 'protocol', 'search'] + .forEach(function(attributeName) { + linkURLWithAnchorAttribute(attributeName); + }); + + Object.defineProperties(proto, { + + 'toString': { + get: function() { + var _this = this; + return function() { + return _this.href; + }; + } + }, + + 'href' : { + get: function() { + return this._anchorElement.href.replace(/\?$/,''); + }, + set: function(value) { + this._anchorElement.href = value; + }, + enumerable: true + }, + + 'pathname' : { + get: function() { + return this._anchorElement.pathname.replace(/(^\/?)/,'/'); + }, + set: function(value) { + this._anchorElement.pathname = value; + }, + enumerable: true + }, + + 'origin': { + get: function() { + // get expected port from protocol + var expectedPort = {'http:': 80, 'https:': 443, 'ftp:': 21}[this._anchorElement.protocol]; + // add port to origin if, expected port is different than actual port + // and it is not empty f.e http://foo:8080 + // 8080 != 80 && 8080 != '' + var addPortToOrigin = this._anchorElement.port != expectedPort && + this._anchorElement.port !== '' + + return this._anchorElement.protocol + + '//' + + this._anchorElement.hostname + + (addPortToOrigin ? (':' + this._anchorElement.port) : ''); + }, + enumerable: true + }, + + 'password': { // TODO + get: function() { + return ''; + }, + set: function(value) { + }, + enumerable: true + }, + + 'username': { // TODO + get: function() { + return ''; + }, + set: function(value) { + }, + enumerable: true + }, + + 'searchParams': { + get: function() { + var searchParams = new URLSearchParams(this.search); + var _this = this; + ['append', 'delete', 'set'].forEach(function(methodName) { + var method = searchParams[methodName]; + searchParams[methodName] = function() { + method.apply(searchParams, arguments); + _this.search = searchParams.toString(); + }; + }); + return searchParams; + }, + enumerable: true + } + }); + + URL.createObjectURL = function(blob) { + return _URL.createObjectURL.apply(_URL, arguments); + }; + + URL.revokeObjectURL = function(url) { + return _URL.revokeObjectURL.apply(_URL, arguments); + }; + + global.URL = URL; + + }; + + if(!checkIfURLIsSupported()) { + polyfillURL(); + } + + if((global.location !== void 0) && !('origin' in global.location)) { + var getOrigin = function() { + return global.location.protocol + '//' + global.location.hostname + (global.location.port ? (':' + global.location.port) : ''); + }; + + try { + Object.defineProperty(global.location, 'origin', { + get: getOrigin, + enumerable: true + }); + } catch(e) { + setInterval(function() { + global.location.origin = getOrigin(); + }, 100); + } + } + +})( + (typeof global !== 'undefined') ? global + : ((typeof window !== 'undefined') ? window + : ((typeof self !== 'undefined') ? self : this)) +); diff --git a/templates/table/colonnade.julius b/templates/table/colonnade.julius new file mode 100644 index 000000000..fc6a7c2c8 --- /dev/null +++ b/templates/table/colonnade.julius @@ -0,0 +1,78 @@ +(function collonadeClosure() { + 'use strict'; + + document.addEventListener('DOMContentLoaded', function DOMContentLoaded() { + + var ASC = 'asc'; + var DESC = 'desc'; + + var table = document.querySelector('table'); + var ths = Array.from(table.querySelectorAll('th')); + + // attach click handler to each table-header + ths.map(function(th) { + th.addEventListener('click', clickHandler); + }); + + // handles click on table header + function clickHandler(event) { + event.preventDefault(); + // should instead be smthg like: JSON.parse(this.dataset.sortparams); + // hardcoded for now + var sortParams = {sorting: 'name', prefix: 'terms'}; + if (sortParams.order) { + sortParams.order = sortParams.order === ASC ? DESC : ASC; + } else { + sortParams.order = ASC; + } + var params = makeParams(sortParams.prefix, sortParams); + var url = new URL(window.location); + for (var p in params) { + url.searchParams.set(p, params[p]); + } + fetchTableFrom(url); + markSorted(this, sortParams.order); + } + + function markSorted(th, order) { + ths.forEach(function(th) { + th.classList.remove('sorted-asc', 'sorted-desc'); + }); + th.classList.add('sorted-' + order); + } + + // fetches new sorted table from url with params and replaces contents of current table + function fetchTableFrom(url) { + fetch(url, { + credentials: 'same-origin' + }).then(function(response) { + if (!response.ok) { + throw ('Looks like there was a problem fetching ' + url.toString() + '. Status Code: ' + response.status); + } + // Examine the text in the response + response.text().then(function(data) { + // replace contents of table body + table.querySelector('tbody').innerHTML = data; + }); + }).catch(function(err) { + console.error(err); + }); + } + + // returns default sort-params for with specific prefix + function makeParams(prefix, custom) { + var defaultParams = Object.assign({ + pagesize: 20, + page: 0, + order: ASC + }, custom); + var res = {}; + for (var p in defaultParams) { + res[prefix + '-' + p] = defaultParams[p]; + } + res['table-only'] = 'true'; + return res; + } + + }); +})(); diff --git a/templates/table/colonnade.lucius b/templates/table/colonnade.lucius new file mode 100644 index 000000000..4fcdad6e2 --- /dev/null +++ b/templates/table/colonnade.lucius @@ -0,0 +1,31 @@ +table th { + cursor: pointer; + position: relative; + padding-right: 20px; +} + +table th.sorted-asc, +table th.sorted-desc { + color: var(--lightbase); +} + +table th.sorted-asc::after, +table th.sorted-desc::after { + content: ''; + position: absolute; + right: 0; + top: 15px; + width: 0; + height: 0; + transform: translateY(-100%); + border-left: 8px solid transparent; + border-right: 8px solid transparent; +} + +table th.sorted-asc::after { + border-top: 8px solid var(--lightbase); +} + +table th.sorted-desc::after { + border-bottom: 8px solid var(--lightbase); +} diff --git a/templates/table/layout.hamlet b/templates/table/layout.hamlet index d268dad12..009e4eb2c 100644 --- a/templates/table/layout.hamlet +++ b/templates/table/layout.hamlet @@ -1,4 +1,6 @@
^{table} -

- _{MsgPage (succ psPage) pageCount} + $if pageCount > 1 +

+ $# TODO: foreach (reachable pages) print link to that page + _{MsgPage (succ psPage) pageCount} From 48963307377a2559c8a34bb06360fb2cfeb7fe5c Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Mon, 9 Apr 2018 22:23:12 +0200 Subject: [PATCH 005/108] removed pure-JS sorting for sortable tables --- src/Foundation.hs | 1 - templates/home.hamlet | 37 --------- templates/standalone/sortable.hamlet | 1 - templates/standalone/sortable.julius | 107 --------------------------- templates/standalone/sortable.lucius | 31 -------- 5 files changed, 177 deletions(-) delete mode 100644 templates/standalone/sortable.hamlet delete mode 100644 templates/standalone/sortable.julius delete mode 100644 templates/standalone/sortable.lucius diff --git a/src/Foundation.hs b/src/Foundation.hs index b5121435d..4efca5572 100644 --- a/src/Foundation.hs +++ b/src/Foundation.hs @@ -445,7 +445,6 @@ defaultMenuLayout menu widget = do $(widgetFile "default-layout") $(widgetFile "standalone/modal") $(widgetFile "standalone/showHide") - $(widgetFile "standalone/sortable") $(widgetFile "standalone/inputs") withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet") diff --git a/templates/home.hamlet b/templates/home.hamlet index 0ee62ec29..a0b39a8ef 100644 --- a/templates/home.hamlet +++ b/templates/home.hamlet @@ -26,43 +26,6 @@

  • Dateien hochladen und abrufen -
    -
    -

    Tabellen -

  • - - - - - - - - -
    ID - TH1 - TH2 - TH3 -
    0 - NT2 - CON2 - 3 -
    1 - 5 - ONT2 - 13 -
    2 - CONT1 - NT2 - 43 -
    3 - 43 - T2C2 - 35 -
    4 - 73 - CA62 - 7 -

    Funktionen zum Testen diff --git a/templates/standalone/sortable.hamlet b/templates/standalone/sortable.hamlet deleted file mode 100644 index 3c42cc911..000000000 --- a/templates/standalone/sortable.hamlet +++ /dev/null @@ -1 +0,0 @@ - diff --git a/templates/standalone/sortable.julius b/templates/standalone/sortable.julius deleted file mode 100644 index 4b988e487..000000000 --- a/templates/standalone/sortable.julius +++ /dev/null @@ -1,107 +0,0 @@ -/** - * delcare a table as sortable by adding class 'js-sortable' - */ - (function() { - 'use strict'; - - window.utils = window.utils || {}; - - window.utils.sortable = function(table) { - var ASC = 1; - var DESC = -1; - - var trs, ths, sortBy, sortDir, trContents; - - function setup() { - trs = table.querySelectorAll('tr'); - ths = table.querySelectorAll('th'); - sortBy = 0; - sortDir = ASC; - trContents = []; - - Array.from(trs).forEach(function(tr, rowIndex) { - if (rowIndex === 0) { - // register table headers as sort-listener - Array.from(tr.querySelectorAll('th')).forEach(function(th, thIndex) { - th.addEventListener('click', function(el) { - sortTableBy(thIndex); - }); - }); - } else { - // register table rows - trContents.push(Array.from(tr.querySelectorAll('td')).map(function(td) { - return td.innerHTML; - })); - } - }); - } - setup(); - - function updateThs(thIndex, sortOrder) { - Array.from(ths).forEach(function (th) { - th.classList.remove('sorted-asc', 'sorted-desc'); - }); - var suffix = sortOrder > 0 ? 'asc' : 'desc'; - ths[thIndex].classList.add('sorted-' + suffix); - } - - function sortTableBy(thIndex) { - var sortKey = thIndex; - var sortOrder = ASC; - if (sortBy === sortKey) { - sortOrder = sortDir === ASC ? DESC : ASC; - } - - trContents.sort(dynamicSortByType(sortKey, sortOrder)); - trContents.sort(dynamicSortByKey(sortKey, sortOrder)); - sortBy = thIndex; - sortDir = sortOrder; - updateThs(thIndex, sortOrder); - - Array.from(trs).forEach(function(tr, trIndex) { - if (trIndex > 0) { - Array.from(tr.querySelectorAll('td')).forEach(function (td, tdIndex) { - td.innerHTML = trContents[trIndex - 1][tdIndex]; - }); - } - }); - } - - function dynamicSortByKey(key, order) { - return function (a,b) { - var aVal = parseInt(a[key]); - var bVal = parseInt(b[key]); - if ((isNaN(aVal) && !isNaN(bVal)) || (!isNaN(aVal) && isNaN(bVal))) { - return 1; - } - aVal = isNaN(aVal) ? a[key] : aVal; - bVal = isNaN(bVal) ? b[key] : bVal; - var result = (aVal < bVal) ? -1 : (aVal > bVal) ? 1 : 0; - return result * order; - } - } - - function dynamicSortByType(key, order) { - return function (a,b) { - var aVal = parseInt(a[key]); - var bVal = parseInt(b[key]); - aVal = isNaN(aVal) ? a[key] : aVal; - bVal = isNaN(bVal) ? b[key] : bVal; - var res = (aVal < bVal ? -1 : aVal > bVal ? 1 : 0); - if (isNaN(aVal) && !isNaN(bVal)) { - res = -1; - } - if (!isNaN(aVal) && isNaN(bVal)) { - res = 1; - } - return res * order; - } - } - }; - })(); - -document.addEventListener('DOMContentLoaded', function() { - Array.from(document.querySelectorAll('.js-sortable')).forEach(function(table) { - utils.sortable(table); - }); -}); diff --git a/templates/standalone/sortable.lucius b/templates/standalone/sortable.lucius deleted file mode 100644 index 2afb76611..000000000 --- a/templates/standalone/sortable.lucius +++ /dev/null @@ -1,31 +0,0 @@ -table.js-sortable th { - cursor: pointer; - position: relative; - padding-right: 20px; -} - -table.js-sortable th.sorted-asc, -table.js-sortable th.sorted-desc { - color: var(--darkbase); -} - -table.js-sortable th.sorted-asc::after, -table.js-sortable th.sorted-desc::after { - content: ''; - position: absolute; - right: 0; - top: 15px; - width: 0; - height: 0; - transform: translateY(-100%); - border-left: 8px solid transparent; - border-right: 8px solid transparent; -} - -table.js-sortable th.sorted-asc::after { - border-top: 8px solid var(--lightbase); -} - -table.js-sortable th.sorted-desc::after { - border-bottom: 8px solid var(--lightbase); -} From 040abcab086bfde92e4620cd5e2bfff5a34fb9e4 Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Mon, 9 Apr 2018 23:36:43 +0200 Subject: [PATCH 006/108] less url-building in frontend for sortable tables --- templates/table/colonnade.hamlet | 2 +- templates/table/colonnade.julius | 59 ++++++++++++-------------------- 2 files changed, 22 insertions(+), 39 deletions(-) diff --git a/templates/table/colonnade.hamlet b/templates/table/colonnade.hamlet index b1de810bf..ef6b1bdbd 100644 --- a/templates/table/colonnade.hamlet +++ b/templates/table/colonnade.hamlet @@ -1,4 +1,4 @@ - +
    $maybe sortableP <- pSortable $with toSortable <- toSortable sortableP diff --git a/templates/table/colonnade.julius b/templates/table/colonnade.julius index fc6a7c2c8..840cccd6a 100644 --- a/templates/table/colonnade.julius +++ b/templates/table/colonnade.julius @@ -6,32 +6,27 @@ var ASC = 'asc'; var DESC = 'desc'; + // TODO: Make use of interpolated dbtIdent var table = document.querySelector('table'); var ths = Array.from(table.querySelectorAll('th')); // attach click handler to each table-header ths.map(function(th) { - th.addEventListener('click', clickHandler); + var link = th.querySelector('a'); + if (link) { + link.addEventListener('click', clickHandler); + } }); // handles click on table header function clickHandler(event) { event.preventDefault(); - // should instead be smthg like: JSON.parse(this.dataset.sortparams); - // hardcoded for now - var sortParams = {sorting: 'name', prefix: 'terms'}; - if (sortParams.order) { - sortParams.order = sortParams.order === ASC ? DESC : ASC; - } else { - sortParams.order = ASC; - } - var params = makeParams(sortParams.prefix, sortParams); - var url = new URL(window.location); - for (var p in params) { - url.searchParams.set(p, params[p]); - } - fetchTableFrom(url); - markSorted(this, sortParams.order); + var url = new URL(window.location.origin + window.location.pathname + this.getAttribute('href')); + var order = this.parentNode.dataset.order || ASC; + // TODO: not working here... getting whole page as response... + url.searchParams.set('table-only', 'true'); + updateTableFrom(url); + markSorted(this.parentNode, order); } function markSorted(th, order) { @@ -39,40 +34,28 @@ th.classList.remove('sorted-asc', 'sorted-desc'); }); th.classList.add('sorted-' + order); + th.dataset.order = order; } // fetches new sorted table from url with params and replaces contents of current table - function fetchTableFrom(url) { + function updateTableFrom(url) { fetch(url, { - credentials: 'same-origin' + headers: { + 'Accept': 'text/html' + } }).then(function(response) { + var contentType = response.headers.get("content-type"); if (!response.ok) { throw ('Looks like there was a problem fetching ' + url.toString() + '. Status Code: ' + response.status); } - // Examine the text in the response - response.text().then(function(data) { - // replace contents of table body - table.querySelector('tbody').innerHTML = data; - }); + return response.text(); + }).then(function(data) { + // replace contents of table body + table.querySelector('tbody').innerHTML = data; }).catch(function(err) { console.error(err); }); } - // returns default sort-params for with specific prefix - function makeParams(prefix, custom) { - var defaultParams = Object.assign({ - pagesize: 20, - page: 0, - order: ASC - }, custom); - var res = {}; - for (var p in defaultParams) { - res[prefix + '-' + p] = defaultParams[p]; - } - res['table-only'] = 'true'; - return res; - } - }); })(); From a544c61be2d2b13690bc54286bafe4a25b6222c3 Mon Sep 17 00:00:00 2001 From: SJost Date: Tue, 10 Apr 2018 12:50:20 +0200 Subject: [PATCH 007/108] Submission upload (Sitzung mit Gregor) --- messages/de.msg | 4 ++- routes | 17 ++++++---- src/CryptoID.hs | 14 ++++++++ src/Foundation.hs | 14 ++++---- src/Handler/CryptoIDDispatch.hs | 12 +++++-- src/Handler/Sheet.hs | 30 +---------------- src/Handler/Submission.hs | 60 ++++++++++++++++++++++++++++++--- src/Handler/Utils.hs | 7 ++-- src/Handler/Utils/Form.hs | 2 +- src/Model/Types.hs | 3 ++ templates/submission.hamlet | 2 +- 11 files changed, 110 insertions(+), 55 deletions(-) diff --git a/messages/de.msg b/messages/de.msg index fb15e4fea..44b84282e 100644 --- a/messages/de.msg +++ b/messages/de.msg @@ -23,4 +23,6 @@ UnauthorizedSchoolLecturer: Sie sind nicht als Veranstalter für dieses Institut UnauthorizedLecturer: Sie sind nicht als Veranstalter für diese Veranstaltung eingetragen. UnauthorizedCorrector: Sie sind nicht als Korrektor für diese Veranstaltung eingetragen. UnauthorizedParticipant: Sie sind nicht als Teilnehmer für diese Veranstaltung registriert. -OnlyUploadOneFile: Bitte nur eine Datei hochladen. \ No newline at end of file +OnlyUploadOneFile: Bitte nur eine Datei hochladen. +SubmissionWrongSheet: Abgabenummer gehört nicht zum angegebenen Übungsblatt. +SubmissionTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termToText tid}-#{courseShortHand} #{sheetName}: Abgabe diff --git a/routes b/routes index 075a60fd4..9552688ea 100644 --- a/routes +++ b/routes @@ -20,17 +20,20 @@ /edit CourseEditR GET POST !lecturer /ex SheetR !registered: - / SheetListR GET - /#Text/show SheetShowR GET !time - /#Text/#SheetFileType/#FilePath SheetFileR GET !time - /new SheetNewR GET POST !lecturer - /#Text/edit SheetEditR GET POST !lecturer - /#Text/delete SheetDelR GET POST !lecturer + / SheetListR GET + /#Text/show SheetShowR GET !time + /#Text/#SheetFileType/#FilePath SheetFileR GET !time + /new SheetNewR GET POST !lecturer + /#Text/edit SheetEditR GET POST !lecturer + /#Text/delete SheetDelR GET POST !lecturer + !/#Text/submission/#SubmissionMode SubmissionR GET POST !time + + -- TODO below /submission SubmissionListR GET POST -/submission/#CryptoUUIDSubmission SubmissionR GET POST +/submission/#CryptoUUIDSubmission SubmissionDemoR GET POST /submissions.zip SubmissionDownloadMultiArchiveR POST !/submission/archive/#FilePath SubmissionDownloadArchiveR GET !/submission/#CryptoUUIDSubmission/#FilePath SubmissionDownloadSingleR GET diff --git a/src/CryptoID.hs b/src/CryptoID.hs index ed2864eab..7c04d7b3f 100644 --- a/src/CryptoID.hs +++ b/src/CryptoID.hs @@ -1,4 +1,5 @@ {-# LANGUAGE DataKinds #-} +{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} @@ -37,3 +38,16 @@ decCryptoIDs [ ''SubmissionId , ''FileId ] {- TODO: Do we need/want CryptoUUIDs for Sheet numbers? -} + + + +newtype SubmissionMode = SubmissionMode (Maybe CryptoUUIDSubmission) + deriving (Show, Read, Eq) + +instance PathPiece SubmissionMode where + fromPathPiece "new" = Just $ SubmissionMode Nothing + fromPathPiece s = SubmissionMode . Just <$> fromPathPiece s + + toPathPiece (SubmissionMode Nothing) = "new" + toPathPiece (SubmissionMode (Just x)) = toPathPiece x + diff --git a/src/Foundation.hs b/src/Foundation.hs index 1ca4de6fa..b4acfa24d 100644 --- a/src/Foundation.hs +++ b/src/Foundation.hs @@ -244,7 +244,7 @@ isAuthorizedDB route@(routeAttrs -> attrs) writeable isAuthorizedDB UsersR _ = adminAccess Nothing -isAuthorizedDB (SubmissionR cID) _ = submissionAccess $ Right cID +isAuthorizedDB (SubmissionDemoR cID) _ = return Authorized -- submissionAccess $ Right cID isAuthorizedDB (SubmissionDownloadSingleR cID _) _ = submissionAccess $ Right cID isAuthorizedDB (SubmissionDownloadArchiveR (splitExtension -> (baseName, _))) _ = submissionAccess . Left . CryptoID $ CI.mk baseName isAuthorizedDB TermEditR _ = adminAccess Nothing @@ -254,10 +254,11 @@ isAuthorizedDB (CourseR t c CourseEditR) _ = courseLecturerAccess . entity isAuthorizedDB (CourseR t c (SheetR SheetListR)) False = return Authorized -- isAuthorizedDB (CourseR t c (SheetR SheetListR)) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c) isAuthorizedDB (CourseR t c (SheetR (SheetShowR s))) _ = return Authorized -- TODO: nur für angemeldete Kursteilnehmer falls sichtbar, sonst nur Lectrurer oder Korrektor -isAuthorizedDB (CourseR t c (SheetR (SheetFileR s _ _))) _ = return Authorized -- TODO: nur für angemeldete Kursteilnehmer falls sichtbar, sonst nur Lectrurer oder Korrektor -isAuthorizedDB (CourseR t c (SheetR SheetNewR)) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c) -isAuthorizedDB (CourseR t c (SheetR (SheetEditR s))) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c) -isAuthorizedDB (CourseR t c (SheetR (SheetDelR s))) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c) +isAuthorizedDB (CourseR t c (SheetR (SheetFileR s _ _))) _ = return Authorized -- TODO: nur für angemeldete Kursteilnehmer falls sichtbar, sonst nur Lectrurer oder Korrektor +isAuthorizedDB (CourseR t c (SheetR SheetNewR)) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c) +isAuthorizedDB (CourseR t c (SheetR (SheetEditR s))) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c) +isAuthorizedDB (CourseR t c (SheetR (SheetDelR s))) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c) +isAuthorizedDB (CourseR t c (SheetR (SubmissionR s m))) _ = return Authorized -- TODO -- submissionAccess $ Right cID isAuthorizedDB (CourseEditIDR cID) _ = do courseId <- decrypt cID courseLecturerAccess courseId @@ -339,9 +340,10 @@ instance YesodBreadcrumbs UniWorX where breadcrumb (CourseR tid csh (SheetR (SheetShowR shn))) = return (shn, Just $ CourseR tid csh $ SheetR SheetListR) breadcrumb (CourseR tid csh (SheetR (SheetEditR shn))) = return ("Edit", Just $ CourseR tid csh $ SheetR $ SheetShowR shn) breadcrumb (CourseR tid csh (SheetR (SheetDelR shn))) = return ("DELETE", Just $ CourseR tid csh $ SheetR $ SheetShowR shn) + breadcrumb (CourseR tid csh (SheetR (SubmissionR shn _))) = return ("Abgabe", Just $ CourseR tid csh $ SheetR $ SheetShowR shn) breadcrumb SubmissionListR = return ("Abgaben", Just HomeR) - breadcrumb (SubmissionR _) = return ("Abgabe", Just SubmissionListR) + breadcrumb HomeR = return ("UniworkY", Nothing) breadcrumb (AuthR _) = return ("Login", Just HomeR) diff --git a/src/Handler/CryptoIDDispatch.hs b/src/Handler/CryptoIDDispatch.hs index 0eff808f2..c604d3e45 100644 --- a/src/Handler/CryptoIDDispatch.hs +++ b/src/Handler/CryptoIDDispatch.hs @@ -20,6 +20,8 @@ import Import hiding (Proxy) import Data.Proxy +import Handler.Utils + import Yesod.Core.Types (HandlerContents(..), ErrorResponse(..)) import qualified Control.Monad.Catch as E (Handler(..)) @@ -30,9 +32,13 @@ class CryptoRoute ciphertext plaintext where instance CryptoRoute UUID SubmissionId where cryptoIDRoute _ (CryptoID -> cID) = do - (_ :: SubmissionId) <- decrypt cID - - return $ SubmissionR cID + (smid :: SubmissionId) <- decrypt cID + (tid,csh,shn) <- runDB $ do + shid <- submissionSheetId <$> get404 smid + Sheet{..} <- get404 shid + Course{..} <- get404 sheetCourseId + return (courseTermId, courseShorthand, sheetName) + return $ CourseR tid csh $ SheetR $ SubmissionR shn $ SubmissionMode $ Just cID class Dispatch ciphertext (x :: [*]) where diff --git a/src/Handler/Sheet.hs b/src/Handler/Sheet.hs index a7f672cc7..4f3b8bf9a 100644 --- a/src/Handler/Sheet.hs +++ b/src/Handler/Sheet.hs @@ -118,35 +118,7 @@ makeSheetForm msId template = identForm FIDsheet $ \html -> do ] ] -fetchSheetAux :: ( BaseBackend backend ~ SqlBackend - , E.SqlSelect b a - , Typeable a, MonadHandler m, IsPersistBackend backend - , PersistQueryRead backend, PersistUniqueRead backend - ) - => (E.SqlExpr (Entity Sheet) -> b) - -> Key Term -> Text -> Text -> ReaderT backend m a -fetchSheetAux prj tid csh shn = - let cachId = encodeUtf8 $ tshow (tid,csh,shn) - in cachedBy cachId $ do - -- Mit Yesod: - -- cid <- getKeyBy404 $ CourseTermShort tid csh - -- getBy404 $ CourseSheet cid shn - -- Mit Esqueleto: - sheetList <- E.select . E.from $ \(course `E.InnerJoin` sheet) -> do - E.on $ course E.^. CourseId E.==. sheet E.^. SheetCourseId - E.where_ $ course E.^. CourseTermId E.==. E.val tid - E.&&. course E.^. CourseShorthand E.==. E.val csh - E.&&. sheet E.^. SheetName E.==. E.val shn - return $ prj sheet - case sheetList of - [sheet] -> return sheet - _other -> notFound -fetchSheet :: TermId -> Text -> Text -> YesodDB UniWorX (Entity Sheet) -fetchSheet = fetchSheetAux id - -fetchSheetId :: TermId -> Text -> Text -> YesodDB UniWorX (Key Sheet) -fetchSheetId tid cid shn = E.unValue <$> fetchSheetAux (E.^. SheetId) tid cid shn -- List Sheets getSheetListCID :: CourseId -> Handler Html @@ -205,6 +177,7 @@ getSheetList courseEnt = do then [whamlet|Es wurden noch keine Übungsblätter angelegt.|] else encodeWidgetTable tableDefault colSheets sheets + -- Show single sheet getSheetShowR :: TermId -> Text -> Text -> Handler Html getSheetShowR tid csh shn = do @@ -228,7 +201,6 @@ getSheetShowR tid csh shn = do $(widgetFile "sheetShow") [whamlet| Under Construction !!! |] -- TODO - getSheetFileR :: TermId -> Text -> Text -> SheetFileType -> FilePath -> Handler TypedContent getSheetFileR tid csh shn typ title = do content <- runDB $ E.select $ E.from $ diff --git a/src/Handler/Submission.hs b/src/Handler/Submission.hs index 3e2160d28..a321b4ddd 100644 --- a/src/Handler/Submission.hs +++ b/src/Handler/Submission.hs @@ -24,6 +24,7 @@ import Control.Monad.Trans.Maybe import Control.Monad.State.Class import Control.Monad.Trans.State.Strict (StateT) +import qualified Data.Maybe import qualified Data.Text as Text import qualified Data.Text.Encoding as Text import qualified Data.CaseInsensitive as CI @@ -42,6 +43,55 @@ import Colonnade import Yesod.Colonnade import qualified Text.Blaze.Html5.Attributes as HA + + +makeSubmissionForm :: Bool -> Form (Source Handler File) +makeSubmissionForm unpackZips = identForm FIDsubmission $ \html -> do + flip (renderAForm FormStandard) html $ + areq (zipFileField unpackZips) "Zip Archiv zur Abgabe" Nothing + <* submitButton + +getSubmissionR, postSubmissionR :: TermId -> Text -> Text -> SubmissionMode -> Handler Html +getSubmissionR = postSubmissionR +postSubmissionR tid csh shn (SubmissionMode mcid) = do + uid <- requireAuthId + msmid <- traverse decrypt mcid + shid <- runDB $ do + shid <- fetchSheetId tid csh shn + case msmid of + Nothing -> return shid + (Just smid) -> do + shid' <- submissionSheetId <$> get404 smid + when (shid /= shid') $ invalidArgsI [MsgSubmissionWrongSheet] + return shid + let unpackZips = True -- undefined -- TODO + ((res,formWidget), formEnctype) <- runFormPost $ makeSubmissionForm unpackZips + case res of + (FormSuccess files) -> do + smid <- runDB $ runConduit $ + transPipe lift files .| Conduit.map Left .| sinkSubmission shid uid ((,False) <$> msmid) + cID <- encrypt smid + redirect $ CourseR tid csh $ SheetR $ SubmissionR shn $ SubmissionMode $ Just cID + (FormFailure msgs) -> forM_ msgs $ (addMessage "warning") . toHtml + _other -> return () + + let pageTitle = MsgSubmissionTitle (unTermKey tid) csh shn + let formTitle = pageTitle + let formText = Nothing :: Maybe UniWorXMessage + actionUrl <- Data.Maybe.fromJust <$> getCurrentRoute + defaultLayout $ do + setTitleI pageTitle + $(widgetFile "formPageI18n") + + + + + + + +------------------------- DEMO BELOW + + submissionTable :: MForm Handler (FormResult [SubmissionId], Widget) submissionTable = do subs <- lift . runDB $ E.select . E.from $ \(sub `E.InnerJoin` sheet `E.InnerJoin` course) -> do @@ -56,7 +106,7 @@ submissionTable = do let anchorCourse (_, _, (_, _, Entity _ Course{..})) = CourseR courseTermId courseShorthand CourseShowR courseText (_, _, (_, _, Entity _ Course{..})) = toWidget courseName - anchorSubmission (_, cUUID, _) = SubmissionR cUUID + anchorSubmission (_, cUUID, _) = SubmissionDemoR cUUID submissionText (cID, _, _) = toWidget . toPathPiece . CI.foldedCase $ ciphertext cID colonnade = mconcat [ headed "Abgabe-ID" $ anchorCell anchorSubmission submissionText @@ -211,9 +261,11 @@ getSubmissionDownloadArchiveR path = do info = ZipInfo { zipComment = Text.encodeUtf8 . tshow $ ciphertext (cUUID :: CryptoUUIDSubmission) } fileEntitySource' =$= produceZip info =$= Conduit.map toFlushBuilder -getSubmissionR, postSubmissionR :: CryptoUUIDSubmission -> Handler Html -getSubmissionR = postSubmissionR -postSubmissionR cID = do + + +getSubmissionDemoR, postSubmissionDemoR :: CryptoUUIDSubmission -> Handler Html +getSubmissionDemoR = postSubmissionDemoR +postSubmissionDemoR cID = do submissionId <- decrypt cID ((uploadResult, uploadWidget), uploadEnctype) <- runFormPost . renderAForm FormStandard $ (,) diff --git a/src/Handler/Utils.hs b/src/Handler/Utils.hs index 33fc5f0f4..72a833f48 100644 --- a/src/Handler/Utils.hs +++ b/src/Handler/Utils.hs @@ -16,7 +16,8 @@ import Handler.Utils.Form as Handler.Utils import Handler.Utils.Table as Handler.Utils import Handler.Utils.Table.Pagination as Handler.Utils -import Handler.Utils.Zip as Handler.Utils -import Handler.Utils.Rating as Handler.Utils +import Handler.Utils.Zip as Handler.Utils +import Handler.Utils.Rating as Handler.Utils import Handler.Utils.Submission as Handler.Utils -import Handler.Utils.Templates as Handler.Utils +import Handler.Utils.Sheet as Handler.Utils +import Handler.Utils.Templates as Handler.Utils diff --git a/src/Handler/Utils/Form.hs b/src/Handler/Utils/Form.hs index 1936769ee..cfd104d15 100644 --- a/src/Handler/Utils/Form.hs +++ b/src/Handler/Utils/Form.hs @@ -44,7 +44,7 @@ import qualified Data.Set as Set -- Unique Form Identifiers to avoid accidents -- ------------------------------------------------ -data FormIdentifier = FIDcourse | FIDsheet +data FormIdentifier = FIDcourse | FIDsheet | FIDsubmission deriving (Enum, Eq, Ord, Bounded, Read, Show) diff --git a/src/Model/Types.hs b/src/Model/Types.hs index 9aac70705..da0073707 100644 --- a/src/Model/Types.hs +++ b/src/Model/Types.hs @@ -158,3 +158,6 @@ time `withinTerm` term = timeYear `mod` 100 == termYear `mod` 100 data StudyFieldType = FieldPrimary | FieldSecondary deriving (Eq, Ord, Enum, Show, Read, Bounded) derivePersistField "StudyFieldType" + + + diff --git a/templates/submission.hamlet b/templates/submission.hamlet index 5c678476a..d8ea8ae89 100644 --- a/templates/submission.hamlet +++ b/templates/submission.hamlet @@ -33,7 +33,7 @@
    Abgabe ersetzen -
    + ^{uploadWidget}
    From 5c1789786db7e0aaea0ad3a3714338727cd8873b Mon Sep 17 00:00:00 2001 From: SJost Date: Tue, 10 Apr 2018 15:16:32 +0200 Subject: [PATCH 008/108] Util-Sheet vergessen --- src/Handler/Utils/Sheet.hs | 49 ++++++++++++++++++++++++++++++++++++++ 1 file changed, 49 insertions(+) create mode 100644 src/Handler/Utils/Sheet.hs diff --git a/src/Handler/Utils/Sheet.hs b/src/Handler/Utils/Sheet.hs new file mode 100644 index 000000000..61c5736dc --- /dev/null +++ b/src/Handler/Utils/Sheet.hs @@ -0,0 +1,49 @@ +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE QuasiQuotes #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} + +module Handler.Utils.Sheet where + +import Import + +import qualified Database.Esqueleto as E +import qualified Database.Esqueleto.Internal.Sql as E + + + + +fetchSheetAux :: ( BaseBackend backend ~ SqlBackend + , E.SqlSelect b a + , Typeable a, MonadHandler m, IsPersistBackend backend + , PersistQueryRead backend, PersistUniqueRead backend + ) + => (E.SqlExpr (Entity Sheet) -> b) + -> TermId -> Text -> Text -> ReaderT backend m a +fetchSheetAux prj tid csh shn = + let cachId = encodeUtf8 $ tshow (tid,csh,shn) + in cachedBy cachId $ do + -- Mit Yesod: + -- cid <- getKeyBy404 $ CourseTermShort tid csh + -- getBy404 $ CourseSheet cid shn + -- Mit Esqueleto: + sheetList <- E.select . E.from $ \(course `E.InnerJoin` sheet) -> do + E.on $ course E.^. CourseId E.==. sheet E.^. SheetCourseId + E.where_ $ course E.^. CourseTermId E.==. E.val tid + E.&&. course E.^. CourseShorthand E.==. E.val csh + E.&&. sheet E.^. SheetName E.==. E.val shn + return $ prj sheet + case sheetList of + [sheet] -> return sheet + _other -> notFound + +fetchSheet :: TermId -> Text -> Text -> YesodDB UniWorX (Entity Sheet) +fetchSheet = fetchSheetAux id + +fetchSheetId :: TermId -> Text -> Text -> YesodDB UniWorX (Key Sheet) +fetchSheetId tid cid shn = E.unValue <$> fetchSheetAux (E.^. SheetId) tid cid shn From f99c8b3b86348d62f70e266687d053afbd408ab8 Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Tue, 10 Apr 2018 21:54:12 +0200 Subject: [PATCH 009/108] include credentials in ajax-call --- templates/table/colonnade.julius | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/templates/table/colonnade.julius b/templates/table/colonnade.julius index 840cccd6a..fcea7dea9 100644 --- a/templates/table/colonnade.julius +++ b/templates/table/colonnade.julius @@ -23,8 +23,8 @@ event.preventDefault(); var url = new URL(window.location.origin + window.location.pathname + this.getAttribute('href')); var order = this.parentNode.dataset.order || ASC; - // TODO: not working here... getting whole page as response... - url.searchParams.set('table-only', 'true'); + // TODO: make use of dbtIdent instead of -terms- + url.searchParams.set('terms-table-only', 'true'); updateTableFrom(url); markSorted(this.parentNode, order); } @@ -40,6 +40,7 @@ // fetches new sorted table from url with params and replaces contents of current table function updateTableFrom(url) { fetch(url, { + credentials: 'same-origin', headers: { 'Accept': 'text/html' } From fcd6703752ca8829fe5e9b4d267206514f2db9ee Mon Sep 17 00:00:00 2001 From: SJost Date: Wed, 11 Apr 2018 13:12:49 +0200 Subject: [PATCH 010/108] Group Submissions mostly done, NOT COMPILING --- messages/de.msg | 13 ++++ models | 3 +- src/Handler/Sheet.hs | 2 +- src/Handler/Submission.hs | 118 +++++++++++++++++++++++++++++++------ src/Handler/Utils/Form.hs | 2 +- src/Handler/Utils/Sheet.hs | 3 + src/Model/Types.hs | 2 +- 7 files changed, 121 insertions(+), 22 deletions(-) diff --git a/messages/de.msg b/messages/de.msg index 44b84282e..76cdbc62d 100644 --- a/messages/de.msg +++ b/messages/de.msg @@ -5,11 +5,13 @@ Page n@Int64 num@Int64: Seite #{tshow n} von #{tshow num} TermEdited tid@TermIdentifier: Semester #{termToText tid} erfolgreich editiert. TermNewTitle: Semester editiere/anlegen. InvalidInput: Eingaben bitte korrigieren. + CourseNewOk tid@TermIdentifier courseShortHand@Text: Kurs #{termToText tid}-#{courseShortHand} wurde erfolgreich erstellt. CourseEditOk tid@TermIdentifier courseShortHand@Text: Kurs #{termToText tid}-#{courseShortHand} wurde erfolgreich geändert. CourseNewDupShort tid@TermIdentifier courseShortHand@Text: Kurs #{termToText tid}-#{courseShortHand} konnte nicht erstellt werden: Es gibt bereits einen anderen Kurs mit dem Kürzel #{courseShortHand} in diesem Semester. CourseEditDupShort tid@TermIdentifier courseShortHand@Text: Kurs #{termToText tid}-#{courseShortHand} konnte nicht geändert werden: Es gibt bereits einen anderen Kurs mit dem Kürzel #{courseShortHand} in diesem Semester. FFSheetName: Name + SheetNewOk tid@TermIdentifier courseShortHand@Text sheetName@Text: Neues Übungsblatt #{sheetName} wurde im Kurs #{termToText tid}-#{courseShortHand} erfolgreich erstellt. SheetTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termToText tid}-#{courseShortHand} #{sheetName} SheetTitleNew tid@TermIdentifier courseShortHand@Text : #{termToText tid}-#{courseShortHand}: Neues Übungsblatt @@ -18,11 +20,22 @@ SheetNameDup tid@TermIdentifier courseShortHand@Text sheetName@Text: Es gi SheetDelTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: Übungsblatt #{sheetName} wirklich aus Kurs #{termToText tid}-#{courseShortHand} herauslöschen? SheetDelText submissionNo@Int: Dies kann nicht mehr rückgängig gemacht werden! Alle Einreichungen gehen ebenfalls verloren! Es gibt #{show submissionNo} Abgaben. SheetDelOk tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termToText tid}-#{courseShortHand}: Übungsblatt #{sheetName} gelöscht. + UnauthorizedSchoolAdmin: Sie sind nicht als Administrator für dieses Institut eingetragen. UnauthorizedSchoolLecturer: Sie sind nicht als Veranstalter für dieses Institut eingetragen. UnauthorizedLecturer: Sie sind nicht als Veranstalter für diese Veranstaltung eingetragen. UnauthorizedCorrector: Sie sind nicht als Korrektor für diese Veranstaltung eingetragen. UnauthorizedParticipant: Sie sind nicht als Teilnehmer für diese Veranstaltung registriert. OnlyUploadOneFile: Bitte nur eine Datei hochladen. + SubmissionWrongSheet: Abgabenummer gehört nicht zum angegebenen Übungsblatt. +SubmissionAlreadyExists: Sie haben bereits eine Abgabe zu diesem Übungsblatt. SubmissionTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termToText tid}-#{courseShortHand} #{sheetName}: Abgabe +SubmissionMember: Mitabgebende(r) +SubmissionArchive: Zip-Archiv der Abgabedatei(en) +SubmissionFile: Datei zur Abgabe +SubmissionAlreadyExistsFor user@Text: #{user} hat bereits eine Abgabe zu diesem Übungsblatt. + +EMailUnknown email@Text: E-Mail #{email} gehört zu keinem bekannten Benutzer. +NotAParticipant user@Text tid@TermIdentifier csh@Text: #{user} ist nicht im Kurs #{termToText tid}-#{csh} angemeldet. + diff --git a/models b/models index de3c17b88..3e0c09966 100644 --- a/models +++ b/models @@ -6,6 +6,7 @@ User displayName Text maxFavourites Int default=12 UniqueAuthentication plugin ident + UniqueEmail email UserAdmin user UserId school SchoolId @@ -147,7 +148,7 @@ SubmissionUser UniqueSubmissionUser userId submissionId SubmissionGroup courseId CourseId - name Text + name Text Maybe SubmissionGroupEdit user UserId time UTCTime diff --git a/src/Handler/Sheet.hs b/src/Handler/Sheet.hs index 4f3b8bf9a..b6a3b148f 100644 --- a/src/Handler/Sheet.hs +++ b/src/Handler/Sheet.hs @@ -332,7 +332,7 @@ getSheetDelR tid csh shn = do (FormSuccess BtnDelete) -> do runDB $ fetchSheetId tid csh shn >>= deleteCascade -- TODO: deleteCascade löscht aber nicht die hochgeladenen Dateien!!! - setMessageI $ MsgSheetDelOk tident csh shn + addMessageI "info" $ MsgSheetDelOk tident csh shn redirect $ CSheetR tid csh SheetListR _other -> do submissionno <- runDB $ do diff --git a/src/Handler/Submission.hs b/src/Handler/Submission.hs index a321b4ddd..142a35bf7 100644 --- a/src/Handler/Submission.hs +++ b/src/Handler/Submission.hs @@ -9,6 +9,7 @@ {-# LANGUAGE TupleSections #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE PatternGuards #-} module Handler.Submission where @@ -34,46 +35,123 @@ import qualified Database.Esqueleto as E import qualified Data.Conduit.List as Conduit import Data.Conduit.ResumableSink +import Data.Set (Set) import Data.Map (Map) import qualified Data.Map as Map import System.FilePath -import Colonnade +import Colonnade hiding (bool) import Yesod.Colonnade import qualified Text.Blaze.Html5.Attributes as HA -makeSubmissionForm :: Bool -> Form (Source Handler File) -makeSubmissionForm unpackZips = identForm FIDsubmission $ \html -> do - flip (renderAForm FormStandard) html $ - areq (zipFileField unpackZips) "Zip Archiv zur Abgabe" Nothing +makeSubmissionForm :: Bool -> SheetGroup -> Form (Source Handler File, [Text]) +makeSubmissionForm unpackZips grouping = identForm FIDsubmission $ \html -> do + flip (renderAForm FormStandard) html $ (,) + <$> areq (zipFileField unpackZips) (fsm $ bool MsgSubmissionFile MsgSubmissionArchive unpackZips) Nothing + <*> (catMaybes <$> replicateM groupNr (aopt textField (fsm MsgSubmissionMember) Nothing)) -- TODO: Convenience: preselect last buddies <* submitButton + where + groupNr + | Arbitrary{..} <- grouping = pred maxParticipants + | otherwise = 0 getSubmissionR, postSubmissionR :: TermId -> Text -> Text -> SubmissionMode -> Handler Html getSubmissionR = postSubmissionR postSubmissionR tid csh shn (SubmissionMode mcid) = do uid <- requireAuthId msmid <- traverse decrypt mcid - shid <- runDB $ do - shid <- fetchSheetId tid csh shn + (Entity shid Sheet{..}) <- runDB $ do + sheet@(Entity shid _) <- fetchSheet tid csh shn case msmid of - Nothing -> return shid + Nothing -> do + submissions <- E.select . E.from $ \(submission `E.InnerJoin` submissionUser) -> do + E.on (submission E.^. SubmissionId E.==. submissionUser E.^. SubmissionUserSubmissionId) + E.where_ $ submissionUser E.^. SubmissionUserUserId E.==. E.val uid + E.&&. submission E.^. SubmissionSheetId E.==. E.val shid + return $ submission E.^. SubmissionId + $logDebugS "Submission.DUPLICATENEW" (tshow submissions) + case submissions of + [] -> return shid + (E.Value smid:_) -> do + cID <- encrypt smid + addMessageI "info" $ MsgSubmissionAlreadyExists + redirect $ CourseR tid csh $ SheetR $ SubmissionR shn $ SubmissionMode $ Just cID + return sheet (Just smid) -> do shid' <- submissionSheetId <$> get404 smid when (shid /= shid') $ invalidArgsI [MsgSubmissionWrongSheet] - return shid + return sheet let unpackZips = True -- undefined -- TODO - ((res,formWidget), formEnctype) <- runFormPost $ makeSubmissionForm unpackZips - case res of - (FormSuccess files) -> do - smid <- runDB $ runConduit $ - transPipe lift files .| Conduit.map Left .| sinkSubmission shid uid ((,False) <$> msmid) - cID <- encrypt smid - redirect $ CourseR tid csh $ SheetR $ SubmissionR shn $ SubmissionMode $ Just cID - (FormFailure msgs) -> forM_ msgs $ (addMessage "warning") . toHtml - _other -> return () + ((res,formWidget), formEnctype) <- runFormPost $ makeSubmissionForm unpackZips sheetGrouping + runDB $ do + res' <- case res of + (FormMissing ) -> return $ FormMissing + (FormFailure failmsg) -> return $ FormFailure failmsgs + (FormSuccess (files,[])) -> return $ FormSuccess (files,[]) -- Type change + (FormSuccess (files, (map CI.mk -> gEMails@(_:_)))) -- Validate AdHoc Group Members + | (Arbitrary {..}) <- sheetGrouping + , length gEMails < maxParticipants -> do -- < since submitting user is already accounted for + let gemails = map CI.foldedCase gEMails + prep ps = Map.fromList $ map (, Nothing) gEMails ++ [(CI.mk m, Just (i,p,s))|(E.Value m, (E.Value i, E.Value p, E.Value s)) <- ps] + participants <- fmap prep . E.select . E.from $ \user -> do + E.where_ $ (E.lower_ $ user E.^. UserEmail) `E.in_` E.valList gemails + isParticipant <- E.sub_select . E.from $ \courseParticipant -> do + E.where_ $ user E.^. UserId E.==. courseParticipant E.^. CourseParticipantUserId + E.&&. courseParticipant E.^. CourseParticipantCourseId E.==. E.val cid + return $ E.countRows E.>. E.val 0 + hasSubmitted <- E.sub_select . E.from $ \(submissionUser `E.InnerJoin` submission) -> do + E.on $ submissionUser E.^. SubmissionUserSubmissionId E.==. submission E.^. SubmissionId + E.where_ $ submissionUser E.^. SubmissionUserUserId E.==. user E.^. UserId + E.&&. submission E.^. SubmissionSheetId E.==. E.val shid + return $ E.countRows E.>. E.val 0 + return (user E.^. UserEmail, (user E.^. UserId, isParticipant, hasSubmitted)) + $logDebugS "SUBMISSION.AdHocGroupValidation" $ tshow participants + mr <- getMessageRender + + let failmsgs = flip Map.foldMapWithKey participants $ + \email -> \case + Nothing -> [mr $ MsgEMailUnknown $ CI.original email] + (Just (_,False,_)) -> [mr $ MsgNotAParticipant (CI.original email) (unTermKey tid) csh] + (Just (_,_, True)) -> [mr $ MsgSubmissionAlreadyExistsFor (CI.original email)] + _other -> mempty + if null failmsgs + then return $ FormSuccess (files, foldMap (\(Just (i,_,_)) -> [i]) participants) + else return $ FormFailure failmsgs + + | otherwise -> return $ FormFailure ["Mismatching number of group participants"] + + + case res' of + (FormSuccess (files,gemails)) -> do + now <- liftIO $ getCurrentTime + smid <- runDB $ do + -- AdHoc + + -- + smid <- runConduit $ transPipe lift files .| Conduit.map Left .| sinkSubmission shid uid ((,False) <$> msmid) + insertUnique $ SubmissionUser uid smid + insert $ SubmissionEdit uid now smid + -- Gruppen Abgaben für Feste Gruppen + groupUids <- fmap setFromList . E.select . E.from $ \(submissionGroupUser `E.InnerJoin` submissionGroup `E.InnerJoin` submissionGroupUser') -> do + E.on $ submissionGroup E.^. SubmissionGroupId E.==. submissionGroupUser' E.^. SubmissionGroupUserSubmissionGroupId + E.on $ submissionGroupUser E.^. SubmissionGroupUserSubmissionGroupId E.==. submissionGroup E.^. SubmissionGroupId + E.where_ $ submissionGroupUser E.^. SubmissionGroupUserUserId E.==. E.val uid + E.&&. submissionGroup E.^. SubmissionGroupCourseId E.==. E.val sheetCourseId + return $ submissionGroupUser' E.^. SubmissionGroupUserUserId + forM_ (groupUids :: Set (E.Value UserId)) $ \(E.Value uid') -> void . insertUnique $ SubmissionUser uid' smid + -- Adhoc Gruppen + + -- TODO + --TODO: SubmissionUser anlegen!!!! + --TODO: Permissions für GruppenAbgabe + return smid + cID <- encrypt smid + redirect $ CourseR tid csh $ SheetR $ SubmissionR shn $ SubmissionMode $ Just cID + (FormFailure msgs) -> forM_ msgs $ (addMessage "warning") . toHtml + _other -> return () let pageTitle = MsgSubmissionTitle (unTermKey tid) csh shn let formTitle = pageTitle @@ -89,6 +167,10 @@ postSubmissionR tid csh shn (SubmissionMode mcid) = do + + + +----------------------------------------------------------------------------------------------- ------------------------- DEMO BELOW diff --git a/src/Handler/Utils/Form.hs b/src/Handler/Utils/Form.hs index cfd104d15..1c5c94f1e 100644 --- a/src/Handler/Utils/Form.hs +++ b/src/Handler/Utils/Form.hs @@ -355,7 +355,7 @@ utcTimeField = Field fsm :: RenderMessage UniWorX msg => msg -> FieldSettings UniWorX -fsm = bfs +fsm = bfs -- TODO: get rid of Bootstrap fsb :: Text -> FieldSettings site fsb = bfs -- Just to avoid annoying Ambiguous Type Errors diff --git a/src/Handler/Utils/Sheet.hs b/src/Handler/Utils/Sheet.hs index 61c5736dc..24db7ae1a 100644 --- a/src/Handler/Utils/Sheet.hs +++ b/src/Handler/Utils/Sheet.hs @@ -47,3 +47,6 @@ fetchSheet = fetchSheetAux id fetchSheetId :: TermId -> Text -> Text -> YesodDB UniWorX (Key Sheet) fetchSheetId tid cid shn = E.unValue <$> fetchSheetAux (E.^. SheetId) tid cid shn + +fetchSheetIdCourseId :: TermId -> Text -> Text -> YesodDB UniWorX (Key Sheet, Key Course) +fetchSheetIdCourseId tid cid shn = bimap E.unValue E.unValue <$> fetchSheetAux ((,) <$> (E.^. SheetId) <*> (E.^. SheetCourseId)) tid cid shn diff --git a/src/Model/Types.hs b/src/Model/Types.hs index da0073707..449d947d7 100644 --- a/src/Model/Types.hs +++ b/src/Model/Types.hs @@ -54,7 +54,7 @@ deriveJSON defaultOptions ''SheetType derivePersistFieldJSON "SheetType" data SheetGroup - = Arbitrary { maxParticipants :: Int } -- Distinguish Limited/Arbitrary + = Arbitrary { maxParticipants :: Int } | RegisteredGroups | NoGroups deriving (Show, Read, Eq) From 08607a5e7c99bd1abbcef845de96b0ad49dc0741 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 11 Apr 2018 14:28:33 +0200 Subject: [PATCH 011/108] Fix javascript issues, 'directions' in sortable-header, sorted attrs --- src/Handler/Utils/Table/Pagination.hs | 8 +++++++- templates/table/colonnade.julius | 3 +-- templates/table/sortable-header.hamlet | 13 ++++++++++--- 3 files changed, 18 insertions(+), 6 deletions(-) diff --git a/src/Handler/Utils/Table/Pagination.hs b/src/Handler/Utils/Table/Pagination.hs index ef3ab45ec..776fd3498 100644 --- a/src/Handler/Utils/Table/Pagination.hs +++ b/src/Handler/Utils/Table/Pagination.hs @@ -153,10 +153,16 @@ dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do let table = $(widgetFile "table/colonnade") pageCount = max 1 . ceiling $ rowCount % psLimit tblLink f = decodeUtf8 . Builder.toLazyByteString . renderQueryText True $ f getParams + withSortLinks Sortable{ sortableContent = Cell{..}, .. } = Cell { cellContents = $(widgetFile "table/sortable-header") - , .. + , cellAttrs = maybe mempty (const sortableAttr) sortableKey <> cellAttrs } + where + directions = [dir | (k, dir) <- psSorting, Just k == sortableKey ] + sortableAttr = foldMap toAttr directions + toAttr SortAsc = Html5.class_ "sorted-asc" + toAttr SortDesc = Html5.class_ "sorted-desc" $(widgetFile "table/layout") where tblLayout :: Widget -> Handler Html diff --git a/templates/table/colonnade.julius b/templates/table/colonnade.julius index fcea7dea9..212ecf4ff 100644 --- a/templates/table/colonnade.julius +++ b/templates/table/colonnade.julius @@ -23,8 +23,7 @@ event.preventDefault(); var url = new URL(window.location.origin + window.location.pathname + this.getAttribute('href')); var order = this.parentNode.dataset.order || ASC; - // TODO: make use of dbtIdent instead of -terms- - url.searchParams.set('terms-table-only', 'true'); + url.searchParams.set(#{String $ wIdent "table-only"}, 'yes'); updateTableFrom(url); markSorted(this.parentNode, order); } diff --git a/templates/table/sortable-header.hamlet b/templates/table/sortable-header.hamlet index 1054b1ce0..b5e006b6a 100644 --- a/templates/table/sortable-header.hamlet +++ b/templates/table/sortable-header.hamlet @@ -1,7 +1,14 @@ ^{cellContents} $maybe flag <- sortableKey
    - "-asc")}>asc - / - "-desc")}>desc + $case directions + $of [SortAsc] + "-desc")}>desc + $of [SortDesc] + "-asc")}>asc + $of [] + "-desc")}>desc + / + "-asc")}>asc + $of _ $nothing From 3047dfe9f2d5fb924a125899dda8fa23972b41da Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 11 Apr 2018 14:34:17 +0200 Subject: [PATCH 012/108] Use psShortcircuit in colonnade.hamlet --- templates/table/colonnade.hamlet | 21 ++++++++++++++------- 1 file changed, 14 insertions(+), 7 deletions(-) diff --git a/templates/table/colonnade.hamlet b/templates/table/colonnade.hamlet index ef6b1bdbd..90951ce7c 100644 --- a/templates/table/colonnade.hamlet +++ b/templates/table/colonnade.hamlet @@ -1,10 +1,17 @@ -
    - $maybe sortableP <- pSortable - $with toSortable <- toSortable sortableP - - $forall OneColonnade{..} <- getColonnade dbtColonnade - ^{widgetFromCell th $ withSortLinks $ toSortable oneColonnadeHead} - $nothing +$if not psShortcircuit +
    + $maybe sortableP <- pSortable + $with toSortable <- toSortable sortableP + + $forall OneColonnade{..} <- getColonnade dbtColonnade + ^{widgetFromCell th $ withSortLinks $ toSortable oneColonnadeHead} + $nothing + + $forall row <- rows + + $forall OneColonnade{..} <- getColonnade dbtColonnade + ^{widgetFromCell td $ oneColonnadeEncode row} +$else $forall row <- rows From 73d535d8c3a7b976146865b34809e36ae47a3833 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 11 Apr 2018 14:37:39 +0200 Subject: [PATCH 013/108] =?UTF-8?q?=E2=80=A6?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- templates/table/colonnade.hamlet | 9 ++++----- templates/table/layout.hamlet | 13 ++++++++----- 2 files changed, 12 insertions(+), 10 deletions(-) diff --git a/templates/table/colonnade.hamlet b/templates/table/colonnade.hamlet index 90951ce7c..b109dd442 100644 --- a/templates/table/colonnade.hamlet +++ b/templates/table/colonnade.hamlet @@ -12,8 +12,7 @@ $if not psShortcircuit $forall OneColonnade{..} <- getColonnade dbtColonnade ^{widgetFromCell td $ oneColonnadeEncode row} $else - - $forall row <- rows - - $forall OneColonnade{..} <- getColonnade dbtColonnade - ^{widgetFromCell td $ oneColonnadeEncode row} + $forall row <- rows + + $forall OneColonnade{..} <- getColonnade dbtColonnade + ^{widgetFromCell td $ oneColonnadeEncode row} diff --git a/templates/table/layout.hamlet b/templates/table/layout.hamlet index 009e4eb2c..eb5651cb3 100644 --- a/templates/table/layout.hamlet +++ b/templates/table/layout.hamlet @@ -1,6 +1,9 @@ -
    +$if not psShortcircuit +
    + ^{table} + $if pageCount > 1 +

    + $# TODO: foreach (reachable pages) print link to that page + _{MsgPage (succ psPage) pageCount} +$else ^{table} - $if pageCount > 1 -

    - $# TODO: foreach (reachable pages) print link to that page - _{MsgPage (succ psPage) pageCount} From 4c4cbd584cd39328ddcf5abe2a244ce6e35f222c Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 11 Apr 2018 15:09:20 +0200 Subject: [PATCH 014/108] Fix build of Submission.hs --- messages/de.msg | 2 +- src/Handler/Submission.hs | 79 +++++++++++++++++++++------------------ 2 files changed, 43 insertions(+), 38 deletions(-) diff --git a/messages/de.msg b/messages/de.msg index 76cdbc62d..9c8582fad 100644 --- a/messages/de.msg +++ b/messages/de.msg @@ -31,7 +31,7 @@ OnlyUploadOneFile: Bitte nur eine Datei hochladen. SubmissionWrongSheet: Abgabenummer gehört nicht zum angegebenen Übungsblatt. SubmissionAlreadyExists: Sie haben bereits eine Abgabe zu diesem Übungsblatt. SubmissionTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termToText tid}-#{courseShortHand} #{sheetName}: Abgabe -SubmissionMember: Mitabgebende(r) +SubmissionMember g@Int: Mitabgebende(r) ###{tshow g} SubmissionArchive: Zip-Archiv der Abgabedatei(en) SubmissionFile: Datei zur Abgabe SubmissionAlreadyExistsFor user@Text: #{user} hat bereits eine Abgabe zu diesem Übungsblatt. diff --git a/src/Handler/Submission.hs b/src/Handler/Submission.hs index 142a35bf7..304101890 100644 --- a/src/Handler/Submission.hs +++ b/src/Handler/Submission.hs @@ -28,6 +28,8 @@ import Control.Monad.Trans.State.Strict (StateT) import qualified Data.Maybe import qualified Data.Text as Text import qualified Data.Text.Encoding as Text + +import Data.CaseInsensitive (CI) import qualified Data.CaseInsensitive as CI import qualified Database.Esqueleto as E @@ -36,6 +38,7 @@ import qualified Data.Conduit.List as Conduit import Data.Conduit.ResumableSink import Data.Set (Set) +import qualified Data.Set as Set import Data.Map (Map) import qualified Data.Map as Map @@ -51,7 +54,7 @@ makeSubmissionForm :: Bool -> SheetGroup -> Form (Source Handler File, [Text]) makeSubmissionForm unpackZips grouping = identForm FIDsubmission $ \html -> do flip (renderAForm FormStandard) html $ (,) <$> areq (zipFileField unpackZips) (fsm $ bool MsgSubmissionFile MsgSubmissionArchive unpackZips) Nothing - <*> (catMaybes <$> replicateM groupNr (aopt textField (fsm MsgSubmissionMember) Nothing)) -- TODO: Convenience: preselect last buddies + <*> (catMaybes <$> sequenceA [aopt textField (fsm $ MsgSubmissionMember g) Nothing | g <- [1..groupNr] ]) -- TODO: Convenience: preselect last buddies <* submitButton where groupNr @@ -86,72 +89,74 @@ postSubmissionR tid csh shn (SubmissionMode mcid) = do return sheet let unpackZips = True -- undefined -- TODO ((res,formWidget), formEnctype) <- runFormPost $ makeSubmissionForm unpackZips sheetGrouping - runDB $ do + mCID <- runDB $ do res' <- case res of (FormMissing ) -> return $ FormMissing - (FormFailure failmsg) -> return $ FormFailure failmsgs + (FormFailure failmsgs) -> return $ FormFailure failmsgs (FormSuccess (files,[])) -> return $ FormSuccess (files,[]) -- Type change (FormSuccess (files, (map CI.mk -> gEMails@(_:_)))) -- Validate AdHoc Group Members | (Arbitrary {..}) <- sheetGrouping , length gEMails < maxParticipants -> do -- < since submitting user is already accounted for let gemails = map CI.foldedCase gEMails + prep :: [(E.Value Text, (E.Value UserId, E.Value Bool, E.Value Bool))] -> Map (CI Text) (Maybe (UserId, Bool, Bool)) prep ps = Map.fromList $ map (, Nothing) gEMails ++ [(CI.mk m, Just (i,p,s))|(E.Value m, (E.Value i, E.Value p, E.Value s)) <- ps] participants <- fmap prep . E.select . E.from $ \user -> do E.where_ $ (E.lower_ $ user E.^. UserEmail) `E.in_` E.valList gemails - isParticipant <- E.sub_select . E.from $ \courseParticipant -> do - E.where_ $ user E.^. UserId E.==. courseParticipant E.^. CourseParticipantUserId - E.&&. courseParticipant E.^. CourseParticipantCourseId E.==. E.val cid - return $ E.countRows E.>. E.val 0 - hasSubmitted <- E.sub_select . E.from $ \(submissionUser `E.InnerJoin` submission) -> do - E.on $ submissionUser E.^. SubmissionUserSubmissionId E.==. submission E.^. SubmissionId - E.where_ $ submissionUser E.^. SubmissionUserUserId E.==. user E.^. UserId - E.&&. submission E.^. SubmissionSheetId E.==. E.val shid - return $ E.countRows E.>. E.val 0 + let + isParticipant = E.sub_select . E.from $ \courseParticipant -> do + E.where_ $ user E.^. UserId E.==. courseParticipant E.^. CourseParticipantUserId + E.&&. courseParticipant E.^. CourseParticipantCourseId E.==. E.val sheetCourseId + return $ E.countRows E.>. E.val (0 :: Int64) + hasSubmitted = E.sub_select . E.from $ \(submissionUser `E.InnerJoin` submission) -> do + E.on $ submissionUser E.^. SubmissionUserSubmissionId E.==. submission E.^. SubmissionId + E.where_ $ submissionUser E.^. SubmissionUserUserId E.==. user E.^. UserId + E.&&. submission E.^. SubmissionSheetId E.==. E.val shid + return $ E.countRows E.>. E.val (0 :: Int64) return (user E.^. UserEmail, (user E.^. UserId, isParticipant, hasSubmitted)) $logDebugS "SUBMISSION.AdHocGroupValidation" $ tshow participants mr <- getMessageRender - let failmsgs = flip Map.foldMapWithKey participants $ - \email -> \case - Nothing -> [mr $ MsgEMailUnknown $ CI.original email] - (Just (_,False,_)) -> [mr $ MsgNotAParticipant (CI.original email) (unTermKey tid) csh] - (Just (_,_, True)) -> [mr $ MsgSubmissionAlreadyExistsFor (CI.original email)] - _other -> mempty - if null failmsgs - then return $ FormSuccess (files, foldMap (\(Just (i,_,_)) -> [i]) participants) - else return $ FormFailure failmsgs + let failmsgs = flip Map.foldMapWithKey participants $ \email -> \case + Nothing -> [mr $ MsgEMailUnknown $ CI.original email] + (Just (_,False,_)) -> [mr $ MsgNotAParticipant (CI.original email) (unTermKey tid) csh] + (Just (_,_, True)) -> [mr $ MsgSubmissionAlreadyExistsFor (CI.original email)] + _other -> mempty + return $ if null failmsgs + then FormSuccess (files, foldMap (\(Just (i,_,_)) -> [i]) participants) + else FormFailure failmsgs | otherwise -> return $ FormFailure ["Mismatching number of group participants"] case res' of - (FormSuccess (files,gemails)) -> do + (FormSuccess (files,(setFromList -> adhocIds))) -> do now <- liftIO $ getCurrentTime - smid <- runDB $ do - -- AdHoc - - -- + smid <- do smid <- runConduit $ transPipe lift files .| Conduit.map Left .| sinkSubmission shid uid ((,False) <$> msmid) + insertUnique $ SubmissionUser uid smid - insert $ SubmissionEdit uid now smid - -- Gruppen Abgaben für Feste Gruppen - groupUids <- fmap setFromList . E.select . E.from $ \(submissionGroupUser `E.InnerJoin` submissionGroup `E.InnerJoin` submissionGroupUser') -> do + -- insert $ SubmissionEdit uid now smid -- sinkSubmission already does this + + -- Determine members of pre-registered group + groupUids <- fmap (setFromList . map E.unValue) . E.select . E.from $ \(submissionGroupUser `E.InnerJoin` submissionGroup `E.InnerJoin` submissionGroupUser') -> do E.on $ submissionGroup E.^. SubmissionGroupId E.==. submissionGroupUser' E.^. SubmissionGroupUserSubmissionGroupId E.on $ submissionGroupUser E.^. SubmissionGroupUserSubmissionGroupId E.==. submissionGroup E.^. SubmissionGroupId E.where_ $ submissionGroupUser E.^. SubmissionGroupUserUserId E.==. E.val uid E.&&. submissionGroup E.^. SubmissionGroupCourseId E.==. E.val sheetCourseId return $ submissionGroupUser' E.^. SubmissionGroupUserUserId - forM_ (groupUids :: Set (E.Value UserId)) $ \(E.Value uid') -> void . insertUnique $ SubmissionUser uid' smid - -- Adhoc Gruppen - -- TODO - --TODO: SubmissionUser anlegen!!!! - --TODO: Permissions für GruppenAbgabe + -- SubmissionUser for all group members (pre-registered & ad-hoc) + forM_ (groupUids `Set.union` adhocIds) $ \uid' -> void . insertUnique $ SubmissionUser uid' smid + return smid cID <- encrypt smid - redirect $ CourseR tid csh $ SheetR $ SubmissionR shn $ SubmissionMode $ Just cID - (FormFailure msgs) -> forM_ msgs $ (addMessage "warning") . toHtml - _other -> return () + return $ Just cID + (FormFailure msgs) -> Nothing <$ forM_ msgs (addMessage "warning" . toHtml) + _other -> return Nothing + + case mCID of + Just cID -> redirect $ CourseR tid csh $ SheetR $ SubmissionR shn $ SubmissionMode $ Just cID + Nothing -> return () let pageTitle = MsgSubmissionTitle (unTermKey tid) csh shn let formTitle = pageTitle From 18f33290bb131d45473901e4f95b66ffdf5019a8 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 11 Apr 2018 15:17:44 +0200 Subject: [PATCH 015/108] Additional sheets for testing --- fill-db.hs | 6 +++++- messages/de.msg | 2 +- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/fill-db.hs b/fill-db.hs index 4cc894464..205d4afd5 100755 --- a/fill-db.hs +++ b/fill-db.hs @@ -105,7 +105,11 @@ main = db $ do void . insert $ Lecturer jost ffp void . insert $ Lecturer gkleen ffp insert_ $ Corrector gkleen ffp (ByProportion 1) - sheetkey <- insert $ Sheet ffp "Blatt 1" Nothing NotGraded NoGroups Nothing Nothing now now Nothing Nothing + sheetkey <- insert $ Sheet ffp "AdHoc-Gruppen" Nothing NotGraded (Arbitrary 3) Nothing Nothing now now Nothing Nothing + insert_ $ SheetEdit gkleen now sheetkey + sheetkey <- insert $ Sheet ffp "Feste Gruppen" Nothing NotGraded RegisteredGroups Nothing Nothing now now Nothing Nothing + insert_ $ SheetEdit gkleen now sheetkey + sheetkey <- insert $ Sheet ffp "Keine Gruppen" Nothing NotGraded NoGroups Nothing Nothing now now Nothing Nothing insert_ $ SheetEdit gkleen now sheetkey -- EIP eip <- insert Course diff --git a/messages/de.msg b/messages/de.msg index 9c8582fad..70a11676a 100644 --- a/messages/de.msg +++ b/messages/de.msg @@ -31,7 +31,7 @@ OnlyUploadOneFile: Bitte nur eine Datei hochladen. SubmissionWrongSheet: Abgabenummer gehört nicht zum angegebenen Übungsblatt. SubmissionAlreadyExists: Sie haben bereits eine Abgabe zu diesem Übungsblatt. SubmissionTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termToText tid}-#{courseShortHand} #{sheetName}: Abgabe -SubmissionMember g@Int: Mitabgebende(r) ###{tshow g} +SubmissionMember g@Int: Mitabgebende(r) ##{tshow g} SubmissionArchive: Zip-Archiv der Abgabedatei(en) SubmissionFile: Datei zur Abgabe SubmissionAlreadyExistsFor user@Text: #{user} hat bereits eine Abgabe zu diesem Übungsblatt. From 796f4d08321c6d70c712b03becdb75c8581dd8ad Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Thu, 12 Apr 2018 00:37:54 +0200 Subject: [PATCH 016/108] clickable ths for toggling of sort-direction --- templates/table/colonnade.hamlet | 30 ++++------ templates/table/colonnade.julius | 61 -------------------- templates/table/layout.hamlet | 14 ++--- templates/table/layout.julius | 79 ++++++++++++++++++++++++++ templates/table/sortable-header.hamlet | 2 - templates/terms.hamlet | 3 +- 6 files changed, 98 insertions(+), 91 deletions(-) delete mode 100644 templates/table/colonnade.julius create mode 100644 templates/table/layout.julius diff --git a/templates/table/colonnade.hamlet b/templates/table/colonnade.hamlet index b109dd442..ef6b1bdbd 100644 --- a/templates/table/colonnade.hamlet +++ b/templates/table/colonnade.hamlet @@ -1,18 +1,12 @@ -$if not psShortcircuit -

    - $maybe sortableP <- pSortable - $with toSortable <- toSortable sortableP - - $forall OneColonnade{..} <- getColonnade dbtColonnade - ^{widgetFromCell th $ withSortLinks $ toSortable oneColonnadeHead} - $nothing - - $forall row <- rows - - $forall OneColonnade{..} <- getColonnade dbtColonnade - ^{widgetFromCell td $ oneColonnadeEncode row} -$else - $forall row <- rows - - $forall OneColonnade{..} <- getColonnade dbtColonnade - ^{widgetFromCell td $ oneColonnadeEncode row} +
    + $maybe sortableP <- pSortable + $with toSortable <- toSortable sortableP + + $forall OneColonnade{..} <- getColonnade dbtColonnade + ^{widgetFromCell th $ withSortLinks $ toSortable oneColonnadeHead} + $nothing + + $forall row <- rows + + $forall OneColonnade{..} <- getColonnade dbtColonnade + ^{widgetFromCell td $ oneColonnadeEncode row} diff --git a/templates/table/colonnade.julius b/templates/table/colonnade.julius deleted file mode 100644 index 212ecf4ff..000000000 --- a/templates/table/colonnade.julius +++ /dev/null @@ -1,61 +0,0 @@ -(function collonadeClosure() { - 'use strict'; - - document.addEventListener('DOMContentLoaded', function DOMContentLoaded() { - - var ASC = 'asc'; - var DESC = 'desc'; - - // TODO: Make use of interpolated dbtIdent - var table = document.querySelector('table'); - var ths = Array.from(table.querySelectorAll('th')); - - // attach click handler to each table-header - ths.map(function(th) { - var link = th.querySelector('a'); - if (link) { - link.addEventListener('click', clickHandler); - } - }); - - // handles click on table header - function clickHandler(event) { - event.preventDefault(); - var url = new URL(window.location.origin + window.location.pathname + this.getAttribute('href')); - var order = this.parentNode.dataset.order || ASC; - url.searchParams.set(#{String $ wIdent "table-only"}, 'yes'); - updateTableFrom(url); - markSorted(this.parentNode, order); - } - - function markSorted(th, order) { - ths.forEach(function(th) { - th.classList.remove('sorted-asc', 'sorted-desc'); - }); - th.classList.add('sorted-' + order); - th.dataset.order = order; - } - - // fetches new sorted table from url with params and replaces contents of current table - function updateTableFrom(url) { - fetch(url, { - credentials: 'same-origin', - headers: { - 'Accept': 'text/html' - } - }).then(function(response) { - var contentType = response.headers.get("content-type"); - if (!response.ok) { - throw ('Looks like there was a problem fetching ' + url.toString() + '. Status Code: ' + response.status); - } - return response.text(); - }).then(function(data) { - // replace contents of table body - table.querySelector('tbody').innerHTML = data; - }).catch(function(err) { - console.error(err); - }); - } - - }); -})(); diff --git a/templates/table/layout.hamlet b/templates/table/layout.hamlet index eb5651cb3..9e83cfeb6 100644 --- a/templates/table/layout.hamlet +++ b/templates/table/layout.hamlet @@ -1,9 +1,7 @@ -$if not psShortcircuit -
    +
    +
    ^{table} - $if pageCount > 1 -

    - $# TODO: foreach (reachable pages) print link to that page - _{MsgPage (succ psPage) pageCount} -$else - ^{table} + $if pageCount > 1 +

    + $# TODO: foreach (reachable pages) print link to that page + _{MsgPage (succ psPage) pageCount} diff --git a/templates/table/layout.julius b/templates/table/layout.julius new file mode 100644 index 000000000..45ca89830 --- /dev/null +++ b/templates/table/layout.julius @@ -0,0 +1,79 @@ +(function collonadeClosure() { + 'use strict'; + + document.addEventListener('DOMContentLoaded', function DOMContentLoaded() { + + var ASC = 'asc'; + var DESC = 'desc'; + + function setupSorting(wrapper) { + + var table = wrapper.querySelector('#' + #{String $ wIdent "table-only"}.replace('-table-only', '')); + var ths = Array.from(table.querySelectorAll('th')); + + // attach click handler to each table-header + ths.forEach(function(th) { + th.addEventListener('click', clickHandler); + // TODO: Remove this forEach once column-description is link + Array.from(th.querySelectorAll('a')).forEach(function(a) { + a.style.display = 'none'; + }) + }); + + // handles click on table header + function clickHandler(event) { + event.preventDefault(); + var link = this.querySelector('a'); + if (!link) { + return false; + } + var href = link.getAttribute('href'); + var url = new URL(window.location.origin + window.location.pathname + href); + var order = this.dataset.order || ASC; + url.searchParams.set(#{String $ wIdent "table-only"}, 'yes'); + updateTableFrom(url); + markAsSorted(this, order); + } + + function markAsSorted(th, order) { + ths.forEach(function(th) { + th.classList.remove('sorted-asc', 'sorted-desc'); + }); + th.classList.add('sorted-' + order); + th.dataset.order = order; + } + + function replaceContent(content) { + wrapper.innerHTML = content; + setupSorting(wrapper); + } + + // fetches new sorted table from url with params and replaces contents of current table + function updateTableFrom(url) { + fetch(url, { + credentials: 'same-origin', + headers: { + 'Accept': 'text/html' + } + }).then(function(response) { + var contentType = response.headers.get("content-type"); + if (!response.ok) { + throw ('Looks like there was a problem fetching ' + url.toString() + '. Status Code: ' + response.status); + } + return response.text(); + }).then(function(data) { + // replace contents of table body + replaceContent(data); + table.querySelector('tbody').innerHTML = data; + }).catch(function(err) { + console.error(err); + }); + } + + } + + // TODO: how to get 'terms' only? + var selector = #{String $ wIdent "table-only"}.replace('-only', '-wrapper'); + setupSorting(document.querySelector('#' + selector)); + }); +})(); diff --git a/templates/table/sortable-header.hamlet b/templates/table/sortable-header.hamlet index b5e006b6a..1f358cbff 100644 --- a/templates/table/sortable-header.hamlet +++ b/templates/table/sortable-header.hamlet @@ -1,6 +1,5 @@ ^{cellContents} $maybe flag <- sortableKey -
    $case directions $of [SortAsc]
    "-desc")}>desc @@ -8,7 +7,6 @@ $maybe flag <- sortableKey "-asc")}>asc $of [] "-desc")}>desc - / "-asc")}>asc $of _ $nothing diff --git a/templates/terms.hamlet b/templates/terms.hamlet index d327861ab..4d5e14631 100644 --- a/templates/terms.hamlet +++ b/templates/terms.hamlet @@ -1,5 +1,4 @@

    Semesterübersicht -
    - ^{table} + ^{table} From e0b3f0921adf4ef57fa1fbac3893a16f72097d62 Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Thu, 12 Apr 2018 23:23:35 +0200 Subject: [PATCH 017/108] signal to the user that a column is sortable --- src/Handler/Utils/Table/Pagination.hs | 1 + templates/table/colonnade.lucius | 15 +++++++++++---- templates/table/layout.julius | 12 ++++++++++++ 3 files changed, 24 insertions(+), 4 deletions(-) diff --git a/src/Handler/Utils/Table/Pagination.hs b/src/Handler/Utils/Table/Pagination.hs index 776fd3498..9dc99a2ef 100644 --- a/src/Handler/Utils/Table/Pagination.hs +++ b/src/Handler/Utils/Table/Pagination.hs @@ -163,6 +163,7 @@ dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do sortableAttr = foldMap toAttr directions toAttr SortAsc = Html5.class_ "sorted-asc" toAttr SortDesc = Html5.class_ "sorted-desc" + -- TODO: add class "sortable" if column is sortable $(widgetFile "table/layout") where tblLayout :: Widget -> Handler Html diff --git a/templates/table/colonnade.lucius b/templates/table/colonnade.lucius index 4fcdad6e2..eddc61f79 100644 --- a/templates/table/colonnade.lucius +++ b/templates/table/colonnade.lucius @@ -9,12 +9,11 @@ table th.sorted-desc { color: var(--lightbase); } -table th.sorted-asc::after, -table th.sorted-desc::after { +table th.sortable::after, +table th.sortable::before { content: ''; position: absolute; right: 0; - top: 15px; width: 0; height: 0; transform: translateY(-100%); @@ -22,7 +21,15 @@ table th.sorted-desc::after { border-right: 8px solid transparent; } -table th.sorted-asc::after { +table th.sortable::before { + top: 21px; + border-top: 8px solid rgba(0, 0, 0, 0.1); +} +table th.sortable::after { + top: 9px; + border-bottom: 8px solid rgba(0, 0, 0, 0.1); +} +table th.sorted-asc::before { border-top: 8px solid var(--lightbase); } diff --git a/templates/table/layout.julius b/templates/table/layout.julius index 45ca89830..f63f64d8b 100644 --- a/templates/table/layout.julius +++ b/templates/table/layout.julius @@ -24,6 +24,7 @@ function clickHandler(event) { event.preventDefault(); var link = this.querySelector('a'); + // abort if there is no link set for this column if (!link) { return false; } @@ -70,6 +71,17 @@ }); } + + // TODO: Remove after class "sortable" gets set by backend + (function () { + ths.forEach(function(th) { + var link = th.querySelector('a'); + // abort if there is no link set for this column + if (!link) return false; + th.classList.add('sortable'); + }) + })(); + } // TODO: how to get 'terms' only? From 4f6d0ffbf71653b74d68e7ade494955617d0d684 Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Thu, 12 Apr 2018 23:29:13 +0200 Subject: [PATCH 018/108] slightly brighter dark --- templates/default-layout.lucius | 3 ++- templates/standalone/modal.lucius | 2 +- templates/widgets/navbar.lucius | 11 +++++------ 3 files changed, 8 insertions(+), 8 deletions(-) diff --git a/templates/default-layout.lucius b/templates/default-layout.lucius index cc33bfe58..3574d3a43 100644 --- a/templates/default-layout.lucius +++ b/templates/default-layout.lucius @@ -20,7 +20,8 @@ --fontbase: #34303a; --fontsec: #5b5861; /* THEME 4 */ - --darkbase: #263C4C; + --darkerbase: #274a65; + --darkbase: #425d79; --lightbase: #598EB5; --lighterbase: #5F98C2; --whitebase: #FCFFFA; diff --git a/templates/standalone/modal.lucius b/templates/standalone/modal.lucius index a511f58c6..f9e1db4e2 100644 --- a/templates/standalone/modal.lucius +++ b/templates/standalone/modal.lucius @@ -70,7 +70,7 @@ justify-content: center; width: 30px; height: 30px; - background-color: var(--darkbase); + background-color: var(--darkerbase); border-radius: 2px; cursor: pointer; z-index: 20; diff --git a/templates/widgets/navbar.lucius b/templates/widgets/navbar.lucius index b04c47366..b1fe881c4 100644 --- a/templates/widgets/navbar.lucius +++ b/templates/widgets/navbar.lucius @@ -8,10 +8,10 @@ height: var(--header-height); padding-right: 5vw; padding-left: 340px; - background: var(--darkbase); /* Old browsers */ - background: -moz-linear-gradient(bottom, var(--darkbase) 0%, #425d79 100%); /* FF3.6-15 */ - background: -webkit-linear-gradient(bottom, var(--darkbase) 0%,#425d79 100%); /* Chrome10-25,Safari5.1-6 */ - background: linear-gradient(to top, var(--darkbase) 0%,#425d79 100%); /* W3C, IE10+, FF16+, Chrome26+, Opera12+, Safari7+ */ + background: var(--darkerbase); /* Old browsers */ + background: -moz-linear-gradient(bottom, var(--darkerbase) 0%, #425d79 100%); /* FF3.6-15 */ + background: -webkit-linear-gradient(bottom, var(--darkerbase) 0%,#425d79 100%); /* Chrome10-25,Safari5.1-6 */ + background: linear-gradient(to top, var(--darkerbase) 0%,#425d79 100%); /* W3C, IE10+, FF16+, Chrome26+, Opera12+, Safari7+ */ color: white; box-shadow: 0 1px 10px rgba(0, 0, 0, 0.1); z-index: 10; @@ -86,8 +86,7 @@ } .navbar .navbar__list-item:not(.navbar__list-item--active):hover { - background-color: var(--darkbase); - color: var(--whitebase); + background-color: var(--darkerbase); } .navbar .navbar__list-item:not(.navbar__list-item--active):hover .navbar__link-wrapper { color: var(--whitebase); From 174297c2ba2119aa0cceebab585c86d81fcb50ed Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Thu, 12 Apr 2018 23:31:01 +0200 Subject: [PATCH 019/108] asidenav with distinguishable title and active-state --- templates/widgets/asidenav.hamlet | 9 +++++---- templates/widgets/asidenav.lucius | 19 ++++++++++++++++--- 2 files changed, 21 insertions(+), 7 deletions(-) diff --git a/templates/widgets/asidenav.hamlet b/templates/widgets/asidenav.hamlet index a46c06ad9..b19ab9d4f 100644 --- a/templates/widgets/asidenav.hamlet +++ b/templates/widgets/asidenav.hamlet @@ -18,10 +18,11 @@ $newline never WiSe 17/18

    - - -
    Teilnehmer - - #{participants} - $maybe capacity <- courseCapacity course - \ von #{capacity} -
    Anmeldezeitraum - - $maybe regFrom <- courseRegisterFrom course - #{formatTimeGerWD regFrom} - $maybe regTo <- courseRegisterTo course - \ bis #{formatTimeGerWD regTo} - -
    - - ^{regWidget} - -
    -

    #{courseName course} - $maybe school <- schoolMB -

    #{schoolName school} - -
    +

    #{courseName course} + $maybe school <- schoolMB +

    #{schoolName school} $maybe descr <- courseDescription course -

    Beschreibung +

    Beschreibung

    #{descr} $maybe link <- courseLinkExternal course -

    Homepage +

    Homepage #{link} + +
    +

    Übersicht + + + +
    Teilnehmer + + #{participants} + $maybe capacity <- courseCapacity course + \ von #{capacity} +
    Anmeldezeitraum + + $maybe regFrom <- courseRegisterFrom course + #{formatTimeGerWD regFrom} + $maybe regTo <- courseRegisterTo course + \ bis #{formatTimeGerWD regTo} + + + ^{regWidget} + +$# TODO: maybe übungsblätter +
    +

    Übungsblätter + + + + + + +
    Blatt + Abgabe ab + Abgabe bis + Bewertung
    + Blatt 1 + Do 11.04.18 + Do 11.04.18 + NotGraded + +$# TODO: maybe klausuren +
    +

    Klausuren + ... +$# ... diff --git a/templates/course.lucius b/templates/course.lucius index a9715afd7..e69de29bb 100644 --- a/templates/course.lucius +++ b/templates/course.lucius @@ -1,19 +0,0 @@ -.course-header { - /*display: flex; - flex-direction: row; - justify-content: space-between;*/ -} - -.course-header__title { - align-self: baseline; -} -.course-header__info { - border: 1px solid var(--greybase); - padding: 13px; - align-self: center; - float: right; -} - -.course-header__info table { - margin: 0; -} From 7b539db6610ac4f287420aeab2fde563a2a656fc Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Fri, 13 Apr 2018 14:32:47 +0200 Subject: [PATCH 029/108] moved breadcrumbs to left side --- templates/widgets/navbar.lucius | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/templates/widgets/navbar.lucius b/templates/widgets/navbar.lucius index b1fe881c4..4b17ebeb1 100644 --- a/templates/widgets/navbar.lucius +++ b/templates/widgets/navbar.lucius @@ -7,7 +7,7 @@ width: 100%; height: var(--header-height); padding-right: 5vw; - padding-left: 340px; + padding-left: 90px; background: var(--darkerbase); /* Old browsers */ background: -moz-linear-gradient(bottom, var(--darkerbase) 0%, #425d79 100%); /* FF3.6-15 */ background: -webkit-linear-gradient(bottom, var(--darkerbase) 0%,#425d79 100%); /* Chrome10-25,Safari5.1-6 */ From 6d1799e65c5b9731f839b0c38900dacc313caffe Mon Sep 17 00:00:00 2001 From: Felix Hamann Date: Fri, 13 Apr 2018 14:34:02 +0200 Subject: [PATCH 030/108] slightly less dominant page actions --- templates/widgets/pageactionprime.hamlet | 1 - templates/widgets/pageactionprime.lucius | 10 +--------- 2 files changed, 1 insertion(+), 10 deletions(-) diff --git a/templates/widgets/pageactionprime.hamlet b/templates/widgets/pageactionprime.hamlet index a681115b5..2c828a4fa 100644 --- a/templates/widgets/pageactionprime.hamlet +++ b/templates/widgets/pageactionprime.hamlet @@ -1,7 +1,6 @@ $newline never $if hasPageActions
    -

    Aktionen: