module Funcons.Exceptions where import Funcons.Types import Funcons.Printer import Data.Text -- handling exception from the interpreter type IException = (Funcons, Funcons, IE) --global, local, exception data IE = SortErr String | Err String --TODO when used? | PartialOp String | Internal String | NoRule | SideCondFail String | InsufficientInput Name | InsufficientInputConsumed Name | PatternMismatch String | StepOnValue showIException :: IException -> String showIException (f0,f,ie) = "Internal Exception: " ++ show ie ++ " on " ++ showFuncons f instance Show IE where show (SortErr err) = "dynamic sort check (" ++ err ++ ")" show NoRule = "no rule to execute" show (Err err) = "exception (" ++ err ++ ")" show (Internal err) = "exception (" ++ err ++ ")" show (SideCondFail str) = str show (PatternMismatch str) = str show (InsufficientInput nm) = "insufficient supply for " ++ unpack nm show (InsufficientInputConsumed nm) = "insufficient input consumed for entity " ++ unpack nm show (PartialOp str) = "partial operation" show StepOnValue = "attempting to step a value" -- which exceptions stop a rule from executing so that the next one can be attempted? failsRule :: IException -> Bool failsRule (_,_,SideCondFail _) = True failsRule (_,_,PatternMismatch _) = True failsRule (_,_,SortErr _) = True failsRule (_,_,PartialOp _) = True failsRule (_,_,StepOnValue) = True failsRule _ = False