module Ideas.Text.OpenMath.FMP where
import Data.List (union)
import Ideas.Text.OpenMath.Dictionary.Quant1 (forallSymbol, existsSymbol)
import Ideas.Text.OpenMath.Dictionary.Relation1 (eqSymbol, neqSymbol)
import Ideas.Text.OpenMath.Object
import Ideas.Text.OpenMath.Symbol
data FMP = FMP
{ quantor :: Symbol
, metaVariables :: [String]
, leftHandSide :: OMOBJ
, relation :: Symbol
, rightHandSide :: OMOBJ
}
toObject :: FMP -> OMOBJ
toObject fmp
| null (metaVariables fmp) = body
| otherwise =
OMBIND (OMS (quantor fmp)) (metaVariables fmp) body
where
body = OMA [OMS (relation fmp), leftHandSide fmp, rightHandSide fmp]
eqFMP :: OMOBJ -> OMOBJ -> FMP
eqFMP lhs rhs = FMP
{ quantor = forallSymbol
, metaVariables = getOMVs lhs `union` getOMVs rhs
, leftHandSide = lhs
, relation = eqSymbol
, rightHandSide = rhs
}
buggyFMP :: OMOBJ -> OMOBJ -> FMP
buggyFMP lhs rhs = (eqFMP lhs rhs)
{ quantor = existsSymbol
, relation = neqSymbol
}