Skip to content

Commit

Permalink
"9:15am. Last night there were thunderbolts shooting all throughout.
Browse files Browse the repository at this point in the history
9:20am. I had some time to think about what I want to do next. I know I said control flow analysis for editor support, but I do not feel like doing that after all. That sort of thing is very auxiliary and I should just leave it for later. Nobody is going to skip over on Spiral because I do not have that.

What I need to do is this in the following order: prepass, partial eval, codegen, typechecking (without constraints). Once I have that, I have something quite usable as a language even if it would be incomplete.

9:25am. I've decided, once I've done the above I am going to start negotiation to procure those chips. I want to do something real while I work on the language on the side much like in 2018.

9:45am. There some internet troubles recently, so I've been delayed by that.

9:50am. I do not feel like starting right away. I still want to dwell on it a little.

Yesterday I did that as well, but did follow through in the end and completed the sematic highlighting for the language. That was great.

Right now, what I need to do is just find the courage and the will to start work on the prepass. I need to break the ice there. Compiling mutually recursive blocks will take some consideration and effort. But once I am done, I should be in the clear to deal with the partial evaluator.

10am. Agh, prepass. Agh, partial evaluator. I went through this so many times before, I can't believe I am going to go through it again. But I have to.

10:05am. Ok, before I start let me do some things to simplify the parser.

I am going to get rid of the PatOperator. If I think about it, there is no reason why (+) should not be a valid name anywhere.

And apart from that, there is something I want to do.

10:10am. Ok, I got rid of that `PatOperator` error. The next thing is the way I do functions.

```fs
    | RawInl of (Pattern * RawExpr) list
    | RawForall of VarString * RawKindExpr * RawExpr
```

I've been thinking yesterday and came to the conclussion that this should be like...

10:15am.

```fs
and RawExpr =
    | RawB
    | RawV of VarString
    | RawLit of Literal
    | RawDefaultLit of string
    | RawSymbolCreate of SymbolString
    | RawType of RawTExpr
    | RawInline of RawExpr // Acts as a join point for the prepass specifically.
    | RawLet of Pattern * body: RawExpr * on_succ: RawExpr
    | RawMatch of body: RawExpr * (Pattern * RawExpr) list
    | RawFun of (VarString * RawKindExpr) list * Pattern list * (Pattern * RawExpr) list
    | RawRecBlock of (VarString * RawExpr) list * on_succ: RawExpr // The bodies of a block must be RawFun
    | RawRecordWith of RawExpr list * RawRecordWith list * RawRecordWithout list
    | RawOp of Op * RawExpr []
    | RawJoinPoint of RawExpr
    | RawAnnot of RawExpr * RawTExpr
    | RawTypecase of RawTExpr * (RawTExpr * RawExpr) list
    | RawModuleOpen of VarString * SymbolString list * on_succ: RawExpr
```

Actualyl I am still not sure. I reallized while I was writing this just now that I do not want both RawFun and RawFunction, but now I have this mess here.

Maybe I should decompose RawFunction into plan RawFun and RawMatch.

10:20am.

```fs
and RawExpr =
    | RawB
    | RawV of VarString
    | RawLit of Literal
    | RawDefaultLit of string
    | RawSymbolCreate of SymbolString
    | RawType of RawTExpr
    | RawInline of RawExpr // Acts as a join point for the prepass specifically.
    | RawMatch of body: RawExpr * (Pattern * RawExpr) list
    | RawFun of (VarString * RawKindExpr) list * Pattern list * RawExpr
    | RawRecBlock of (VarString * RawExpr) list * on_succ: RawExpr // The bodies of a block must be RawFun
    | RawRecordWith of RawExpr list * RawRecordWith list * RawRecordWithout list
    | RawOp of Op * RawExpr []
    | RawJoinPoint of RawExpr
    | RawAnnot of RawExpr * RawTExpr
    | RawTypecase of RawTExpr * (RawTExpr * RawExpr) list
    | RawModuleOpen of VarString * SymbolString list * on_succ: RawExpr
```

Let me do it like this. This is enough in terms of primitives.

