{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} module Language.Symantic.Expr.Error where import Data.Proxy (Proxy(..)) import Data.Text (Text) import qualified Data.Text as Text import Language.Symantic.Lib.Data.Bool import Language.Symantic.Type import Language.Symantic.Expr.Root import Language.Symantic.Expr.Alt -- * Type family 'Error_of_Expr' -- | The error(s) of an expression. type family Error_of_Expr (ast:: *) (ex:: *) :: * type instance Error_of_Expr ast (Expr_Root ex) = Error_Expr_Alt (Error_Expr (Error_of_Type ast (Type_Root_of_Expr (ex (Expr_Root ex)))) (Type_Root_of_Expr (ex (Expr_Root ex))) ast) (Error_of_Expr ast (ex (Expr_Root ex))) type instance Error_of_Expr ast (Expr_Alt curr next root) = Error_of_Expr_Alt ast (Error_of_Expr ast (curr root)) (Error_of_Expr ast (next root)) -- ** Type family 'Error_of_Expr_Alt' -- | Remove 'No_Error_Expr' type when building the error of an expression. type family Error_of_Expr_Alt ast curr next where Error_of_Expr_Alt ast No_Error_Expr next = next Error_of_Expr_Alt ast curr No_Error_Expr = curr Error_of_Expr_Alt ast curr next = Error_Expr_Alt curr next -- * Type 'Error_Expr_Alt' -- | Error expression making an alternative between two error expressions. data Error_Expr_Alt curr next = Error_Expr_Alt_Curr curr | Error_Expr_Alt_Next next deriving (Eq, Show) -- ** Type 'Lift_Error_Expr' -- | Apply 'Peano_of_Error_Expr' on 'Lift_Error_ExprP'. type Lift_Error_Expr err errs = Lift_Error_ExprP (Peano_of_Error_Expr err errs) err errs -- | Convenient wrapper around 'lift_error_exprP', -- passing it the 'Peano' number from 'Peano_of_Error_Expr'. lift_error_expr :: forall err errs. Lift_Error_Expr err errs => err -> errs lift_error_expr = lift_error_exprP (Proxy::Proxy (Peano_of_Error_Expr err errs)) -- *** Type family 'Peano_of_Error_Expr' -- | Return a 'Peano' number derived from the location -- of a given error expression within a given error expression stack, -- which is used to avoid @OverlappingInstances@. type family Peano_of_Error_Expr (err:: *) (errs:: *) :: * where Peano_of_Error_Expr err err = Zero Peano_of_Error_Expr err (Error_Expr_Alt err next) = Zero Peano_of_Error_Expr other (Error_Expr_Alt curr next) = Succ (Peano_of_Error_Expr other next) -- *** Class 'Lift_Error_ExprP' -- | Lift a given expression to the top of a given expression stack including it, -- by constructing the appropriate sequence of 'Error_Expr_Alt_Curr' and 'Error_Expr_Alt_Next'. class Lift_Error_ExprP (p:: *) err errs where lift_error_exprP :: Proxy p -> err -> errs instance Lift_Error_ExprP Zero curr curr where lift_error_exprP _ = id instance Lift_Error_ExprP Zero curr (Error_Expr_Alt curr next) where lift_error_exprP _ = Error_Expr_Alt_Curr instance Lift_Error_ExprP p other next => Lift_Error_ExprP (Succ p) other (Error_Expr_Alt curr next) where lift_error_exprP _ = Error_Expr_Alt_Next . lift_error_exprP (Proxy::Proxy p) -- ** Type 'Unlift_Error_Expr' -- | Apply 'Peano_of_Error_Expr' on 'Unlift_Error_ExprP'. type Unlift_Error_Expr ex exs = Unlift_Error_ExprP (Peano_of_Error_Expr ex exs) ex exs -- | Convenient wrapper around 'unlift_error_exprP', -- passing it the 'Peano' number from 'Peano_of_Error_Expr'. unlift_error_expr :: forall ex exs. Unlift_Error_Expr ex exs => exs -> Maybe ex unlift_error_expr = unlift_error_exprP (Proxy::Proxy (Peano_of_Error_Expr ex exs)) -- *** Class 'Unlift_Error_ExprP' -- | Try to unlift a given expression error out of a given expression error stack including it, -- by deconstructing the appropriate sequence of 'Error_Expr_Alt_Curr' and 'Error_Expr_Alt_Next'. class Unlift_Error_ExprP (p:: *) ex exs where unlift_error_exprP :: Proxy p -> exs -> Maybe ex instance Unlift_Error_ExprP Zero curr curr where unlift_error_exprP _ = Just instance Unlift_Error_ExprP Zero curr (Error_Expr_Alt curr next) where unlift_error_exprP _ (Error_Expr_Alt_Curr x) = Just x unlift_error_exprP _ (Error_Expr_Alt_Next _) = Nothing instance Unlift_Error_ExprP p other next => Unlift_Error_ExprP (Succ p) other (Error_Expr_Alt curr next) where unlift_error_exprP _ (Error_Expr_Alt_Next x) = unlift_error_exprP (Proxy::Proxy p) x unlift_error_exprP _ (Error_Expr_Alt_Curr _) = Nothing -- * Type 'Error_Expr_Read' -- | Common expression errors. data Error_Expr err_ty ty ast = Error_Expr_Wrong_number_of_arguments ast Int -- ^ Wrong number of arguments applied to a term, -- the integer is the number of arguments expected. | Error_Expr_Type_mismatch ast (Exists_Type ty) (Exists_Type ty) -- ^ Mismatch between respectively expected and actual type. | Error_Expr_Constraint_missing ast {-Exists_Dict-} (Exists_Type ty) -- ^ A 'Constraint' is missing. | Error_Expr_Read Error_Read ast -- ^ Error when reading a literal. | Error_Expr_Type err_ty ast -- ^ Error when parsing a type. | Error_Expr_Unsupported ast -- ^ Given syntax is supported by none -- of the expression parser components -- of the expression stack. | Error_Expr_Unsupported_here ast -- ^ Given syntax not supported by -- the current expression parser component. deriving (Eq, Show) -- | Convenient type alias. type Error_Expr_of_Root ast root = Error_Expr (Error_of_Type ast (Type_Root_of_Expr root)) (Type_Root_of_Expr root) ast -- | Convenient wrapper around 'lift_error_expr', -- passing the type family boilerplate. error_expr :: forall ast ex ty. (ty ~ Type_Root_of_Expr ex) => Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast (Root_of_Expr ex)) => Proxy ex -> Error_Expr (Error_of_Type ast ty) ty ast -> Error_of_Expr ast (Root_of_Expr ex) error_expr _ = lift_error_expr -- | Parsing utility to return 'Error_Expr_Unsupported' -- or 'Error_Expr_Unsupported_here' -- according to the given expression. error_expr_unsupported :: forall ast ex ty root. ( root ~ Root_of_Expr ex , ty ~ Type_Root_of_Expr ex , IBool (Is_Last_Expr ex root) , Lift_Error_Expr (Error_Expr (Error_of_Type ast ty) ty ast) (Error_of_Expr ast root) ) => Proxy ex -> ast -> Error_of_Expr ast (Root_of_Expr ex) error_expr_unsupported ex ast = case iBool :: SBool (Is_Last_Expr ex root) of STrue -> error_expr ex $ Error_Expr_Unsupported ast SFalse -> error_expr ex $ Error_Expr_Unsupported_here ast -- ** Type 'No_Error_Expr' -- | A discarded error. data No_Error_Expr = No_Error_Expr deriving (Eq, Show) -- * Type 'Error_Read' -- | Error parsing a host-term. data Error_Read = Error_Read Text deriving (Eq, Show) -- | Parse a host-term. read_safe :: Read h => Text -> Either Error_Read h read_safe t = case reads $ Text.unpack t of [(x, "")] -> Right x _ -> Left $ Error_Read t