weekdaze-0.0.0.2: A school-timetable problem-solver.

Safe HaskellNone
LanguageHaskell2010

WeekDaze.Model.TimetableForWeek

Contents

Description

AUTHOR
Dr. Alistair Ward
DESCRIPTION
  • Define the data-structure, required to hold a single week's bookings, for any observer-id.
  • It forms a complete timetable, when combined with similar data-structures, for all observers.
Synopsis

Types

Type-synonyms

type TimetableForWeek timeslotId resourceIds level = Array Day (TimetableForDay timeslotId resourceIds level) Source #

A timetable for observers with identical scheduling-requirements, for any week.

type Booking timeslotId resourceIds level = (Time timeslotId, Lesson resourceIds level) Source #

A lesson qualified by the time at which it is booked.

type GenericTimetableToMarkup minimumContrastRatio timetable Source #

Arguments

 = TimeAxes Bool

Whether to merge duplicate lessons, between adjacent days & also between consecutive time-slots.

-> TimeAxes Bool

Whether to depict axis-labels.

-> Weekend

Define the days which constitute the weekend.

-> Maybe (GenerateLessonColourFrom, minimumContrastRatio)

Whether to generate the colour of a lesson from one of its attributes, or to delegate colouring to a CSS-file.

-> timetable

The timetable to represent; which can be from any view, or merely a slice dedicated to one observerId.

-> Html 
  • A basic specification required to convert a timetable to XHTML.
  • The first three parameters supply auxiliary information required for styling.

type GenericTimetableToMarkup' locationId minimumContrastRatio teacherId timeslotId timetable = MeetingsByTime timeslotId locationId teacherId -> GenericTimetableToMarkup minimumContrastRatio timetable Source #

Enhance GenericTimetableToMarkup, with parameters for styling.

type GeneralisedLessonRunlengthByTimeslotIdByDay timeslotId resourceIds level = Array Day (GeneralisedLessonRunlengthByTimeslotId timeslotId resourceIds level) Source #

A runlength-encoded list of generalised (i.e. potentially undefined) lessons, indexed by the day & then timeslotId, at which each runlength begins.

type RunlengthsByTimeslotIdByLessonByDay resourceIds level timeslotId = Array Day (RunlengthsByTimeslotIdByLesson resourceIds level timeslotId) Source #

A runlength-encoded list of generalised (i.e. potentially undefined) lessons, indexed by the day & then timeslotId, at which each runlength begins.

Constants

Functions

calculateAverageAbsoluteDeviationOfFreeLessonsPerDay :: (Ix timeslotId, Resource resource, Fractional average) => resource -> TimetableForWeek timeslotId resourceIds level -> average Source #