The reason what I want to fuse RawInl and RawFun into one is because during typechecking I want one place where the typechecker will put in new foralls and constraints. The most sensible thing is to select `RawFun` as nodes for that. I can easily separate them into individual foralls and inls in a later stage after that.

Also, for patterns, I want to do some extra validation.

10:25am. Ok, let me get this out of the way.

10:30am. No, I am not sure I feel like it.

```
| RawFun of (VarString * RawKindExpr) list * Pattern list * RawExpr
```

If I have this, then the first two of these might turn out to be empty which will end up similar to `RawInline`.

I can't deal with this.

In the typechecker, I think I'll just fuse the `RawForalls` and `RawInl` into a single node on my own.

Ok, then, validation.

```fs
    loop pat |> ignore
    errors.ToArray()
```

For this to work, I need to return the errors and pat as they are.

```fs
let pattern_validate (errors : PatternCompilationErrors -> unit) pat =
    let rec loop pat =
        match pat with
        | PatDefaultValue _ | PatValue _ | PatSymbol _ | PatE | PatB -> Set.empty
        | PatVar x -> Set.singleton x
        | PatDyn p | PatAnnot (p,_) | PatNominal(_,p) | PatActive (_,p) | PatUnbox p | PatWhen(p, _) -> loop p
        | PatRecordMembers items ->
            let symbols = Collections.Generic.HashSet()
            let injects = Collections.Generic.HashSet()
            let x =
                List.map (fun item ->
                    match item with
                    | PatRecordMembersSymbol(keyword,name) ->
                        if symbols.Add(keyword) = false then errors (DuplicateRecordSymbol keyword); Set.empty else loop name
                    | PatRecordMembersInjectVar(var,name) ->
                        if injects.Add(var) = false then errors (DuplicateRecordInjection var); Set.empty else loop name
                    ) items
            match x with _ :: _ :: _ -> Set.intersectMany x |> Set.iter (DuplicateVar >> errors) | _ -> ()
            Set.unionMany x
        | PatPair(a,b) | PatAnd(a,b) ->
            let a, b = loop a, loop b
            Set.intersect a b |> Set.iter (DuplicateVar >> errors)
            a + b
        | PatOr(a,b) -> let a, b = loop a, loop b in if a = b then a else errors DisjointOrPattern; a
    loop pat
```

Let me just pass in a function into this.

```fs
let patterns_validate pats =
    let errors = ResizeArray()
    match List.map (fun (r,x) -> r, pattern_validate (fun x -> errors.Add(r,x)) x) pats with
    | (_,x) :: y -> List.fold (fun x (r,y) -> Set.intersect x y |> Set.iter (fun x -> errors.Add(r,DuplicateVar x)); y) x y |> ignore
    | _ -> ()
    errors.ToArray()
```

Here, now patterns should be validated across.

10:50am.

```fs
let patterns_validate pats =
    let errors' = ResizeArray()
    let l =
        List.map (fun (r,x) ->
            let errors = ResizeArray()
            let ret = r, pattern_validate errors.Add x
            errors'.Add(r,InvalidPattern(errors.ToArray()))
            ret
            ) pats
    match l with
    | (_,x) :: y ->
        List.fold (fun x (r,y) ->
            Set.intersect x y
            |> Set.iter (fun x ->
                errors'.Add(r,ShadowedVar x))
                y
                ) x y
        |> ignore
    | _ -> ()
```

No, I got it wrong, but now I am drowning in this.

Let me do it from the top again.

```fs
let patterns_validate pats =
    let l = List.map (fun (r,x) -> let errors = ResizeArray() in r, pattern_validate errors.Add x, errors) pats
    match l with
    | (_,x,_) :: y -> y |> List.fold (fun x (_,y,errors) -> Set.intersect x y |> Set.iter (fun x -> errors.Add(ShadowedVar x)); y) x |> ignore
    | _ -> ()
    l |> List.map (fun (r,_,errors) -> r, InvalidPattern(errors.ToArray()))
```

Ok, this is much better.

```fs
        | _, (_, PatVar _), _, _ ->
            match patterns_validate (if is_rec then name :: pats else pats) with
```

I'll add the name to this. Now if I write something like...

