Skip to content

Commit

Permalink
top level module and it's syntax rule
Browse files Browse the repository at this point in the history
  • Loading branch information
butterunderflow committed Feb 5, 2024
1 parent 5cdf77c commit 3e30932
Show file tree
Hide file tree
Showing 4 changed files with 47 additions and 12 deletions.
3 changes: 3 additions & 0 deletions lib/syntax/lexer.mll
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,9 @@ rule token = parse
| "rec" { REC }
| "type" { TYPE }
| "end" { END }
| "module" { MODULE }
| "struct" { STRUCT }
| "sig" { SIG }
| "=" { EQ }
| "|" { OR }
| '(' { LPAREN }
Expand Down
10 changes: 7 additions & 3 deletions lib/syntax/parser.mly
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,9 @@
%token LET
%token REC
%token END
%token MODULE
%token SIG
%token STRUCT
%token <string> IDENT
%token <string> MIDENT
%token <string> TYPEVAR
Expand Down Expand Up @@ -53,9 +56,10 @@ top_levels:
rest=top_levels
{ Top_type (n, tvs, vs) :: rest }
| LET p=pattern EQ e=expr rest=top_levels { Top_let (p, e) :: rest }
| LET REC funcs=separated_list(AND, function_bind)
rest=top_levels
{ Top_letrec funcs :: rest }
| LET REC funcs=separated_list(AND, function_bind) rest=top_levels
{ Top_letrec funcs :: rest }
| MODULE m_name=MIDENT EQ STRUCT m_body=top_levels END rest=top_levels
{ Top_mod (m_name, m_body) :: rest };

pattern:
| n=IDENT { PVar n }
Expand Down
14 changes: 10 additions & 4 deletions lib/syntax/parsetree.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,18 +34,24 @@ type variant = string * type_expr list [@@deriving sexp]

type type_paras = string list [@@deriving sexp]

type functor_paras = string list [@@deriving sexp]

type top_level =
| Top_let of pattern * expr
| Top_letrec of (string * paras * expr) list
| Top_type of string * type_paras * variant list
| Top_mod of string * mod_body
| Top_modrec of (string * functor_paras * mod_body * path) list
[@@deriving sexp]

type mod_body = top_level list [@@deriving sexp]

type program = top_level list [@@deriving sexp]
and mod_body = top_level list [@@deriving sexp]

type path =
and path =
| PName of string
| PMem of path * string
| PApply of path * path
[@@deriving sexp]


type program = top_level list [@@deriving sexp]

32 changes: 27 additions & 5 deletions lib/test/parse_test.ml
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ let print_parsed_path str =
let print_parsed_type_expr str =
parse_string_type_expr str |> sexp_of_type_expr |> print_sexp


let%expect_test "Test: full program parsing" =
print_parsed_program {|let x = 1|};
[%expect {|
Expand All @@ -31,21 +30,22 @@ let%expect_test "Test: full program parsing" =
(Top_letrec ((foo ((PBare x)) (EApp (EVar foo) (EVar x)))))) |}];
print_parsed_program {|let rec f (x:int) = 1|};
[%expect
{| ((Top_letrec ((f ((PAnn x (TCons int ()))) (EConst (CInt 1)))))) |}]
{| ((Top_letrec ((f ((PAnn x (TCons int ()))) (EConst (CInt 1)))))) |}]

let%expect_test "Test: path parsing" =
let%expect_test "Test: path parsing" =
print_parsed_path {|X|};
[%expect {| (PName X) |}];
print_parsed_path {|X.Y|};
[%expect {| (PMem (PName X) Y) |}];
print_parsed_path {|X(Y)|};
[%expect {| (PApply (PName X) (PName Y)) |}];
print_parsed_path {|X.Y(Z(N))(W.M.N)|};
[%expect {|
[%expect
{|
(PApply (PApply (PMem (PName X) Y) (PApply (PName Z) (PName N)))
(PMem (PMem (PName W) M) N)) |}]

let%expect_test "Test: type expression parsing" =
let%expect_test "Test: type expression parsing" =
print_parsed_type_expr "string";
[%expect {| (TCons string ()) |}];
print_parsed_type_expr "(string) list";
Expand All @@ -57,3 +57,25 @@ let%expect_test "Test: type expression parsing" =
print_parsed_type_expr "(string, 'x, 'y) list";
[%expect {| (TCons list ((TCons string ()) (TVar 'x) (TVar 'y))) |}]

let%expect_test "Test: top level module" =
print_parsed_program
{|
module X = struct
end
|};
[%expect {|
((Top_mod X ())) |}];
print_parsed_program
{|
module X = struct
let x = 1
let rec y = 3
module Y = struct
end
end
|};
[%expect {|
((Top_mod X
((Top_let (PVar x) (EConst (CInt 1)))
(Top_letrec ((y () (EConst (CInt 3))))) (Top_mod Y ())))) |}]

0 comments on commit 3e30932

Please sign in to comment.