fix: user with a pre-assigned room count towards the capacity limit
This commit is contained in:
parent
46e6ca9217
commit
4fc05351fa
@ -267,8 +267,8 @@ examAutoOccurrence :: forall seed.
|
||||
-> Map UserId (User, Maybe ExamOccurrenceId)
|
||||
-> (Maybe (ExamOccurrenceMapping ExamOccurrenceId), Map UserId (Maybe ExamOccurrenceId))
|
||||
examAutoOccurrence (hash -> seed) rule ExamAutoOccurrenceConfig{..} occurrences users
|
||||
| sum occurrences < usersCount
|
||||
|| sum occurrences <= 0
|
||||
| sum occurrences' < usersCount
|
||||
|| sum occurrences' <= 0
|
||||
|| Map.null users
|
||||
= nullResult
|
||||
| otherwise
|
||||
@ -277,7 +277,7 @@ examAutoOccurrence (hash -> seed) rule ExamAutoOccurrenceConfig{..} occurrences
|
||||
-> ( Nothing
|
||||
, flip Map.mapWithKey users $ \uid (_, mOcc)
|
||||
-> let randomOcc = flip evalRand (mkStdGen $ hashWithSalt seed uid) $
|
||||
weighted $ over _2 fromIntegral <$> occurrences'
|
||||
weighted $ over _2 fromIntegral <$> occurrences''
|
||||
in Just $ fromMaybe randomOcc mOcc
|
||||
)
|
||||
_ | Just (postprocess -> (resMapping, result)) <- bestOption
|
||||
@ -309,21 +309,28 @@ examAutoOccurrence (hash -> seed) rule ExamAutoOccurrenceConfig{..} occurrences
|
||||
in Map.mapKeysWith Set.union (take . F.minimum . Set.map length $ Map.keysSet matrUsers) matrUsers
|
||||
_ -> Map.singleton [] $ Map.keysSet users
|
||||
|
||||
occurrences' :: Map ExamOccurrenceId Natural
|
||||
-- ^ reduce room capacity for every pre-assigned user by 1
|
||||
occurrences' = foldl' (flip $ Map.adjust predOrZero) occurrences $ Map.mapMaybe snd users
|
||||
where
|
||||
predOrZero :: Natural -> Natural
|
||||
predOrZero 0 = 0
|
||||
predOrZero n = pred n
|
||||
|
||||
occurrences' :: [(ExamOccurrenceId, Natural)]
|
||||
occurrences'' :: [(ExamOccurrenceId, Natural)]
|
||||
-- ^ Minimise number of occurrences used
|
||||
--
|
||||
-- Prefer occurrences with higher capacity
|
||||
--
|
||||
-- If a single occurrence can accommodate all participants, pick the one with
|
||||
-- the least capacity
|
||||
occurrences'
|
||||
occurrences''
|
||||
| not eaocMinimizeRooms
|
||||
= Map.toList occurrences
|
||||
| Just largeEnoughs <- fromNullable . filter ((>= usersCount) . view _2) $ Map.toList occurrences
|
||||
= Map.toList occurrences'
|
||||
| Just largeEnoughs <- fromNullable . filter ((>= usersCount) . view _2) $ Map.toList occurrences'
|
||||
= pure $ minimumBy (comparing $ view _2) largeEnoughs
|
||||
| otherwise
|
||||
= view _2 . foldl' accF (0, []) . sortOn (Down . view _2) $ Map.toList occurrences
|
||||
= view _2 . foldl' accF (0, []) . sortOn (Down . view _2) $ Map.toList occurrences'
|
||||
where
|
||||
accF :: (Natural, [(ExamOccurrenceId, Natural)])
|
||||
-> (ExamOccurrenceId, Natural)
|
||||
@ -469,7 +476,7 @@ examAutoOccurrence (hash -> seed) rule ExamAutoOccurrenceConfig{..} occurrences
|
||||
charCost :: [CI Char] -> [CI Char] -> Extended Rational
|
||||
charCost pA pB = Finite (max 1 $ List.genericLength (pA `lcp` pB) * eaocFinenessCost * fromIntegral longestLine) ^ 2
|
||||
where
|
||||
longestLine = maximum . mapNonNull (view _2) $ impureNonNull occurrences'
|
||||
longestLine = maximum . mapNonNull (view _2) $ impureNonNull occurrences''
|
||||
|
||||
|
||||
lcp :: Eq a => [a] -> [a] -> [a]
|
||||
@ -485,7 +492,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` (pack . 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
|
||||
@ -493,7 +500,7 @@ examAutoOccurrence (hash -> seed) rule ExamAutoOccurrenceConfig{..} occurrences
|
||||
-- finenessCost n = Finite (max 1 $ fromIntegral n * eaocFinenessCost * fromIntegral longestLine) ^ 2 * length occurrences'
|
||||
|
||||
distributeFine :: Natural -> Maybe (Extended Rational, _)
|
||||
distributeFine n = distribute (usersFineness n) occurrences' lineNudges charCost
|
||||
distributeFine n = distribute (usersFineness n) occurrences'' lineNudges charCost
|
||||
|
||||
maximumFineness = fromIntegral . F.minimum . Set.map length $ Map.keysSet users'
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user