```
inl rec f f = ...
```

I should get an error that the variable is shadowed. Though Spiral allows shadowing, in this case it should definitely be an error.

Let me try it out.

```fs
Server bound to: tcp://*:13805
Unhandled exception: System.ArgumentOutOfRangeException: Specified argument was out of the range of valid values. (Parameter 'index')
   at System.Char.IsUpper(String s, Int32 index)
   at Spiral.Tokenize.process_error@284.Invoke(String x) in C:\Users\Marko\Source\Repos\The Spiral Language\The Spiral Language v0.2 (typechecking)\Tokenize.fs:line 284
```

Am getting this exception now.

11:05am. This is strange. Why am I getting an error here?

```fs
Server bound to: tcp://*:13805
[|[]; []; []; []|]
```

These are the ers here.

They are all just empty...

I have no idea. Let me commit here and I'll revert to a previous commit for a bit.

I need to figure out what change was responsible for this."
  • Loading branch information
mrakgr committed Jul 25, 2020
1 parent 4923f93 commit e4a4a24
Show file tree
Hide file tree
Showing 2 changed files with 21 additions and 20 deletions.
39 changes: 20 additions & 19 deletions The Spiral Language v0.2 (typechecking)/BlockParsing.fs
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ type Env = {

type PatternCompilationErrors =
| DisjointOrPattern
| InvalidOp of string
| DuplicateVar of string
| ShadowedVar of string
| DuplicateRecordSymbol of string
| DuplicateRecordInjection of string

Expand Down Expand Up @@ -293,7 +293,6 @@ and Pattern =
| PatB
| PatE
| PatVar of VarString
| PatOperator of VarString // Isn't actually a pattern. Is just here to help the inl/let statement parser.
| PatDyn of Pattern
| PatUnbox of Pattern
| PatAnnot of Pattern * RawTExpr
Expand Down Expand Up @@ -364,11 +363,9 @@ let inline indent i op next d = if op i (col d) then next d else Error []

let record_var d = (read_var <|> rounds read_op) d

let pattern_validate pat =
let errors = ResizeArray()
let pattern_validate (errors : PatternCompilationErrors -> unit) pat =
let rec loop pat =
match pat with
| PatOperator x -> errors.Add(InvalidOp x); Set.empty
| PatDefaultValue _ | PatValue _ | PatSymbol _ | PatE | PatB -> Set.empty
| PatVar x -> Set.singleton x
| PatDyn p | PatAnnot (p,_) | PatNominal(_,p) | PatActive (_,p) | PatUnbox p | PatWhen(p, _) -> loop p
Expand All @@ -379,21 +376,25 @@ let pattern_validate pat =
List.map (fun item ->
match item with
| PatRecordMembersSymbol(keyword,name) ->
if symbols.Add(keyword) = false then errors.Add(DuplicateRecordSymbol keyword); Set.empty else loop name
if symbols.Add(keyword) = false then errors (DuplicateRecordSymbol keyword); Set.empty else loop name
| PatRecordMembersInjectVar(var,name) ->
if injects.Add(var) = false then errors.Add(DuplicateRecordInjection var); Set.empty else loop name
if injects.Add(var) = false then errors (DuplicateRecordInjection var); Set.empty else loop name
) items
match x with _ :: _ :: _ -> Set.intersectMany x |> Set.iter (DuplicateVar >> errors.Add) | _ -> ()
match x with _ :: _ :: _ -> Set.intersectMany x |> Set.iter (DuplicateVar >> errors) | _ -> ()
Set.unionMany x
| PatPair(a,b) | PatAnd(a,b) ->
let a, b = loop a, loop b
Set.intersect a b |> Set.iter (DuplicateVar >> errors.Add)
Set.intersect a b |> Set.iter (DuplicateVar >> errors)
a + b
| PatOr(a,b) -> let a, b = loop a, loop b in if a = b then a else errors.Add(DisjointOrPattern); a
loop pat |> ignore
errors.ToArray()
| PatOr(a,b) -> let a, b = loop a, loop b in if a = b then a else errors DisjointOrPattern; a
loop pat

let patterns_validate pats = List.choose (fun (r,x) -> let x = pattern_validate x in if 0 < x.Length then Some (r, InvalidPattern x) else None) pats
let patterns_validate pats =
let l = List.map (fun (r,x) -> let errors = ResizeArray() in r, pattern_validate errors.Add x, errors) pats
match l with
| (_,x,_) :: y -> y |> List.fold (fun x (_,y,errors) -> Set.intersect x y |> Set.iter (fun x -> errors.Add(ShadowedVar x)); y) x |> ignore
| _ -> ()
l |> List.map (fun (r,_,errors) -> r, InvalidPattern(errors.ToArray()))

let inl_or_let_process (r, (is_let, is_rec, name, foralls, pats, body)) _ =
match body with
Expand All @@ -406,8 +407,8 @@ let inl_or_let_process (r, (is_let, is_rec, name, foralls, pats, body)) _ =
| _ -> name, pats
let dyn_if_let x = if is_let then x else PatDyn x
match is_rec, name, foralls, pats with
| _, (_, (PatVar _ | PatOperator _)), _, _ ->
match patterns_validate pats with
| _, (_, PatVar _), _, _ ->
match patterns_validate (if is_rec then name :: pats else pats) with
| [] ->
let body =
List.foldBack (fun (_,pat) body -> RawInl [dyn_if_let pat,body]) pats body
Expand Down Expand Up @@ -548,7 +549,7 @@ and root_pattern s =
let pat_symbol = read_symbol |>> PatSymbol
let pat_rounds = rounds (fun s ->
let (+) = alt (index s)
(root_pattern + (read_op |>> PatOperator) + (fun _ -> Ok PatB)) s)
(root_pattern + (read_op |>> PatVar) + (fun _ -> Ok PatB)) s)

