2018-02-20 01:28:29 +03:00
(* Opening a library for generic programming ( https://github.com/dboulytchev/GT ) .
The library provides " @type ... " syntax extension and plugins like show , etc .
* )
2019-04-02 19:51:46 +03:00
module OrigList = List
2019-10-11 17:25:58 +03:00
2018-02-25 14:48:13 +03:00
open GT
(* Opening a library for combinator-based syntax analysis *)
2018-03-27 01:51:22 +03:00
open Ostap
open Combinators
2020-01-14 05:36:03 +03:00
module Subst =
struct
module H = Hashtbl . Make ( struct type t = string let hash = Hashtbl . hash let equal = ( = ) end )
let tab = ( H . create 1024 : string H . t )
let attach infix op = H . add tab infix op
let subst id = match H . find_opt tab id with None -> id | Some op -> op
end
2020-01-14 03:30:17 +03:00
let infix_name infix =
let b = Buffer . create 64 in
Buffer . add_string b " i__Infix_ " ;
Seq . iter ( fun c -> Buffer . add_string b ( string_of_int @@ Char . code c ) ) @@ String . to_seq infix ;
2020-01-14 05:36:03 +03:00
let s = Buffer . contents b in
Subst . attach s ( " operator " ^ infix ) ;
s
2020-01-14 03:30:17 +03:00
let sys_infix_name infix =
let b = Buffer . create 64 in
Buffer . add_string b " s__Infix_ " ;
Seq . iter ( fun c -> Buffer . add_string b ( string_of_int @@ Char . code c ) ) @@ String . to_seq infix ;
2020-01-14 05:36:03 +03:00
let s = Buffer . contents b in
Subst . attach s ( " operator " ^ infix ) ;
s
2018-04-25 01:06:18 +03:00
2019-03-25 00:13:42 +03:00
exception Semantic_error of string
2019-08-14 01:59:44 +03:00
2019-12-24 03:59:05 +03:00
module Loc =
struct
@ type t = int * int with show , html
2020-01-11 16:38:25 +03:00
module H = Hashtbl . Make ( struct type t = string let hash = Hashtbl . hash let equal = ( = = ) end )
let tab = ( H . create 1024 : t H . t )
let attach s loc = H . add tab s loc
let get = H . find_opt tab
2019-12-24 03:59:05 +03:00
end
2020-01-11 16:38:25 +03:00
let report_error ? ( loc = None ) str =
raise ( Semantic_error ( str ^ match loc with None -> " " | Some ( l , c ) -> Printf . sprintf " at (%d, %d) " l c ) )
2019-12-24 03:59:05 +03:00
2018-04-25 01:06:18 +03:00
(* Values *)
module Value =
struct
2019-10-05 00:16:50 +03:00
(* The type for name designation: global or local variable, argument, reference to closure, etc. *)
@ type designation =
| Global of string
| Local of int
| Arg of int
| Access of int
2019-10-11 17:25:58 +03:00
| Fun of string
2019-12-29 01:12:40 +03:00
with show , html
2019-10-05 00:16:50 +03:00
2019-09-24 01:12:04 +03:00
@ type ( ' a , ' b ) t =
2019-04-02 19:51:46 +03:00
| Empty
2019-10-05 00:16:50 +03:00
| Var of designation
2019-09-24 01:12:04 +03:00
| Elem of ( ' a , ' b ) t * int
2019-09-22 20:15:15 +03:00
| Int of int
| String of bytes
2019-09-24 01:12:04 +03:00
| Array of ( ' a , ' b ) t array
| Sexp of string * ( ' a , ' b ) t array
| Closure of string list * ' a * ' b
2019-10-11 17:25:58 +03:00
| FunRef of string * string list * ' a * int
2019-09-22 20:15:15 +03:00
| Builtin of string
2019-12-29 01:12:40 +03:00
with show , html
2018-04-25 01:06:18 +03:00
2019-08-14 01:59:44 +03:00
let to_int = function
| Int n -> n
2018-04-25 01:06:18 +03:00
| _ -> failwith " int value expected "
2019-08-14 01:59:44 +03:00
let to_string = function
| String s -> s
2018-04-25 01:06:18 +03:00
| _ -> failwith " string value expected "
let to_array = function
| Array a -> a
| _ -> failwith " array value expected "
2019-04-02 19:51:46 +03:00
let sexp s vs = Sexp ( s , Array . of_list vs )
2018-04-25 01:06:18 +03:00
let of_int n = Int n
let of_string s = String s
let of_array a = Array a
let tag_of = function
| Sexp ( t , _ ) -> t
| _ -> failwith " symbolic expression expected "
2019-08-14 01:59:44 +03:00
let update_string s i x = Bytes . set s i x ; s
2018-11-13 09:54:04 +03:00
let update_array a i x = a . ( i ) <- x ; a
2019-04-07 23:42:20 +03:00
let update_elem x i v =
match x with
| Sexp ( _ , a ) | Array a -> ignore ( update_array a i v )
| String a -> ignore ( update_string a i ( Char . chr @@ to_int v ) )
2019-08-14 01:59:44 +03:00
2018-10-31 20:10:50 +03:00
let string_val v =
let buf = Buffer . create 128 in
let append s = Buffer . add_string buf s in
let rec inner = function
| Int n -> append ( string_of_int n )
2018-11-13 09:54:04 +03:00
| String s -> append " \" " ; append @@ Bytes . to_string s ; append " \" "
| Array a -> let n = Array . length a in
append " [ " ; Array . iteri ( fun i a -> ( if i > 0 then append " , " ) ; inner a ) a ; append " ] "
2019-04-02 19:51:46 +03:00
| Sexp ( t , a ) -> let n = Array . length a in
2019-03-07 21:12:43 +03:00
if t = " cons "
then (
append " { " ;
let rec inner_list = function
2019-04-02 19:51:46 +03:00
| [| |] -> ()
| [| x ; Int 0 |] -> inner x
2019-08-14 01:59:44 +03:00
| [| x ; Sexp ( " cons " , a ) |] -> inner x ; append " , " ; inner_list a
2019-03-07 21:12:43 +03:00
in inner_list a ;
append " } "
)
else (
append t ;
2019-04-02 19:51:46 +03:00
( if n > 0 then ( append " ( " ; Array . iteri ( fun i a -> ( if i > 0 then append " , " ) ; inner a ) a ;
2019-03-07 21:12:43 +03:00
append " ) " ) )
)
2018-10-31 20:10:50 +03:00
in
inner v ;
2018-11-13 09:54:04 +03:00
Bytes . of_string @@ Buffer . contents buf
2019-08-14 01:59:44 +03:00
2018-04-25 01:06:18 +03:00
end
2019-08-14 01:59:44 +03:00
2019-09-22 20:15:15 +03:00
(* Builtins *)
module Builtin =
struct
2019-10-16 21:07:27 +03:00
let list = [ " read " ; " write " ; " .elem " ; " .length " ; " .array " ; " .stringval " ]
2019-09-22 20:15:15 +03:00
let bindings () = List . map ( fun name -> name , Value . Builtin name ) list
let names = List . map ( fun name -> name , false ) list
let eval ( st , i , o , vs ) args = function
| " read " -> ( match i with z :: i' -> ( st , i' , o , ( Value . of_int z ) :: vs ) | _ -> failwith " Unexpected end of input " )
| " write " -> ( st , i , o @ [ Value . to_int @@ List . hd args ] , Value . Empty :: vs )
| " .elem " -> let [ b ; j ] = args in
( st , i , o , let i = Value . to_int j in
( match b with
| Value . String s -> Value . of_int @@ Char . code ( Bytes . get s i )
| Value . Array a -> a . ( i )
| Value . Sexp ( _ , a ) -> a . ( i )
) :: vs
)
| " .length " -> ( st , i , o , ( Value . of_int ( match List . hd args with Value . Sexp ( _ , a ) | Value . Array a -> Array . length a | Value . String s -> Bytes . length s ) ) :: vs )
| " .array " -> ( st , i , o , ( Value . of_array @@ Array . of_list args ) :: vs )
| " .stringval " -> let [ a ] = args in ( st , i , o , ( Value . of_string @@ Value . string_val a ) :: vs )
end
2018-03-27 01:51:22 +03:00
(* States *)
module State =
struct
2019-08-14 01:59:44 +03:00
2018-03-27 01:51:22 +03:00
(* State: global state, local state, scope variables *)
2019-10-11 17:25:58 +03:00
@ type ' a t =
2019-09-22 20:15:15 +03:00
| I
2019-10-11 17:25:58 +03:00
| G of ( string * bool ) list * ( string , ' a ) arrow
| L of ( string * bool ) list * ( string , ' a ) arrow * ' a t
2019-12-23 21:05:57 +03:00
with show , html
2019-10-11 17:25:58 +03:00
(* Get the depth level of a state *)
let rec level = function
| I -> 0
| G _ -> 1
| L ( _ , _ , st ) -> 1 + level st
(* Prune state to a certain level *)
let prune st n =
let rec inner n st =
match st with
| I -> st , 0
| G ( xs , s ) -> st , 1
| L ( xs , s , st' ) ->
let st'' , l = inner n st' in
( if l > = n then st'' else st ) , l + 1
in
fst @@ inner n st
2018-05-01 03:37:29 +03:00
(* Undefined state *)
2020-01-14 03:30:17 +03:00
let undefined x =
2020-01-14 05:36:03 +03:00
report_error ~ loc : ( Loc . get x ) ( Printf . sprintf " undefined name \" %s \" " ( Subst . subst x ) )
2018-05-04 02:59:23 +03:00
2019-09-22 20:15:15 +03:00
(* Create a state from bindings list *)
2020-01-14 05:36:03 +03:00
let from_list l = fun x -> try List . assoc x l with Not_found -> report_error ~ loc : ( Loc . get x ) ( Printf . sprintf " undefined name \" %s \" " ( Subst . subst x ) )
2019-09-22 20:15:15 +03:00
2018-05-04 02:59:23 +03:00
(* Bind a variable to a value in a state *)
2019-08-14 01:59:44 +03:00
let bind x v s = fun y -> if x = y then v else s y
2018-05-04 02:59:23 +03:00
2019-09-22 20:15:15 +03:00
(* empty state *)
let empty = I
2018-03-27 01:51:22 +03:00
2019-09-22 20:15:15 +03:00
(* Scope operation: checks if a name is in a scope *)
let in_scope x s = List . exists ( fun ( y , _ ) -> y = x ) s
(* Scope operation: checks if a name designates variable *)
let is_var x s = try List . assoc x s with Not_found -> false
2019-08-14 01:59:44 +03:00
(* Update: non-destructively "modifies" the state s by binding the variable x
2018-03-27 01:51:22 +03:00
to value v and returns the new state w . r . t . a scope
* )
2020-01-14 03:30:17 +03:00
let update x v s =
2018-05-01 03:37:29 +03:00
let rec inner = function
2020-01-11 16:38:25 +03:00
| I -> report_error " uninitialized state "
2019-09-19 18:37:08 +03:00
| G ( scope , s ) ->
2019-09-22 20:15:15 +03:00
if is_var x scope
then G ( scope , bind x v s )
2020-01-14 05:36:03 +03:00
else report_error ~ loc : ( Loc . get x ) ( Printf . sprintf " name \" %s \" is undefined or does not designate a variable " ( Subst . subst x ) )
2018-05-01 03:37:29 +03:00
| L ( scope , s , enclosing ) ->
2019-09-22 20:15:15 +03:00
if in_scope x scope
then if is_var x scope
then L ( scope , bind x v s , enclosing )
2020-01-14 05:36:03 +03:00
else report_error ~ loc : ( Loc . get x ) ( Printf . sprintf " name \" %s \" does not designate a variable " ( Subst . subst x ) )
2019-09-22 20:15:15 +03:00
else L ( scope , s , inner enclosing )
2018-05-01 03:37:29 +03:00
in
2019-09-22 20:15:15 +03:00
inner s
2018-04-02 05:58:02 +03:00
2018-03-27 01:51:22 +03:00
(* Evals a variable in a state w.r.t. a scope *)
2018-05-01 03:37:29 +03:00
let rec eval s x =
match s with
2020-01-04 22:28:57 +03:00
| I -> report_error " uninitialized state "
2019-09-22 20:15:15 +03:00
| G ( _ , s ) -> s x
| L ( scope , s , enclosing ) -> if in_scope x scope then s x else eval enclosing x
2018-03-27 01:51:22 +03:00
(* Drops a scope *)
2018-05-02 22:36:27 +03:00
let leave st st' =
let rec get = function
2020-01-04 22:28:57 +03:00
| I -> report_error " uninitialized state "
2019-09-22 20:15:15 +03:00
| G _ as st -> st
2018-05-02 22:36:27 +03:00
| L ( _ , _ , e ) -> get e
in
let g = get st in
let rec recurse = function
2019-09-24 01:12:04 +03:00
| I -> g
2018-05-02 22:36:27 +03:00
| L ( scope , s , e ) -> L ( scope , s , recurse e )
| G _ -> g
in
recurse st'
2019-09-24 01:12:04 +03:00
(* Creates a new scope, based on a given state *)
let rec enter st xs =
match st with
2020-01-04 22:28:57 +03:00
| I -> report_error " uninitialized state "
2019-09-24 01:12:04 +03:00
| G _ -> L ( xs , undefined , st )
| L ( _ , _ , e ) -> enter e xs
2018-05-02 22:36:27 +03:00
(* Push a new local scope *)
2019-09-29 02:35:04 +03:00
let push st s xs =
match st with
| I -> G ( xs @ Builtin . names , List . fold_left ( fun s ( name , value ) -> bind name value s ) s ( Builtin . bindings () ) )
| _ -> L ( xs , s , st )
2018-03-27 01:51:22 +03:00
2018-05-02 22:36:27 +03:00
(* Drop a local scope *)
2019-09-29 02:35:04 +03:00
let drop = function L ( _ , _ , e ) -> e | G _ -> I
2019-08-14 01:59:44 +03:00
2019-09-22 20:15:15 +03:00
(* Observe a variable in a state and print it to stderr *)
let observe st x =
2019-09-24 01:12:04 +03:00
Printf . eprintf " %s=%s \n %! " x ( try show ( Value . t ) ( fun _ -> " <expr> " ) ( fun _ -> " <state> " ) @@ eval st x with _ -> " undefined " )
2019-09-22 20:15:15 +03:00
2018-04-25 01:06:18 +03:00
end
2019-04-02 19:51:46 +03:00
(* Patterns *)
module Pattern =
struct
(* The type for patterns *)
@ type t =
(* wildcard "-" *) | Wildcard
(* S-expression *) | Sexp of string * t list
(* array *) | Array of t list
(* identifier *) | Named of string * t
(* ground integer *) | Const of int
(* ground string *) | String of string
2019-08-14 01:59:44 +03:00
(* boxed value *) | Boxed
(* unboxed value *) | UnBoxed
2019-04-02 19:51:46 +03:00
(* any string value *) | StringTag
(* any sexp value *) | SexpTag
(* any array value *) | ArrayTag
2019-09-25 00:25:40 +03:00
(* any closure *) | ClosureTag
2019-10-11 17:25:58 +03:00
with show , foldl , html
2019-04-02 19:51:46 +03:00
2019-08-14 01:59:44 +03:00
(* Pattern parser *)
2019-04-02 19:51:46 +03:00
ostap (
2019-08-14 01:59:44 +03:00
parse :
! ( Ostap . Util . expr
2019-04-02 19:51:46 +03:00
( fun x -> x )
( Array . map ( fun ( a , s ) ->
2019-08-14 01:59:44 +03:00
a ,
List . map ( fun s -> ostap ( - $ ( s ) ) , ( fun x y -> Sexp ( " cons " , [ x ; y ] ) ) ) s )
[| ` Righta , [ " : " ] |]
2019-04-02 19:51:46 +03:00
)
2019-08-14 01:59:44 +03:00
primary ) ;
2019-04-02 19:51:46 +03:00
primary :
% " _ " { Wildcard }
| t : UIDENT ps : ( - " ( " ! ( Util . list ) [ parse ] - " ) " ) ? { Sexp ( t , match ps with None -> [] | Some ps -> ps ) }
| " [ " ps : ( ! ( Util . list0 ) [ parse ] ) " ] " { Array ps }
| " { " ps : ( ! ( Util . list0 ) [ parse ] ) " } " { match ps with
| [] -> UnBoxed
| _ -> List . fold_right ( fun x acc -> Sexp ( " cons " , [ x ; acc ] ) ) ps UnBoxed
}
2020-01-11 16:38:25 +03:00
| l : $ x : LIDENT y : ( - " @ " parse ) ? { Loc . attach x l # coord ; match y with None -> Named ( x , Wildcard ) | Some y -> Named ( x , y ) }
2019-12-25 20:42:28 +03:00
| s : ( " - " ) ? c : DECIMAL { Const ( match s with None -> c | _ -> ~ - c ) }
2019-12-31 00:59:28 +03:00
| s : STRING { String s }
2019-04-02 19:51:46 +03:00
| c : CHAR { Const ( Char . code c ) }
2019-12-24 03:59:05 +03:00
| % " true " { Const 1 }
| % " false " { Const 0 }
2019-04-02 19:51:46 +03:00
| " # " % " boxed " { Boxed }
| " # " % " unboxed " { UnBoxed }
| " # " % " string " { StringTag }
| " # " % " sexp " { SexpTag }
| " # " % " array " { ArrayTag }
2019-09-25 00:25:40 +03:00
| " # " % " fun " { ClosureTag }
2019-04-02 19:51:46 +03:00
| - " ( " parse - " ) "
)
2019-08-14 01:59:44 +03:00
let vars p = transform ( t ) ( fun f -> object inherit [ string list , _ ] @ t [ foldl ] f method c_Named s _ name p = name :: f s p end ) [] p
2019-04-02 19:51:46 +03:00
end
2018-02-20 01:28:29 +03:00
(* Simple expressions: syntax and semantics *)
module Expr =
struct
2019-08-14 01:59:44 +03:00
(* The type of configuration: a state, an input stream, an output stream,
and a stack of values
2019-04-02 19:51:46 +03:00
* )
2019-10-17 15:30:50 +03:00
@ type ' a value = ( ' a , ' a value State . t array ) Value . t with show , html
@ type ' a config = ' a value State . t * int list * int list * ' a value list with show , html
2019-12-26 00:17:34 +03:00
(* Reff : parsed expression should return value Reff ( look for ":=" ) ;
Val : - // - returns simple value ;
Void : parsed expression should not return any value ; * )
2020-01-05 01:26:13 +03:00
@ type atr = Reff | Void | Val | Weak with show , html
2019-08-14 01:59:44 +03:00
(* The type for expressions. Note, in regular OCaml there is no "@type..."
notation , it came from GT .
2018-02-20 01:28:29 +03:00
* )
2019-10-11 17:25:58 +03:00
@ type t =
2019-04-02 19:51:46 +03:00
(* integer constant *) | Const of int
(* array *) | Array of t list
(* string *) | String of string
(* S-expressions *) | Sexp of string * t list
2020-01-05 22:54:09 +03:00
(* variable *) | Var of string
2019-04-02 19:51:46 +03:00
(* reference ( aka "lvalue" ) *) | Ref of string
(* binary operator *) | Binop of string * t * t
(* element extraction *) | Elem of t * t
(* reference to an element *) | ElemRef of t * t
(* length *) | Length of t
(* string conversion *) | StringVal of t
(* function call *) | Call of t * t list
(* assignment *) | Assign of t * t
2019-08-14 01:59:44 +03:00
(* composition *) | Seq of t * t
2019-04-02 19:51:46 +03:00
(* empty statement *) | Skip
(* conditional *) | If of t * t * t
(* loop with a pre-condition *) | While of t * t
(* loop with a post-condition *) | Repeat of t * t
2019-12-26 00:17:34 +03:00
(* pattern-matching *) | Case of t * ( Pattern . t * t ) list * Loc . t * atr
2019-04-02 19:51:46 +03:00
(* return statement *) | Return of t option
2019-04-10 22:15:08 +03:00
(* ignore a value *) | Ignore of t
(* unit value *) | Unit
2019-10-11 17:25:58 +03:00
(* entering the scope *) | Scope of ( string * decl ) list * t
2019-09-25 00:25:40 +03:00
(* lambda expression *) | Lambda of string list * t
2019-08-14 01:59:44 +03:00
(* leave a scope *) | Leave
2019-10-11 17:25:58 +03:00
(* intrinsic ( for evaluation ) *) | Intrinsic of ( t config , t config ) arrow
(* control ( for control flow ) *) | Control of ( t config , t * t config ) arrow
2019-11-25 15:26:00 +03:00
and decl = [ ` Local | ` Public | ` Extern | ` PublicExtern ] * [ ` Fun of string list * t | ` Variable of t option ]
2019-12-12 17:42:45 +03:00
with show , html
2019-09-19 00:15:02 +03:00
2020-01-05 01:26:13 +03:00
let notRef = function Reff -> false | _ -> true
let isVoid = function Void | Weak -> true | _ -> false
2019-09-10 01:03:23 +03:00
(* Available binary operators:
!! - - - disjunction
&& - - - conjunction
= = , != , < = , < , > = , > - - - comparisons
+ , - - - - addition , subtraction
* , / , % - - - multiplication , division , reminder
* )
2018-04-02 07:00:36 +03:00
2019-04-02 19:51:46 +03:00
(* Update state *)
2019-09-22 20:15:15 +03:00
let update st x v =
2019-04-02 19:51:46 +03:00
match x with
2019-10-05 00:16:50 +03:00
| Value . Var ( Value . Global x ) -> State . update x v st
2019-04-07 23:42:20 +03:00
| Value . Elem ( x , i ) -> Value . update_elem x i v ; st
2020-01-11 16:38:25 +03:00
| _ -> report_error ( Printf . sprintf " invalid value \" %s \" in update " @@ show ( Value . t ) ( fun _ -> " <expr> " ) ( fun _ -> " <state> " ) x )
2019-08-14 01:59:44 +03:00
2018-02-20 01:28:29 +03:00
(* Expression evaluator
2019-04-02 19:51:46 +03:00
val eval : env -> config -> k -> t -> config
2018-04-02 07:00:36 +03:00
2019-08-14 01:59:44 +03:00
Takes an environment , a configuration and an expresion , and returns another configuration . The
2018-04-02 07:00:36 +03:00
environment supplies the following method
2018-04-03 07:21:59 +03:00
method definition : env -> string -> int list -> config -> config
2018-04-02 07:00:36 +03:00
2019-08-14 01:59:44 +03:00
which takes an environment ( of the same type ) , a name of the function , a list of actual parameters and a configuration ,
2018-04-02 07:00:36 +03:00
an returns a pair : the return value for the call and the resulting configuration
2019-08-14 01:59:44 +03:00
* )
2018-04-02 05:58:02 +03:00
let to_func op =
let bti = function true -> 1 | _ -> 0 in
let itb b = b < > 0 in
let ( | > ) f g = fun x y -> f ( g x y ) in
match op with
| " + " -> ( + )
| " - " -> ( - )
| " * " -> ( * )
| " / " -> ( / )
| " % " -> ( mod )
| " < " -> bti | > ( < )
| " <= " -> bti | > ( < = )
| " > " -> bti | > ( > )
| " >= " -> bti | > ( > = )
| " == " -> bti | > ( = )
| " != " -> bti | > ( < > )
| " && " -> fun x y -> bti ( itb x && itb y )
| " !! " -> fun x y -> bti ( itb x | | itb y )
2019-08-14 01:59:44 +03:00
| _ -> failwith ( Printf . sprintf " Unknown binary operator %s " op )
2019-04-02 19:51:46 +03:00
2019-08-14 01:59:44 +03:00
let seq x = function Skip -> x | y -> Seq ( x , y )
2019-04-02 19:51:46 +03:00
let schedule_list h :: tl =
List . fold_left seq h tl
2019-08-14 01:59:44 +03:00
let rec take = function
2019-04-02 19:51:46 +03:00
| 0 -> fun rest -> [] , rest
| n -> fun h :: tl -> let tl' , rest = take ( n - 1 ) tl in h :: tl' , rest
2019-09-25 16:38:14 +03:00
let rec eval ( ( st , i , o , vs ) as conf ) k expr =
2019-09-22 20:15:15 +03:00
let print_values vs =
Printf . eprintf " Values: \n %! " ;
2019-09-24 01:12:04 +03:00
List . iter ( fun v -> Printf . eprintf " %s \n %! " @@ show ( Value . t ) ( fun _ -> " <expr> " ) ( fun _ -> " <state> " ) v ) vs ;
2019-09-22 20:15:15 +03:00
Printf . eprintf " End Values \n %! "
in
2018-04-02 05:58:02 +03:00
match expr with
2019-09-25 00:25:40 +03:00
| Lambda ( args , body ) ->
2019-10-17 15:30:50 +03:00
eval ( st , i , o , Value . Closure ( args , body , [| st |] ) :: vs ) Skip k
2019-09-29 02:35:04 +03:00
| Scope ( defs , body ) ->
2019-09-22 20:15:15 +03:00
let vars , body , bnds =
List . fold_left
( fun ( vs , bd , bnd ) -> function
2019-11-24 02:30:32 +03:00
| ( name , ( _ , ` Variable value ) ) -> ( name , true ) :: vs , ( match value with None -> bd | Some v -> Seq ( Ignore ( Assign ( Ref name , v ) ) , bd ) ) , bnd
| ( name , ( _ , ` Fun ( args , b ) ) ) -> ( name , false ) :: vs , bd , ( name , Value . FunRef ( name , args , b , 1 + State . level st ) ) :: bnd
2019-09-22 20:15:15 +03:00
)
( [] , body , [] )
2019-11-24 02:30:32 +03:00
( List . rev @@
List . map ( function
2020-01-14 05:36:03 +03:00
| ( name , ( ` Extern , _ ) ) -> report_error ( Printf . sprintf " external names ( \" %s \" ) not supported in evaluation " ( Subst . subst name ) )
2019-11-24 02:30:32 +03:00
| x -> x
)
defs )
2019-09-22 20:15:15 +03:00
in
2019-09-29 02:35:04 +03:00
eval ( State . push st ( State . from_list bnds ) vars , i , o , vs ) k ( Seq ( body , Leave ) )
2019-09-19 00:15:02 +03:00
| Unit ->
2019-09-25 16:38:14 +03:00
eval ( st , i , o , Value . Empty :: vs ) Skip k
2019-09-19 00:15:02 +03:00
| Ignore s ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ s ; Intrinsic ( fun ( st , i , o , vs ) -> ( st , i , o , List . tl vs ) ) ] )
2019-04-02 19:51:46 +03:00
| Control f ->
let s , conf' = f conf in
2019-09-25 16:38:14 +03:00
eval conf' k s
2019-04-02 19:51:46 +03:00
| Intrinsic f ->
2019-09-25 16:38:14 +03:00
eval ( f conf ) Skip k
2019-04-02 19:51:46 +03:00
| Const n ->
2019-09-25 16:38:14 +03:00
eval ( st , i , o , ( Value . of_int n ) :: vs ) Skip k
2019-04-02 19:51:46 +03:00
| String s ->
2019-09-25 16:38:14 +03:00
eval ( st , i , o , ( Value . of_string @@ Bytes . of_string s ) :: vs ) Skip k
2018-10-31 20:10:50 +03:00
| StringVal s ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ s ; Intrinsic ( fun ( st , i , o , s :: vs ) -> ( st , i , o , ( Value . of_string @@ Value . string_val s ) :: vs ) ) ] )
2019-04-02 19:51:46 +03:00
| Var x ->
2019-10-11 17:25:58 +03:00
let v =
match State . eval st x with
| Value . FunRef ( _ , args , body , level ) ->
2019-10-17 15:30:50 +03:00
Value . Closure ( args , body , [| State . prune st level |] )
2019-10-11 17:25:58 +03:00
| v -> v
in
eval ( st , i , o , v :: vs ) Skip k
2019-04-02 19:51:46 +03:00
| Ref x ->
2019-11-24 02:30:32 +03:00
eval ( st , i , o , ( Value . Var ( Value . Global x ) ) :: vs ) Skip k (* only Value.Global is supported in interpretation *)
2018-04-25 01:06:18 +03:00
| Array xs ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list ( xs @ [ Intrinsic ( fun ( st , i , o , vs ) -> let es , vs' = take ( List . length xs ) vs in Builtin . eval ( st , i , o , vs' ) ( List . rev es ) " .array " ) ] ) )
2018-04-25 01:06:18 +03:00
| Sexp ( t , xs ) ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list ( xs @ [ Intrinsic ( fun ( st , i , o , vs ) -> let es , vs' = take ( List . length xs ) vs in ( st , i , o , Value . Sexp ( t , Array . of_list ( List . rev es ) ) :: vs' ) ) ] ) )
2018-04-02 07:00:36 +03:00
| Binop ( op , x , y ) ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ x ; y ; Intrinsic ( fun ( st , i , o , y :: x :: vs ) -> ( st , i , o , ( Value . of_int @@ to_func op ( Value . to_int x ) ( Value . to_int y ) ) :: vs ) ) ] )
2019-04-02 19:51:46 +03:00
| Elem ( b , i ) ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ b ; i ; Intrinsic ( fun ( st , i , o , j :: b :: vs ) -> Builtin . eval ( st , i , o , vs ) [ b ; j ] " .elem " ) ] )
2019-04-02 19:51:46 +03:00
| ElemRef ( b , i ) ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ b ; i ; Intrinsic ( fun ( st , i , o , j :: b :: vs ) -> ( st , i , o , ( Value . Elem ( b , Value . to_int j ) ) :: vs ) ) ] )
2018-04-25 01:06:18 +03:00
| Length e ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ e ; Intrinsic ( fun ( st , i , o , v :: vs ) -> Builtin . eval ( st , i , o , vs ) [ v ] " .length " ) ] )
2019-09-22 20:15:15 +03:00
| Call ( f , args ) ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list ( f :: args @ [ Intrinsic ( fun ( st , i , o , vs ) ->
2019-09-22 20:15:15 +03:00
let es , vs' = take ( List . length args + 1 ) vs in
let f :: es = List . rev es in
( match f with
| Value . Builtin name ->
Builtin . eval ( st , i , o , vs' ) es name
2019-09-24 01:12:04 +03:00
| Value . Closure ( args , body , closure ) ->
2019-10-17 15:30:50 +03:00
let st' = State . push ( State . leave st closure . ( 0 ) ) ( State . from_list @@ List . combine args es ) ( List . map ( fun x -> x , true ) args ) in
2019-09-25 16:38:14 +03:00
let st'' , i' , o' , vs'' = eval ( st' , i , o , [] ) Skip body in
2019-10-17 15:30:50 +03:00
closure . ( 0 ) <- st'' ;
2019-09-22 20:15:15 +03:00
( State . leave st'' st , i' , o' , match vs'' with [ v ] -> v :: vs' | _ -> Value . Empty :: vs' )
2020-01-11 16:38:25 +03:00
| _ -> report_error ( Printf . sprintf " callee did not evaluate to a function: \" %s \" " ( show ( Value . t ) ( fun _ -> " <expr> " ) ( fun _ -> " <state> " ) f ) )
2019-09-22 20:15:15 +03:00
) ) ] ) )
2019-09-25 16:38:14 +03:00
| Leave -> eval ( State . drop st , i , o , vs ) Skip k
2019-04-02 19:51:46 +03:00
| Assign ( x , e ) ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ x ; e ; Intrinsic ( fun ( st , i , o , v :: x :: vs ) -> ( update st x v , i , o , v :: vs ) ) ] )
2019-04-02 19:51:46 +03:00
| Seq ( s1 , s2 ) ->
2019-09-25 16:38:14 +03:00
eval conf ( seq s2 k ) s1
2019-04-02 19:51:46 +03:00
| Skip ->
2019-09-25 16:38:14 +03:00
( match k with Skip -> conf | _ -> eval conf Skip k )
2019-04-02 19:51:46 +03:00
| If ( e , s1 , s2 ) ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ e ; Control ( fun ( st , i , o , e :: vs ) -> ( if Value . to_int e < > 0 then s1 else s2 ) , ( st , i , o , vs ) ) ] )
2019-04-02 19:51:46 +03:00
| While ( e , s ) ->
2019-09-25 16:38:14 +03:00
eval conf k ( schedule_list [ e ; Control ( fun ( st , i , o , e :: vs ) -> ( if Value . to_int e < > 0 then seq s expr else Skip ) , ( st , i , o , vs ) ) ] )
2019-04-02 19:51:46 +03:00
| Repeat ( s , e ) ->
2019-09-25 16:38:14 +03:00
eval conf ( seq ( While ( Binop ( " == " , e , Const 0 ) , s ) ) k ) s
| Return e -> ( match e with None -> ( st , i , o , [] ) | Some e -> eval ( st , i , o , [] ) Skip e )
2019-12-26 00:17:34 +03:00
| Case ( e , bs , _ , _ ) ->
2019-04-02 19:51:46 +03:00
let rec branch ( ( st , i , o , v :: vs ) as conf ) = function
2019-09-24 01:12:04 +03:00
| [] -> failwith ( Printf . sprintf " Pattern matching failed: no branch is selected while matching %s \n " ( show ( Value . t ) ( fun _ -> " <expr> " ) ( fun _ -> " <state> " ) v ) )
2019-04-02 19:51:46 +03:00
| ( patt , body ) :: tl ->
let rec match_patt patt v st =
let update x v = function
| None -> None
| Some s -> Some ( State . bind x v s )
in
match patt , v with
| Pattern . Named ( x , p ) , v -> update x v ( match_patt p v st )
| Pattern . Wildcard , _ -> st
| Pattern . Sexp ( t , ps ) , Value . Sexp ( t' , vs ) when t = t' && List . length ps = Array . length vs -> match_list ps ( Array . to_list vs ) st
| Pattern . Array ps , Value . Array vs when List . length ps = Array . length vs -> match_list ps ( Array . to_list vs ) st
| Pattern . Const n , Value . Int n' when n = n' -> st
| Pattern . String s , Value . String s' when s = Bytes . to_string s' -> st
2019-08-14 01:59:44 +03:00
| Pattern . Boxed , Value . String _
2019-04-02 19:51:46 +03:00
| Pattern . Boxed , Value . Array _
| Pattern . UnBoxed , Value . Int _
2019-08-14 01:59:44 +03:00
| Pattern . Boxed , Value . Sexp ( _ , _ )
2019-04-02 19:51:46 +03:00
| Pattern . StringTag , Value . String _
2019-08-14 01:59:44 +03:00
| Pattern . ArrayTag , Value . Array _
2019-09-25 00:25:40 +03:00
| Pattern . ClosureTag , Value . Closure _
2019-04-02 19:51:46 +03:00
| Pattern . SexpTag , Value . Sexp ( _ , _ ) -> st
2019-08-14 01:59:44 +03:00
| _ -> None
2019-04-02 19:51:46 +03:00
and match_list ps vs s =
match ps , vs with
| [] , [] -> s
| p :: ps , v :: vs -> match_list ps vs ( match_patt p v s )
| _ -> None
in
match match_patt patt v ( Some State . undefined ) with
| None -> branch conf tl
2019-09-25 16:38:14 +03:00
| Some st' -> eval ( State . push st st' ( List . map ( fun x -> x , false ) @@ Pattern . vars patt ) , i , o , vs ) k ( Seq ( body , Leave ) )
2019-08-14 01:59:44 +03:00
in
2019-09-25 16:38:14 +03:00
eval conf Skip ( schedule_list [ e ; Intrinsic ( fun conf -> branch conf bs ) ] )
2019-08-14 01:59:44 +03:00
2020-01-05 01:26:13 +03:00
(* Expression parser. You can use the following terminals:
LIDENT - - - a non - empty identifier a - z [ a - zA - Z0 - 9_ ] * as a string
UIDENT - - - a non - empty identifier A - Z [ a - zA - Z0 - 9_ ] * as a string
DECIMAL - - - a decimal constant [ 0 - 9 ] + as a string
* )
2019-09-10 01:03:23 +03:00
2019-09-10 15:54:37 +03:00
(* places ignore if expression should be void *)
2020-01-05 01:26:13 +03:00
let ignore atr expr = match atr with Void -> Ignore expr | _ -> expr
2019-09-10 15:54:37 +03:00
2020-01-05 01:26:13 +03:00
(* places dummy value if required *)
let materialize atr expr =
match atr with
| Weak -> Seq ( expr , Const 0 )
| _ -> expr
2020-01-05 22:54:09 +03:00
(* semantics for infixes created in runtime *)
2019-09-10 15:54:37 +03:00
let sem s = ( fun x atr y -> ignore atr ( Call ( Var s , [ x ; y ] ) ) ) , ( fun _ -> Val , Val )
let sem_init s = fun x atr y ->
ignore atr (
match s with
| " : " -> Sexp ( " cons " , [ x ; y ] )
| " := " -> Assign ( x , y )
2020-01-14 03:30:17 +03:00
| _ -> Binop ( s , x , y )
2019-09-10 15:54:37 +03:00
)
2019-09-10 01:03:23 +03:00
(* ======= *)
2019-09-10 15:54:37 +03:00
let left f c x a y = f ( c x ) a y
let right f c x a y = c ( f x a y )
2019-09-10 01:03:23 +03:00
2019-09-10 15:54:37 +03:00
let expr f ops opnd atr =
2019-09-10 01:03:23 +03:00
let ops =
Array . map
2019-09-10 15:54:37 +03:00
( fun ( assoc , ( atrs , list ) ) ->
2019-09-10 01:03:23 +03:00
let g = match assoc with ` Lefta | ` Nona -> left | ` Righta -> right in
2019-09-10 15:54:37 +03:00
assoc = ` Nona , ( atrs , altl ( List . map ( fun ( oper , sema ) -> ostap ( ! ( oper ) { g sema } ) ) list ) )
2019-09-10 01:03:23 +03:00
)
ops
in
2019-09-10 15:54:37 +03:00
let atrr i atr = snd ( fst ( snd ops . ( i ) ) atr ) in
let atrl i atr = fst ( fst ( snd ops . ( i ) ) atr ) in
let n = Array . length ops in
let op i = snd ( snd ops . ( i ) ) in
2019-09-10 01:03:23 +03:00
let nona i = fst ops . ( i ) in
let id x = x in
let ostap (
2019-09-10 15:54:37 +03:00
inner [ l ] [ c ] [ atr ] : f [ ostap (
{ n = l } = > x : opnd [ atr ] { c x }
| { n > l && not ( nona l ) } = > ( - x : inner [ l + 1 ] [ id ] [ atrl l atr ] - o : op [ l ] y : inner [ l ] [ o c x atr ] [ atrr l atr ] |
x : inner [ l + 1 ] [ id ] [ atr ] { c x } )
| { n > l && nona l } = > ( x : inner [ l + 1 ] [ id ] [ atrl l atr ] o : op [ l ] y : inner [ l + 1 ] [ id ] [ atrr l atr ] { c ( o id x atr y ) } |
x : inner [ l + 1 ] [ id ] [ atr ] { c x } )
) ]
)
2019-09-10 01:03:23 +03:00
in
2019-09-10 15:54:37 +03:00
ostap ( inner [ 0 ] [ id ] [ atr ] )
2020-01-05 01:26:13 +03:00
let atr' = atr
2020-01-05 22:54:09 +03:00
let not_a_reference s = new Reason . t ( Msg . make " not a reference " [| |] ( Msg . Locator . Point s # coord ) )
2020-01-14 05:15:19 +03:00
(* UGLY! *)
let predefined_op : ( Obj . t -> Obj . t -> Obj . t ) ref = Pervasives . ref ( fun _ _ -> invalid_arg " must not happen " )
2020-01-05 22:54:09 +03:00
2019-09-10 01:03:23 +03:00
(* ======= *)
ostap (
2019-09-19 00:15:02 +03:00
parse [ def ] [ infix ] [ atr ] : h : basic [ def ] [ infix ] [ Void ] - " ; " t : parse [ def ] [ infix ] [ atr ] { Seq ( h , t ) }
| basic [ def ] [ infix ] [ atr ] ;
2019-09-29 02:35:04 +03:00
scope [ def ] [ infix ] [ atr ] [ e ] : < ( d , infix' ) > : def [ infix ] expr : e [ infix' ] [ atr ] { Scope ( d , expr ) } ;
2019-09-10 15:54:37 +03:00
2019-11-29 23:56:03 +03:00
basic [ def ] [ infix ] [ atr ] : ! ( expr ( fun x -> x ) ( Array . map ( fun ( a , ( atr , l ) ) -> a , ( atr , List . map ( fun ( s , _ , f ) -> ostap ( - $ ( s ) ) , f ) l ) ) infix ) ( primary def infix ) atr ) ;
2019-09-10 15:54:37 +03:00
2019-09-19 00:15:02 +03:00
primary [ def ] [ infix ] [ atr ] :
2019-12-25 20:42:28 +03:00
s : ( s : " - " ? { match s with None -> fun x -> x | _ -> fun x -> Binop ( " - " , Const 0 , x ) } )
2019-12-26 20:02:30 +03:00
b : base [ def ] [ infix ] [ Val ] is : ( " . " f : LIDENT args : ( - " ( " ! ( Util . list ) [ parse def infix Val ] - " ) " ) ? { ` Post ( f , args ) }
| " . " % " length " { ` Len }
| " . " % " string " { ` Str }
| " [ " i : parse [ def ] [ infix ] [ Val ] " ] " { ` Elem i }
| " ( " args : ! ( Util . list0 ) [ parse def infix Val ] " ) " { ` Call args }
) +
2019-09-10 15:54:37 +03:00
= > { match ( List . hd ( List . rev is ) ) , atr with
2019-09-22 22:25:05 +03:00
| ` Elem i , Reff -> true
2019-09-10 15:54:37 +03:00
| _ , Reff -> false
| _ , _ -> true } = >
2019-12-26 20:02:30 +03:00
{
let is =
let rec fix_is = function
| [ ] -> []
| [ x ] -> [ x ]
| ` Post ( f , None ) :: ` Call args :: tl when args != [] -> ` Post ( f , Some args ) :: fix_is tl
| x :: tl -> x :: fix_is tl
in
fix_is is
in
2019-09-10 15:54:37 +03:00
let lastElem = List . hd ( List . rev is ) in
let is = List . rev ( List . tl ( List . rev is ) ) in
let b =
List . fold_left
( fun b ->
function
2019-12-21 18:04:39 +03:00
| ` Elem i -> Elem ( b , i )
| ` Len -> Length b
| ` Str -> StringVal b
| ` Post ( f , args ) -> Call ( Var f , b :: match args with None -> [] | Some args -> args )
2019-12-26 00:17:34 +03:00
| ` Call args -> ( match b with Sexp _ -> invalid_arg " retry! " | _ -> Call ( b , args ) )
2019-09-10 15:54:37 +03:00
)
b
is
in
let res = match lastElem , atr with
2019-12-21 18:04:39 +03:00
| ` Elem i , Reff -> ElemRef ( b , i )
2019-12-25 20:42:28 +03:00
| ` Elem i , _ -> Elem ( b , i )
| ` Len , _ -> Length b
| ` Str , _ -> StringVal b
| ` Post ( f , args ) , _ -> Call ( Var f , b :: match args with None -> [] | Some args -> args )
2020-01-04 22:28:57 +03:00
| ` Call args , _ -> ( match b with Sexp _ -> invalid_arg " retry! " | _ -> Call ( b , args ) )
2019-09-10 15:54:37 +03:00
in
2019-12-25 20:42:28 +03:00
ignore atr ( s res )
2019-09-10 01:03:23 +03:00
}
2019-09-19 00:15:02 +03:00
| base [ def ] [ infix ] [ atr ] ;
base [ def ] [ infix ] [ atr ] :
2020-01-05 22:54:09 +03:00
l : $ n : DECIMAL = > { notRef atr } :: ( not_a_reference l ) = > { ignore atr ( Const n ) }
2020-01-11 16:38:25 +03:00
| l : $ s : STRING = > { notRef atr } :: ( not_a_reference l ) = > { ignore atr ( String s ) }
2020-01-05 22:54:09 +03:00
| l : $ c : CHAR = > { notRef atr } :: ( not_a_reference l ) = > { ignore atr ( Const ( Char . code c ) ) }
2019-12-23 18:40:48 +03:00
2020-01-05 22:54:09 +03:00
| l : $ c : ( % " true " { Const 1 } | % " false " { Const 0 } ) = > { notRef atr } :: ( not_a_reference l ) = > { ignore atr c }
2019-12-23 18:40:48 +03:00
2020-01-14 05:15:19 +03:00
| l : $ % " infix " s : INFIX = > { notRef atr } :: ( not_a_reference l ) = > {
if ( (* UGLY! *) Obj . magic ! predefined_op ) infix s
then (
if s = " := "
then report_error ~ loc : ( Some l # coord ) ( Printf . sprintf " can not capture predefined operator \" := \" " )
else
let name = sys_infix_name s in Loc . attach name l # coord ; ignore atr ( Var name )
)
else (
let name = infix_name s in Loc . attach name l # coord ; ignore atr ( Var name )
)
}
2020-01-11 16:38:25 +03:00
| l : $ % " fun " " ( " args : ! ( Util . list0 ) [ ostap ( l : $ x : LIDENT { Loc . attach x l # coord ; x } ) ] " ) "
" { " body : scope [ def ] [ infix ] [ Weak ] [ parse def ] " } " = > { notRef atr } :: ( not_a_reference l ) = > { ignore atr ( Lambda ( args , body ) ) }
2020-01-05 22:54:09 +03:00
| l : $ " [ " es : ! ( Util . list0 ) [ parse def infix Val ] " ] " = > { notRef atr } :: ( not_a_reference l ) = > { ignore atr ( Array es ) }
2019-09-29 02:35:04 +03:00
| - " { " scope [ def ] [ infix ] [ atr ] [ parse def ] - " } "
2020-01-05 22:54:09 +03:00
| l : $ " { " es : ! ( Util . list0 ) [ parse def infix Val ] " } " = > { notRef atr } :: ( not_a_reference l ) = > { ignore atr ( match es with
2019-09-19 00:15:02 +03:00
| [] -> Const 0
| _ -> List . fold_right ( fun x acc -> Sexp ( " cons " , [ x ; acc ] ) ) es ( Const 0 ) )
}
2020-01-05 22:54:09 +03:00
| l : $ t : UIDENT args : ( - " ( " ! ( Util . list ) [ parse def infix Val ] - " ) " ) ? = > { notRef atr } :: ( not_a_reference l ) = > { ignore atr ( Sexp ( t , match args with
2019-09-19 00:15:02 +03:00
| None -> []
| Some args -> args ) )
}
2020-01-11 16:38:25 +03:00
| l : $ x : LIDENT { Loc . attach x l # coord ; if notRef atr then ignore atr ( Var x ) else Ref x }
2019-09-10 15:54:37 +03:00
2020-01-05 01:26:13 +03:00
| { isVoid atr } = > % " skip " { materialize atr Skip }
2019-09-10 15:54:37 +03:00
2019-09-29 02:35:04 +03:00
| % " if " e : parse [ def ] [ infix ] [ Val ] % " then " the : scope [ def ] [ infix ] [ atr ] [ parse def ]
2020-01-05 03:33:17 +03:00
elif : ( % " elif " parse [ def ] [ infix ] [ Val ] % " then " scope [ def ] [ infix ] [ atr ] [ parse def ] ) *
2020-01-05 01:26:13 +03:00
els : ( % " else " scope [ def ] [ infix ] [ atr ] [ parse def ] ) ? % " fi "
{ If ( e , the , List . fold_right ( fun ( e , t ) elif -> If ( e , t , elif ) ) elif ( match els with Some e -> e | _ -> materialize atr Skip ) ) }
2019-09-29 02:35:04 +03:00
| % " while " e : parse [ def ] [ infix ] [ Val ] % " do " s : scope [ def ] [ infix ] [ Void ] [ parse def ]
2020-01-05 01:26:13 +03:00
= > { isVoid atr } = > % " od " { materialize atr ( While ( e , s ) ) }
2019-09-10 15:54:37 +03:00
2019-09-29 02:35:04 +03:00
| % " for " i : parse [ def ] [ infix ] [ Void ] " , " c : parse [ def ] [ infix ] [ Val ] " , " s : parse [ def ] [ infix ] [ Void ] % " do " b : scope [ def ] [ infix ] [ Void ] [ parse def ] = > { isVoid atr } = > % " od "
2020-01-05 01:26:13 +03:00
{ materialize atr ( Seq ( i , While ( c , Seq ( b , s ) ) ) ) }
2019-09-10 15:54:37 +03:00
2020-01-05 01:26:13 +03:00
| % " repeat " s : scope [ def ] [ infix ] [ Void ] [ parse def ] % " until " e : basic [ def ] [ infix ] [ Val ] = > { isVoid atr } = > { materialize atr ( Repeat ( s , e ) ) }
2019-11-24 02:30:32 +03:00
| % " return " e : basic [ def ] [ infix ] [ Val ] ? = > { isVoid atr } = > { Return e }
2019-09-10 15:54:37 +03:00
2019-12-25 20:42:28 +03:00
| % " case " l : $ e : parse [ def ] [ infix ] [ Val ] % " of " bs : ! ( Util . listBy ) [ ostap ( " | " ) ] [ ostap ( ! ( Pattern . parse ) - " -> " scope [ def ] [ infix ] [ atr ] [ parse def ] ) ] % " esac "
2019-12-26 00:17:34 +03:00
{ Case ( e , bs , l # coord , atr ) }
2019-09-19 00:15:02 +03:00
| - " ( " parse [ def ] [ infix ] [ atr ] - " ) "
2019-09-10 01:03:23 +03:00
)
2019-09-10 15:54:37 +03:00
end
2019-09-10 01:03:23 +03:00
(* Infix helpers *)
module Infix =
struct
2019-11-29 23:56:03 +03:00
2020-01-14 05:15:19 +03:00
@ type kind = Predefined | Public | Local with show
@ type ass = [ ` Lefta | ` Righta | ` Nona ] with show
@ type loc = [ ` Before of string | ` After of string | ` At of string ] with show
@ type export = ( ass * string * loc ) list with show
2020-01-14 03:30:17 +03:00
@ type showable = ( ass * string * kind ) list array with show
2019-11-29 23:56:03 +03:00
type t = ( [ ` Lefta | ` Righta | ` Nona ] * ( ( Expr . atr -> ( Expr . atr * Expr . atr ) ) * ( ( string * kind * ( Expr . t -> Expr . atr -> Expr . t -> Expr . t ) ) list ) ) ) array
2019-09-10 01:03:23 +03:00
2020-01-14 03:30:17 +03:00
let show_infix ( infix : t ) =
show ( showable ) @@ Array . map ( fun ( ass , ( _ , l ) ) -> List . map ( fun ( str , kind , _ ) -> ass , str , kind ) l ) infix
2019-11-29 23:56:03 +03:00
let extract_exports infix =
let ass_string = function ` Lefta -> " L " | ` Righta -> " R " | _ -> " I " in
let exported =
Array . map
( fun ( ass , ( _ , ops ) ) ->
2019-12-18 18:44:01 +03:00
( ass , List . rev @@ List . map ( fun ( s , kind , _ ) -> s , kind ) @@ List . filter ( function ( _ , Public , _ ) | ( _ , Predefined , _ ) -> true | _ -> false ) ops )
2019-11-29 23:56:03 +03:00
)
infix
in
let _ , exports =
Array . fold_left
( fun ( loc , acc ) ( ass , list ) ->
let rec inner ( loc , acc ) = function
| [] -> ( loc , acc )
| ( s , kind ) :: tl ->
let loc' = match tl with [] -> ` After s | _ -> ` At s in
( fun again ->
2019-12-18 18:44:01 +03:00
match kind with
| Public -> again ( loc' , ( ass , s , loc ) :: acc )
| _ -> again ( loc' , acc )
2019-11-29 23:56:03 +03:00
)
2019-12-18 18:44:01 +03:00
( match tl with [] -> fun acc -> acc | _ -> fun acc -> inner acc tl )
2019-11-29 23:56:03 +03:00
in
inner ( loc , acc ) list
)
( ` Before " := " , [] )
exported
in List . rev exports
2020-01-14 03:30:17 +03:00
let is_predefined op =
List . exists ( fun x -> op = x ) [ " : " ; " !! " ; " && " ; " == " ; " != " ; " <= " ; " < " ; " >= " ; " > " ; " + " ; " - " ; " * " ; " / " ; " % " ; " := " ]
2019-11-29 23:56:03 +03:00
2020-01-14 05:15:19 +03:00
(*
List . iter ( fun op ->
Printf . eprintf " F,%s \n " ( sys_infix_name op ) ;
(*
Printf . eprintf " // Functional synonym for built-in operator \" %s \" ; \n " op ;
Printf . eprintf " int L%s (void *p, void *q) { \n " ( sys_infix_name op ) ;
Printf . eprintf " ASSERT_UNBOXED( \" captured %s:1 \" , p); \n " op ;
Printf . eprintf " ASSERT_UNBOXED( \" captured %s:2 \" , q); \n \n " op ;
Printf . eprintf " return BOX(UNBOX(p) %s UNBOX(q)); \n " op ;
Printf . eprintf " } \n \n " * )
) [ " : " ; " !! " ; " && " ; " == " ; " != " ; " <= " ; " < " ; " >= " ; " > " ; " + " ; " - " ; " * " ; " / " ; " % " ]
* )
2019-09-10 01:03:23 +03:00
let default : t =
2019-09-10 00:46:10 +03:00
Array . map ( fun ( a , s ) ->
a ,
2019-09-10 15:54:37 +03:00
( ( fun _ -> ( if ( List . hd s ) = " := " then Expr . Reff else Expr . Val ) , Expr . Val ) ,
2019-11-29 23:56:03 +03:00
List . map ( fun s -> s , Predefined , Expr . sem_init s ) s )
2019-09-10 00:46:10 +03:00
)
[|
` Righta , [ " := " ] ;
` Righta , [ " : " ] ;
2019-09-10 01:03:23 +03:00
` Lefta , [ " !! " ] ;
` Lefta , [ " && " ] ;
` Nona , [ " == " ; " != " ; " <= " ; " < " ; " >= " ; " > " ] ;
2019-12-20 00:23:35 +03:00
` Lefta , [ " + " ; " - " ] ;
2019-09-10 01:03:23 +03:00
` Lefta , [ " * " ; " / " ; " % " ] ;
2019-09-10 00:46:10 +03:00
|]
2019-09-10 01:03:23 +03:00
exception Break of [ ` Ok of t | ` Fail of string ]
2020-01-14 05:15:19 +03:00
2019-09-10 01:03:23 +03:00
let find_op infix op cb ce =
try
2019-11-29 23:56:03 +03:00
Array . iteri ( fun i ( _ , ( _ , l ) ) -> if List . exists ( fun ( s , _ , _ ) -> s = op ) l then raise ( Break ( cb i ) ) ) infix ;
2019-09-10 01:03:23 +03:00
ce ()
with Break x -> x
2019-04-02 19:51:46 +03:00
2020-01-14 05:15:19 +03:00
let predefined_op infix op =
Array . exists
( fun ( _ , ( _ , l ) ) ->
List . exists ( fun ( s , p , _ ) -> s = op && p = Predefined ) l
)
infix ;;
(* UGLY!!! *)
Expr . predefined_op := ( Obj . magic ) predefined_op ;;
2020-01-11 16:38:25 +03:00
let no_op op coord = ` Fail ( Printf . sprintf " infix \" %s \" not found in the scope " op )
2019-09-10 01:03:23 +03:00
2019-11-29 23:56:03 +03:00
let kind_of = function true -> Public | _ -> Local
let at coord op newp public ( sem , _ ) ( infix : t ) =
2019-09-10 01:03:23 +03:00
find_op infix op
( fun i ->
` Ok ( Array . init ( Array . length infix )
( fun j ->
if j = i
2020-01-14 03:30:17 +03:00
then let ( a , ( atr , l ) ) = infix . ( i ) in ( a , ( (* atr *) ( fun _ -> Expr . Val , Expr . Val ) , ( ( newp , kind_of public , sem ) :: ( List . filter ( fun ( op' , _ , _ ) -> op' < > newp ) l ) ) ) )
2019-09-10 01:03:23 +03:00
else infix . ( j )
) )
)
( fun _ -> no_op op coord )
2019-11-29 23:56:03 +03:00
let before coord op newp ass public ( sem , atr ) ( infix : t ) =
2019-09-10 01:03:23 +03:00
find_op infix op
( fun i ->
` Ok ( Array . init ( 1 + Array . length infix )
( fun j ->
if j < i
then infix . ( j )
2019-11-29 23:56:03 +03:00
else if j = i then ( ass , ( atr , [ newp , kind_of public , sem ] ) )
2019-09-10 01:03:23 +03:00
else infix . ( j - 1 )
) )
)
( fun _ -> no_op op coord )
2019-11-29 23:56:03 +03:00
let after coord op newp ass public ( sem , atr ) ( infix : t ) =
2019-09-10 01:03:23 +03:00
find_op infix op
( fun i ->
` Ok ( Array . init ( 1 + Array . length infix )
( fun j ->
if j < = i
then infix . ( j )
2019-11-29 23:56:03 +03:00
else if j = i + 1 then ( ass , ( atr , [ newp , kind_of public , sem ] ) )
2019-09-10 01:03:23 +03:00
else infix . ( j - 1 )
) )
)
( fun _ -> no_op op coord )
2019-08-14 01:59:44 +03:00
2018-02-20 01:28:29 +03:00
end
2019-03-25 00:13:42 +03:00
2018-03-27 01:51:22 +03:00
(* Function and procedure definitions *)
module Definition =
struct
2019-09-19 00:15:02 +03:00
(* The type for a definition: aither a function/infix, or a local variable *)
2019-09-19 15:52:20 +03:00
type t = string * [ ` Fun of string list * Expr . t | ` Variable of Expr . t option ]
2019-11-24 02:30:32 +03:00
let unopt_mod = function None -> ` Local | Some m -> m
2019-09-19 00:15:02 +03:00
2018-03-27 01:51:22 +03:00
ostap (
2020-01-11 16:38:25 +03:00
arg : l : $ x : LIDENT { Loc . attach x l # coord ; x } ;
2019-11-29 23:56:03 +03:00
position [ pub ] [ ass ] [ coord ] [ newp ] :
2020-01-14 03:30:17 +03:00
% " at " s : INFIX { match ass with
| ` Nona -> Infix . at coord s newp pub
| _ -> report_error ~ loc : ( Some coord ) ( Printf . sprintf " associativity for infix \" %s \" can not be specified (it is inherited from that for \" %s \" ) " newp s )
2020-01-11 16:38:25 +03:00
}
2020-01-14 03:30:17 +03:00
| f : ( % " before " { Infix . before } | % " after " { Infix . after } ) s : INFIX { f coord s newp ass pub } ;
2019-03-25 00:13:42 +03:00
head [ infix ] :
2020-01-11 16:38:25 +03:00
m : ( % " external " { ` Extern } | % " public " e : ( % " external " ) ? { match e with None -> ` Public | _ -> ` PublicExtern } ) ? % " fun " l : $ name : LIDENT { Loc . attach name l # coord ; unopt_mod m , name , name , infix }
2019-11-24 02:30:32 +03:00
| m : ( % " public " { ` Public } ) ? ass : ( % " infix " { ` Nona } | % " infixl " { ` Lefta } | % " infixr " { ` Righta } )
2020-01-14 03:30:17 +03:00
l : $ op : ( s : INFIX { s } )
2019-11-29 23:56:03 +03:00
md : position [ match m with Some _ -> true | _ -> false ] [ ass ] [ l # coord ] [ op ] {
2020-01-14 03:30:17 +03:00
if m < > None && Infix . is_predefined op then report_error ~ loc : ( Some l # coord ) ( Printf . sprintf " redefinition of standard infix operator \" %s \" can not be exported " op ) ;
let name = infix_name op in
Loc . attach name l # coord ;
2019-09-10 15:54:37 +03:00
match md ( Expr . sem name ) infix with
2019-11-24 02:30:32 +03:00
| ` Ok infix' -> unopt_mod m , op , name , infix'
2020-01-11 16:38:25 +03:00
| ` Fail msg -> report_error ~ loc : ( Some l # coord ) msg
2019-04-02 19:51:46 +03:00
} ;
2020-01-11 16:38:25 +03:00
local_var [ m ] [ infix ] [ expr ] [ def ] : l : $ name : LIDENT value : ( - " = " expr [ def ] [ infix ] [ Expr . Val ] ) ? {
Loc . attach name l # coord ;
2019-11-24 02:30:32 +03:00
match m , value with
2020-01-11 16:38:25 +03:00
| ` Extern , Some _ -> report_error ~ loc : ( Some l # coord ) ( Printf . sprintf " initial value for an external variable \" %s \" can not be specified " name )
2019-11-24 02:30:32 +03:00
| _ -> name , ( m , ` Variable value )
} ;
2020-01-11 16:38:25 +03:00
parse [ infix ] [ expr ] [ def ] :
2019-11-25 15:26:00 +03:00
m : ( % " local " { ` Local } | % " public " e : ( % " external " ) ? { match e with None -> ` Public | Some _ -> ` PublicExtern } | % " external " { ` Extern } )
2019-11-24 02:30:32 +03:00
locs : ! ( Util . list ( local_var m infix expr def ) ) " ; " { locs , infix }
| - < ( m , orig_name , name , infix' ) > : head [ infix ] - " ( " - args : ! ( Util . list0 arg ) - " ) "
2020-01-11 16:38:25 +03:00
( l : $ " { " body : expr [ def ] [ infix' ] [ Expr . Weak ] " } " {
2019-11-24 02:30:32 +03:00
match m with
2020-01-11 16:38:25 +03:00
| ` Extern -> report_error ~ loc : ( Some l # coord ) ( Printf . sprintf " body for external function \" %s \" can not be specified " orig_name )
2019-11-24 02:30:32 +03:00
| _ -> [ ( name , ( m , ` Fun ( args , body ) ) ) ] , infix'
} |
2020-01-11 16:38:25 +03:00
l : $ " ; " {
2019-11-24 02:30:32 +03:00
match m with
| ` Extern -> [ ( name , ( m , ` Fun ( args , Expr . Skip ) ) ) ] , infix'
2020-01-11 16:38:25 +03:00
| _ -> report_error ~ loc : ( Some l # coord ) ( Printf . sprintf " missing body for the function/infix \" %s \" " orig_name )
2019-11-24 02:30:32 +03:00
} )
2018-03-27 01:51:22 +03:00
)
end
2019-11-29 23:56:03 +03:00
2019-11-27 03:14:25 +03:00
module Interface =
struct
(* Generates an interface file. *)
2019-11-29 23:56:03 +03:00
let gen ( ( imps , ifxs ) , p ) =
2019-11-27 03:14:25 +03:00
let buf = Buffer . create 256 in
let append str = Buffer . add_string buf str in
List . iter ( fun i -> append " I, " ; append i ; append " ; \n " ) imps ;
( match p with
| Expr . Scope ( decls , _ ) ->
List . iter
( function
| ( name , ( ` Public , item ) ) | ( name , ( ` PublicExtern , item ) ) ->
( match item with
| ` Fun _ -> append " F, " ; append name ; append " ; \n "
| ` Variable _ -> append " V, " ; append name ; append " ; \n "
)
| _ -> ()
)
decls ;
2019-11-29 23:56:03 +03:00
| _ -> () ) ;
List . iter
( function ( ass , op , loc ) ->
let append_op op = append " \" " ; append op ; append " \" " in
append ( match ass with ` Lefta -> " L, " | ` Righta -> " R, " | _ -> " N, " ) ;
append_op op ;
append " , " ;
( match loc with ` At op -> append " T, " ; append_op op | ` After op -> append " A, " ; append_op op | ` Before op -> append " B, " ; append_op op ) ;
append " ; \n "
) ifxs ;
2019-11-27 03:14:25 +03:00
Buffer . contents buf
(* Read an interface file *)
let read fname =
let ostap (
funspec : " F " " , " i : IDENT " ; " { ` Fun i } ;
varspec : " V " " , " i : IDENT " ; " { ` Variable i } ;
import : " I " " , " i : IDENT " ; " { ` Import i } ;
2019-11-29 23:56:03 +03:00
infix : a : ass " , " op : STRING " , " l : loc " ; " { ` Infix ( a , op , l ) } ;
ass : " L " { ` Lefta } | " R " { ` Righta } | " N " { ` Nona } ;
loc : m : mode " , " op : STRING { m op } ;
mode : " T " { fun x -> ` At x } | " A " { fun x -> ` After x } | " B " { fun x -> ` Before x } ;
interface : ( funspec | varspec | import | infix ) *
2019-11-27 03:14:25 +03:00
)
in
try
let s = Util . read fname in
( match Util . parse ( object
inherit Matcher . t s
inherit Util . Lexers . ident [] s
2019-11-29 23:56:03 +03:00
inherit Util . Lexers . string s
2019-11-27 03:14:25 +03:00
inherit Util . Lexers . skip [ Matcher . Skip . whitespaces " \t \n " ] s
end )
( ostap ( interface - EOF ) )
with
| ` Ok intfs -> Some intfs
2020-01-11 16:38:25 +03:00
| ` Fail er -> report_error ( Printf . sprintf " malformed interface file \" %s \" : %s " fname er )
2019-11-27 03:14:25 +03:00
)
with Sys_error _ -> None
let find import paths =
let rec inner = function
| [] -> None
| p :: paths ->
( match read ( Filename . concat p ( import ^ " .i " ) ) with
| None -> inner paths
| Some i -> Some ( p , i )
)
in
match inner paths with
| Some ( path , intfs ) -> path , intfs
2020-01-11 16:38:25 +03:00
| None -> report_error ( Printf . sprintf " could not find an interface file for import \" %s \" " import )
2018-02-25 14:48:13 +03:00
2019-11-27 03:14:25 +03:00
end
2019-11-29 23:56:03 +03:00
2019-11-27 03:14:25 +03:00
(* The top-level definitions *)
2018-02-25 14:48:13 +03:00
2018-02-20 02:53:58 +03:00
(* Top-level evaluator
2018-02-25 14:48:13 +03:00
eval : t -> int list -> int list
Takes a program and its input stream , and returns the output stream
* )
2019-11-27 03:14:25 +03:00
let eval ( _ , expr ) i =
2019-09-25 16:38:14 +03:00
let _ , _ , o , _ = Expr . eval ( State . empty , i , [] , [] ) Skip expr in
2018-04-02 07:00:36 +03:00
o
2018-04-02 05:58:02 +03:00
2018-02-25 14:48:13 +03:00
(* Top-level parser *)
2019-03-25 00:13:42 +03:00
ostap (
2020-01-05 03:33:17 +03:00
imports [ cmd ] : l : $ is : ( % " import " ! ( Util . list ( ostap ( UIDENT ) ) ) - " ; " ) * {
2019-12-18 18:44:01 +03:00
let is = " Std " :: List . flatten is in
2019-11-29 23:56:03 +03:00
let infix =
List . fold_left
( fun infix import ->
List . fold_left
( fun infix item ->
2019-12-18 18:44:01 +03:00
let insert name infix md =
2020-01-14 03:30:17 +03:00
let name = infix_name name in
2019-11-29 23:56:03 +03:00
match md ( Expr . sem name ) infix with
| ` Ok infix' -> infix'
2020-01-11 16:38:25 +03:00
| ` Fail msg -> report_error msg
2019-11-29 23:56:03 +03:00
in
match item with
2019-12-31 00:59:28 +03:00
| ` Infix ( _ , op , ` At op' ) -> insert op infix ( Infix . at l # coord op' op false )
| ` Infix ( ass , op , ` Before op' ) -> insert op infix ( Infix . before l # coord op' op ass false )
| ` Infix ( ass , op , ` After op' ) -> insert op infix ( Infix . after l # coord op' op ass false )
2019-11-29 23:56:03 +03:00
| _ -> infix
)
infix
( snd ( Interface . find import cmd # get_include_paths ) )
)
Infix . default
is
in
is , infix
} ;
parse [ cmd ] :
2020-01-05 03:33:17 +03:00
< ( is , infix ) > : imports [ cmd ] < ( d , infix' ) > : definitions [ infix ] expr : ! ( Expr . parse definitions infix' Expr . Weak ) ? {
2019-11-29 23:56:03 +03:00
( is , Infix . extract_exports infix' ) , Expr . Scope ( d , match expr with None -> Expr . Skip | Some e -> e )
2019-11-24 02:30:32 +03:00
} ;
2019-09-29 02:47:07 +03:00
definitions [ infix ] :
2020-01-11 16:38:25 +03:00
< ( def , infix' ) > : ! ( Definition . parse infix ( fun def infix atr -> Expr . scope def infix atr ( Expr . parse def ) ) definitions ) < ( defs , infix'' ) > : definitions [ infix' ] {
2019-11-24 02:30:32 +03:00
def @ defs , infix''
}
2019-03-25 00:13:42 +03:00
| empty { [] , infix }
)