chore: bump to ghc-8.10
This commit is contained in:
parent
1d956a5fdc
commit
b9181de154
@ -96,7 +96,7 @@ sampleIntegral = sampleN scaleIntegral
|
||||
|
||||
|
||||
instance PathPiece DiffTime where
|
||||
toPathPiece = toPathPiece . MkFixed @E12 . diffTimeToPicoseconds
|
||||
toPathPiece = (toPathPiece :: Pico -> Text) . MkFixed . diffTimeToPicoseconds
|
||||
fromPathPiece t = fromPathPiece t <&> \(MkFixed ps :: Pico) -> picosecondsToDiffTime ps
|
||||
|
||||
|
||||
|
||||
@ -252,7 +252,7 @@ executables:
|
||||
uniworx:
|
||||
main: main.hs
|
||||
source-dirs: app
|
||||
ghc-options: -threaded -rtsopts "-with-rtsopts=-N -T"
|
||||
ghc-options: -threaded -rtsopts "-with-rtsopts=-N -T -xn"
|
||||
dependencies:
|
||||
- uniworx
|
||||
when:
|
||||
@ -277,7 +277,7 @@ executables:
|
||||
ghc-options:
|
||||
- -main-is Load
|
||||
- -threaded
|
||||
- -rtsopts "-with-rtsopts=-N -T"
|
||||
- -rtsopts "-with-rtsopts=-N -T -xn"
|
||||
source-dirs: load
|
||||
dependencies:
|
||||
- uniworx
|
||||
@ -311,8 +311,7 @@ tests:
|
||||
ghc-options:
|
||||
- -fno-warn-orphans
|
||||
- -threaded
|
||||
- -rtsopts
|
||||
- -with-rtsopts=-N
|
||||
- -rtsopts "-with-rtsopts=-N -xn"
|
||||
hlint:
|
||||
main: Hlint.hs
|
||||
other-modules: []
|
||||
|
||||
@ -101,6 +101,8 @@ import qualified Network.Minio as Minio
|
||||
|
||||
import Web.ServerSession.Core (StorageException(..))
|
||||
|
||||
import GHC.RTS.Flags (getRTSFlags)
|
||||
|
||||
-- Import all relevant handler modules here.
|
||||
-- (HPack takes care to add new modules to our cabal file nowadays.)
|
||||
import Handler.News
|
||||
@ -200,6 +202,7 @@ makeFoundation appSettings'@AppSettings{..} = do
|
||||
runAppLoggingT tempFoundation $ do
|
||||
$logInfoS "InstanceID" $ UUID.toText appInstanceID
|
||||
$logDebugS "Configuration" $ tshow appSettings'
|
||||
$logDebugS "RTSFlags" . tshow =<< liftIO getRTSFlags
|
||||
|
||||
smtpPool <- for appSmtpConf $ \c -> do
|
||||
$logDebugS "setup" "SMTP-Pool"
|
||||
|
||||
@ -77,8 +77,8 @@ instance ToWidget site a => ToWidget site (CI a) where
|
||||
instance RenderMessage site a => RenderMessage site (CI a) where
|
||||
renderMessage f ls msg = renderMessage f ls $ CI.original msg
|
||||
|
||||
instance Lift t => Lift (CI t) where
|
||||
lift (CI.original -> orig) = [e|CI.mk $(lift orig)|]
|
||||
instance (CI.FoldCase t, Lift t) => Lift (CI t) where
|
||||
liftTyped (CI.original -> orig) = [||CI.mk $$(liftTyped orig)||]
|
||||
|
||||
|
||||
instance (CI.FoldCase s, PathPiece s) => PathPiece (CI s) where
|
||||
|
||||
@ -719,20 +719,6 @@ tagAccessPredicate AuthSubmissionGroup = APDB $ \mAuthId route _ -> case route o
|
||||
return Authorized
|
||||
r -> $unsupportedAuthPredicate AuthSubmissionGroup r
|
||||
tagAccessPredicate AuthTime = APDB $ \mAuthId route _ -> case route of
|
||||
CApplicationR tid ssh csh _ _ -> maybeT (unauthorizedI MsgUnauthorizedApplicationTime) $ do
|
||||
course <- $cachedHereBinary (tid, ssh, csh) . MaybeT . getKeyBy $ TermSchoolCourseShort tid ssh csh
|
||||
allocationCourse <- $cachedHereBinary course . lift . getBy $ UniqueAllocationCourse course
|
||||
allocation <- for allocationCourse $ \(Entity _ AllocationCourse{..}) -> $cachedHereBinary allocationCourseAllocation . MaybeT $ get allocationCourseAllocation
|
||||
|
||||
case allocation of
|
||||
Nothing -> return ()
|
||||
Just Allocation{..} -> do
|
||||
cTime <- liftIO getCurrentTime
|
||||
guard $ NTop allocationStaffAllocationFrom <= NTop (Just cTime)
|
||||
guard $ NTop (Just cTime) <= NTop allocationStaffAllocationTo
|
||||
|
||||
return Authorized
|
||||
|
||||
CExamR tid ssh csh examn subRoute -> maybeT (unauthorizedI MsgUnauthorizedExamTime) $ do
|
||||
course <- $cachedHereBinary (tid, ssh, csh) . MaybeT . getKeyBy $ TermSchoolCourseShort tid ssh csh
|
||||
Entity eId Exam{..} <- $cachedHereBinary (course, examn) . MaybeT . getBy $ UniqueExam course examn
|
||||
@ -2111,7 +2097,7 @@ siteLayout' headingOverride widget = do
|
||||
-> let route = navRoute'
|
||||
ident = navIdent
|
||||
in $(widgetFile "widgets/navbar/item")
|
||||
NavPageActionPrimary{ navLink = navLink@NavLink{..}, .. }
|
||||
NavPageActionPrimary{ navLink = navLink@NavLink{..} }
|
||||
-> let pWidget
|
||||
| NavTypeLink{..} <- navType
|
||||
, navModal
|
||||
@ -2130,7 +2116,7 @@ siteLayout' headingOverride widget = do
|
||||
sWidgets = navChildren'
|
||||
& map (\(l, i, r) -> navWidget (NavPageActionSecondary l, i, Just r, []))
|
||||
in $(widgetFile "widgets/pageaction/primary-wrapper")
|
||||
NavPageActionSecondary{ navLink = navLink@NavLink{..}, .. }
|
||||
NavPageActionSecondary{ navLink = navLink@NavLink{..} }
|
||||
| NavTypeLink{..} <- navType
|
||||
, navModal
|
||||
-> customModal Modal
|
||||
@ -4535,25 +4521,25 @@ routeNormalizers =
|
||||
return $ route & typesUsing @RouteChildren @CourseShorthand . filtered (== csh) .~ courseShorthand
|
||||
ncSheet = maybeOrig $ \route -> do
|
||||
CSheetR tid ssh csh shn _ <- return route
|
||||
Entity cid Course{..} <- MaybeT . $cachedHereBinary (tid, ssh, csh) . lift . getBy $ TermSchoolCourseShort tid ssh csh
|
||||
cid <- MaybeT . $cachedHereBinary (tid, ssh, csh) . lift . getKeyBy $ TermSchoolCourseShort tid ssh csh
|
||||
Entity _ Sheet{..} <- MaybeT . $cachedHereBinary (cid, shn) . lift . getBy $ CourseSheet cid shn
|
||||
caseChanged shn sheetName
|
||||
return $ route & typesUsing @RouteChildren @SheetName . filtered (== shn) .~ sheetName
|
||||
ncMaterial = maybeOrig $ \route -> do
|
||||
CMaterialR tid ssh csh mnm _ <- return route
|
||||
Entity cid Course{..} <- MaybeT . $cachedHereBinary (tid, ssh, csh) . lift . getBy $ TermSchoolCourseShort tid ssh csh
|
||||
cid <- MaybeT . $cachedHereBinary (tid, ssh, csh) . lift . getKeyBy $ TermSchoolCourseShort tid ssh csh
|
||||
Entity _ Material{..} <- MaybeT . $cachedHereBinary (cid, mnm) . lift . getBy $ UniqueMaterial cid mnm
|
||||
caseChanged mnm materialName
|
||||
return $ route & typesUsing @RouteChildren @MaterialName . filtered (== mnm) .~ materialName
|
||||
ncTutorial = maybeOrig $ \route -> do
|
||||
CTutorialR tid ssh csh tutn _ <- return route
|
||||
Entity cid Course{..} <- MaybeT . $cachedHereBinary (tid, ssh, csh) . lift . getBy $ TermSchoolCourseShort tid ssh csh
|
||||
cid <- MaybeT . $cachedHereBinary (tid, ssh, csh) . lift . getKeyBy $ TermSchoolCourseShort tid ssh csh
|
||||
Entity _ Tutorial{..} <- MaybeT . $cachedHereBinary (cid, tutn) . lift . getBy $ UniqueTutorial cid tutn
|
||||
caseChanged tutn tutorialName
|
||||
return $ route & typesUsing @RouteChildren @TutorialName . filtered (== tutn) .~ tutorialName
|
||||
ncExam = maybeOrig $ \route -> do
|
||||
CExamR tid ssh csh examn _ <- return route
|
||||
Entity cid Course{..} <- MaybeT . $cachedHereBinary (tid, ssh, csh) . lift . getBy $ TermSchoolCourseShort tid ssh csh
|
||||
cid <- MaybeT . $cachedHereBinary (tid, ssh, csh) . lift . getKeyBy $ TermSchoolCourseShort tid ssh csh
|
||||
Entity _ Exam{..} <- MaybeT . $cachedHereBinary (cid, examn) . lift . getBy $ UniqueExam cid examn
|
||||
caseChanged examn examName
|
||||
return $ route & typesUsing @RouteChildren @ExamName . filtered (== examn) .~ examName
|
||||
@ -5095,7 +5081,7 @@ instance YesodAuth UniWorX where
|
||||
_other -> return res
|
||||
|
||||
$logDebugS "auth" $ tshow Creds{..}
|
||||
UniWorX{ appSettings' = AppSettings{ appUserDefaults = UserDefaultConf{..}, ..}, .. } <- getYesod
|
||||
UniWorX{..} <- getYesod
|
||||
|
||||
flip catches excHandlers $ case appLdapPool of
|
||||
Just ldapPool
|
||||
|
||||
@ -539,7 +539,7 @@ courseEditHandler miButtonAction mbCourseForm = do
|
||||
upsertAllocationCourse :: (MonadThrow m, MonadHandler m, HandlerSite m ~ UniWorX) => CourseId -> Maybe AllocationCourseForm -> ReaderT SqlBackend m ()
|
||||
upsertAllocationCourse cid cfAllocation = do
|
||||
now <- liftIO getCurrentTime
|
||||
Course{..} <- getJust cid
|
||||
Course{} <- getJust cid
|
||||
prevAllocationCourse <- getBy $ UniqueAllocationCourse cid
|
||||
prevAllocation <- fmap join . traverse get $ allocationCourseAllocation . entityVal <$> prevAllocationCourse
|
||||
userAdmin <- fromMaybe False <$> for prevAllocation (\Allocation{..} -> hasWriteAccessTo $ SchoolR allocationSchool SchoolEditR)
|
||||
|
||||
@ -33,7 +33,7 @@ postCNEditR tid ssh csh cID = do
|
||||
, courseNewsSummary = cnfSummary
|
||||
, courseNewsLastEdit = now
|
||||
}
|
||||
let mkFilter CourseNewsFileResidual{..} = [ CourseNewsFileNews ==. nId ]
|
||||
let mkFilter CourseNewsFileResidual{} = [ CourseNewsFileNews ==. nId ]
|
||||
in void . replaceFileReferences mkFilter (CourseNewsFileResidual nId) $ traverse_ id cnfFiles
|
||||
addMessageI Success MsgCourseNewsEdited
|
||||
redirect $ CourseR tid ssh csh CShowR :#: [st|news-#{toPathPiece cID}|]
|
||||
|
||||
@ -92,7 +92,7 @@ participantInvitationConfig = InvitationConfig{..}
|
||||
itAuthority <- HashSet.singleton . Right <$> liftHandler requireAuthId
|
||||
return $ InvitationTokenConfig itAuthority Nothing Nothing Nothing
|
||||
invitationRestriction _ _ = return Authorized
|
||||
invitationForm (Entity _ Course{..}) _ uid = hoistAForm lift . wFormToAForm $ do
|
||||
invitationForm _ _ uid = hoistAForm lift . wFormToAForm $ do
|
||||
now <- liftIO getCurrentTime
|
||||
studyFeatures <- wreq (studyFeaturesFieldFor Nothing False [] $ Just uid)
|
||||
(fslI MsgCourseStudyFeature & setTooltip MsgCourseStudyFeatureTip) Nothing
|
||||
|
||||
@ -263,7 +263,7 @@ deregisterParticipant :: UserId -> CourseId -> DB ()
|
||||
deregisterParticipant uid cid = do
|
||||
deleteApplications uid cid
|
||||
part <- fmap (assertM . has $ _entityVal . _courseParticipantState . _CourseParticipantActive) . getBy $ UniqueParticipant uid cid
|
||||
forM_ part $ \(Entity partId CourseParticipant{..}) -> do
|
||||
forM_ part $ \(Entity partId CourseParticipant{}) -> do
|
||||
update partId [CourseParticipantState =. CourseParticipantInactive False]
|
||||
audit $ TransactionCourseParticipantDeleted cid uid
|
||||
|
||||
|
||||
@ -115,7 +115,7 @@ courseUserProfileSection (Entity cid Course{..}) (Entity uid User{ userShowSex =
|
||||
, formSubmit = FormAutoSubmit
|
||||
, formAnchor = Just registrationFieldFrag
|
||||
}
|
||||
for_ mRegistration $ \(Entity pId CourseParticipant{..}) ->
|
||||
for_ mRegistration $ \(Entity pId CourseParticipant{}) ->
|
||||
formResult regFieldRes $ \courseParticipantField' -> do
|
||||
lift . runDB $ do
|
||||
update pId [ CourseParticipantField =. courseParticipantField' ]
|
||||
|
||||
@ -113,7 +113,7 @@ postECorrectR tid ssh csh examn = do
|
||||
mayEditResults <- hasWriteAccessTo $ CExamR tid ssh csh examn EUsersR
|
||||
|
||||
response <- runDB . exceptT (<$ transactionUndo) return $ do
|
||||
Entity eId Exam{..} <- lift $ fetchExam tid ssh csh examn
|
||||
Entity eId Exam{} <- lift $ fetchExam tid ssh csh examn
|
||||
euid <- traverse decrypt ciqUser
|
||||
|
||||
guardMExceptT (maybe True ((>= 3) . length) $ euid ^? _Left) $
|
||||
|
||||
@ -81,10 +81,9 @@ mkExamTable (Entity cid Course{..}) = do
|
||||
|
||||
getCExamListR :: TermId -> SchoolId -> CourseShorthand -> Handler Html
|
||||
getCExamListR tid ssh csh = do
|
||||
(Entity _ Course{..}, examTable) <- runDB $ do
|
||||
examTable <- runDB $ do
|
||||
c <- getBy404 $ TermSchoolCourseShort tid ssh csh
|
||||
(_, examTable) <- mkExamTable c
|
||||
return (c, examTable)
|
||||
view _2 <$> mkExamTable c
|
||||
|
||||
siteLayoutMsg (prependCourseTitle tid ssh csh MsgExamsHeading) $ do
|
||||
setTitleI $ prependCourseTitle tid ssh csh MsgExamsHeading
|
||||
|
||||
@ -36,9 +36,9 @@ instance Button UniWorX ButtonExamRegister where
|
||||
|
||||
postERegisterR :: TermId -> SchoolId -> CourseShorthand -> ExamName -> Handler Html
|
||||
postERegisterR tid ssh csh examn = do
|
||||
Entity uid User{..} <- requireAuth
|
||||
uid <- requireAuthId
|
||||
|
||||
Entity eId Exam{..} <- runDB $ fetchExam tid ssh csh examn
|
||||
Entity eId Exam{} <- runDB $ fetchExam tid ssh csh examn
|
||||
|
||||
((btnResult, _), _) <- runFormPost $ buttonForm' [BtnExamRegister, BtnExamDeregister]
|
||||
|
||||
@ -63,11 +63,11 @@ postERegisterR tid ssh csh examn = do
|
||||
|
||||
postERegisterOccR :: TermId -> SchoolId -> CourseShorthand -> ExamName -> ExamOccurrenceName -> Handler Html
|
||||
postERegisterOccR tid ssh csh examn occn = do
|
||||
Entity uid User{..} <- requireAuth
|
||||
(Entity eId Exam{..}, Entity occId ExamOccurrence{..}) <- runDB $ do
|
||||
eexam@(Entity eId _) <- fetchExam tid ssh csh examn
|
||||
occ <- getBy404 $ UniqueExamOccurrence eId occn
|
||||
return (eexam, occ)
|
||||
uid <- requireAuthId
|
||||
(eId, occId) <- runDB $ do
|
||||
Entity eId _ <- fetchExam tid ssh csh examn
|
||||
occ <- getKeyBy404 $ UniqueExamOccurrence eId occn
|
||||
return (eId, occ)
|
||||
|
||||
((btnResult, _), _) <- runFormPost buttonForm
|
||||
|
||||
|
||||
@ -69,7 +69,7 @@ getSheetListR tid ssh csh = do
|
||||
, sortable Nothing (i18nCell MsgSubmission)
|
||||
$ \DBRow{dbrOutput=(Entity _ Sheet{..}, _, mbSub, _)} -> case mbSub of
|
||||
Nothing -> mempty
|
||||
(Just (Entity sid Submission{..})) ->
|
||||
(Just (Entity sid Submission{})) ->
|
||||
let mkCid = encrypt sid -- TODO: executed twice
|
||||
mkRoute = do
|
||||
cid' <- mkCid
|
||||
|
||||
@ -122,7 +122,7 @@ colSelect :: forall act h. (Semigroup act, Monoid act, Headedness h) => Colonnad
|
||||
colSelect = dbSelect (_1 . applying _2) id $ \DBRow{ dbrOutput=(_, _, _, _, _, _, cid, _) } -> return cid
|
||||
|
||||
colSubmittors :: IsDBTable m a => Colonnade Sortable CorrectionTableData (DBCell m a)
|
||||
colSubmittors = sortable (Just "submittors") (i18nCell MsgSubmissionUsers) $ \DBRow{ dbrOutput=(_, Entity _ Sheet{..}, course, _, _, users, _, hasAccess) } ->
|
||||
colSubmittors = sortable (Just "submittors") (i18nCell MsgSubmissionUsers) $ \DBRow{ dbrOutput=(_, _, course, _, _, users, _, hasAccess) } ->
|
||||
let
|
||||
csh = course ^. _2
|
||||
tid = course ^. _3
|
||||
@ -136,8 +136,8 @@ colSubmittors = sortable (Just "submittors") (i18nCell MsgSubmissionUsers) $ \DB
|
||||
| otherwise -> mempty
|
||||
|
||||
colSMatrikel :: IsDBTable m a => Colonnade Sortable CorrectionTableData (DBCell m a)
|
||||
colSMatrikel = sortable (Just "submittors-matriculation") (i18nCell MsgMatrikelNr) $ \DBRow{ dbrOutput=(_, Entity _ Sheet{..}, (_, csh, tid, ssh), _, _, users, _, hasAccess) } ->
|
||||
let protoCell = listCell (Map.toList $ Map.mapMaybe (\x@(User{..}, _, _) -> (x,) <$> assertM (not . null) userMatrikelnummer) users) $ \(userId, ((User{..}, _, _), matr)) -> anchorCellCM $cacheIdentHere (CourseR tid ssh csh . CUserR <$> encrypt userId) matr
|
||||
colSMatrikel = sortable (Just "submittors-matriculation") (i18nCell MsgMatrikelNr) $ \DBRow{ dbrOutput=(_, _, (_, csh, tid, ssh), _, _, users, _, hasAccess) } ->
|
||||
let protoCell = listCell (Map.toList $ Map.mapMaybe (\x@(User{userMatrikelnummer}, _, _) -> (x,) <$> assertM (not . null) userMatrikelnummer) users) $ \(userId, (_, matr)) -> anchorCellCM $cacheIdentHere (CourseR tid ssh csh . CUserR <$> encrypt userId) matr
|
||||
in if | hasAccess -> protoCell & cellAttrs <>~ [("class", "list--inline list--comma-separated")]
|
||||
| otherwise -> mempty
|
||||
|
||||
|
||||
@ -15,7 +15,7 @@ import qualified Data.CaseInsensitive as CI
|
||||
|
||||
getCTutorialListR :: TermId -> SchoolId -> CourseShorthand -> Handler Html
|
||||
getCTutorialListR tid ssh csh = do
|
||||
Entity cid Course{..} <- runDB . getBy404 $ TermSchoolCourseShort tid ssh csh
|
||||
cid <- runDB . getKeyBy404 $ TermSchoolCourseShort tid ssh csh
|
||||
MsgRenderer mr <- getMsgRenderer
|
||||
|
||||
let
|
||||
|
||||
@ -16,7 +16,7 @@ import Handler.Tutorial.TutorInvite
|
||||
getCTutorialNewR, postCTutorialNewR :: TermId -> SchoolId -> CourseShorthand -> Handler Html
|
||||
getCTutorialNewR = postCTutorialNewR
|
||||
postCTutorialNewR tid ssh csh = do
|
||||
Entity cid Course{..} <- runDB . getBy404 $ TermSchoolCourseShort tid ssh csh
|
||||
cid <- runDB . getKeyBy404 $ TermSchoolCourseShort tid ssh csh
|
||||
|
||||
((newTutResult, newTutWidget), newTutEnctype) <- runFormPost $ tutorialForm cid Nothing
|
||||
|
||||
|
||||
@ -477,7 +477,7 @@ examAutoOccurrence (hash -> seed) rule ExamAutoOccurrenceConfig{..} occurrences
|
||||
bestOption :: Maybe [(ExamOccurrenceId, [[CI Char]])]
|
||||
bestOption = case rule of
|
||||
ExamRoomSurname -> do
|
||||
(_cost, res) <- distribute (sortBy (RFC5051.compareUnicode `on` toListOf (_1 . folded . to CI.foldedCase)) . Map.toAscList $ fromIntegral . Set.size <$> users') occurrences' lineNudges charCost
|
||||
(_cost, res) <- distribute (sortBy (RFC5051.compareUnicode `on` (pack . toListOf (_1 . folded . to CI.foldedCase))) . Map.toAscList $ fromIntegral . Set.size <$> users') occurrences' lineNudges charCost
|
||||
-- traceM $ show cost
|
||||
return res
|
||||
ExamRoomMatriculation -> do
|
||||
|
||||
@ -257,7 +257,7 @@ multiActionField :: forall action a.
|
||||
-> FieldSettings UniWorX
|
||||
-> Maybe action
|
||||
-> (Html -> MForm Handler (FormResult a, [FieldView UniWorX]))
|
||||
multiActionField minp acts (actField, actExternal, actMessage) fs@FieldSettings{..} defAction csrf = do
|
||||
multiActionField minp acts (actField, actExternal, actMessage) fs defAction csrf = do
|
||||
(actionRes, actionView) <- minp (checkBool (`Map.member` acts) MsgMultiActionUnknownAction actField) fs defAction
|
||||
results <- mapM (fmap (over _2 ($ [])) . aFormToForm) acts
|
||||
|
||||
@ -285,7 +285,7 @@ multiActionOpts' :: forall action a.
|
||||
-> FieldSettings UniWorX
|
||||
-> Maybe action
|
||||
-> (Html -> MForm Handler (FormResult a, [FieldView UniWorX]))
|
||||
multiActionOpts' minp acts mActsOpts fs@FieldSettings{..} defAction csrf = do
|
||||
multiActionOpts' minp acts mActsOpts fs defAction csrf = do
|
||||
actsOpts <- liftHandler mActsOpts
|
||||
let actsOpts' = OptionList
|
||||
{ olOptions = filter (flip Map.member acts . optionInternalValue) $ olOptions actsOpts
|
||||
@ -397,7 +397,7 @@ explainedMultiAction' :: forall action a.
|
||||
-> FieldSettings UniWorX
|
||||
-> Maybe action
|
||||
-> (Html -> MForm Handler (FormResult a, [FieldView UniWorX]))
|
||||
explainedMultiAction' minp acts mActsOpts fs@FieldSettings{..} defAction csrf = do
|
||||
explainedMultiAction' minp acts mActsOpts fs defAction csrf = do
|
||||
(actsOpts, actsReadExternal) <- liftHandler mActsOpts
|
||||
let actsOpts' = filter (flip Map.member acts . optionInternalValue . view _1) actsOpts
|
||||
actsReadExternal' = assertM (flip Map.member acts) . actsReadExternal
|
||||
|
||||
@ -31,7 +31,7 @@ import qualified Data.Char as Char
|
||||
|
||||
|
||||
validateRating :: SheetType -> Rating' -> [RatingValidityException]
|
||||
validateRating ratingSheetType Rating'{ ratingPoints=Just rp, .. }
|
||||
validateRating ratingSheetType Rating'{ ratingPoints=Just rp }
|
||||
| rp < 0
|
||||
= [RatingNegative]
|
||||
| NotGraded <- ratingSheetType
|
||||
@ -93,7 +93,7 @@ ratingFile :: ( MonadHandler m
|
||||
, HandlerSite m ~ UniWorX
|
||||
)
|
||||
=> CryptoFileNameSubmission -> Rating -> m File
|
||||
ratingFile cID rating@Rating{ ratingValues = Rating'{..}, .. } = do
|
||||
ratingFile cID rating@Rating{ ratingValues = Rating'{..} } = do
|
||||
mr'@(MsgRenderer mr) <- getMsgRenderer
|
||||
dtFmt <- getDateTimeFormatter
|
||||
fileModified <- maybe (liftIO getCurrentTime) return ratingTime
|
||||
|
||||
@ -320,7 +320,7 @@ submissionMultiArchive anonymous (Set.toList -> ids) = do
|
||||
respondSource typeZip . (<* lift cleanup) . transPipe (runDBRunner dbrunner) $ do
|
||||
let
|
||||
fileEntitySource' :: (Rating, Entity Submission, Maybe UTCTime, (SheetName,CourseShorthand,SchoolId,TermId,Bool)) -> ConduitT () File (YesodDB UniWorX) ()
|
||||
fileEntitySource' (rating, Entity submissionID Submission{..}, subTime, (shn,csh,ssh,tid,sheetAnonymous)) = do
|
||||
fileEntitySource' (rating, Entity submissionID Submission{}, subTime, (shn,csh,ssh,tid,sheetAnonymous)) = do
|
||||
cID <- encrypt submissionID
|
||||
|
||||
let
|
||||
|
||||
@ -450,7 +450,7 @@ instance Traversable DBRow where
|
||||
newtype PSValidator m x = PSValidator { runPSValidator :: DBTable m x -> Maybe PaginationInput -> ([SomeMessage UniWorX], PaginationSettings) }
|
||||
|
||||
instance Default (PSValidator m x) where
|
||||
def = PSValidator $ \DBTable{..} -> \case
|
||||
def = PSValidator $ \DBTable{} -> \case
|
||||
Nothing -> def
|
||||
Just pi -> swap . (\act -> execRWS act pi def) $ do
|
||||
asks piSorting >>= maybe (return ()) (\s -> modify $ \ps -> ps { psSorting = s })
|
||||
|
||||
@ -27,7 +27,7 @@ import qualified Database.Esqueleto as E
|
||||
determineCrontab :: DB (Crontab JobCtl)
|
||||
-- ^ Extract all future jobs from the database (sheet deadlines, ...)
|
||||
determineCrontab = execWriterT $ do
|
||||
UniWorX{ appSettings' = AppSettings{..}, .. } <- getYesod
|
||||
UniWorX{ appSettings' = AppSettings{..} } <- getYesod
|
||||
|
||||
case appJobFlushInterval of
|
||||
Just interval -> tell $ HashMap.singleton
|
||||
@ -343,7 +343,7 @@ determineCrontab = execWriterT $ do
|
||||
|
||||
|
||||
let
|
||||
externalExamJobs (Entity nExternalExam ExternalExam{..}) = do
|
||||
externalExamJobs nExternalExam = do
|
||||
newestResult <- lift . E.select . E.from $ \externalExamResult -> do
|
||||
E.where_ $ externalExamResult E.^. ExternalExamResultExam E.==. E.val nExternalExam
|
||||
return . E.max_ $ externalExamResult E.^. ExternalExamResultLastChanged
|
||||
@ -360,7 +360,7 @@ determineCrontab = execWriterT $ do
|
||||
}
|
||||
_other -> return ()
|
||||
|
||||
runConduit $ transPipe lift (selectSource [] []) .| C.mapM_ externalExamJobs
|
||||
runConduit $ transPipe lift (selectKeys [] []) .| C.mapM_ externalExamJobs
|
||||
|
||||
let
|
||||
allocationJobs (Entity nAllocation Allocation{..}) = do
|
||||
|
||||
@ -20,7 +20,7 @@ import qualified Data.Text as Text
|
||||
|
||||
dispatchNotificationSubmissionEdited :: UserId -> SubmissionId -> UserId -> Handler ()
|
||||
dispatchNotificationSubmissionEdited nInitiator nSubmission jRecipient = userMailT jRecipient $ do
|
||||
(Course{..}, Sheet{..}, Submission{..}, initiator, coSubmittors) <- liftHandler . runDB $ do
|
||||
(Course{..}, Sheet{..}, Submission{}, initiator, coSubmittors) <- liftHandler . runDB $ do
|
||||
submission <- getJust nSubmission
|
||||
sheet <- belongsToJust submissionSheet submission
|
||||
course <- belongsToJust sheetCourse sheet
|
||||
@ -55,7 +55,7 @@ dispatchNotificationSubmissionEdited nInitiator nSubmission jRecipient = userMai
|
||||
|
||||
dispatchNotificationSubmissionUserCreated :: UserId -> SubmissionId -> UserId -> Handler ()
|
||||
dispatchNotificationSubmissionUserCreated nUser nSubmission jRecipient = userMailT jRecipient $ do
|
||||
(User{..}, Course{..}, Sheet{..}, Submission{..}, coSubmittors) <- liftHandler . runDB $ do
|
||||
(User{..}, Course{..}, Sheet{..}, Submission{}, coSubmittors) <- liftHandler . runDB $ do
|
||||
submission <- getJust nSubmission
|
||||
sheet <- belongsToJust submissionSheet submission
|
||||
course <- belongsToJust sheetCourse sheet
|
||||
|
||||
@ -38,7 +38,7 @@ dispatchJobSynchroniseLdap numIterations epoch iteration
|
||||
|
||||
dispatchJobSynchroniseLdapUser :: UserId -> JobHandler UniWorX
|
||||
dispatchJobSynchroniseLdapUser jUser = JobHandlerException $ do
|
||||
UniWorX{ appSettings' = AppSettings{..}, .. } <- getYesod
|
||||
UniWorX{..} <- getYesod
|
||||
case appLdapPool of
|
||||
Just ldapPool ->
|
||||
runDB . void . runMaybeT . handleExc $ do
|
||||
|
||||
@ -418,7 +418,7 @@ instance FromJSON AppSettings where
|
||||
Ldap.Plain host -> not $ null host
|
||||
appLdapConf <- P.fromList . mapMaybe (assertM nonEmptyHost) <$> o .:? "ldap" .!= []
|
||||
appSmtpConf <- assertM (not . null . smtpHost) <$> o .:? "smtp"
|
||||
let validMemcachedConf MemcachedConf{memcachedConnectInfo = Memcached.ConnectInfo{..}, ..} = and
|
||||
let validMemcachedConf MemcachedConf{memcachedConnectInfo = Memcached.ConnectInfo{..}} = and
|
||||
[ not $ null connectHost
|
||||
, numConnection > 0
|
||||
, connectionIdleTime >= 0
|
||||
|
||||
@ -151,8 +151,8 @@ maybeAttribute a c (Just v) = [(a,c v)]
|
||||
|
||||
|
||||
newtype PrettyValue = PrettyValue { unPrettyValue :: Value }
|
||||
deriving (Eq, Read, Show, Generic, Typeable, Data)
|
||||
deriving newtype (Hashable, IsString, TH.Lift, FromJSON, ToJSON, NFData)
|
||||
deriving (Eq, Read, Show, Generic, Typeable, Data, TH.Lift)
|
||||
deriving newtype (Hashable, IsString, FromJSON, ToJSON, NFData)
|
||||
|
||||
instance ToContent PrettyValue where
|
||||
toContent = toContent . Builder.toLazyText . Aeson.encodePrettyToTextBuilder
|
||||
@ -166,8 +166,8 @@ toPrettyJSON = PrettyValue . toJSON
|
||||
|
||||
|
||||
newtype YamlValue = YamlValue { unYamlValue :: Value }
|
||||
deriving (Eq, Read, Show, Generic, Typeable, Data)
|
||||
deriving newtype (Hashable, IsString, TH.Lift, FromJSON, ToJSON, NFData)
|
||||
deriving (Eq, Read, Show, Generic, Typeable, Data, TH.Lift)
|
||||
deriving newtype (Hashable, IsString, FromJSON, ToJSON, NFData)
|
||||
|
||||
instance ToContent YamlValue where
|
||||
toContent = toContent . Yaml.encode
|
||||
|
||||
@ -71,10 +71,10 @@ curryN :: Int -> ExpQ
|
||||
curryN n = do
|
||||
fn <- newName "foo"
|
||||
xs <- replicateM n $ newName "x"
|
||||
let pat = map VarP (fn:xs)
|
||||
let tup = TupE (map VarE xs)
|
||||
let rhs = AppE (VarE fn) tup
|
||||
return $ LamE pat rhs
|
||||
let pat = map varP (fn:xs)
|
||||
let tup = tupE (map varE xs)
|
||||
let rhs = appE (varE fn) tup
|
||||
lamE pat rhs
|
||||
|
||||
uncurryN :: Int -> ExpQ
|
||||
uncurryN n = do
|
||||
|
||||
@ -137,7 +137,7 @@ instance (IsSessionData sess, Binary (Decomposed sess)) => Storage (MemcachedSql
|
||||
deleteSession MemcachedSqlStorage{..} sessId
|
||||
= liftIO . handleIf Memcached.isKeyNotFound (const $ return ()) $ Memcached.delete (memcachedSqlSessionId # sessId) mcdSqlMemcached
|
||||
|
||||
deleteAllSessionsOfAuthId MemcachedSqlStorage{..} authId = do
|
||||
deleteAllSessionsOfAuthId MemcachedSqlStorage{} authId = do
|
||||
now <- liftIO getCurrentTime
|
||||
void $ upsert
|
||||
( MemcachedSessionExpiration authId now )
|
||||
|
||||
@ -57,6 +57,7 @@ newtype CachedMemoT k v m a = CachedMemoT { runCachedMemoT' :: ReaderT Loc m a }
|
||||
, MonadIO
|
||||
, MonadThrow, MonadCatch, MonadMask, MonadLogger, MonadLoggerIO
|
||||
, MonadResource, MonadHandler, MonadWidget
|
||||
, MonadUnliftIO
|
||||
)
|
||||
deriving newtype ( MFunctor, MMonad, MonadTrans )
|
||||
|
||||
@ -67,9 +68,6 @@ instance MonadReader r m => MonadReader r (CachedMemoT k v m) where
|
||||
reader = CachedMemoT . lift . reader
|
||||
local f (CachedMemoT act) = CachedMemoT $ mapReaderT (local f) act
|
||||
|
||||
instance MonadUnliftIO m => MonadUnliftIO (CachedMemoT k v m) where
|
||||
askUnliftIO = (\UnliftIO{..} -> UnliftIO $ \(CachedMemoT f) -> unliftIO f) <$> CachedMemoT askUnliftIO
|
||||
|
||||
|
||||
-- | Uses `cachedBy` with a `Binary`-encoded @k@
|
||||
instance (Typeable v, Binary k, MonadHandler m) => MonadMemo k v (CachedMemoT k v m) where
|
||||
|
||||
153
stack.yaml
153
stack.yaml
@ -34,91 +34,124 @@ extra-deps:
|
||||
commit: f8170266ab25b533576e96715bedffc5aa4f19fa
|
||||
subdirs:
|
||||
- colonnade
|
||||
- git: git@gitlab2.rz.ifi.lmu.de:uni2work/minio-hs.git
|
||||
commit: 9a4e3889a93cf71d6bbf45b673f6353b39f15d9f
|
||||
# - git: git@gitlab2.rz.ifi.lmu.de:uni2work/minio-hs.git
|
||||
# commit: 9a4e3889a93cf71d6bbf45b673f6353b39f15d9f
|
||||
- ../minio-hs
|
||||
|
||||
|
||||
# - colonnade-1.2.0.2
|
||||
- hsass-0.8.0
|
||||
- hlibsass-0.1.8.1
|
||||
- tz-0.1.3.3
|
||||
# # - colonnade-1.2.0.2
|
||||
# - hsass-0.8.0
|
||||
# - hlibsass-0.1.8.1
|
||||
# - tz-0.1.3.3
|
||||
|
||||
# - zip-stream-0.2.0.1
|
||||
# # - zip-stream-0.2.0.1
|
||||
|
||||
- uuid-crypto-1.4.0.0
|
||||
- filepath-crypto-0.1.0.0
|
||||
- cryptoids-0.5.1.0
|
||||
- cryptoids-types-1.0.0
|
||||
- cryptoids-class-0.0.0
|
||||
# - uuid-crypto-1.4.0.0
|
||||
# - filepath-crypto-0.1.0.0
|
||||
# - cryptoids-0.5.1.0
|
||||
# - cryptoids-types-1.0.0
|
||||
# - cryptoids-class-0.0.0
|
||||
|
||||
- system-locale-0.3.0.0
|
||||
# - system-locale-0.3.0.0
|
||||
|
||||
- hlint-test-0.1.0.0
|
||||
# - hlint-test-0.1.0.0
|
||||
|
||||
- pkcs7-1.0.0.1
|
||||
# - pkcs7-1.0.0.1
|
||||
|
||||
- systemd-2.2.0
|
||||
# - systemd-2.2.0
|
||||
|
||||
# - directory-1.3.4.0
|
||||
# # - directory-1.3.4.0
|
||||
|
||||
# - HaXml-1.25.5
|
||||
# # - HaXml-1.25.5
|
||||
|
||||
# - persistent-2.10.4
|
||||
# - persistent-postgresql-2.10.1
|
||||
# - persistent-template-2.7.3
|
||||
# - esqueleto-3.2.3
|
||||
# # - persistent-2.10.4
|
||||
# # - persistent-postgresql-2.10.1
|
||||
# # - persistent-template-2.7.3
|
||||
# # - esqueleto-3.2.3
|
||||
|
||||
- sandi-0.5
|
||||
- storable-endian-0.2.6
|
||||
# - universe-1.2
|
||||
# - universe-base-1.1.1
|
||||
# - universe-reverse-instances-1.1
|
||||
# - unliftio-pool-0.2.1.0
|
||||
# - universe-instances-extended-1.1.1
|
||||
# - universe-some-1.2
|
||||
# - some-1.0.0.3
|
||||
# - sandi-0.5
|
||||
# - storable-endian-0.2.6
|
||||
# # - universe-1.2
|
||||
# # - universe-base-1.1.1
|
||||
# # - universe-reverse-instances-1.1
|
||||
# # - unliftio-pool-0.2.1.0
|
||||
# # - universe-instances-extended-1.1.1
|
||||
# # - universe-some-1.2
|
||||
# # - some-1.0.0.3
|
||||
|
||||
# - network-bsd-2.8.1.0
|
||||
# # - network-bsd-2.8.1.0
|
||||
|
||||
# - persistent-qq-2.9.1
|
||||
# # - persistent-qq-2.9.1
|
||||
|
||||
# - process-1.6.5.1
|
||||
# # - process-1.6.5.1
|
||||
|
||||
# - generic-lens-1.2.0.0
|
||||
# # - generic-lens-1.2.0.0
|
||||
|
||||
- prometheus-metrics-ghc-1.0.1
|
||||
- wai-middleware-prometheus-1.0.0
|
||||
# - prometheus-metrics-ghc-1.0.1
|
||||
# - wai-middleware-prometheus-1.0.0
|
||||
|
||||
# - extended-reals-0.2.3.0
|
||||
# # - extended-reals-0.2.3.0
|
||||
|
||||
- pandoc-2.9.2
|
||||
- doclayout-0.3
|
||||
- doctemplates-0.8.1
|
||||
# - emojis-0.1
|
||||
# - hslua-module-system-0.2.1
|
||||
# - ipynb-0.1
|
||||
# - jira-wiki-markup-1.0.0
|
||||
# - HsYAML-0.2.1.0
|
||||
# - cmark-gfm-0.2.1
|
||||
# - haddock-library-1.8.0
|
||||
# - pandoc-types-1.20
|
||||
# - skylighting-0.8.3.2
|
||||
# - skylighting-core-0.8.3.2
|
||||
# - texmath-0.12.0.1
|
||||
# - pandoc-2.9.2
|
||||
# - doclayout-0.3
|
||||
# - doctemplates-0.8.1
|
||||
# # - emojis-0.1
|
||||
# # - hslua-module-system-0.2.1
|
||||
# # - ipynb-0.1
|
||||
# # - jira-wiki-markup-1.0.0
|
||||
# # - HsYAML-0.2.1.0
|
||||
# # - cmark-gfm-0.2.1
|
||||
# # - haddock-library-1.8.0
|
||||
# # - pandoc-types-1.20
|
||||
# # - skylighting-0.8.3.2
|
||||
# # - skylighting-core-0.8.3.2
|
||||
# # - texmath-0.12.0.1
|
||||
|
||||
- binary-instances-1
|
||||
# - binary-instances-1
|
||||
|
||||
- acid-state-0.16.0
|
||||
# - acid-state-0.16.0
|
||||
|
||||
- unidecode-0.1.0.4
|
||||
# - unidecode-0.1.0.4
|
||||
|
||||
- token-bucket-0.1.0.1
|
||||
# - token-bucket-0.1.0.1
|
||||
|
||||
- normaldistribution-1.1.0.3
|
||||
# - normaldistribution-1.1.0.3
|
||||
|
||||
- unordered-containers-0.2.11.0
|
||||
# - unordered-containers-0.2.11.0
|
||||
|
||||
- base64-bytestring-1.1.0.0
|
||||
# - base64-bytestring-1.1.0.0
|
||||
|
||||
resolver: lts-15.12
|
||||
- acid-state-0.16.0.1@sha256:d43f6ee0b23338758156c500290c4405d769abefeb98e9bc112780dae09ece6f,6207
|
||||
- bytebuild-0.3.6.0@sha256:aec785c906db5c7ec730754683196eb99a0d48e0deff7d4034c7b58307040b85,2982
|
||||
- byteslice-0.2.3.0@sha256:3ebcc77f8ac9fec3ca1a8304e66cfe0a1590c9272b768f2b19637e06de00bf6d,2014
|
||||
- bytesmith-0.3.7.0@sha256:a11e4ca0fb72cd966c21d82dcc2eb7f3aa748b3fbfe30ab6c7fa8beea38c8e83,1863
|
||||
- commonmark-0.1.0.2@sha256:fbff7a2ade0ce7d699964a87f765e503a3a9e22542c05f0f02ba7aad64e38af4,3278
|
||||
- commonmark-extensions-0.2.0.1@sha256:647aa8dba5fd46984ddedc15c3693c9c4d9655503d42006576bd8f0dadf8cd39,3176
|
||||
- commonmark-pandoc-0.2.0.0@sha256:84a9f6846d4fe33e9f0dcd938ef1c83162fb4fe81cca66315249e86414aac226,1167
|
||||
- contiguous-0.5.1@sha256:902b74d8e369fef384c20b116c3c81e65eca2672d79f525ab374fe98ee50e9d4,1757
|
||||
- cryptoids-0.5.1.0@sha256:729cd89059c6b6a50e07b2e279f6d95ee9432caeedc7e2f38f71e59c422957bc,1570
|
||||
- cryptoids-class-0.0.0@sha256:8d22912538faa99849fed7f51eb742fbbf5f9557d04e1d81bcac408d88c16c30,985
|
||||
- cryptoids-types-1.0.0@sha256:96a74b33a32ebeebf5bee08e2a205e5c1585b4b46b8bac086ca7fde49aec5f5b,1271
|
||||
- filepath-crypto-0.1.0.0@sha256:e02bc15858cf06edf9788a38b5b58d45e82c7f5589785a178a903d792af04125,1593
|
||||
- hlibsass-0.1.10.1@sha256:08db56c633e9a83a642d8ea57dffa93112b092d05bf8f3b07491cfee9ee0dfa5,2565
|
||||
- hsass-0.8.0@sha256:05fb3d435dbdf9f66a98db4e1ee57a313170a677e52ab3a5a05ced1fc42b0834,2899
|
||||
- ip-1.7.2@sha256:2148bbc7b5e66ea7273b6014bb30483cc656b2cd4e53efaf165c2223bdbbeb46,3742
|
||||
- natural-arithmetic-0.1.2.0@sha256:ac25a0561c8378530a62f02df83680afb193ed1059bb43e3130e0074b5b3f16b,3411
|
||||
- normaldistribution-1.1.0.3@sha256:2615b784c4112cbf6ffa0e2b55b76790290a9b9dff18a05d8c89aa374b213477,2160
|
||||
- pandoc-2.10.1@sha256:23d7ec480c7cb86740475a419d6ca4819987b6dd23bbae9b50bc3d42a7ed2f9f,36933
|
||||
- pkcs7-1.0.0.1@sha256:b26e5181868667abbde3ce17f9a61cf705eb695da073cdf82e1f9dfd6cc11176,3594
|
||||
- primitive-offset-0.2.0.0@sha256:f8006927d5c0a3e83707610bbc5514aabe8f84a907ecb07edd2c815f58299dea,843
|
||||
- primitive-unlifted-0.1.3.0@sha256:a98f827740f5dcf097d885b3a47c32f4462204449620abc9d51b8c4f8619f9e6,1427
|
||||
- prometheus-metrics-ghc-1.0.1.1@sha256:d378a7186a967140fe0e09d325fe5e3bfd7b77a1123934b40f81fdfed2eacbdc,1233
|
||||
- run-st-0.1.1.0@sha256:a43245bb23984089016772481bf52bfe63eaff0c5040303f69c9b15e80872fdc,883
|
||||
- sandi-0.5@sha256:b278d072ca717706ea38f9bd646e023f7f2576a778fb43565b434f93638849aa,3010
|
||||
- system-locale-0.3.0.0@sha256:13b3982403d8ac8cc6138e68802be8d8e7cf7ebc4cbc7e47e99e3c0dd1be066a,1529
|
||||
- token-bucket-0.1.0.1@sha256:d8e85f2fc373939975e7ace7907baee177531ab6e43df94e330a2357e64a2d11,1899
|
||||
- tuples-0.1.0.0@sha256:7006c1cab721ad3e39cdbf1ccb07ec050b94d654cc6e39277d46241eee6ac7c9,1088
|
||||
- tz-0.1.3.4@sha256:bd311e202b8bdd15bcd6a4ca182e69794949d3b3b9f4aa835e9ccff011284979,5086
|
||||
- unidecode-0.1.0.4@sha256:99581ee1ea334a4596a09ae3642e007808457c66893b587e965b31f15cbf8c4d,1144
|
||||
- uuid-crypto-1.4.0.0@sha256:9e2f271e61467d9ea03e78cddad75a97075d8f5108c36a28d59c65abb3efd290,1325
|
||||
- wai-middleware-prometheus-1.0.0@sha256:1625792914fb2139f005685be8ce519111451cfb854816e430fbf54af46238b4,1314
|
||||
|
||||
resolver: nightly-2020-08-08
|
||||
allow-newer: true
|
||||
|
||||
301
stack.yaml.lock
301
stack.yaml.lock
@ -151,204 +151,225 @@ packages:
|
||||
git: git@gitlab2.rz.ifi.lmu.de:uni2work/colonnade.git
|
||||
commit: f8170266ab25b533576e96715bedffc5aa4f19fa
|
||||
- completed:
|
||||
cabal-file:
|
||||
size: 9845
|
||||
sha256: 674630347209bc5f7984e8e9d93293510489921f2d2d6092ad1c9b8c61b6560a
|
||||
name: minio-hs
|
||||
version: 1.5.2
|
||||
git: git@gitlab2.rz.ifi.lmu.de:uni2work/minio-hs.git
|
||||
hackage: acid-state-0.16.0.1@sha256:d43f6ee0b23338758156c500290c4405d769abefeb98e9bc112780dae09ece6f,6207
|
||||
pantry-tree:
|
||||
size: 4517
|
||||
sha256: ef7c5960da571c6cb41337b0bd30740bac92b4781b375be704093fdadd17330d
|
||||
commit: 9a4e3889a93cf71d6bbf45b673f6353b39f15d9f
|
||||
size: 13678
|
||||
sha256: d57bcb2ad5e01fe7424abbcf9e58cf943027b5c4a8496d93625c57b6e1272274
|
||||
original:
|
||||
git: git@gitlab2.rz.ifi.lmu.de:uni2work/minio-hs.git
|
||||
commit: 9a4e3889a93cf71d6bbf45b673f6353b39f15d9f
|
||||
hackage: acid-state-0.16.0.1@sha256:d43f6ee0b23338758156c500290c4405d769abefeb98e9bc112780dae09ece6f,6207
|
||||
- completed:
|
||||
hackage: hsass-0.8.0@sha256:82d55fb2a10342accbc4fe80d263163f40a138d8636e275aa31ffa81b14abf01,2792
|
||||
hackage: bytebuild-0.3.6.0@sha256:aec785c906db5c7ec730754683196eb99a0d48e0deff7d4034c7b58307040b85,2982
|
||||
pantry-tree:
|
||||
size: 1448
|
||||
sha256: dc39ed0207b8b22d2713054421dbd5452baa9704df75bedf17f04f97a29f3d9a
|
||||
size: 844
|
||||
sha256: 5e6fd3de57a4d44257fb475433633939459e0294fafe79b21ff67aeb93a81591
|
||||
original:
|
||||
hackage: hsass-0.8.0
|
||||
hackage: bytebuild-0.3.6.0@sha256:aec785c906db5c7ec730754683196eb99a0d48e0deff7d4034c7b58307040b85,2982
|
||||
- completed:
|
||||
hackage: hlibsass-0.1.8.1@sha256:7005d0f3fee66e776300117f6bf31583bf310f58df6d7f552c8811bd406abfc8,2564
|
||||
hackage: byteslice-0.2.3.0@sha256:3ebcc77f8ac9fec3ca1a8304e66cfe0a1590c9272b768f2b19637e06de00bf6d,2014
|
||||
pantry-tree:
|
||||
size: 8441
|
||||
sha256: c3c1fe56c35eed093772b9900d7038287b829d67960c6f96a82c9dc46b203db0
|
||||
size: 1095
|
||||
sha256: 9ada4e1c418e8d9029edefdf664c64ff419ed1f02564e5a0dd28dd03e1e716a6
|
||||
original:
|
||||
hackage: hlibsass-0.1.8.1
|
||||
hackage: byteslice-0.2.3.0@sha256:3ebcc77f8ac9fec3ca1a8304e66cfe0a1590c9272b768f2b19637e06de00bf6d,2014
|
||||
- completed:
|
||||
hackage: tz-0.1.3.3@sha256:b9de0c1b10825460ff14a237209a8bf7747f47979601d35621276556bf63d2ca,5086
|
||||
hackage: bytesmith-0.3.7.0@sha256:a11e4ca0fb72cd966c21d82dcc2eb7f3aa748b3fbfe30ab6c7fa8beea38c8e83,1863
|
||||
pantry-tree:
|
||||
size: 1180
|
||||
sha256: ae6af45f3dba5a478ea9cc77c718f955fcc5c96f2dc0f4ede34c4a15a3e85ac1
|
||||
size: 1185
|
||||
sha256: 3396c1b29577cff2491382d0b144fe586c75987e9ad28bc0cadbc88a97ee7315
|
||||
original:
|
||||
hackage: tz-0.1.3.3
|
||||
hackage: bytesmith-0.3.7.0@sha256:a11e4ca0fb72cd966c21d82dcc2eb7f3aa748b3fbfe30ab6c7fa8beea38c8e83,1863
|
||||
- completed:
|
||||
hackage: uuid-crypto-1.4.0.0@sha256:9e2f271e61467d9ea03e78cddad75a97075d8f5108c36a28d59c65abb3efd290,1325
|
||||
hackage: commonmark-0.1.0.2@sha256:fbff7a2ade0ce7d699964a87f765e503a3a9e22542c05f0f02ba7aad64e38af4,3278
|
||||
pantry-tree:
|
||||
size: 364
|
||||
sha256: 6650b51ea060397c412b07b256c043546913292973284a7149ddd08f489b3e48
|
||||
size: 1346
|
||||
sha256: 991da6da60804286b9ea23a1522e18ceeabddfdf416787231db9fd047c163f53
|
||||
original:
|
||||
hackage: uuid-crypto-1.4.0.0
|
||||
hackage: commonmark-0.1.0.2@sha256:fbff7a2ade0ce7d699964a87f765e503a3a9e22542c05f0f02ba7aad64e38af4,3278
|
||||
- completed:
|
||||
hackage: filepath-crypto-0.1.0.0@sha256:e02bc15858cf06edf9788a38b5b58d45e82c7f5589785a178a903d792af04125,1593
|
||||
hackage: commonmark-extensions-0.2.0.1@sha256:647aa8dba5fd46984ddedc15c3693c9c4d9655503d42006576bd8f0dadf8cd39,3176
|
||||
pantry-tree:
|
||||
size: 623
|
||||
sha256: bce236365ebdc6e5c46f740876a6fb5ad688e8ee3b305933822ab027e5b5fd86
|
||||
size: 2927
|
||||
sha256: 89e1ee05938d558834c397a3a22cdacc755a1941c144f4c1f3daf8a1ede943ce
|
||||
original:
|
||||
hackage: filepath-crypto-0.1.0.0
|
||||
hackage: commonmark-extensions-0.2.0.1@sha256:647aa8dba5fd46984ddedc15c3693c9c4d9655503d42006576bd8f0dadf8cd39,3176
|
||||
- completed:
|
||||
hackage: commonmark-pandoc-0.2.0.0@sha256:84a9f6846d4fe33e9f0dcd938ef1c83162fb4fe81cca66315249e86414aac226,1167
|
||||
pantry-tree:
|
||||
size: 326
|
||||
sha256: aa88fb10bd382b8d942b51b2ad0b94f52a72a4e37c8085abc5c380964c7eeb7c
|
||||
original:
|
||||
hackage: commonmark-pandoc-0.2.0.0@sha256:84a9f6846d4fe33e9f0dcd938ef1c83162fb4fe81cca66315249e86414aac226,1167
|
||||
- completed:
|
||||
hackage: contiguous-0.5.1@sha256:902b74d8e369fef384c20b116c3c81e65eca2672d79f525ab374fe98ee50e9d4,1757
|
||||
pantry-tree:
|
||||
size: 442
|
||||
sha256: 39ee8ba3b4725ed1057429cd1f613275bfecbc618f289559203bebb1ff4a259e
|
||||
original:
|
||||
hackage: contiguous-0.5.1@sha256:902b74d8e369fef384c20b116c3c81e65eca2672d79f525ab374fe98ee50e9d4,1757
|
||||
- completed:
|
||||
hackage: cryptoids-0.5.1.0@sha256:729cd89059c6b6a50e07b2e279f6d95ee9432caeedc7e2f38f71e59c422957bc,1570
|
||||
pantry-tree:
|
||||
size: 513
|
||||
sha256: 563e8d2b616ec3e0e7984d6b069095b6c3959065c0bb047fc8dd5809711a3e6b
|
||||
original:
|
||||
hackage: cryptoids-0.5.1.0
|
||||
- completed:
|
||||
hackage: cryptoids-types-1.0.0@sha256:96a74b33a32ebeebf5bee08e2a205e5c1585b4b46b8bac086ca7fde49aec5f5b,1271
|
||||
pantry-tree:
|
||||
size: 268
|
||||
sha256: 0e9b11f6414a0a179cd11dec55261a1f9995663fcf27bfd4a386c48652655404
|
||||
original:
|
||||
hackage: cryptoids-types-1.0.0
|
||||
hackage: cryptoids-0.5.1.0@sha256:729cd89059c6b6a50e07b2e279f6d95ee9432caeedc7e2f38f71e59c422957bc,1570
|
||||
- completed:
|
||||
hackage: cryptoids-class-0.0.0@sha256:8d22912538faa99849fed7f51eb742fbbf5f9557d04e1d81bcac408d88c16c30,985
|
||||
pantry-tree:
|
||||
size: 359
|
||||
sha256: 6a5af7c785c230501fa6088ecf963c7de7463ab75b3f646510612f17dff69744
|
||||
original:
|
||||
hackage: cryptoids-class-0.0.0
|
||||
hackage: cryptoids-class-0.0.0@sha256:8d22912538faa99849fed7f51eb742fbbf5f9557d04e1d81bcac408d88c16c30,985
|
||||
- completed:
|
||||
hackage: system-locale-0.3.0.0@sha256:13b3982403d8ac8cc6138e68802be8d8e7cf7ebc4cbc7e47e99e3c0dd1be066a,1529
|
||||
hackage: cryptoids-types-1.0.0@sha256:96a74b33a32ebeebf5bee08e2a205e5c1585b4b46b8bac086ca7fde49aec5f5b,1271
|
||||
pantry-tree:
|
||||
size: 446
|
||||
sha256: 3b22af3e6315835bf614a0d30381ec7e47aca147b59ba601aeaa26f1fdc19373
|
||||
size: 268
|
||||
sha256: 0e9b11f6414a0a179cd11dec55261a1f9995663fcf27bfd4a386c48652655404
|
||||
original:
|
||||
hackage: system-locale-0.3.0.0
|
||||
hackage: cryptoids-types-1.0.0@sha256:96a74b33a32ebeebf5bee08e2a205e5c1585b4b46b8bac086ca7fde49aec5f5b,1271
|
||||
- completed:
|
||||
hackage: hlint-test-0.1.0.0@sha256:e427c0593433205fc629fb05b74c6b1deb1de72d1571f26142de008f0d5ee7a9,1814
|
||||
hackage: filepath-crypto-0.1.0.0@sha256:e02bc15858cf06edf9788a38b5b58d45e82c7f5589785a178a903d792af04125,1593
|
||||
pantry-tree:
|
||||
size: 442
|
||||
sha256: 347eac6c8a3c02fc0101444d6526b57b3c27785809149b12f90d8db57c721fea
|
||||
size: 623
|
||||
sha256: bce236365ebdc6e5c46f740876a6fb5ad688e8ee3b305933822ab027e5b5fd86
|
||||
original:
|
||||
hackage: hlint-test-0.1.0.0
|
||||
hackage: filepath-crypto-0.1.0.0@sha256:e02bc15858cf06edf9788a38b5b58d45e82c7f5589785a178a903d792af04125,1593
|
||||
- completed:
|
||||
hackage: pkcs7-1.0.0.1@sha256:b26e5181868667abbde3ce17f9a61cf705eb695da073cdf82e1f9dfd6cc11176,3594
|
||||
hackage: hlibsass-0.1.10.1@sha256:08db56c633e9a83a642d8ea57dffa93112b092d05bf8f3b07491cfee9ee0dfa5,2565
|
||||
pantry-tree:
|
||||
size: 316
|
||||
sha256: ab3c2d2880179a945ab3122c51d1657ab4a7a628292b646e047cd32b0751a80c
|
||||
size: 11229
|
||||
sha256: 39b62f1f3f30c5a9e12f9c6a040d6863edb5ce81951452e649152a18145ee1bc
|
||||
original:
|
||||
hackage: pkcs7-1.0.0.1
|
||||
hackage: hlibsass-0.1.10.1@sha256:08db56c633e9a83a642d8ea57dffa93112b092d05bf8f3b07491cfee9ee0dfa5,2565
|
||||
- completed:
|
||||
hackage: systemd-2.2.0@sha256:a41399ad921e3c90bb04219a66821631c17c94326961f9b6c71542abb042375f,1477
|
||||
hackage: hsass-0.8.0@sha256:05fb3d435dbdf9f66a98db4e1ee57a313170a677e52ab3a5a05ced1fc42b0834,2899
|
||||
pantry-tree:
|
||||
size: 520
|
||||
sha256: 188d4e07a62653b24091dc25c0222deb7a95037630d17a13327d269391050b7d
|
||||
size: 1448
|
||||
sha256: b25aeb947cb4e0b550f8a6f226d06503ef0edcb54712ad9cdd4fb2b05bf16c7c
|
||||
original:
|
||||
hackage: systemd-2.2.0
|
||||
hackage: hsass-0.8.0@sha256:05fb3d435dbdf9f66a98db4e1ee57a313170a677e52ab3a5a05ced1fc42b0834,2899
|
||||
- completed:
|
||||
hackage: sandi-0.5@sha256:b278d072ca717706ea38f9bd646e023f7f2576a778fb43565b434f93638849aa,3010
|
||||
hackage: ip-1.7.2@sha256:2148bbc7b5e66ea7273b6014bb30483cc656b2cd4e53efaf165c2223bdbbeb46,3742
|
||||
pantry-tree:
|
||||
size: 3455
|
||||
sha256: 5ca7ce4bc22ab9d4427bb149b5e283ab9db43375df14f7131fdfd48775f36350
|
||||
size: 1437
|
||||
sha256: c60e78361b92eebfa341027377787e39de5a16218ab605456cf4cf1de5f58b2a
|
||||
original:
|
||||
hackage: sandi-0.5
|
||||
hackage: ip-1.7.2@sha256:2148bbc7b5e66ea7273b6014bb30483cc656b2cd4e53efaf165c2223bdbbeb46,3742
|
||||
- completed:
|
||||
hackage: storable-endian-0.2.6@sha256:cae7aac2bfe6037660b2cf294891867e69bcd74e739a3b3ea759e9ad99d6c889,801
|
||||
hackage: natural-arithmetic-0.1.2.0@sha256:ac25a0561c8378530a62f02df83680afb193ed1059bb43e3130e0074b5b3f16b,3411
|
||||
pantry-tree:
|
||||
size: 223
|
||||
sha256: 6a8e43727f9b146238d4064fffc39d629f06622106922487fea922ec73aaee1e
|
||||
size: 716
|
||||
sha256: e1e5b16f53fe2a7378d38dcae5069dcc1c6e37f8e1473f091ae1f7d788b1c688
|
||||
original:
|
||||
hackage: storable-endian-0.2.6
|
||||
- completed:
|
||||
hackage: prometheus-metrics-ghc-1.0.1@sha256:d12cd520cbedff91bd193e0192056474723e953e69cdf817fb79494d110df390,1231
|
||||
pantry-tree:
|
||||
size: 293
|
||||
sha256: b412f2835ee5791a7f4f634c416227b70bae50511666d9f68683e5e21b5c2821
|
||||
original:
|
||||
hackage: prometheus-metrics-ghc-1.0.1
|
||||
- completed:
|
||||
hackage: wai-middleware-prometheus-1.0.0@sha256:1625792914fb2139f005685be8ce519111451cfb854816e430fbf54af46238b4,1314
|
||||
pantry-tree:
|
||||
size: 307
|
||||
sha256: 6d64803c639ed4c7204ea6fab0536b97d3ee16cdecb9b4a883cd8e56d3c61402
|
||||
original:
|
||||
hackage: wai-middleware-prometheus-1.0.0
|
||||
- completed:
|
||||
hackage: pandoc-2.9.2@sha256:fa04b214c79328a4519093a5e82fe961a21179539165b98773a6f8bfb66bc662,36181
|
||||
pantry-tree:
|
||||
size: 88080
|
||||
sha256: 95eeae57b3d00eb7fa1accacab31e032f4d535c8c2cb992891a20d694eb00339
|
||||
original:
|
||||
hackage: pandoc-2.9.2
|
||||
- completed:
|
||||
hackage: doclayout-0.3@sha256:06c03875b1645e6ab835c40f9b73fd959b6c4232c01d06f07debedfae46723f2,2059
|
||||
pantry-tree:
|
||||
size: 425
|
||||
sha256: ed2fc2dd826fbba67cb8018979be437b215735fab90dcc49ad30b296f7005eed
|
||||
original:
|
||||
hackage: doclayout-0.3
|
||||
- completed:
|
||||
hackage: doctemplates-0.8.1@sha256:be34c3210d9ebbba1c10100e30d8c3ba3b6c34653ec2ed15f09e5d05055aa37d,3111
|
||||
pantry-tree:
|
||||
size: 2303
|
||||
sha256: 9d4d8e7a85166ffd951b02f87be540607b55084c04730932346072329adf4913
|
||||
original:
|
||||
hackage: doctemplates-0.8.1
|
||||
- completed:
|
||||
hackage: binary-instances-1@sha256:b17565598b8df3241f9b46fa8e3a3368ecc8e3f2eb175d7c28f319042a6f5c79,2613
|
||||
pantry-tree:
|
||||
size: 1035
|
||||
sha256: 938ffc6990cac12681c657f7afa93737eecf335e6f0212d8c0b7c1ea3e0f40f4
|
||||
original:
|
||||
hackage: binary-instances-1
|
||||
- completed:
|
||||
hackage: acid-state-0.16.0@sha256:a5640fd8d99bdb5f152476a2ae56cc8eb81864b280c8ec7d1387e81296ed844d,6190
|
||||
pantry-tree:
|
||||
size: 13678
|
||||
sha256: c6e4b7f00d2a500e6286beafe3a2da7ba898a9ea31f5744df57cdce8a8f5890f
|
||||
original:
|
||||
hackage: acid-state-0.16.0
|
||||
- completed:
|
||||
hackage: unidecode-0.1.0.4@sha256:99581ee1ea334a4596a09ae3642e007808457c66893b587e965b31f15cbf8c4d,1144
|
||||
pantry-tree:
|
||||
size: 492
|
||||
sha256: 4959068a0caf410dd4b8046f0b0138e3cf6471abb0cc865c9993db3b2930d283
|
||||
original:
|
||||
hackage: unidecode-0.1.0.4
|
||||
- completed:
|
||||
hackage: token-bucket-0.1.0.1@sha256:d8e85f2fc373939975e7ace7907baee177531ab6e43df94e330a2357e64a2d11,1899
|
||||
pantry-tree:
|
||||
size: 399
|
||||
sha256: b0b4a08ea1bf76bd108310f64d7f80e0f30b61ddc3d71f6cab7bdce329d2c1fa
|
||||
original:
|
||||
hackage: token-bucket-0.1.0.1
|
||||
hackage: natural-arithmetic-0.1.2.0@sha256:ac25a0561c8378530a62f02df83680afb193ed1059bb43e3130e0074b5b3f16b,3411
|
||||
- completed:
|
||||
hackage: normaldistribution-1.1.0.3@sha256:2615b784c4112cbf6ffa0e2b55b76790290a9b9dff18a05d8c89aa374b213477,2160
|
||||
pantry-tree:
|
||||
size: 269
|
||||
sha256: 856818862d12df8b030fa9cfef2c4ffa604d06f0eb057498db245dfffcd60e3c
|
||||
original:
|
||||
hackage: normaldistribution-1.1.0.3
|
||||
hackage: normaldistribution-1.1.0.3@sha256:2615b784c4112cbf6ffa0e2b55b76790290a9b9dff18a05d8c89aa374b213477,2160
|
||||
- completed:
|
||||
hackage: unordered-containers-0.2.11.0@sha256:ba70b8a9d7eebc2034bf92e5690b2dd71200e76aa9f3f93e0b6be3f27f244d18,4998
|
||||
hackage: pandoc-2.10.1@sha256:23d7ec480c7cb86740475a419d6ca4819987b6dd23bbae9b50bc3d42a7ed2f9f,36933
|
||||
pantry-tree:
|
||||
size: 1416
|
||||
sha256: d9b83f62373f509a441223f22f12e22e39b38ef3275dfca7c190a4795bebfed5
|
||||
size: 89646
|
||||
sha256: 08c8b20356152b9ee8161bacafda2dc1bed13d7db4cbf38ab040c1977b2d28d5
|
||||
original:
|
||||
hackage: unordered-containers-0.2.11.0
|
||||
hackage: pandoc-2.10.1@sha256:23d7ec480c7cb86740475a419d6ca4819987b6dd23bbae9b50bc3d42a7ed2f9f,36933
|
||||
- completed:
|
||||
hackage: base64-bytestring-1.1.0.0@sha256:190264fef9e65d9085f00ccda419137096d1dc94777c58272bc96821dc7f37c3,2334
|
||||
hackage: pkcs7-1.0.0.1@sha256:b26e5181868667abbde3ce17f9a61cf705eb695da073cdf82e1f9dfd6cc11176,3594
|
||||
pantry-tree:
|
||||
size: 850
|
||||
sha256: 9ade5b5911df97c37b249b84f123297049f19578cae171c647bf47683633427c
|
||||
size: 316
|
||||
sha256: ab3c2d2880179a945ab3122c51d1657ab4a7a628292b646e047cd32b0751a80c
|
||||
original:
|
||||
hackage: base64-bytestring-1.1.0.0
|
||||
hackage: pkcs7-1.0.0.1@sha256:b26e5181868667abbde3ce17f9a61cf705eb695da073cdf82e1f9dfd6cc11176,3594
|
||||
- completed:
|
||||
hackage: primitive-offset-0.2.0.0@sha256:f8006927d5c0a3e83707610bbc5514aabe8f84a907ecb07edd2c815f58299dea,843
|
||||
pantry-tree:
|
||||
size: 368
|
||||
sha256: 6dbc2fbfd70920a1de5a76d3715506edc0895c81a2f7b856d3abb027865d4605
|
||||
original:
|
||||
hackage: primitive-offset-0.2.0.0@sha256:f8006927d5c0a3e83707610bbc5514aabe8f84a907ecb07edd2c815f58299dea,843
|
||||
- completed:
|
||||
hackage: primitive-unlifted-0.1.3.0@sha256:a98f827740f5dcf097d885b3a47c32f4462204449620abc9d51b8c4f8619f9e6,1427
|
||||
pantry-tree:
|
||||
size: 420
|
||||
sha256: c882dca2a96b98d02b0d21875b651edb11ac67d90e736c0de7a92c410a19eb7f
|
||||
original:
|
||||
hackage: primitive-unlifted-0.1.3.0@sha256:a98f827740f5dcf097d885b3a47c32f4462204449620abc9d51b8c4f8619f9e6,1427
|
||||
- completed:
|
||||
hackage: prometheus-metrics-ghc-1.0.1.1@sha256:d378a7186a967140fe0e09d325fe5e3bfd7b77a1123934b40f81fdfed2eacbdc,1233
|
||||
pantry-tree:
|
||||
size: 293
|
||||
sha256: 0732085a4148b269bbc15eeb7ab422e65ac287878a42a7388a7b6e140ec740e5
|
||||
original:
|
||||
hackage: prometheus-metrics-ghc-1.0.1.1@sha256:d378a7186a967140fe0e09d325fe5e3bfd7b77a1123934b40f81fdfed2eacbdc,1233
|
||||
- completed:
|
||||
hackage: run-st-0.1.1.0@sha256:a43245bb23984089016772481bf52bfe63eaff0c5040303f69c9b15e80872fdc,883
|
||||
pantry-tree:
|
||||
size: 269
|
||||
sha256: 06d5d7ecf185a26c15e48cda6c30e8865dae715c528a31466701272fae36d822
|
||||
original:
|
||||
hackage: run-st-0.1.1.0@sha256:a43245bb23984089016772481bf52bfe63eaff0c5040303f69c9b15e80872fdc,883
|
||||
- completed:
|
||||
hackage: sandi-0.5@sha256:b278d072ca717706ea38f9bd646e023f7f2576a778fb43565b434f93638849aa,3010
|
||||
pantry-tree:
|
||||
size: 3455
|
||||
sha256: 5ca7ce4bc22ab9d4427bb149b5e283ab9db43375df14f7131fdfd48775f36350
|
||||
original:
|
||||
hackage: sandi-0.5@sha256:b278d072ca717706ea38f9bd646e023f7f2576a778fb43565b434f93638849aa,3010
|
||||
- completed:
|
||||
hackage: system-locale-0.3.0.0@sha256:13b3982403d8ac8cc6138e68802be8d8e7cf7ebc4cbc7e47e99e3c0dd1be066a,1529
|
||||
pantry-tree:
|
||||
size: 446
|
||||
sha256: 3b22af3e6315835bf614a0d30381ec7e47aca147b59ba601aeaa26f1fdc19373
|
||||
original:
|
||||
hackage: system-locale-0.3.0.0@sha256:13b3982403d8ac8cc6138e68802be8d8e7cf7ebc4cbc7e47e99e3c0dd1be066a,1529
|
||||
- completed:
|
||||
hackage: token-bucket-0.1.0.1@sha256:d8e85f2fc373939975e7ace7907baee177531ab6e43df94e330a2357e64a2d11,1899
|
||||
pantry-tree:
|
||||
size: 399
|
||||
sha256: b0b4a08ea1bf76bd108310f64d7f80e0f30b61ddc3d71f6cab7bdce329d2c1fa
|
||||
original:
|
||||
hackage: token-bucket-0.1.0.1@sha256:d8e85f2fc373939975e7ace7907baee177531ab6e43df94e330a2357e64a2d11,1899
|
||||
- completed:
|
||||
hackage: tuples-0.1.0.0@sha256:7006c1cab721ad3e39cdbf1ccb07ec050b94d654cc6e39277d46241eee6ac7c9,1088
|
||||
pantry-tree:
|
||||
size: 320
|
||||
sha256: 57009cc671ed8e43738be3bf7b1392461ad086083df633a2f4f9c7206a14a79c
|
||||
original:
|
||||
hackage: tuples-0.1.0.0@sha256:7006c1cab721ad3e39cdbf1ccb07ec050b94d654cc6e39277d46241eee6ac7c9,1088
|
||||
- completed:
|
||||
hackage: tz-0.1.3.4@sha256:bd311e202b8bdd15bcd6a4ca182e69794949d3b3b9f4aa835e9ccff011284979,5086
|
||||
pantry-tree:
|
||||
size: 1179
|
||||
sha256: f6b8517eaaf3588afd1b3025fe6874a1ffff611001a803a26094c9cb40bc33f6
|
||||
original:
|
||||
hackage: tz-0.1.3.4@sha256:bd311e202b8bdd15bcd6a4ca182e69794949d3b3b9f4aa835e9ccff011284979,5086
|
||||
- completed:
|
||||
hackage: unidecode-0.1.0.4@sha256:99581ee1ea334a4596a09ae3642e007808457c66893b587e965b31f15cbf8c4d,1144
|
||||
pantry-tree:
|
||||
size: 492
|
||||
sha256: 4959068a0caf410dd4b8046f0b0138e3cf6471abb0cc865c9993db3b2930d283
|
||||
original:
|
||||
hackage: unidecode-0.1.0.4@sha256:99581ee1ea334a4596a09ae3642e007808457c66893b587e965b31f15cbf8c4d,1144
|
||||
- completed:
|
||||
hackage: uuid-crypto-1.4.0.0@sha256:9e2f271e61467d9ea03e78cddad75a97075d8f5108c36a28d59c65abb3efd290,1325
|
||||
pantry-tree:
|
||||
size: 364
|
||||
sha256: 6650b51ea060397c412b07b256c043546913292973284a7149ddd08f489b3e48
|
||||
original:
|
||||
hackage: uuid-crypto-1.4.0.0@sha256:9e2f271e61467d9ea03e78cddad75a97075d8f5108c36a28d59c65abb3efd290,1325
|
||||
- completed:
|
||||
hackage: wai-middleware-prometheus-1.0.0@sha256:1625792914fb2139f005685be8ce519111451cfb854816e430fbf54af46238b4,1314
|
||||
pantry-tree:
|
||||
size: 307
|
||||
sha256: 6d64803c639ed4c7204ea6fab0536b97d3ee16cdecb9b4a883cd8e56d3c61402
|
||||
original:
|
||||
hackage: wai-middleware-prometheus-1.0.0@sha256:1625792914fb2139f005685be8ce519111451cfb854816e430fbf54af46238b4,1314
|
||||
snapshots:
|
||||
- completed:
|
||||
size: 494635
|
||||
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/15/12.yaml
|
||||
sha256: a71c4293d8f461f455ff0d9815dfe4ab2f1adacd7e0bbc9a218f46ced8c4929a
|
||||
original: lts-15.12
|
||||
size: 524392
|
||||
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/nightly/2020/8/8.yaml
|
||||
sha256: 21b78cd42414558e6e381666a51ab92b405f969ab1d675137fd55ef557edc9a4
|
||||
original: nightly-2020-08-08
|
||||
|
||||
@ -43,7 +43,7 @@ insertFile residual fileTitle = do
|
||||
|
||||
fillDb :: DB ()
|
||||
fillDb = do
|
||||
AppSettings{ appUserDefaults = UserDefaultConf{..}, .. } <- getsYesod $ view appSettings
|
||||
AppSettings{ appUserDefaults = UserDefaultConf{..} } <- getsYesod $ view appSettings
|
||||
now <- liftIO getCurrentTime
|
||||
let
|
||||
insert' :: (PersistRecordBackend r (YesodPersistBackend UniWorX), AtLeastOneUniqueKey r) => r -> YesodDB UniWorX (Key r)
|
||||
|
||||
Loading…
Reference in New Issue
Block a user