let (+) = alt (index s)
(pat_rounds + pat_nominal + pat_wildcard + pat_dyn + pat_value + pat_record + pat_symbol + pat_active) s
Expand Down Expand Up @@ -806,7 +807,7 @@ and root_term d =
| x, xs ->
let l = x :: xs
let body = l |> List.map (function
| (_,(_,(PatVar name | PatOperator name)),body),true -> name, body
| (_,(_, PatVar name),body),true -> name, body
| _ -> failwith "Compiler error: Recursive inl/let statements should always have PatVar or PatOperator for names and should always be recursive."
)
Ok(fun on_succ -> RawRecBlock(body, on_succ))
Expand Down Expand Up @@ -853,8 +854,8 @@ type TopStatement =
| TopPrototypeInstance of prototype_name: VarString * nominal_name: VarString * nominal_foralls: ForallVars * RawExpr

let top_inl_or_let_process = function
| (_,(_,(PatVar name | PatOperator name)),(RawForall _ | RawInl _ as body)),_ -> Ok(TopInl(name, body))
| (r,(_,(PatVar _ | PatOperator _)),_),_ -> Error [r, ExpectedGlobalFunction]
| (_,(_,PatVar name),(RawForall _ | RawInl _ as body)),_ -> Ok(TopInl(name, body))
| (r,(_,PatVar _),_),_ -> Error [r, ExpectedGlobalFunction]
| (_,(r,_),_),_ -> Error [r, ExpectedVarOrOpAsNameOfGlobalStatement]
let top_inl_or_let = inl_or_let root_term root_pattern_pair >>= fun x _ -> top_inl_or_let_process x

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -65,8 +65,8 @@ let show_parser_error = function
| InvalidPattern l ->
let f = function
| DisjointOrPattern -> "All the branches of an or pattern have to have the same variables."
| InvalidOp x -> sprintf "Operator %s is allowed only in the first position of a statement as its name." x
| DuplicateVar x -> sprintf "Duplicate variable %s." x
| ShadowedVar x -> sprintf "Invalid shadowing of variable %s." x
| DuplicateRecordSymbol x -> sprintf "Duplicate record symbol %s." x
| DuplicateRecordInjection x -> sprintf "Duplicate record injection %s." x
let l = Array.map f (Array.distinct l)
Expand Down

0 comments on commit e4a4a24

Please sign in to comment.