Maintainer | bastiaan.heeren@ou.nl |
---|---|
Stability | provisional |
Portability | portable (depends on ghc) |
Safe Haskell | None |
Language | Haskell98 |
Recognize.Data.Math
Description
Defines the Math
type and closely associated functions.
Synopsis
- ppExpr :: Expr -> String
- isFunctionDefinition :: Expr -> Bool
- isDefinition :: Expr -> Bool
- data Math = M {}
- newtype MathParseError = MathParseError {}
- arbitraryPrintable :: Gen String
- mathListHtml :: [Math] -> HTMLBuilder
- isParseError :: Math -> Bool
- printMath :: Math -> String
- makeMath :: Expr -> Math
- showMathList :: [Math] -> String
- getExpr :: Monad m => Math -> m Expr
- getRelation :: Monad m => Math -> m (Relation Expr)
- getRelationE :: Monad m => Expr -> m (Relation Expr)
- getEq :: Monad m => Math -> m (Equation Expr)
- getEqE :: Monad m => Expr -> m (Equation Expr)
- getChainedEq :: Monad m => Math -> m [Expr]
- isEq :: Expr -> Bool
- chainedEqSymbol :: Symbol
- functionCallSymbol :: Symbol
- isChainedEqSymbol :: Symbol -> Bool
- isChainedEq :: Expr -> Bool
- isFunctionCallSymbol :: Symbol -> Bool
- isFunctionCall :: Expr -> Bool
Documentation
isFunctionDefinition :: Expr -> Bool Source #
isDefinition :: Expr -> Bool Source #
Constructors
M | |
newtype MathParseError Source #
Constructors
MathParseError | |
Instances
Eq MathParseError Source # | |
Defined in Recognize.Data.Math Methods (==) :: MathParseError -> MathParseError -> Bool # (/=) :: MathParseError -> MathParseError -> Bool # | |
Show MathParseError Source # | |
Defined in Recognize.Data.Math Methods showsPrec :: Int -> MathParseError -> ShowS # show :: MathParseError -> String # showList :: [MathParseError] -> ShowS # | |
Arbitrary MathParseError Source # | |
Defined in Recognize.Data.Math | |
ToXML MathParseError Source # | |
Defined in Recognize.Data.Math | |
InXML MathParseError Source # | |
Defined in Recognize.Data.Math Methods fromXML :: Monad m => XML -> m MathParseError # listFromXML :: Monad m => XML -> m [MathParseError] # |
mathListHtml :: [Math] -> HTMLBuilder Source #
isParseError :: Math -> Bool Source #
showMathList :: [Math] -> String Source #
isChainedEqSymbol :: Symbol -> Bool Source #
isChainedEq :: Expr -> Bool Source #
isFunctionCallSymbol :: Symbol -> Bool Source #
isFunctionCall :: Expr -> Bool Source #