yanais/ocaml/libsyntax/tagGroup.ml
2024-02-15 18:16:42 +01:00

32 lines
1.3 KiB
OCaml

open Tys
module FieldsReg = Map.Make(String)
(* a tag group, which has an underlying type, and a bunch of key-index pairs *)
type t = loc_span_full * Literal.int_size * (int FieldsReg.t)
let rev_lookup ival ((_, _, frg): t) =
FieldsReg.filter (fun nam -> fun x -> x == ival) frg |> FieldsReg.choose
let parse_opt ps =
let rec inner ps (osp, oisz, frg) = match ps.lt with
| (DotIdent nam, s)::(LLiteral Literal.LNatural nat, _)::(SemiColon, s3)::lt ->
let ps = { ps with lt; offset = loc_span_end s3; } in
(match FieldsReg.find_opt nam frg with
| None -> inner ps (osp, isz, FieldsReg.add nam nat frg)
| Some x -> Yanais_syntax_err (ERecordDupIdent nam, ps.file, s) |> raise)
| (Brace Close, s)::lt ->
let ps = { ps with lt; offset = loc_span_end s; } in
((osp, oisz, frg), ps)
| (k, s)::lt -> Yanais_syntax_err (EExpected XTagGroupItem, ps.file, s) |> raise
| [] -> Yanais_syntax_err (EUnexpectedEof XTagGroupItem, ps.file, osp) |> raise
match ps.lt with
| (KTagGroup, s1)::(LLiteral Literal.LIntSize isz, _)::(Brace Open, s3)::lt ->
let ps = { ps with lt; offset = loc_span_end s3; } in
let acc = ((ps.file, s1), isz, FieldsReg.empty) in
Some (inner ps acc)
| _ -> None
let parse ps = require XTagGroup parse_opt ps