From afd550dc8245e61ab6b148c72cdf133e6b7836d1 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Roman=20Smr=C5=BE?= Date: Fri, 27 Sep 2024 20:30:25 +0200 Subject: Default and context-provided values for function arguments --- src/Parser/Core.hs | 18 +++++++++++++----- src/Parser/Expr.hs | 4 ++-- src/Test.hs | 21 +++++++++++++++------ src/Test/Builtins.hs | 2 +- 4 files changed, 31 insertions(+), 14 deletions(-) diff --git a/src/Parser/Core.hs b/src/Parser/Core.hs index ab6079a..f40889a 100644 --- a/src/Parser/Core.hs +++ b/src/Parser/Core.hs @@ -134,11 +134,19 @@ unifyExpr off pa expr = if | Just (Refl :: FunctionType a :~: b) <- eqT -> do - case exprArgs expr of - remaining - | anull remaining -> return (FunctionEval expr) - | otherwise -> parseError $ FancyError off $ S.singleton $ ErrorFail $ T.unpack $ - "missing function arguments" + let FunctionArguments remaining = exprArgs expr + showType ( Nothing, SomeArgumentType atype ) = "`<" <> textExprType atype <> ">'" + showType ( Just (ArgumentKeyword kw), SomeArgumentType atype ) = "`" <> kw <> " <" <> textExprType atype <> ">'" + err = parseError . FancyError off . S.singleton . ErrorFail . T.unpack + + defaults <- forM (M.toAscList remaining) $ \case + arg@(_, SomeArgumentType NoDefault) -> err $ "missing " <> showType arg <> " argument" + (kw, SomeArgumentType (ExprDefault def)) -> return (kw, SomeExpr def) + (kw, SomeArgumentType atype@ContextDefault) -> do + SomeExpr context <- gets testContext + context' <- unifyExpr off atype context + return (kw, SomeExpr context') + return (FunctionEval $ ArgsApp (FunctionArguments $ M.fromAscList defaults) expr) | Just (Refl :: DynamicType :~: b) <- eqT , Undefined msg <- expr diff --git a/src/Parser/Expr.hs b/src/Parser/Expr.hs index 8ae0f77..4b1a89e 100644 --- a/src/Parser/Expr.hs +++ b/src/Parser/Expr.hs @@ -355,9 +355,9 @@ variable = label "variable" $ do SomeExpr e'@(FunVariable (FunctionArguments argTypes) _ _) -> do let check poff kw expr = do case M.lookup kw argTypes of - Just expected -> do + Just (SomeArgumentType (_ :: ArgumentType expected)) -> do withRecovery registerParseError $ do - void $ unify poff expected (someExprType expr) + void $ unify poff (ExprTypePrim (Proxy @expected)) (someExprType expr) return expr Nothing -> do registerParseError $ FancyError poff $ S.singleton $ ErrorFail $ T.unpack $ diff --git a/src/Test.hs b/src/Test.hs index b0a91bd..b8b44ed 100644 --- a/src/Test.hs +++ b/src/Test.hs @@ -19,6 +19,7 @@ module Test ( ArgumentKeyword(..), FunctionArguments(..), anull, exprArgs, + SomeArgumentType(..), ArgumentType(..), Regex(RegexPart, RegexString), regexMatch, ) where @@ -30,6 +31,7 @@ import Data.List import Data.Map (Map) import Data.Map qualified as M import Data.Scientific +import Data.String import Data.Text (Text) import Data.Text qualified as T import Data.Typeable @@ -157,7 +159,7 @@ newtype TypeVar = TypeVar Text data SomeExprType = forall a. ExprType a => ExprTypePrim (Proxy a) | ExprTypeVar TypeVar - | forall a. ExprType a => ExprTypeFunction (FunctionArguments SomeExprType) (Proxy a) + | forall a. ExprType a => ExprTypeFunction (FunctionArguments SomeArgumentType) (Proxy a) someExprType :: SomeExpr -> SomeExprType someExprType (SomeExpr (DynVariable tvar _ _)) = ExprTypeVar tvar @@ -173,7 +175,7 @@ textSomeExprType (ExprTypeVar (TypeVar name)) = name textSomeExprType (ExprTypeFunction _ r) = "function:" <> textExprType r -data SomeVarValue = forall a. ExprType a => SomeVarValue (FunctionArguments SomeExprType) (SourceLine -> FunctionArguments SomeExpr -> a) +data SomeVarValue = forall a. ExprType a => SomeVarValue (FunctionArguments SomeArgumentType) (SourceLine -> FunctionArguments SomeExpr -> a) fromSomeVarValue :: forall a m. (ExprType a, MonadFail m) => SourceLine -> VarName -> SomeVarValue -> m a fromSomeVarValue sline name (SomeVarValue args (value :: SourceLine -> args -> b)) = do @@ -205,7 +207,7 @@ data ExprEnumerator a = ExprEnumerator (a -> a -> [a]) (a -> a -> a -> [a]) data Expr a where Variable :: ExprType a => SourceLine -> VarName -> Expr a DynVariable :: TypeVar -> SourceLine -> VarName -> Expr DynamicType - FunVariable :: ExprType a => FunctionArguments SomeExprType -> SourceLine -> VarName -> Expr (FunctionType a) + FunVariable :: ExprType a => FunctionArguments SomeArgumentType -> SourceLine -> VarName -> Expr (FunctionType a) ArgsApp :: FunctionArguments SomeExpr -> Expr (FunctionType a) -> Expr (FunctionType a) FunctionEval :: Expr (FunctionType a) -> Expr a Pure :: a -> Expr a @@ -282,8 +284,8 @@ gatherVars = fmap (uniqOn fst . sortOn fst) . helper _ -> Nothing -data ArgumentKeyword = ArgumentKeyword Text - deriving (Show, Eq, Ord) +newtype ArgumentKeyword = ArgumentKeyword Text + deriving (Show, Eq, Ord, IsString) newtype FunctionArguments a = FunctionArguments (Map (Maybe ArgumentKeyword) a) deriving (Show, Semigroup, Monoid) @@ -291,7 +293,7 @@ newtype FunctionArguments a = FunctionArguments (Map (Maybe ArgumentKeyword) a) anull :: FunctionArguments a -> Bool anull (FunctionArguments args) = M.null args -exprArgs :: Expr (FunctionType a) -> FunctionArguments SomeExprType +exprArgs :: Expr (FunctionType a) -> FunctionArguments SomeArgumentType exprArgs (FunVariable args _ _) = args exprArgs (ArgsApp (FunctionArguments applied) expr) = let FunctionArguments args = exprArgs expr @@ -307,6 +309,13 @@ funFromSomeVarValue sline name (SomeVarValue args (value :: SourceLine -> args - err = T.unpack $ T.concat [ T.pack "expected function returning ", textExprType @a Proxy, T.pack ", but variable '", textVarName name, T.pack "' has ", (if anull args then "type" else "function type returting ") <> textExprType @b Proxy ] +data SomeArgumentType = forall a. ExprType a => SomeArgumentType (ArgumentType a) + +data ArgumentType a + = NoDefault + | ExprDefault (Expr a) + | ContextDefault + data Regex = RegexCompiled Text RE.Regex | RegexPart Text diff --git a/src/Test/Builtins.hs b/src/Test/Builtins.hs index b768bb9..3f42335 100644 --- a/src/Test/Builtins.hs +++ b/src/Test/Builtins.hs @@ -20,7 +20,7 @@ getArg (FunctionArguments args) kw = _ -> error "parameter mismatch" builtinGuard :: SomeVarValue -builtinGuard = SomeVarValue (FunctionArguments $ M.singleton Nothing (ExprTypePrim (Proxy @Bool))) $ +builtinGuard = SomeVarValue (FunctionArguments $ M.singleton Nothing (SomeArgumentType (NoDefault @Bool))) $ \sline args -> TestBlock [ Guard sline (getArg args Nothing) ] builtinWait :: SomeVarValue -- cgit v1.2.3