{-# LANGUAGE MultiParamTypeClasses, ExistentialQuantification #-} ----------------------------------------------------------------------------- -- Copyright 2019, Advise-Me project team. This file is distributed under -- the terms of the Apache License 2.0. For more information, see the files -- "LICENSE.txt" and "NOTICE.txt", which are included in the distribution. ----------------------------------------------------------------------------- -- | -- Maintainer : bastiaan.heeren@ou.nl -- Stability : provisional -- Portability : portable (depends on ghc) -- -- This module defines the data type that is used to describe the diagnosis of some solution to an exercise. -- This information is then used to generate evidence during assessment. -- ----------------------------------------------------------------------------- module Recognize.Data.Attribute where import Control.Arrow import Data.List.NonEmpty import Ideas.Common.Rewriting.Term import Ideas.Text.XML hiding (Attribute) import Domain.Math.Expr import Domain.Math.Data.Relation import Recognize.Data.Op import Recognize.Data.RuleId data Attribute = Expand Op -- ^ Expand a formula by a certain operation | Implicit Op -- ^ Implicitly expand a formula | Forget Op -- ^ Forgot to expand a formula | ForgetSym Symbol -- ^ Forgot to expand with a symbol | Normalized -- ^ Is a normalized expression | InvalidEquation -- 5 == 6 Expr -- Left Expr -- Right | UnequalRelations -- 3x=40 | x = 40/2 (Relation Expr) -- before relation (Relation Expr) -- after relation | Recovery -- ^ Recover a made mistake | NonMatchingParentheses -- ^ Incorrect placement of parentheses | IncorrectDistribution | IncorrectFactorization | InvertedFraction -- ^ expected: 5/6, provided: 6/5 | InvalidCommutativity Symbol -- ^ expected: 5-6, provided: 6-5 | AtomMixedUp -- expected: 5 + 6, provided: 8 + 8 Expr -- wrong Expr -- correct | Sloppiness | OperatorMixedUp -- expected: 5-6, provided: 5+6 Symbol -- wrong Symbol -- correct | Misconception Concept -- wrong Concept -- correct | AsymmetricRelation | InequalityStrictness | Approximation | RoundingError | CommonMistake -- ^ defined per exercise | CapturedWildcard String Expr | PartialMatch Expr | MatchedBy Expr Expr | ARule -- Applied an ideas rule to some expression RuleId -- Matches an ideas rule (NonEmpty Expr) -- list expressions that rule is applied to Expr -- resulting expression | ARuleR -- Applied an ideas rule to some relation RuleId -- Matches an ideas rule (Relation Expr) -- relation that rule is applied to (Relation Expr) -- resulting relation | Label String | LabelE String Expr | FinalAnswer Expr | NExpr Expr -- ^ Expression that is a Number or Natural | Other String deriving (Eq, Show,Ord) instance ToXML Attribute where toXML e = case e of Expand o -> makeXML "expand" (text o) Implicit o -> makeXML "implicit" (text o) Forget o -> makeXML "forget" (text o) ForgetSym o -> makeXML "forgetsym" (text o) InvalidCommutativity o -> makeXML "invalidcommutativity" (text o) Normalized -> makeXML "normalized" mempty (InvalidEquation e1 e2) -> makeXML "invalidequation" $ mconcat [element "left" [text e1], element "right" [text e2]] Recovery -> makeXML "recovery" mempty NonMatchingParentheses -> makeXML "nonmatchingparentheses" mempty IncorrectDistribution -> makeXML "incorrectdistribution" mempty IncorrectFactorization -> makeXML "incorrectfactorization" mempty InvertedFraction -> makeXML "invertedfraction" mempty CapturedWildcard s e -> makeXML "capturedwildcard" $ mconcat [element "wildcard" [text s],element "expr" [text e]] AtomMixedUp e1 e2 -> makeXML "atommixedup" $ mconcat [element "left" [text e1], element "right" [text e2]] Sloppiness -> makeXML "sloppiness" mempty OperatorMixedUp w c -> makeXML "operatormixedup" $ mconcat [element "wrong" [text w], element "correct" [text c]] Misconception w c -> makeXML "misconception" $ mconcat [element "wrong" [text w], element "correct" [text c]] AsymmetricRelation -> makeXML "asymmetricrelation" mempty InequalityStrictness -> makeXML "inequalitystrictness" mempty RoundingError -> makeXML "roundingerror" mempty CommonMistake -> makeXML "commonmistake" mempty Approximation -> makeXML "approximation" mempty Other s -> makeXML "other" (string s) isMistake :: Attribute -> Bool isMistake (InvalidEquation _ _) = True isMistake NonMatchingParentheses = True isMistake (InvalidCommutativity _) = True isMistake (ForgetSym _) = True isMistake IncorrectDistribution = True isMistake IncorrectFactorization = True isMistake InvertedFraction = True isMistake (AtomMixedUp _ _) = True isMistake Sloppiness = True isMistake (OperatorMixedUp _ _) = True isMistake (Misconception _ _) = True isMistake AsymmetricRelation = True isMistake InequalityStrictness = True isMistake RoundingError = True isMistake CommonMistake = True isMistake _ = False isApproximation :: Attribute -> Bool isApproximation Approximation = True isApproximation _ = False isLabelAttr :: Attribute -> Bool isLabelAttr (Label _) = True isLabelAttr (LabelE _ _) = True isLabelAttr _ = False isCommonMistake :: Attribute -> Bool isCommonMistake CommonMistake = True isCommonMistake _ = False data Concept = Area | Perimeter | Square | Triangle | Volume | Rectangle | HalfPerimeter deriving (Eq, Show, Ord) infixl 7 Attribute -> [(a, [Attribute])] xs xs