| Maintainer | bastiaan.heeren@ou.nl | 
|---|---|
| Stability | provisional | 
| Portability | portable (depends on ghc) | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Recognize.SubExpr.SEParser
Description
Synopsis
- type SEParser = ParserT SEState Math Identity
- get :: MonadState s m => m s
- put :: MonadState s m => s -> m ()
- gets :: MonadState s m => (s -> a) -> m a
- modify :: MonadState s m => (s -> s) -> m ()
- seParse :: SEParser a -> [Math] -> Maybe a
- data SEState = SEState {- optGrow :: Bool
- growF :: Expr -> Expr
- optIterate :: Bool
- optTraverse :: Bool
- optSimplify :: Bool
- optSkipOnce :: Bool
- chainedEquations :: Bool
- precision :: Int
- matchings :: Set Expr
- usedVariables :: Map String Expr
- inputType :: Maybe [InputType]
- matchPredicate :: Expr -> Bool
 
- getVarKey :: Expr -> SEParser String
- addMatching :: Expr -> SEParser ()
- data InputType
- determineInputType :: Expr -> InputType
- conformsTo :: Expr -> InputType -> Bool
- resetAfter :: SEParser a -> SEParser a
- resetSEState :: SEParser SEState
SubExpression Parser
get :: MonadState s m => m s #
Return the state from the internals of the monad.
put :: MonadState s m => s -> m () #
Replace the state inside the monad.
gets :: MonadState s m => (s -> a) -> m a #
Gets specific component of the state, using a projection function supplied.
modify :: MonadState s m => (s -> s) -> m () #
Monadic state transformer.
Maps an old state to a new state inside a state monad. The old state is thrown away.
     Main> :t modify ((+1) :: Int -> Int)
     modify (...) :: (MonadState Int a) => a ()This says that modify (+1) acts over any
    Monad that is a member of the MonadState class,
    with an Int state.
User state
The user state of the subexpression recognizer
It carries parameters for the recognizer, mapping of vars to expressions and other information
Constructors
| SEState | |
| Fields 
 | |
addMatching :: Expr -> SEParser () Source #
Input type
Describes some math type
Constructors
| Expr | |
| Definition | |
| Equation | |
| LinearWithType RelationType | |
| Linear | 
determineInputType :: Expr -> InputType Source #
Determine the input type of the given expression
conformsTo :: Expr -> InputType -> Bool Source #
Given an expression, check whether it matches the specified input type.
resetAfter :: SEParser a -> SEParser a Source #
Reset the user state to dSEState after executing the parser
resetSEState :: SEParser SEState Source #
Reset the user state to dSEState. Returns the user state before resetting.