----------------------------------------------------------------------------- -- 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.Approach where import Control.Monad import Data.List import Ideas.Text.HTML import Ideas.Text.XML import Test.QuickCheck class HasApproach a where approach :: a -> Approach -- | Approach = Category data Approach = Algebraic | Arithmetic | Numerical | Recursive | Generalizing | Graphical | Other String | NoApproach deriving (Eq, Ord) instance Show Approach where show Algebraic = "algebraic" show Arithmetic = "arithmetic" show Numerical = "numerical" show Recursive = "recursive" show Generalizing = "generalizing" show Graphical = "graphical" show (Other s) = "Other: " ++ s show NoApproach = "noapproach" instance ToHTML Approach where toHTML = text instance ToXML Approach where toXML a = makeXML "approach" $ text a instance InXML Approach where fromXML xml = do unless (name xml == "approach") $ fail "expecting element" case getData xml of "algebraic" -> return Algebraic "arithmetic" -> return Arithmetic "numerical" -> return Numerical "recursive" -> return Recursive "generalizing" -> return Generalizing "graphical" -> return Graphical "noapproach" -> return NoApproach txt | "Other: " `isPrefixOf` txt -> return (Other (drop 7 txt)) | otherwise -> fail $ "unknown approach " ++ txt instance Arbitrary Approach where arbitrary = oneof (pure <$> [Algebraic,Arithmetic, Numerical, Recursive, Generalizing, Graphical, Other "", NoApproach])