X-Git-Url: https://svn.cri.mines-paristech.fr/git/Faustine.git/blobdiff_plain/4d5f39ea1ae1eff1d8eadf7875851be467e40a47..64fedf639ee3d2bd048028414097632726d24d42:/interpretor/faustexp.ml?ds=sidebyside

diff --git a/interpretor/faustexp.ml b/interpretor/faustexp.ml
index 684eb75..cc725ba 100644
--- a/interpretor/faustexp.ml
+++ b/interpretor/faustexp.ml
@@ -6,21 +6,30 @@
 *)
 
 open Types;;
+open Basic;;
+open Symbol;;
 open Value;;
 open Signal;;
 open Beam;;
 
 exception NotYetDone;;
 exception Dimension_error of string;;
+exception Process_error of string;;
+
+
+(* PARSER *)
+
+let exp_of_string s = (Parser.main Lexer.token (Lexing.from_string s));;
+
 
 class dimension : int * int -> dimension_type = 
   fun (init : int * int) -> 
     object (self)
-      val dim_input = fst init
-      val dim_output = snd init
+      val _input = fst init
+      val _output = snd init
 
-      method input = dim_input
-      method output = dim_output
+      method input = _input
+      method output = _output
 
       method par : dimension_type -> dimension_type = 
 	fun dim -> 
@@ -52,230 +61,219 @@ class dimension : int * int -> dimension_type =
 	  else raise (Dimension_error "rec dimension not matched.")
     end;;
 
-class process : faust_exp -> process_type = 
+class virtual process = 
   fun (exp_init : faust_exp) ->
-  object (self)
-    val exp = exp_init
-    val left = 
-      match exp_init with
-      |	Const b -> exp_init
-      |	Ident s -> exp_init
-      |	Par (e1, e2) -> e1
-      |	Seq (e1, e2) -> e1
-      |	Split (e1, e2) -> e1
-      |	Merge (e1, e2) -> e1
-      |	Rec (e1, e2) -> e1
-
-    val right = 
-      match exp_init with
-      |	Const b -> exp_init
-      |	Ident s -> exp_init
-      |	Par (e1, e2) -> e2
-      |	Seq (e1, e2) -> e2
-      |	Split (e1, e2) -> e2
-      |	Merge (e1, e2) -> e2
-      |	Rec (e1, e2) -> e2
-
-    val proc_left = 
-
-      val dim = new dimension
-      val delay = 0
-      method get_exp = exp
-      method get_dim = dim
-      method get_delay = delay
-      method to_string = "NotYetDone"
-      method virtual evaluate : beam_type -> beam_type
-  end;;
-
+    object
+      val _exp = exp_init
+      val virtual _dim : dimension_type
+      val virtual _delay : int
+      method exp = _exp
+      method dim = _dim
+      method delay = _delay
+      method virtual eval : beam_type -> beam_type
+    end
 
 class proc_const : faust_exp -> process_type = 
   fun (exp_init : faust_exp) ->
-    object (self)
-      val exp = exp_init
-      val dim = 
-      method evaluate = fun b1 ->
-	
-      end;;
-
-
-class exp_ident = 
-  object
-      inherit expression
-
-      end;;
-
-
-class exp_par = 
-  object
-     inherit expression
-
-      end;;
-
-
-class exp_split = 
-  object
-     inherit expression
+    let _const = 
+      match exp_init with
+      | Const b -> b
+      | _ -> raise (Process_error "const process constructor.") in
 
