ideas-1.8: Feedback services for intelligent tutoring systems

Maintainerbastiaan.heeren@ou.nl
Stabilityprovisional
Portabilityportable (depends on ghc)
Safe HaskellNone
LanguageHaskell98

Ideas.Common.Exercise

Contents

Description

The Exercise record defines all the components that are needed for calculating feedback for one class of exercises. The fields of an exercise have to be consistent; consistency can be checked with the Ideas.Common.ExerciseTests module.

Synopsis

Exercise record

data Exercise a Source #

For constructing an empty exercise, use function emptyExercise or makeExercise.

Constructors

NewExercise 

Fields

  • exerciseId :: Id

    Identifier that uniquely determines the exercise: see HasId for how to use values with identifiers.

  • status :: Status

    The status of the exercise.

  • parser :: String -> Either String a

    Parser for expressions of the exercise class, which either results in an error (Left) or a result (Right).

  • prettyPrinter :: a -> String

    Pretty-printer for expressions of the exercise class. Pretty-printing should be the inverse of parsing.

  • equivalence :: Context a -> Context a -> Bool

    Tests wether two expressions (with their contexts) are semantically equivalent. Use withoutContext for defining the equivalence check when the context is not relevant.

  • similarity :: Context a -> Context a -> Bool

    Tests wether two expressions (with their contexts) are syntactically the same, or nearly so. Expressions that are similar must also be equivalent. Use withoutContext if the context is not relevant for the similarity check.

  • suitable :: Predicate a

    Predicate suitable identifies which expressions can be solved by the strategy of the exercise class. It acts as the pre-condition of the strategy.

  • ready :: Predicate a

    Predicate ready checks if an expression is in a solved form (accepted as a final solution). It acts as the post-condition of the strategy.

  • strategy :: LabeledStrategy (Context a)

    The rewrite strategy that specifies how to solve an exercise.

  • canBeRestarted :: Bool

    Is it possible to restart the rewrite strategy at any point in time? Restarting the strategy is needed when a student deviates from the strategy (detour). By default, restarting is assumed to be possible.

  • extraRules :: [Rule (Context a)]

    Are there extra rules, possibly buggy, that do not appear in the strategy? Use ruleset to get all rules.

  • ruleOrdering :: Rule (Context a) -> Rule (Context a) -> Ordering

    The rule ordering is a tiebreaker in situations where more than one rule can be used (e.g. feedback services onefirst and derivation; other feedback services return all possible rules).

  • constraints :: [Constraint (Context a)]

    Constraints for constraint-based tutors. A constraint contains a relevance condition and a satisfaction condition.

  • navigation :: a -> ContextNavigator a

    A navigator is needed for traversing the expression and for using the traversal strategy combinators. By default, an exercise has no navigator.

  • examples :: Examples a

    A finite list of examples, each with an assigned difficulty.

  • hasTermView :: Maybe (View Term a)

    Conversion to and from the (generic) Term datatype. Needed for representing the expression in the OpenMath standard.

  • hasTypeable :: Maybe (IsTypeable a)

    Representation of the type of expression: this provides a back door for exercise-specific functionality.

  • properties :: Map Id (Dynamic a)

    Extra exercise-specific properties, not used by the default feedback services.

Instances
Apply Exercise Source # 
Instance details

Defined in Ideas.Common.Exercise

Methods

applyAll :: Exercise a -> a -> [a] Source #

HasTypeable Exercise Source # 
Instance details

Defined in Ideas.Common.Exercise

Eq (Exercise a) Source # 
Instance details

Defined in Ideas.Common.Exercise

Methods

(==) :: Exercise a -> Exercise a -> Bool #

(/=) :: Exercise a -> Exercise a -> Bool #

Ord (Exercise a) Source # 
Instance details

Defined in Ideas.Common.Exercise

Methods

compare :: Exercise a -> Exercise a -> Ordering #

(<) :: Exercise a -> Exercise a -> Bool #

(<=) :: Exercise a -> Exercise a -> Bool #

(>) :: Exercise a -> Exercise a -> Bool #

(>=) :: Exercise a -> Exercise a -> Bool #

max :: Exercise a -> Exercise a -> Exercise a #

min :: Exercise a -> Exercise a -> Exercise a #

HasId (Exercise a) Source # 
Instance details

Defined in Ideas.Common.Exercise

Methods

getId :: Exercise a -> Id Source #

changeId :: (Id -> Id) -> Exercise a -> Exercise a Source #

emptyExercise :: Exercise a Source #

The emptyExercise constructor function provides sensible defaults for all fields of the Exercise record.

makeExercise :: (Show a, Eq a, IsTerm a) => Exercise a Source #

In addition to the defaults of emptyExercise, this constructor sets the fields prettyPrinter, similarity, and hasTermView.

Convenience functions

prettyPrinterContext :: Exercise a -> Context a -> String Source #

Pretty print a value in its context.

isReady :: Exercise a -> a -> Bool Source #

Checks if an expression is in a solved form.

isSuitable :: Exercise a -> a -> Bool Source #

Checks if the expression is suitable and can be solved by the strategy.