Calculates the average absolute deviation (https://en.wikipedia.org/wiki/Absolute_deviation#Average_absolute_deviation) in the number of free-periods, over the days in the week on which the resource is actually available.

calculateUtilisationRatio :: (Ix timeslotId, HumanResource humanResource, Fractional teachingRatio) => NTimeslots -> humanResource -> TimetableForWeek timeslotId resourceIds level -> teachingRatio Source #

  • The number of lessons booked for the specified human-resource, relative to the limit of their teaching-time.
  • This factors into the denominator, both the availability of the resource, & the ratio of that working-time for which they're required to be in teaching rather than some other job-role.

locateUnallocatedAvailableTimes Source #

Arguments

:: (Ix timeslotId, Resource resource) 
=> resource

Used to determine availability.

-> TimetableForWeek timeslotId resourceIds level 
-> [Time timeslotId] 
  • Finds the coordinates of all unallocated times, when the specified resource is available.
  • CAVEAT: doesn't account for times reserved for meetings.

findGeneralisedLessonRunlengthsByTimeslotIdByDay :: (Ix timeslotId, Enum timeslotId, Eq resourceIds, Eq level) => TimetableForWeek timeslotId resourceIds level -> GeneralisedLessonRunlengthByTimeslotIdByDay timeslotId resourceIds level Source #

Finds consecutive equal generalised (i.e. potentially undefined) lessons, & the run-length of each sequence, indexed by day & then timeslotId.

findSeparatedEqualLessonsWithinAnyDay :: (Ix timeslotId, Ord resourceIds, Ord level) => TimetableForWeek timeslotId resourceIds level -> LessonRunlengths resourceIds level Source #

Finds separated equal lessons, within the timetable for any single day.

findSeparatedEqualSubjectLessonsWithinAnyDay :: (Ix timeslotId, Eq resourceIds, Ord level) => TimetableForWeek timeslotId resourceIds level -> LessonRunlengths resourceIds level Source #

Finds separated lessons of equal subject, within the timetable for any single day.

findSeparatedEqualLessonRunlengthsByStartingTimeslotIdByLessonByDay :: (Ix timeslotId, Ord resourceIds, Ord level) => TimetableForWeek timeslotId resourceIds level -> RunlengthsByTimeslotIdByLessonByDay resourceIds level timeslotId Source #

  • Finds runlengths of separated equal lessons, within the timetable for any single day; separated unallocated time-slots don't qualify.
  • Returns an array indexed by day, of lists associated by common lesson, of lists associated by starting timeslotId, of runlengths.

countSubjectWorkload :: (Ix timeslotId, Ord level) => Subject level -> TimetableForWeek timeslotId resourceIds level -> NTimeslots Source #

Returns the total number of lesson-definitions currently booked for the specified subject.

countWorkloadByLesson :: (Ix timeslotId, Ord level, Ord resourceIds) => TimetableForWeek timeslotId resourceIds level -> Map (Lesson resourceIds level) NTimeslots Source #

  • Returns the total number of each type of lesson currently booked.
  • CAVEAT: if zero of the requested lesson have been booked, then there won't be any matching key in the map.
  • CAVEAT: be careful with the interpretation of these results, unless it can be guaranteed that all lessons for a given subject are identical (i.e. they use the same resourceIds); otherwise the workload returned for a subject could be split amongst different lessons. Whilst this is typically the case for the student-view of a timetableForWeek, it's may not be the case for other views, since the student-class may vary.

countUnallocatedAvailableTimeslots :: (Ix timeslotId, Resource resource) => resource -> TimetableForWeek timeslotId resourceIds level -> NTimeslots Source #

  • Counts the total number of unallocated time-slots, discounting those when the observer is unavailable.
  • CAVEAT: this function takes no account of the possibility that when the observer represents a student-body, some time-slots may be allocated for unsupervised study, & the remainder must be multiplied by the number of members in the student-body.

extractLessons :: Ix timeslotId => TimetableForWeek timeslotId resourceIds level -> [Lesson resourceIds level] Source #

Extracts the lessons from the specified timetable, discarding the booking-time.

extractTimes :: Ix timeslotId => TimetableForWeek timeslotId resourceIds level -> [Time timeslotId] Source #

Extract the list of all times in the specified timetable, regardless of whether a lesson has been booked there.

extractDistinctLessons :: (Ix timeslotId, Ord resourceIds, Ord level) => TimetableForWeek timeslotId resourceIds level -> Set (Lesson resourceIds level) Source #

Extracts the set of distinct lessons from the specified timetable.

extractMaybeLessonsAt :: Ix timeslotId => timeslotId -> TimetableForWeek timeslotId resourceIds level -> Array Day (GeneralisedLesson resourceIds level) Source #

Extracts any lesson-definitions, from the specified timeslot-Id on each day.

getFreePeriodCompliance Source #

Arguments

:: (Ix timeslotId, Resource resource, Fractional ratio) 
=> FreePeriodPreference

This observer's preferred position, within any day, of free time-slots.

-> TimesByDay timeslotId

The meeting-times for the groups of which this observer is a member.

-> resource

The observer for whom this weekly timetable was intended.

-> TimetableForWeek timeslotId resourceIds level 
-> [ratio]

The portion of those free time-slots in each day, which meet the observer's preference.

Measure the ratio, for each day on which the observer, for whom this weekly timetable was intended, is available, of those free (neither reserved for a meeting nor booked with a lesson) time-slots which comply with the specified preference, to the total number of free time-slots,

Constructor

mkFreeTimetableForWeek :: (Ix timeslotId, Enum timeslotId) => Interval timeslotId -> TimetableForWeek timeslotId resourceIds level Source #

Constructor. Create an unallocated timetable, for a whole week.

Accessors

getMaybeLesson :: Ix timeslotId => Time timeslotId -> TimetableForWeek timeslotId resourceIds level -> GeneralisedLesson resourceIds level Source #

Get any lesson booked at the specified time.

getBookedTime :: Booking timeslotId resourceIds level -> Time timeslotId Source #

Accessor.

getBookedLesson :: Booking timeslotId resourceIds level -> Lesson resourceIds level Source #

Accessor.

Mutators

defineTimeslot :: Ix timeslotId => (Time timeslotId, GeneralisedLesson resourceIds level) -> TimetableForWeek timeslotId resourceIds level -> TimetableForWeek timeslotId resourceIds level Source #

Replace any lesson-definition at the specified time-coordinate.

undefineTimeslots :: (Ix timeslotId, Foldable foldable) => TimetableForWeek timeslotId resourceIds level -> foldable (Time timeslotId) -> TimetableForWeek timeslotId resourceIds level Source #

Undefines any lesson booked at each of the specified time-coordinates.

Predicates

hasMatchingLessonAt Source #

Arguments

:: Ix timeslotId 
=> (Lesson resourceIds level -> Bool)

Determines the suitability of any lesson at the specified time.

-> Time timeslotId

The time at which to look for a lesson.

-> TimetableForWeek timeslotId resourceIds level 
-> Bool 

True if a booking already exists in the timetable which matches the specified predicate.

isBookedWith Source #

Arguments

:: (Ix timeslotId, Eq level, Eq resourceIds) 
=> Booking timeslotId resourceIds level

The time & lesson to match.

-> TimetableForWeek timeslotId resourceIds level 
-> Bool 

True if the specified booking already exists in the timetable.

areAllSpecifiedTimesBookable Source #

Arguments

:: (Resource resource, Ix timeslotId) 
=> resource 
-> TimetableForWeek timeslotId resourceIds level

The timetable whose bookings to inspect.

-> Course synchronisationId level timeslotId

The course whose specified times, to query.

-> Bool 

True if all the times specified by a course, are currently unbooked, & the resource is regularly available on each requested day.

isBookedOnAdjacentDay Source #

Arguments

:: (Eq level, Eq resourceIds) 
=> TimetableForWeek timeslotId resourceIds level

The timetable whose bookings to inspect.

-> Lesson resourceIds level

The lesson to match.

-> Day

Today.

-> Bool 

True if the specified lesson is booked an an adjacent day.

isDefinedTimeslot :: Ix timeslotId => Time timeslotId -> TimetableForWeek timeslotId resourceIds level -> Bool Source #

True if a booking has been made at the specified time in the timetable.

isRunlengthReducibleAt Source #

Arguments

:: (Ix timeslotId, Enum timeslotId, Eq level, Eq resourceIds) 
=> TimetableForWeek timeslotId resourceIds level

The timetable whose bookings to inspect.

-> Time timeslotId 
-> Course synchronisationId level timeslotId 
-> Bool 
  • True if the course requires only a trivial minimumConsecutiveLessons, or the referenced lesson is at either end of a runlength which exceeds minimumConsecutiveLessons.
  • If True, then minimumConsecutiveLessons doesn't preclude the referenced lesson from being unbooked; though there may be other reasons why it shouldn't.
  • CAVEAT: if minimumConsecutiveLessons==1 , but a runlength of three or more have been booked, then unbooking the middle one will result in a split session.

Translation

toXHtml Source #

Arguments

:: (Ix timeslotId, Resource resource, Eq level, Eq resourceIds, Fractional minimumContrastRatio, Ord minimumContrastRatio, Show level, Show resourceIds, HTML level, HTML locationId, HTML resourceIds, HTML synchronisationId, HTML teacherId, HTML timeslotId) 
=> (Lesson resourceIds level -> Course synchronisationId level timeslotId)

Find the course to which the specified lesson belongs.

-> resource

The resource by whom the timetable was designed to be viewed.

-> GenericTimetableToMarkup' locationId minimumContrastRatio teacherId timeslotId (TimetableForWeek timeslotId resourceIds level) 

Render in XHTML, as a table, with days varying horizontally & timeslotIds varying vertically.

xpickle :: (Ix timeslotId, XmlPickler level, XmlPickler resourceIds, XmlPickler timeslotId, Show level) => PU (TimetableForWeek timeslotId resourceIds level) Source #

Defines a pickler to convert the specified timetable to, or from, XML.