+    object (self)
+      inherit process exp_init
+      val _dim = new dimension (0,1)
+      val _delay = 0
+      method private const = _const
+      method eval : beam_type -> beam_type = 
+	fun (input : beam_type) ->
+	  if input#get = [||] then
+	    new beam [| new signal 0 (fun t -> new value self#const)|]
+	  else
+	    raise (Process_error "proc_const accepts no input.")
       end;;
 
 
-class exp_merge = 
-  object
-     inherit expression
+class proc_ident : faust_exp -> process_type = 
+  fun (exp_init : faust_exp) ->
+    let _symbol = 
+	  match exp_init with
+	  | Ident s -> s
+	  | _ -> raise (Process_error "ident process constructor.") in
 
+    object (self)
+      inherit process exp_init
+      val _dim = new dimension (dimension_of_symbol _symbol)
+      val _delay = delay_of_symbol _symbol      
+      method private symb = _symbol
+
+      method private beam_of_ident : int -> signal_type -> beam_type = 
+	fun (n : int) ->
+	  fun (s : signal_type) ->
+	    if n = (self#dim)#input then 
+	      new beam [|s|]
+	    else raise (Process_error ("Ident " ^ string_of_symbol self#symb))
+
+      method eval : beam_type -> beam_type = 
+	fun (input : beam_type) ->
+	  let n = Array.length input#get in
+	  match self#symb with
+	  | Pass -> self#beam_of_ident n input#get.(0)
+	  | Stop -> if n = 1 then new beam [||] 
+	            else raise (Process_error "Ident !")
+	  | Add -> self#beam_of_ident n 
+		((input#get.(0))#add input#get.(1))
+	  | Sub -> self#beam_of_ident n 
+		((input#get.(0))#sub input#get.(1))
+	  | Mul -> self#beam_of_ident n 
+		((input#get.(0))#mul input#get.(1))
+	  | Div -> self#beam_of_ident n 
+		((input#get.(0))#div input#get.(1))
+	  | Mem -> self#beam_of_ident n 
+		((input#get.(0))#mem)
+	  | Delay -> self#beam_of_ident n 
+		((input#get.(0))#delay input#get.(1))
+	  | Floor -> self#beam_of_ident n 
+		((input#get.(0))#floor)
+	  | Int -> self#beam_of_ident n 
+		((input#get.(0))#int)
+	  | Sin -> self#beam_of_ident n 
+		((input#get.(0))#sin)
+	  | Cos -> self#beam_of_ident n 
+		((input#get.(0))#cos)
+	  | Atan -> self#beam_of_ident n 
+		((input#get.(0))#atan)
+	  | Atan2 -> self#beam_of_ident n 
+		((input#get.(0))#atan2 input#get.(1))
+	  | Sqrt -> self#beam_of_ident n 
+		((input#get.(0))#sqrt)
+	  | Rdtable -> self#beam_of_ident n 
+		((input#get.(1))#rdtable input#get.(0) input#get.(2))
+	  | Mod -> self#beam_of_ident n 
+		((input#get.(0))#_mod input#get.(1))
+	  | Vectorize -> self#beam_of_ident n 
+		((input#get.(0))#vectorize input#get.(1))
+	  | Vconcat -> self#beam_of_ident n 
+		((input#get.(0))#vconcat input#get.(1))
+	  | Vpick -> self#beam_of_ident n 
+		((input#get.(0))#vpick input#get.(1))
+	  | Serialize -> self#beam_of_ident n 
+		(input#get.(0))#serialize
+	  | Larger -> self#beam_of_ident n 
+		((input#get.(0))#larger input#get.(1))
+	  | Smaller -> self#beam_of_ident n 
+		((input#get.(0))#smaller input#get.(1))
+	  | Prefix -> self#beam_of_ident n 
+		((input#get.(1))#prefix input#get.(0))
+	  | Select2 -> self#beam_of_ident n 
+		((input#get.(0))#select2 input#get.(1) input#get.(2))
+	  | Select3 -> self#beam_of_ident n 
+		((input#get.(0))#select3 input#get.(1) 
+		   input#get.(2) input#get.(3))
       end;;
 
-class exp_seq = 
-  object
-     inherit expression
+class virtual process_binary =
+  fun (exp_init : faust_exp) ->
+    let (exp_left, exp_right) = 
+      match exp_init with
+      | Par (e1, e2) -> (e1, e2)
+      |	Seq (e1, e2) -> (e1, e2)
+      |	Split (e1, e2) -> (e1, e2)
+      |	Merge (e1, e2) -> (e1, e2)
+      |	Rec (e1, e2) -> (e1, e2)
+      | _ -> raise (Process_error "binary process constructor.") in
+    let proc_left = (new proc_factory)#make exp_left in
+    let proc_right = (new proc_factory)#make exp_right in
+    
+    object
+      inherit process exp_init
+      method private proc_left = proc_left
+      method private proc_right = proc_right
+
+      val _dim = 
+	match exp_init with
+	| Par (e1, e2) -> (proc_left#dim)#par proc_right#dim
+	| Seq (e1, e2) -> (proc_left#dim)#seq proc_right#dim
+	| Split (e1, e2) -> (proc_left#dim)#split proc_right#dim
+	| Merge (e1, e2) -> (proc_left#dim)#merge proc_right#dim
+	| Rec (e1, e2) -> (proc_left#dim)#_rec proc_right#dim
+	| _ -> raise (Process_error "binary process constructor.")
+
+      val _delay = 
+	match exp_init with
+	| Par (e1, e2) -> max proc_left#delay proc_right#delay
+	| Seq (e1, e2) -> proc_left#delay + proc_right#delay
+	| Split (e1, e2) -> proc_left#delay + proc_right#delay
+	| Merge (e1, e2) -> proc_left#delay + proc_right#delay
+	| Rec (e1, e2) -> proc_left#delay + proc_right#delay
+	| _ -> raise (Process_error "binary process constructor.")
+    end
+
+and proc_par : faust_exp -> process_type = 
+  fun (exp_init : faust_exp) ->
+    object (self)
+      inherit process_binary exp_init
+      method eval : beam_type -> beam_type = 
+	fun (input : beam_type) ->
+	  let (sub_input1, sub_input2) = input#cut self#proc_left#dim#input in
+	  let sub_output1 = self#proc_left#eval sub_input1 in
+	  let sub_output2 = self#proc_right#eval sub_input2 in
+	  sub_output1#append sub_output2
+      end
+
+and proc_split : faust_exp -> process_type =
+  fun (exp_init : faust_exp) ->
+    object (self)
+      inherit process_binary exp_init
+      method eval : beam_type -> beam_type = 
+	fun (input : beam_type) ->
+	  let mid_output = self#proc_left#eval input in
+	  let mid_input = mid_output#matching self#proc_right#dim#input in
+	  self#proc_right#eval mid_input
+      end
 
-      end;;
 
-class exp_rec = 
+and proc_merge : faust_exp -> process_type =
+  fun (exp_init : faust_exp) -> 
+    object (self)
+      inherit process_binary exp_init
+      method eval : beam_type -> beam_type = 
+	fun (input : beam_type) ->
+	  let mid_output = self#proc_left#eval input in
+	  let mid_input = mid_output#matching self#proc_right#dim#input in
+	  self#proc_right#eval mid_input
+      end
+
+and proc_seq : faust_exp -> process_type =
+  fun (exp_init : faust_exp) -> 
+    object (self)
+      inherit process_binary exp_init
+      method eval : beam_type -> beam_type = 
+	fun (input : beam_type) ->
+	  let mid_output = self#proc_left#eval input in
+	  self#proc_right#eval mid_output
+      end
+
+and proc_rec : faust_exp -> process_type =
+  fun (exp_init : faust_exp) -> 
+  object (self)
+    inherit process_binary exp_init
+    method eval : beam_type -> beam_type = 
+      fun (input : beam_type) ->
+	let mid_output = self#proc_left#eval input in
+	self#proc_right#eval mid_output
+  end
+
+and proc_factory = 
   object
-     inherit expression
-
-      end;;
-
-*)
-
-
-
-
-(* PROCESS DELAY ESTIMATION *)
-
-(** val delay : faust_exp -> int, returns the number of delays estimated staticly.
-Attention: delays of "@" is estimated as 10 constant, 
-delays of "vectorize" and "serialize" haven't been implemented, 
-delays of "rdtable" hasn't been implemented.*)
-let rec delay exp_faust = match exp_faust with
-	|Const v	->	0
-	|Ident s	->
-		(
-			match s with
-			|Add			->	0
-			|Sup			->	0		
-			|Mul			->	0
-			|Div			->	0
-			|Pass			->	0
-			|Stop			->	0
-			|Mem			->	1
-			|Delay			->	100000 
-			|Floor		        ->	0
-			|Int			->	0
-			|Sin			->	0
-			|Rdtable		->	100000
-			|Mod			->	0
-			|Larger			->	0
-			|Smaller		->	0
-			|Vectorize		->	100
-			|Concat			->	0
-			|Nth			->	0
-			|Serialize		->	0
-			|Prefix	 	        ->	1
-			|Selecttwo		->	0
-			|Selectthree		->	0
-		)
-	|Par (e1, e2)	->	max (delay e1) (delay e2)
-	|Seq (e1, e2)	->	(delay e1) + (delay e2)
-	|Split (e1, e2)	->	(delay e1) + (delay e2)
-	|Merge (e1, e2)	->	(delay e1) + (delay e2)
-	|Rec (e1, e2)	->	delay e1;;	
-
-
-(* PARSER *)
-
-(** val exp_of_string : string -> faust_exp, faust expression parser. *)
-let exp_of_string s = (Parser.main Lexer.token (Lexing.from_string s));;
-
-
-
-(* PROCESS DIMENSION ESTIMATION *)
-(* process dimension := (size of input beam, size of output beam).*)
-
-
-(** val get_root : dimension -> int * int, returns the root of dimension tree. *)
-let get_root = fun d_tree -> match d_tree with
-                        | End d -> d
-			| Tree (d, branches) -> d;;
-
-
-(** val subtree : dimention -> int -> dimension, returns a subtree of dimension tree.*)
-let subtree = fun d_tree -> fun i ->
-  match d_tree with
-  | End d -> raise (Beam_Matching_Error "Subtree left absent.")
-  | Tree (d, branches) -> (
-      match branches with 
-	(left, right) -> if i = 0 then left else right);;
-
-(** val subtree_left : dimension -> dimension, returns the left subtree of dimension tree.*)
-let subtree_left = fun d_tree -> subtree d_tree 0;;
-
-
-(** val subtree_right : dimension -> dimension, returns the right subtree of dimension tree.*)
-let subtree_right = fun d_tree -> subtree d_tree 1;;
-
-(** val dim : faust_exp -> int * int, returns dimension for faust expression, 
-along with beam matching.*)
-let rec dim exp_faust = 
-
-(** val dimension_constructor : ((int * int) -> (int * int) -> (int * int)) -> faust_exp 
--> faust_exp -> dimension,
-returns the dimension tree of constructor(e1, e2).*)
-        let dimension_constructor = fun constructor -> fun e1 -> fun e2 ->
-	    let subtree1 = dim e1 in
-	    let subtree2 = dim e2 in
-	    let root = constructor (get_root subtree1) (get_root subtree2) in
-	    Tree (root, (subtree1, subtree2)) in
-
-        match exp_faust with
-	|Const v -> End (0, 1)
-	|Ident s -> 
-		(
-			match s with
-			|Add			->	End (2, 1)
-			|Sup			->	End (2, 1)		
-			|Mul			->	End (2, 1)
-			|Div			->	End (2, 1)
-			|Pass			->	End (1, 1)
-			|Stop			->	End (1, 0)
-			|Mem			->	End (1, 1)
-			|Delay			->	End (2, 1)
-			|Floor	    	        ->      End (1, 1)
-			|Int			->	End (1, 1)
-			|Sin			->	End (1, 1)
-			|Rdtable		->	End (3, 1)
-			|Mod  		        ->	End (2, 1)
-			|Vectorize		->	End (2, 1)
-			|Concat			->	End (2, 1)
-			|Nth			->	End (2, 1)
-			|Serialize		->	End (1, 1)
-			|Larger			->	End (2, 1)
-			|Smaller		->	End (2, 1)
-			|Prefix		        ->	End (2, 1)
-			|Selecttwo		->	End (3, 1)
-			|Selectthree		->	End (4, 1)
-		)
-
-	|Par (e1, e2)           ->      dimension_constructor d_par e1 e2
-	|Seq (e1, e2)		->	dimension_constructor d_seq e1 e2
-	|Split (e1, e2)		->	dimension_constructor d_split e1 e2
-	|Merge (e1, e2)		->	dimension_constructor d_merge e1 e2
-	|Rec (e1, e2)		->	dimension_constructor d_rec e1 e2;;
-
-
-
-(* AUXILIARY 'CONVERT_TO_STRING' FUNCTIONS *)
-
-(** val print_exp : faust_exp -> unit, print to console the input faust expression.*)
-let print_exp exp = 
-  let rec string_of_exp exp = match exp with
-    |Const v		->	"Const" ^ " (" ^ (string_of_value v) ^ ")"
-    |Ident s		->	"Ident" ^ " \"" ^ "s" ^ "\""
-    |Par (e1, e2)	->	"Par" ^ " (" ^ (string_of_exp e1) ^ ", " ^ (string_of_exp e2) ^ ")"
-    |Seq (e1, e2)	->	"Seq" ^ " (" ^ (string_of_exp e1) ^ ", " ^ (string_of_exp e2) ^ ")"
-    |Split (e1, e2)	->	"Split" ^ " (" ^ (string_of_exp e1) ^ ", " ^ (string_of_exp e2) ^ ")"
-    |Merge (e1, e2)	->	"Merge" ^ " (" ^ (string_of_exp e1) ^ ", " ^ (string_of_exp e2) ^ ")"
-    |Rec (e1, e2)	->	"Rec" ^ " (" ^ (string_of_exp e1) ^ ", " ^ (string_of_exp e2) ^ ")"
-  in
-    print_string("Parer : Types.faust_exp = "^ (string_of_exp exp));;
+      method make : faust_exp -> process_type = 
+	fun (exp : faust_exp) ->
+	  match exp with
+	  | Const b -> new proc_const exp
+	  | Ident s -> new proc_ident exp
+	  | Par (e1, e2) -> new proc_par exp
+	  | Seq (e1, e2) -> new proc_seq exp
+	  | Split (e1, e2) -> new proc_split exp
+	  | Merge (e1, e2) -> new proc_merge exp
+	  | Rec (e1, e2) -> new proc_rec exp
+  end;;