ruleset :: Exercise a -> [Rule (Context a)] Source #

Returns a sorted list of rules, without duplicates.

getRule :: Monad m => Exercise a -> Id -> m (Rule (Context a)) Source #

Finds a rule of an exercise based on its identifier.

ruleOrderingWith :: HasId b => [b] -> Rule a -> Rule a -> Ordering Source #

Makes a rule ordering based on a list of values with identifiers (e.g., a list of rules). Rules with identifiers that are not in the list are considered after the rules in the list, and are sorted based on their identifier.

violations :: Exercise a -> Context a -> [(Constraint (Context a), String)] Source #

Get all constraint violations

Status

data Status Source #

The status of an exercise class.

Constructors

Stable

A released exercise that has undergone some thorough testing

Provisional

A released exercise, possibly with some deficiencies

Alpha

An exercise that is under development

Experimental

An exercise for experimentation purposes only

Instances
Eq Status Source # 
Instance details

Defined in Ideas.Common.Exercise

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Show Status Source # 
Instance details

Defined in Ideas.Common.Exercise

isPublic :: Exercise a -> Bool Source #

An exercise with the status Stable or Provisional

isPrivate :: Exercise a -> Bool Source #

An exercise that is not public

Examples

data Examples a Source #

Instances
Functor Examples Source # 
Instance details

Defined in Ideas.Common.Examples

Methods

fmap :: (a -> b) -> Examples a -> Examples b #

(<$) :: a -> Examples b -> Examples a #

Semigroup (Examples a) Source # 
Instance details

Defined in Ideas.Common.Examples

Methods

(<>) :: Examples a -> Examples a -> Examples a #

sconcat :: NonEmpty (Examples a) -> Examples a #

stimes :: Integral b => b -> Examples a -> Examples a #

Monoid (Examples a) Source # 
Instance details

Defined in Ideas.Common.Examples

Methods

mempty :: Examples a #

mappend :: Examples a -> Examples a -> Examples a #

mconcat :: [Examples a] -> Examples a #

data Difficulty Source #

readDifficulty :: String -> Maybe Difficulty Source #

Parser for difficulty levels, which ignores non-alpha charactes (including spaces) and upper/lower case distinction.

examplesFor :: Difficulty -> [a] -> Examples a Source #

List of examples with the same difficulty

examplesWithDifficulty :: [(Difficulty, a)] -> Examples a Source #

List of examples with their own difficulty

examplesContext :: Exercise a -> Examples (Context a) Source #

Returns the examples of an exercise class lifted to a context.

testGenerator :: Exercise a -> Maybe (Gen a) Source #

An exercise generator for testing purposes (including corner cases); first generator only.

randomTerm :: QCGen -> Exercise a -> Maybe Difficulty -> Maybe a Source #

Returns a random exercise of a certain difficulty with some random number generator. The field randomExercise is used; if this is not defined (i.e., Nothing), one of the examples is used instead.

randomTerms :: QCGen -> Exercise a -> Maybe Difficulty -> [a] Source #

Returns a list of randomly generated terms of a certain difficulty.

Context

inContext :: Exercise a -> a -> Context a Source #

Puts a value into a context with an empty environment.

withoutContext :: (a -> a -> Bool) -> Context a -> Context a -> Bool Source #

Function for defining equivalence or similarity without taking the context into account.

Type casting

useTypeable :: Typeable a => Maybe (IsTypeable a) Source #

Encapsulates a type representation (use for hasTypeable field).

castFrom :: (HasTypeable f, Typeable b) => f a -> a -> Maybe b Source #

castTo :: (HasTypeable f, Typeable a) => f b -> a -> Maybe b Source #

Exercise properties

setProperty :: (IsId n, Typeable val) => n -> val -> Exercise a -> Exercise a Source #

Set an exercise-specific property (with a dynamic type)

getProperty :: (IsId n, Typeable val) => n -> Exercise a -> Maybe val Source #

Get an exercise-specific property (of a dynamic type)

setPropertyF :: (IsId n, Typeable f) => n -> f a -> Exercise a -> Exercise a Source #

Set an exercise-specific property (with a dynamic type) that is parameterized over the exercise term.

getPropertyF :: (IsId n, Typeable f) => n -> Exercise a -> Maybe (f a) Source #

Get an exercise-specific property (of a dynamic type) that is parameterized over the exercise term.

Derivations

showDerivation :: Exercise a -> a -> String Source #

Shows the default derivation for a given start term. The specified rule ordering is used for selection.

showDerivations :: Exercise a -> a -> String Source #

Shows all derivations for a given start term. Warning: there can be many derivations.

printDerivation :: Exercise a -> a -> IO () Source #

Prints the default derivation for a given start term. The specified rule ordering is used for selection.

printDerivations :: Exercise a -> a -> IO () Source #

Prints all derivations for a given start term. Warning: there can be many derivations.

diffEnvironment :: HasEnvironment a => Derivation s a -> Derivation (s, Environment) a Source #

Adds the difference of the environments in a derivation to the steps. Bindings with identifier location are ignored. This utility function is useful for printing derivations.