{-# LANGUAGE 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) -- ----------------------------------------------------------------------------- module Recognize.Data.MathStoryProblem ( Task(..) , MathStoryProblem, mathStoryProblem , problemId, processInputs , inputFile, networkFile, singleNetwork , getExercise, diagnose, analyzers , Analyzer, analyzer , lexer, parser, recognizer, collector ) where import Data.Maybe import Ideas.Common.Library hiding (recognizer, recognize, parser) import Ideas.Text.HTML import Ideas.Text.XML import Bayes.Evidence import Bayes.Network ( Network ) import Recognize.Data.DiagnoseResult import Recognize.Data.Entry import Recognize.Data.MathParserOutput import Recognize.Data.Diagnosis import Recognize.Data.StringLexer import Recognize.Data.DiagnoseError import Recognize.Data.Solution import Recognize.Data.Approach ( Approach(Other) ) getExercise :: MathStoryProblem -> Exercise b getExercise e = emptyExercise { exerciseId = getId e } data Task = Task (MathStoryProblem) instance Show Task where show = showId instance HasId Task where getId (Task pr) = getId pr changeId f (Task pr) = Task (changeId f pr) findAnalyzer :: MathStoryProblem -> InputId -> Analyzer findAnalyzer pr i = fromMaybe analyzer (lookup i (analyzers pr)) data MathStoryProblem = MSP { problemId :: Id , processInputs :: [Input] -> [Input] , analyzers :: [(InputId, Analyzer)] , inputFile :: Maybe FilePath , networkFile :: Maybe FilePath , singleNetwork :: Network () } data Analyzer = A { lexer :: Maybe Language -> Input -> LexerOutput , parser :: LexerOutput -> MathParserOutput , recognizer :: MathParserOutput -> Either DiagnoseError Diagnosis , collector :: Diagnosis -> Evidence } instance Show MathStoryProblem where show = show . problemId instance HasId MathStoryProblem where getId = problemId changeId f pr = pr { problemId = f (problemId pr) } mathStoryProblem :: MathStoryProblem mathStoryProblem = MSP { problemId = mempty , processInputs = id , analyzers = [] , inputFile = Nothing , networkFile = Nothing , singleNetwork = mempty } analyzer :: Analyzer analyzer = A { lexer = stringLexer mempty , parser = mathParser mempty . stringLexerOutput , recognizer = \_ -> Left Unknown , collector = const mempty } ----------------------------------------------------------------------------- diagnose :: MathStoryProblem -> Solution -> Entry diagnose e sol = Entry (map f inps) where inps = processInputs e (inputs sol) f = diagnoseInput e (language sol) -- | @diagnosePipeline inputId e o i@ specifies how the input from some exercise is handled. -- The input is lexed, parsed and then recognized. Any information from earlier phases is propagated to later phases. diagnoseInput :: MathStoryProblem -> Maybe Language -> Input -> DiagnoseResult diagnoseInput pr lang i = DiagnoseResult { originalInput = i , lexerOutput = lex_out , parserOutput = parse_out , diagnosis = diag_out , evidence = col_out } where ana = findAnalyzer pr (getInputId i) lex_out = lexer ana lang i parse_out = parser ana lex_out diag_out = recognizer ana parse_out col_out = either (const . collector ana $ newDiagnosis (Other "dummy diagnosis") []) (collector ana) diag_out