Maintainer | bastiaan.heeren@ou.nl |
---|---|
Stability | provisional |
Portability | portable (depends on ghc) |
Safe Haskell | None |
Language | Haskell98 |
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.
- data Exercise a = NewExercise {
- exerciseId :: Id
- status :: Status
- parser :: String -> Either String a
- prettyPrinter :: a -> String
- equivalence :: Context a -> Context a -> Bool
- similarity :: Context a -> Context a -> Bool
- suitable :: Predicate a
- ready :: Predicate a
- strategy :: LabeledStrategy (Context a)
- canBeRestarted :: Bool
- extraRules :: [Rule (Context a)]
- ruleOrdering :: Rule (Context a) -> Rule (Context a) -> Ordering
- navigation :: a -> ContextNavigator a
- examples :: Examples a
- randomExercise :: Maybe (QCGen -> Maybe Difficulty -> a)
- testGenerator :: Maybe (Gen a)
- hasTermView :: Maybe (View Term a)
- hasTypeable :: Maybe (IsTypeable a)
- properties :: Map Id (Dynamic a)
- emptyExercise :: Exercise a
- makeExercise :: (Show a, Eq a, IsTerm a) => Exercise a
- prettyPrinterContext :: Exercise a -> Context a -> String
- isReady :: Exercise a -> a -> Bool
- isSuitable :: Exercise a -> a -> Bool
- ruleset :: Exercise a -> [Rule (Context a)]
- getRule :: Monad m => Exercise a -> Id -> m (Rule (Context a))
- ruleOrderingWith :: HasId b => [b] -> Rule a -> Rule a -> Ordering
- data Status
- isPublic :: Exercise a -> Bool
- isPrivate :: Exercise a -> Bool
- type Examples a = [(Difficulty, a)]
- data Difficulty
- = VeryEasy
- | Easy
- | Medium
- | Difficult
- | VeryDifficult
- readDifficulty :: String -> Maybe Difficulty
- level :: Difficulty -> [a] -> Examples a
- mapExamples :: (a -> b) -> Examples a -> Examples b
- examplesContext :: Exercise a -> Examples (Context a)
- inContext :: Exercise a -> a -> Context a
- withoutContext :: (a -> a -> Bool) -> Context a -> Context a -> Bool
- useTypeable :: Typeable a => Maybe (IsTypeable a)
- castFrom :: (HasTypeable f, Typeable b) => f a -> a -> Maybe b
- castTo :: (HasTypeable f, Typeable a) => f b -> a -> Maybe b
- setProperty :: (IsId n, Typeable val) => n -> val -> Exercise a -> Exercise a
- getProperty :: (IsId n, Typeable val) => n -> Exercise a -> Maybe val
- setPropertyF :: (IsId n, Typeable f) => n -> f a -> Exercise a -> Exercise a
- getPropertyF :: (IsId n, Typeable f) => n -> Exercise a -> Maybe (f a)
- simpleGenerator :: Gen a -> Maybe (QCGen -> Maybe Difficulty -> a)
- useGenerator :: (Maybe Difficulty -> Gen a) -> Maybe (QCGen -> Maybe Difficulty -> a)
- randomTerm :: QCGen -> Exercise a -> Maybe Difficulty -> Maybe a
- randomTerms :: QCGen -> Exercise a -> Maybe Difficulty -> [a]
- showDerivation :: Exercise a -> a -> String
- showDerivations :: Exercise a -> a -> String
- printDerivation :: Exercise a -> a -> IO ()
- printDerivations :: Exercise a -> a -> IO ()
- diffEnvironment :: HasEnvironment a => Derivation s a -> Derivation (s, Environment) a
- defaultDerivation :: Exercise a -> a -> Maybe (Derivation (Rule (Context a), Environment) (Context a))
- allDerivations :: Exercise a -> a -> [Derivation (Rule (Context a), Environment) (Context a)]
Exercise record
For constructing an empty exercise, use function emptyExercise
or
makeExercise
.
NewExercise | |
|
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.
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.
Status
The status of an exercise class.
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 |
Examples
type Examples a = [(Difficulty, a)] Source #
data Difficulty Source #
readDifficulty :: String -> Maybe Difficulty Source #
Parser for difficulty levels, which ignores non-alpha charactes (including spaces) and upper/lower case distinction.
level :: Difficulty -> [a] -> Examples a Source #
Assigns a difficulty level to a list of expressions.
mapExamples :: (a -> b) -> Examples a -> Examples b Source #
examplesContext :: Exercise a -> Examples (Context a) Source #
Returns the examples of an exercise class lifted to a context.
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).
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.
Random generators
simpleGenerator :: Gen a -> Maybe (QCGen -> Maybe Difficulty -> a) Source #
Makes a random exercise generator from a QuickCheck generator; the exercise
generator ignores the difficulty level. See the randomExercise
field.
useGenerator :: (Maybe Difficulty -> Gen a) -> Maybe (QCGen -> Maybe Difficulty -> a) Source #
Makes a random exercise generator based on a QuickCheck generator for a
particular difficulty level. See the randomExercise
field.
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.
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.
defaultDerivation :: Exercise a -> a -> Maybe (Derivation (Rule (Context a), Environment) (Context a)) Source #
allDerivations :: Exercise a -> a -> [Derivation (Rule (Context a), Environment) (Context a)] Source #