added optional expected return type for match groups
authorBrendan Hansen <brendan.f.hansen@gmail.com>
Wed, 28 Dec 2022 17:22:29 +0000 (11:22 -0600)
committerBrendan Hansen <brendan.f.hansen@gmail.com>
Wed, 28 Dec 2022 17:22:29 +0000 (11:22 -0600)
13 files changed:
compiler/include/astnodes.h
compiler/include/errors.h
compiler/src/astnodes.c
compiler/src/checker.c
compiler/src/entities.c
compiler/src/errors.c
compiler/src/parser.c
compiler/src/symres.c
compiler/src/utils.c
core/alloc/heap.onyx
core/hash/hash.onyx
core/string/string.onyx
docs/todo

index f6bb55b9717605d1a7095450030e473ed5cc6bc7..de02e1aea9a1c20bac29067d6848e702073a7a10 100644 (file)
@@ -1089,6 +1089,9 @@ struct AstOverloadedFunction {
     // function.
     bh_imap            all_overloads;
 
+    AstType *expected_return_node;
+    Type    *expected_return_type;
+
     b32 locked : 1;
     b32 only_local_functions : 1;
 };
@@ -1407,6 +1410,11 @@ struct AstForeignBlock {
     u32 foreign_block_number;
 };
 
+typedef struct EntityJobData {
+    enum TypeMatch (*func)(void *job_data);
+    void *job_data;
+} EntityJobData;
+
 typedef enum EntityState {
     Entity_State_Error,
 
@@ -1457,6 +1465,7 @@ typedef enum EntityType {
     Entity_Type_Struct_Member_Default,
     Entity_Type_Memory_Reservation,
     Entity_Type_Expression,
+    Entity_Type_Job,                    // Represents an arbitrary job (function pointer).
     Entity_Type_Global,
     Entity_Type_Overloaded_Function,
     Entity_Type_Function,
@@ -1507,6 +1516,7 @@ typedef struct Entity {
         AstInterface          *interface;
         AstConstraint         *constraint;
         AstDirectiveLibrary   *library;
+        EntityJobData         *job_data;
     };
 } Entity;
 
@@ -1528,6 +1538,7 @@ Entity* entity_heap_top(EntityHeap* entities);
 void entity_heap_change_top(EntityHeap* entities, Entity* new_top);
 void entity_heap_remove_top(EntityHeap* entities);
 void entity_change_type(EntityHeap* entities, Entity *ent, EntityType new_type);
+void entity_heap_add_job(EntityHeap *entities, enum TypeMatch (*func)(void *), void *job_data);
 
 // If target_arr is null, the entities will be placed directly in the heap.
 void add_entities_for_node(bh_arr(Entity *)* target_arr, AstNode* node, Scope* scope, Package* package);
@@ -1728,6 +1739,7 @@ typedef enum TypeMatch {
     TYPE_MATCH_YIELD,
     TYPE_MATCH_SPECIAL, // Only used for nest polymorph function lookups
 } TypeMatch;
+
 #define unify_node_and_type(node, type) (unify_node_and_type_((node), (type), 1))
 TypeMatch unify_node_and_type_(AstTyped** pnode, Type* type, b32 permanent);
 
@@ -1790,10 +1802,19 @@ AstFunction* polymorphic_proc_build_only_header_with_slns(AstFunction* pp, bh_ar
 b32 potentially_convert_function_to_polyproc(AstFunction *func);
 AstPolyCallType* convert_call_to_polycall(AstCall* call);
 
+
+typedef struct OverloadReturnTypeCheck {
+    Type *expected_type;
+    AstTyped *node;
+    OnyxToken *group;
+} OverloadReturnTypeCheck;
+
 void add_overload_option(bh_arr(OverloadOption)* poverloads, u64 precedence, AstTyped* overload);
 AstTyped* find_matching_overload_by_arguments(bh_arr(OverloadOption) overloads, Arguments* args);
 AstTyped* find_matching_overload_by_type(bh_arr(OverloadOption) overloads, Type* type);
 void report_unable_to_match_overload(AstCall* call, bh_arr(OverloadOption) overloads);
+void report_incorrect_overload_expected_type(Type *given, Type *expected, OnyxToken *overload, OnyxToken *group);
+void ensure_overload_returns_correct_type(AstTyped *overload, AstOverloadedFunction *group);
 
 void expand_macro(AstCall** pcall, AstFunction* template);
 AstFunction* macro_resolve_header(AstMacro* macro, Arguments* args, OnyxToken* callsite, b32 error_if_failed);
index c9420d466f88b1954c0db7bbffa6cc3acbecdcba..92d4a4385b5df2efcfaf7d70e314fe3eddf12c7f 100644 (file)
@@ -35,6 +35,7 @@ extern OnyxErrors msgs;
 void onyx_errors_init(bh_arr(bh_file_contents)* files);
 void onyx_errors_enable();
 void onyx_errors_disable();
+b32 onyx_errors_are_enabled();
 void onyx_submit_error(OnyxError error);
 void onyx_report_error(OnyxFilePos pos, OnyxErrorRank rank, char * format, ...);
 void onyx_submit_warning(OnyxError error);
index 755ae7faa6321111e8c4c86b882a19db707af1ee..22f27ff227f3ea351215f326666750c704f0ce04 100644 (file)
@@ -177,6 +177,7 @@ const char* entity_type_strings[Entity_Type_Count] = {
     "Struct Member Default",
     "Memory Reservation",
     "Expression",
+    "Job",
     "Global",
     "Overloaded_Function",
     "Function",
@@ -666,8 +667,12 @@ TypeMatch unify_node_and_type_(AstTyped** pnode, Type* type, b32 permanent) {
         if (func->kind == Ast_Kind_Function)
             func->flags |= Ast_Flag_Function_Used;
 
-        *pnode = func;
-        node = *pnode;
+        if (permanent) {
+            ensure_overload_returns_correct_type(func, (AstOverloadedFunction *) node);
+            *pnode = func;
+        }
+
+        node = func;
     }
 
     if (node->kind == Ast_Kind_Polymorphic_Proc) {
index 61685cb77276943a49d2299c4b100219d1719f66..b3d8a51ed458f537a1a1e36d7fea01fc5384d867 100644 (file)
@@ -576,7 +576,10 @@ static CheckStatus check_resolve_callee(AstCall* call, AstTyped** effective_call
     if (call->kind == Ast_Kind_Intrinsic_Call) return Check_Success;
 
     AstTyped* callee = (AstTyped *) strip_aliases((AstNode *) call->callee);
+    AstTyped* original_callee = callee;
+
     b32 calling_a_macro = 0;
+    b32 need_to_check_overload_return_type = 0;
 
     if (callee->kind == Ast_Kind_Overloaded_Function) {
         AstTyped* new_callee = find_matching_overload_by_arguments(
@@ -592,6 +595,8 @@ static CheckStatus check_resolve_callee(AstCall* call, AstTyped** effective_call
             YIELD(call->token->pos, "Waiting for overloaded function option to pass type-checking.");
         }
 
+        need_to_check_overload_return_type = 1;
+
         callee = new_callee;
     }
 
@@ -633,6 +638,10 @@ static CheckStatus check_resolve_callee(AstCall* call, AstTyped** effective_call
                 callee->token->text, callee->token->length);
     }
 
+    if (need_to_check_overload_return_type) {
+        ensure_overload_returns_correct_type(callee, (AstOverloadedFunction *) original_callee);
+    }
+
     *effective_callee = callee;
     return Check_Success;
 }
@@ -2421,12 +2430,12 @@ CheckStatus check_function(AstFunction* func) {
     return Check_Success;
 }
 
-CheckStatus check_overloaded_function(AstOverloadedFunction* func) {
+CheckStatus check_overloaded_function(AstOverloadedFunction* ofunc) {
     b32 done = 1;
 
     bh_imap all_overloads;
     bh_imap_init(&all_overloads, global_heap_allocator, 4);
-    build_all_overload_options(func->overloads, &all_overloads);
+    build_all_overload_options(ofunc->overloads, &all_overloads);
 
     bh_arr_each(bh__imap_entry, entry, all_overloads.entries) {
         AstTyped* node = (AstTyped *) entry->key;
@@ -2451,10 +2460,39 @@ CheckStatus check_overloaded_function(AstOverloadedFunction* func) {
         }
     }
 
-    bh_imap_free(&all_overloads);
+    if (!done) {
+        bh_imap_free(&all_overloads);
+        YIELD(ofunc->token->pos, "Waiting for all options to pass type-checking.");
+    }
+
+    if (ofunc->expected_return_node) {
+        ofunc->expected_return_type = type_build_from_ast(context.ast_alloc, ofunc->expected_return_node);
+        if (!ofunc->expected_return_type) YIELD(ofunc->token->pos, "Waiting to construct expected return type.");
 
-    if (done) return Check_Success;
-    else      YIELD(func->token->pos, "Waiting for all options to pass type-checking.");
+        bh_arr_each(bh__imap_entry, entry, all_overloads.entries) {
+            AstTyped* node = (AstTyped *) entry->key;
+
+            if (node->kind == Ast_Kind_Function) {
+                AstFunction *func = (AstFunction *) node;
+
+                if (!func->type) continue;
+                if (!func->type->Function.return_type) continue;
+
+                Type *return_type = func->type->Function.return_type;
+                if (return_type == &type_auto_return) continue;
+
+                if (!types_are_compatible(return_type, ofunc->expected_return_type)) {
+                    report_incorrect_overload_expected_type(return_type, ofunc->expected_return_type, func->token, ofunc->token);
+                    bh_imap_free(&all_overloads);
+                    return Check_Error;
+                }
+            }
+        }
+    }
+    
+
+    bh_imap_free(&all_overloads);
+    return Check_Success;
 }
 
 CheckStatus check_struct(AstStructType* s_node) {
@@ -3287,6 +3325,18 @@ poly_query_done:
     return Check_Complete;
 }
 
+CheckStatus check_arbitrary_job(EntityJobData *job) {
+    TypeMatch result = job->func(job->job_data);
+
+    switch (result) {
+        case TYPE_MATCH_SUCCESS: return Check_Complete;
+        case TYPE_MATCH_FAILED:  return Check_Error;
+        case TYPE_MATCH_YIELD:   return Check_Yield_Macro;
+    }
+
+    return Check_Error;
+}
+
 void check_entity(Entity* ent) {
     CheckStatus cs = Check_Success;
 
@@ -3325,6 +3375,8 @@ void check_entity(Entity* ent) {
             }
             break;
 
+        case Entity_Type_Job: cs = check_arbitrary_job(ent->job_data); break;
+
         default: break;
     }
 
index 0ceb2f9286b5eb8fdd34bdc11f1379493aa40264..f679db1f41b201f41ed108b34d334c5cced7d19f 100644 (file)
@@ -146,6 +146,19 @@ void entity_change_type(EntityHeap* entities, Entity *ent, EntityType new_type)
     ent->type = new_type;
 }
 
+void entity_heap_add_job(EntityHeap *entities, TypeMatch (*func)(void *), void *job_data) {
+    EntityJobData *job = bh_alloc(global_heap_allocator, sizeof(*job));
+    job->func = func;
+    job->job_data = job_data;
+    
+    Entity ent;
+    ent.type = Entity_Type_Job;
+    ent.state = Entity_State_Check_Types;
+    ent.job_data = job;
+
+    entity_heap_insert(entities, ent);
+}
+
 // NOTE(Brendan Hansen): Uses the entity heap in the context structure
 void add_entities_for_node(bh_arr(Entity *) *target_arr, AstNode* node, Scope* scope, Package* package) {
 #define ENTITY_INSERT(_ent)                                     \
index 35731588b14e9894e82a9026ac67ec2d8fa0a046..70180f35962d87725e4313e216c6e85d5c29898e 100644 (file)
@@ -98,6 +98,10 @@ void onyx_errors_disable() {
     errors_enabled = 0;
 }
 
+b32 onyx_errors_are_enabled() {
+    return errors_enabled;
+}
+
 b32 onyx_has_errors() {
     bh_arr_each(OnyxError, err, errors.errors) {
         if (err->rank >= Error_Waiting_On) return 1;
index 93f363caba4add01b1539a62952e51cae9ddc134..ba93e0a401ca270ab9c1d89daf83d6e2739bb452 100644 (file)
@@ -746,7 +746,17 @@ static AstTyped* parse_factor(OnyxParser* parser) {
             else if (parse_possible_directive(parser, "unquote")) {
                 AstDirectiveInsert* insert = make_node(AstDirectiveInsert, Ast_Kind_Directive_Insert);
                 insert->token = parser->curr - 1;
+
+                // Parsing calls is disabled here for the potential future feature
+                // of using a call-like syntax for passing "parameters" to inserted
+                // code blocks. Something like `#unquote foo(x, y)`. This would require
+                // different parsing than the normal call so it would just be detected
+                // here manually. Also, it does not hurt having this here because there
+                // is currently no way to dynamically get a code block to insert from
+                // a call, because it is impossible to "return" a code block.
+                parser->parse_calls = 0;
                 insert->code_expr = parse_expression(parser, 0);
+                parser->parse_calls = 1;
 
                 retval = (AstTyped *) insert;
                 break;
@@ -2408,11 +2418,9 @@ static AstOverloadedFunction* parse_overloaded_function(OnyxParser* parser, Onyx
 
     // This could be checked elsewhere?
     if (locked && local) {
-        onyx_report_error(token->pos, Error_Critical, "Only one of '#locked' and '#local' can because use at a time.");
+        onyx_report_error(token->pos, Error_Critical, "Only one of '#locked' and '#local' can be use at a time.");
     }
 
-    expect_token(parser, '{');
-
     AstOverloadedFunction* ofunc = make_node(AstOverloadedFunction, Ast_Kind_Overloaded_Function);
     ofunc->token = token;
     ofunc->flags |= Ast_Flag_Comptime;
@@ -2421,6 +2429,14 @@ static AstOverloadedFunction* parse_overloaded_function(OnyxParser* parser, Onyx
 
     bh_arr_new(global_heap_allocator, ofunc->overloads, 4);
 
+    if (peek_token(0)->type == Token_Type_Right_Arrow) {
+        expect_token(parser, Token_Type_Right_Arrow);
+
+        ofunc->expected_return_node = parse_type(parser);
+    }
+
+    expect_token(parser, '{');
+
     u64 precedence = 0;
     while (!consume_token_if_next(parser, '}')) {
         if (parser->hit_unexpected_token) return ofunc;
index ea997211ada2e1bef04aaf2bc3e359964a4f5090..38e848953fe276558353ec41d8e1001282a5ad26 100644 (file)
@@ -1203,6 +1203,11 @@ static SymresStatus symres_overloaded_function(AstOverloadedFunction* ofunc) {
     bh_arr_each(OverloadOption, overload, ofunc->overloads) {
         SYMRES(expression, &overload->option);
     }
+
+    if (ofunc->expected_return_node) {
+        SYMRES(type, &ofunc->expected_return_node);
+    }
+
     return Symres_Success;
 }
 
index 53f0a12210c6c4769875a4c1ea9d0d7cd9a881bf..61b476775c2fa93d6caadcb35bbbc57c50c6f640 100644 (file)
@@ -580,6 +580,73 @@ void report_unable_to_match_overload(AstCall* call, bh_arr(OverloadOption) overl
     bh_imap_free(&all_overloads);
 }
 
+void report_incorrect_overload_expected_type(Type *given, Type *expected, OnyxToken *overload, OnyxToken *group) {
+    onyx_report_error(overload->pos, Error_Critical,
+            "Expected this overload option to return '%s', but instead it returns '%s'.",
+            type_get_name(expected), type_get_name(given));
+
+    onyx_report_error(group->pos, Error_Critical, "Here is where the overloaded function was defined.");
+}
+
+static TypeMatch ensure_overload_returns_correct_type_job(void *raw_data) {
+    OverloadReturnTypeCheck *data = raw_data;
+    Type *expected_type = data->expected_type;
+    AstTyped *node      = data->node;
+
+    assert(expected_type && node);
+    
+    // If the entity on the node has been completed and unused,
+    // skip checking this because the function is likely not used.
+    if (node->entity && node->entity->state >= Entity_State_Finalized) {
+        return TYPE_MATCH_SUCCESS;
+    }
+
+    // HACK: This case should go away, but there were issues with some overloads
+    // not ever completing there auto return type resolution, likely because they
+    // were not actually used. This creates a problem here because this code
+    // will still wait for them. As a cheap solution, if there is a cycle detected,
+    // return success, even if the types may not match.
+    if (context.cycle_almost_detected > 0) {
+        return TYPE_MATCH_SUCCESS;
+    }
+
+    AstFunction *func = (AstFunction *) node;
+    if (func->kind == Ast_Kind_Macro) {
+        func = (AstFunction *) ((AstMacro *) func)->body;
+    }
+
+    if (!func->type) return TYPE_MATCH_YIELD;
+    if (!func->type->Function.return_type) return TYPE_MATCH_YIELD;
+
+    Type *return_type = func->type->Function.return_type;
+    if (return_type == &type_auto_return) return TYPE_MATCH_YIELD;
+
+    if (!types_are_compatible(return_type, expected_type)) {
+        report_incorrect_overload_expected_type(return_type, expected_type, func->token, data->group);
+        return TYPE_MATCH_FAILED;
+    }
+
+    return TYPE_MATCH_SUCCESS;
+}
+
+void ensure_overload_returns_correct_type(AstTyped *overload, AstOverloadedFunction *group) {
+    // This might not be entirely right as the type might not have been constructed yet, I think?
+    //
+    // Also, as a HACK, this does not check for the correct return type when errors are disabled.
+    // Errors are only disabled when doing something non-permantent, like checking an interface
+    // constraint, so this is a cheap way to tell if that is where we are coming from.
+    //
+    if (group->expected_return_type && onyx_errors_are_enabled()) {
+        OverloadReturnTypeCheck *data = bh_alloc_item(context.ast_alloc, OverloadReturnTypeCheck);
+        data->expected_type = group->expected_return_type;
+        data->node = overload;
+        data->group = group->token;
+
+        entity_heap_add_job(&context.entities, ensure_overload_returns_correct_type_job, data);
+    }
+}
+
+
 
 //
 // Macros
@@ -1254,4 +1321,4 @@ void track_declaration_for_tags(AstNode *node) {
     if (context.options->generate_tag_file) {
         bh_arr_push(context.tag_locations, node);
     }
-}
\ No newline at end of file
+}
index 2c43fd5c22737f6a4d27bb9c0d3a4656782eb1a1..caaee215e454391a8a268deceb00f116180e8ab3 100644 (file)
@@ -182,17 +182,17 @@ get_freed_size :: () => {
             // assert(hb_ptr.size & Allocated_Flag == Allocated_Flag, "Corrupted heap on free. This could be due to a double free, or using memory past were you allocated it.");
 
             if cast(uintptr) hb_ptr < cast(uintptr) __heap_start {
-                log("FREEING STATIC DATA");
+                log(.Error, "Core", "FREEING STATIC DATA");
                 return;
             }
 
             if hb_ptr.size & Allocated_Flag != Allocated_Flag {
-                log("INVALID DOUBLE FREE");
+                log(.Error, "Core", "INVALID DOUBLE FREE");
                 return;
             }
 
             if hb_ptr.magic_number != Alloc_Block_Magic_Number {
-                log("FREEING INVALID BLOCK");
+                log(.Error, "Core", "FREEING INVALID BLOCK");
                 return;
             }
         }
index 95ee4f2cbc50492a1e34300d1963cc3ae97bd10d..9ab6333f5aae22eba5fd5ba2cabad6605c6903a7 100644 (file)
@@ -1,6 +1,6 @@
 package core.hash
 
-to_u32 :: #match {
+to_u32 :: #match -> u32 {
     // Does this need to have a higher precedence value?
     // Because if I wanted to have a custom type as the key
     // of a map that only looks at some of the members of the
index bb19ac63b0b1bfe059edfa0ba69a7e5d8b8fb604..685282e2c254fd7f7bf5c99e5351b4d88e0c30c6 100644 (file)
@@ -3,7 +3,7 @@ package core.string
 use core
 
 #doc "Generic procedure for turning something into a string."
-as_str :: #match {}
+as_str :: #match -> str {}
 
 #local HasAsStrMethod :: interface (t: $T) {
     { T.as_str(t) } -> str;
index 2ca2809b1033ad5bfdfca0e08db72fee96197df9..1176007ce9bf9c959f49aeff19a9e93f85dac454 100644 (file)
--- a/docs/todo
+++ b/docs/todo
@@ -233,4 +233,40 @@ Making a proper "linkage" phase of the compiler:  :ProperLinking
         - The stack
         - The data section
         - The stack size
-        - The memory constraints (in pages)
\ No newline at end of file
+        - The memory constraints (in pages)
+
+Add mandatory return type for a matched group.
+    [x] Parse the syntax
+        - `#match -> u32`
+        - `#match #local -> u32 {}`
+    [x] When the return type of an overload is definitely known,
+        check it immediately.
+    [x] Otherwise, when the return type is known, through polymorph
+        substitution or auto return evaluation, then check the return
+        type is correctly.
+    [ ] This should have the same rules as the interface
+        return type matching, meaning a polymorphic structure can match an
+        instance of that structure. For example,
+        `#match -> Iterator { x => iter.comp(x, #(it)) }`
+
+Parameterized Code Blocks:
+    As code blocks are being used more and more as an alternative to closures
+    or lambdas, I'm seeing the possibility for more confusion and less readability
+    in code that heavily uses them. In order to make things a little clearer,
+    code blocks are now going to be able to take "parameters" that allow you
+    to explicitly give a name to the important symbol(s) in a code block.
+
+    [ ] Add parsing for this feature
+        - #(...)       Code block with no parameters
+        - #|x|(...)    Code block with one parameter
+        - #|x, y|(...) Code block with two parameters
+
+        - #quote |x| {...}
+        - #quote |x, y| {...}
+        
+        - #unquote code
+        - #unquote code(x)
+        - #unquote code(x, y)
+
+
+