module Recognize.SubExpr.SEParser
(
SEParser, get, put, gets, modify, seParse
, SEState(..), getVarKey, addMatching
, InputType(..), determineInputType, conformsTo, resetAfter, resetSEState
) where
import Control.Applicative
import Control.Monad
import Control.Monad.State
import qualified Data.Map as M
import Data.Maybe
import qualified Data.Set as S
import Domain.Math.Expr
import Domain.Math.Data.Relation
import Recognize.Data.Math
import qualified Recognize.Expr.Functions as F
import Recognize.SubExpr.Functions
import Recognize.Parsing.Parser
import Control.Monad.Identity
data InputType = Expr | Definition | Equation | LinearWithType RelationType | Linear deriving (Eq,Show)
conformsTo :: Expr -> InputType -> Bool
conformsTo e Expr = isNothing $ getEqE e
conformsTo e Definition = isJust $ do
(x :==: _) <- getEqE e
guard $ isFunctionCall x || F.isVar x
conformsTo e Equation = isJust $ do
rel <- getRelationE e
let x = leftHandSide rel
let y = rightHandSide rel
guard (not (F.hasVar x || F.hasVar y) && not (isFunctionCall x))
conformsTo e Linear = isJust $ do
rel <- getRelationE e
let x = leftHandSide rel
let y = rightHandSide rel
guard (not (F.isVar x) && (F.hasVar x || F.hasVar y))
conformsTo e (LinearWithType t) = (conformsTo e Linear) && (isJust $ do
rel <- getRelationE e
let sym = relationType rel
guard (sym == t))
determineInputType :: Expr -> InputType
determineInputType e
| e `conformsTo` Definition = Definition
| e `conformsTo` Equation = Equation
| e `conformsTo` Linear = Linear
| e `conformsTo` (LinearWithType EqualTo) = Linear
| e `conformsTo` (LinearWithType LessThan) = Linear
| otherwise = Expr
data SEState = SEState
{ optGrow :: Bool
, growF :: Expr -> Expr
, optIterate :: Bool
, optTraverse :: Bool
, optSimplify :: Bool
, optSkipOnce :: Bool
, chainedEquations :: Bool
, precision :: Int
, matchings :: S.Set Expr
, usedVariables :: M.Map String Expr
, inputType :: Maybe [InputType]
, matchPredicate :: Expr -> Bool
}
emptyState :: SEState
emptyState = SEState
{ optGrow = False
, growF = id
, optIterate = True
, optTraverse = True
, optSimplify = True
, optSkipOnce = False
, chainedEquations = False
, precision = 2
, matchings = S.empty
, usedVariables = M.empty
, inputType = Nothing
, matchPredicate = const True
}
type SEParser = ParserT SEState Math Identity
seParse :: SEParser a -> [Math] -> Maybe a
seParse p ss =
case runIdentity (runParserT p emptyState ss) of
[] -> Nothing
(a, _, _):_ -> Just a
getVarKey :: Expr -> SEParser String
getVarKey (Sym s [Var x]) = guard (isVarSymbol s) >> return x
getVarKey _ = empty
addMatching :: Expr -> SEParser ()
addMatching e =
modify $ \st -> st { matchings = S.insert e (matchings st) }
resetAfter :: SEParser a -> SEParser a
resetAfter sp = do
a <- sp
put emptyState
return a
resetSEState :: SEParser SEState
resetSEState = do
us <- get
put emptyState
return us