Safe Haskell | None |
---|---|
Language | Haskell2010 |
WeekDaze.ProblemConfiguration.ProblemParameters
Description
AUTHOR
- Dr. Alistair Ward
DESCRIPTION
- Encapsulates the data which defines the problem, rather than the solution-mechanism, or its presentation.
Synopsis
- data ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId = MkProblemParameters {
- getProblemValidationSwitches :: ProblemValidationSwitches
- getTimetableValidationSwitches :: TimetableValidationSwitches
- getTimeslotIdBounds :: Interval timeslotId
- getLocationCatalogue :: LocationCatalogue locationId campus
- getTeacherRegister :: TeacherRegister teacherId synchronisationId level timeslotId locationId teachingRatio
- getStudentBodyRegister :: StudentBodyRegister level stream teachingRatio
- getGroupCatalogue :: GroupCatalogue timeslotId locationId
- timeslotIdBoundsTag :: String
- calculateNTimeslotsPerDay :: Enum timeslotId => Interval timeslotId -> NTimeslots
- extractDistinctGroupMembership :: RealFrac teachingRatio => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Membership
- findExcessTotalWorkloadByStudentBody :: (Enum timeslotId, Ord level, Ord synchronisationId, Ord timeslotId, RealFrac teachingRatio) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Map StudentBody NTimeslots
- findHumanResourceIdsByGroupId :: (Ord teacherId, RealFrac teachingRatio) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> (ResourceIdsByGroupId StudentBody, ResourceIdsByGroupId teacherId)
- findSynchronousMeetingsByTimeByStudentBodyMnemonic :: (Ord timeslotId, RealFrac teachingRatio) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Map StudentBody (Map (Time timeslotId) [Id])
- findSynchronousMeetingsByTimeByTeacherId :: (Ord timeslotId, RealFrac teachingRatio) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Map teacherId (Map (Time timeslotId) [Id])
- reduceStudentBodyRegister :: (Ord level, Ord stream, Ord teachingRatio) => MnemonicSeparator -> ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [[StudentBody]] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId)
- removeRedundantCourses :: Ord level => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [(teacherId, Knowledge level)] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId)
- removePointlessGroups :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [Id] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId)
- removeUnsubscribedGroups :: RealFrac teachingRatio => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [Id] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId)
- mergeConstraintsOnSynchronisedCourses :: (Ord level, Ord synchronisationId, Ord teacherId, Ord timeslotId, Show synchronisationId, Show timeslotId) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId
- disableAnyValidationInappropriateForTemporaryStudentBodyMerger :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [String] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId)
- hasAnyFreePeriodPreference :: RealFrac teachingRatio => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Bool
- hasVariousMinimumConsecutiveLessons :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Bool
Types
Data-types
data ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId Source #
Encapsulates the data which defines the problem.
Constructors
MkProblemParameters | |
Fields
|
Instances
(Eq timeslotId, Eq locationId, Eq campus, Eq teacherId, Eq level, Eq synchronisationId, Eq teachingRatio, Eq stream) => Eq (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source # | |
Defined in WeekDaze.ProblemConfiguration.ProblemParameters Methods (==) :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Bool # (/=) :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Bool # | |
(Show timeslotId, Show locationId, Show campus, Show teacherId, Show synchronisationId, Show level, Show teachingRatio, Show stream) => Show (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source # | |
Defined in WeekDaze.ProblemConfiguration.ProblemParameters Methods showsPrec :: Int -> ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> ShowS # show :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> String # showList :: [ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId] -> ShowS # | |
(NFData campus, NFData level, NFData locationId, NFData stream, NFData synchronisationId, NFData teacherId, NFData teachingRatio, NFData timeslotId) => NFData (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source # | |
Defined in WeekDaze.ProblemConfiguration.ProblemParameters Methods rnf :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> () # | |
(Default campus, Default stream, Eq campus, Eq stream, XmlPickler campus, XmlPickler level, XmlPickler locationId, XmlPickler stream, XmlPickler synchronisationId, XmlPickler teacherId, XmlPickler teachingRatio, XmlPickler timeslotId, Ord level, Ord locationId, Ord synchronisationId, Ord teacherId, Ord timeslotId, Real teachingRatio, Show campus, Show level, Show synchronisationId, Show timeslotId) => XmlPickler (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source # | |
Defined in WeekDaze.ProblemConfiguration.ProblemParameters Methods xpickle :: PU (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) # | |
(Enum timeslotId, Ord level, Ord locationId, Ord stream, Ord synchronisationId, Ord teacherId, Ord timeslotId, RealFrac teachingRatio, Show level, Show locationId, Show stream, Show synchronisationId, Show teacherId, Show teachingRatio, Show timeslotId) => SelfValidator (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source # | |
Defined in WeekDaze.ProblemConfiguration.ProblemParameters Methods getErrors :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> [String] # isValid :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Bool # | |
(Enum timeslotId, Ord level, Ord synchronisationId, Ord teacherId, Ord timeslotId, RealFrac teachingRatio, Show level, Show synchronisationId, Show teacherId, Show timeslotId) => Configuration (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source # | |
Defined in WeekDaze.ProblemConfiguration.ProblemParameters Methods issueWarnings :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> [String] Source # |
Constants
timeslotIdBoundsTag :: String Source #
Used to qualify XML.
Functions
calculateNTimeslotsPerDay :: Enum timeslotId => Interval timeslotId -> NTimeslots Source #
- Get the length of the list defined by the specified bounds.
- CAVEAT: this implementation accounts for the potential fence-post error when called for a closed interval of
Integral
timeslots, but will result in an equivalent error if (bizarrely) called for an interval ofFractional
quantities. Regrettably, it can't be restricted toIntegral
, because it may legitimately be required to work withChar
.
extractDistinctGroupMembership :: RealFrac teachingRatio => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Membership Source #
Finds the set of groups, of which a human-resource claims membership.
findExcessTotalWorkloadByStudentBody :: (Enum timeslotId, Ord level, Ord synchronisationId, Ord timeslotId, RealFrac teachingRatio) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Map StudentBody NTimeslots Source #
Finds student-bodies, who've requested more subjects (both core & optional), than can be taught by the courses on offer, in the time allocated to tuition.
findHumanResourceIdsByGroupId :: (Ord teacherId, RealFrac teachingRatio) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> (ResourceIdsByGroupId StudentBody, ResourceIdsByGroupId teacherId) Source #
Finds the members (student-bodies, teachers) of each group.
findSynchronousMeetingsByTimeByStudentBodyMnemonic :: (Ord timeslotId, RealFrac teachingRatio) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Map StudentBody (Map (Time timeslotId) [Id]) Source #
- For each student-body, identifies times at which they have attend more than one meeting. for any of the groups of which they're a member.
- Returns the offending group-ids.
findSynchronousMeetingsByTimeByTeacherId :: (Ord timeslotId, RealFrac teachingRatio) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Map teacherId (Map (Time timeslotId) [Id]) Source #
- For each teacherId, identifies times at which they have attend more than one meeting. for any of the groups of which they're a member.
- Returns the offending group-ids.
reduceStudentBodyRegister :: (Ord level, Ord stream, Ord teachingRatio) => MnemonicSeparator -> ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [[StudentBody]] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source #
- Merges those student-bodies whose profiles are identical, into a student-body.
- Also writes the list of those students affected.
removeRedundantCourses :: Ord level => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [(teacherId, Knowledge level)] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source #
- Removes courses from the teacherRegister, which aren't required by any student.
- Writes an association-list of teacherId & any knowledge they offer for which there's no demand; where there's a requirement for all a teacher's knowledge, then no data is written for that teacher, rather than writing a null set.
removePointlessGroups :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [Id] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source #
Remove any groups from the groupCatalogue which have zero meeting-times.
removeUnsubscribedGroups :: RealFrac teachingRatio => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [Id] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source #
Remove any groups from the groupCatalogue to which neither student-bodies nor teachers have subscribed.
mergeConstraintsOnSynchronisedCourses :: (Ord level, Ord synchronisationId, Ord teacherId, Ord timeslotId, Show synchronisationId, Show timeslotId) => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId Source #
Proxies request to mergeConstraintsOnSynchronisedCourses
.
disableAnyValidationInappropriateForTemporaryStudentBodyMerger :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Writer [String] (ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId) Source #
- When temporary student-body mergers are permitted according to the execution-options, some problem-validation switches are inappropriate & should be disabled to prevent false positives.
- Also writes the names of any disabled switches.
Predicates
hasAnyFreePeriodPreference :: RealFrac teachingRatio => ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Bool Source #
True if any student-body or teacher has a preference for the location of any free timeslots in their working day.
hasVariousMinimumConsecutiveLessons :: ProblemParameters campus level locationId stream synchronisationId teacherId teachingRatio timeslotId -> Bool Source #
Whether courses offer different minimumConsecutiveLessons.