module Top.Implementation.Basic where
import Control.Arrow
import Top.Constraint
import Top.Util.Option
import Top.Implementation.General
import Top.Interface.Basic
import Top.Monad.Select
import Top.Util.Embedding
import Top.Util.Empty
data BasicState info m = BasicState
{ constraints :: Constraints m
, errors :: [(info, ErrorLabel)]
, conditions :: [(m Bool, String)]
, optionStop :: Option Bool
, optionCheck :: Option Bool
}
instance SolveState (BasicState info m) where
stateName _ = "Basic State"
stateOptions s = [show (optionStop s), show (optionCheck s)]
instance Empty (BasicState info m) where
empty = BasicState
{ constraints = []
, errors = []
, conditions = []
, optionStop = stopOption
, optionCheck = checkOption
}
instance Show (BasicState info m) where
show s
| null (constraints s) = overview
| otherwise =
unlines $
["Constraints", "-----------"] ++
map ((" "++) . show) (constraints s) ++
[overview]
where
overview = "("++show (length (constraints s))++" constraints, "++
show (length (errors s))++" errors, "++
show (length (conditions s))++" checks)"
instance Embedded ClassBasic (BasicState info m) (BasicState info m) where embedding = idE
instance Embedded ClassBasic (Fix (BasicState info) x m) (BasicState info m) where embedding = fromFstFixE embedding
instance ( MonadState s m
, Embedded ClassBasic s (BasicState info m)
) =>
HasBasic (SelectFix (BasicState info) m) info where
pushConstraints xs =
modify (\s -> s { constraints = map (mapConstraint deselectFix) xs ++ constraints s })
popConstraint =
do cs <- gets constraints
case cs of
[] -> return Nothing
(x:xs) -> do modify (\s -> s { constraints = xs })
return (Just (mapConstraint selectFix x))
discardConstraints =
modify (\s -> s { constraints = [] })
addLabeledError label info =
do modify (\s -> s { errors = (info, label) : errors s })
stop <- getOption stopAfterFirstError
when stop discardConstraints
getLabeledErrors =
gets errors
updateErrorInfo f =
do errs <- getLabeledErrors
newErrs <- let g (info, label) =
do newInfo <- f info
return (newInfo, label)
in mapM g errs
modify (\s -> s { errors = newErrs })
addCheck text check =
modify (\s -> s { conditions = (deselectFix check, text) : conditions s})
getChecks =
gets (map (first selectFix) . conditions)
stopAfterFirstError = useOption optionStop (\x s -> s { optionStop = x })
checkConditions = useOption optionCheck (\x s -> s { optionCheck = x })