(**
Module: Faustexp
- Description: dimension estimation and delay estimation of faust expressions.
+ Description: Faust expression evaluation
@author WANG Haisheng
- Created: 03/06/2013 Modified: 04/06/2013
+ Created: 03/06/2013 Modified: 04/08/2013
*)
open Types;;
+open Basic;;
+open Symbol;;
open Value;;
+open Signal;;
+open Beam;;
+
+exception NotYetDone;;
+exception Dimension_error of string;;
+exception Process_error of string;;
+
+class dimension : int * int -> dimension_type =
+ fun (init : int * int) ->
+ object (self)
+ val _input = fst init
+ val _output = snd init
+
+ method input = _input
+ method output = _output
+
+ method par : dimension_type -> dimension_type =
+ fun dim ->
+ new dimension
+ ((self#input + dim#input), (self#output + dim#output))
+
+ method seq : dimension_type -> dimension_type =
+ fun dim ->
+ if self#output = dim#input then
+ new dimension (self#input, dim#output)
+ else raise (Dimension_error "seq dimension not matched.")
+
+ method split : dimension_type -> dimension_type =
+ fun dim ->
+ if dim#input mod self#output = 0 then
+ new dimension (self#input, dim#output)
+ else raise (Dimension_error "split dimension not matched.")
+
+ method merge : dimension_type -> dimension_type =
+ fun dim ->
+ if self#output mod dim#input = 0 then
+ new dimension (self#input, dim#output)
+ else raise (Dimension_error "merge dimension not matched.")
+
+ method _rec : dimension_type -> dimension_type =
+ fun dim ->
+ if self#output >= dim#input && self#input >= dim#output then
+ new dimension (self#input - dim#output, self#output)
+ else raise (Dimension_error "rec dimension not matched.")
+ end;;
+
+(*
+class process : faust_exp -> process_type =
+ 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;;
+*)
+
+class proc_const : faust_exp -> process_type =
+ fun (exp_init : faust_exp) ->
+ object (self)
+ val _exp = exp_init
+ val _dim = new dimension (0,1)
+ val _delay = 0
+ val _const =
+ match exp_init with
+ | Const b -> b
+ | _ -> raise (Process_error "const process constructor.")
+
+ method exp = _exp
+ method dim = _dim
+ method delay = _delay
+ 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 proc_ident : faust_exp -> process_type =
+ fun (exp_init : faust_exp) ->
+ object (self)
+ val _exp = exp_init
+ val _symbol =
+ match exp_init with
+ | Ident s -> s
+ | _ -> raise (Process_error "ident process constructor.")
+
+ val _dim = new dimension (dimension_of_symbol self#symb)
+ val _delay = delay_of_symbol _symbol
+
+ method exp = _exp
+ method dim = _dim
+ method delay = _delay
+ method 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))#vectorzie 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))
+ | Selec2 -> 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 proc_par : faust_exp -> process_type =
+ fun (exp_init : faust_exp) ->
+ object (self)
+ val _exp = exp_init
+ val _exp_left =
+ match exp_init with
+ | Par (e1, e2) -> e1
+ | _ -> raise (Process_error "par process constructor.")
+ val _exp_right =
+ match exp_init with
+ | Par (e1, e2) -> e2
+ | _ -> raise (Process_error "par process constructor.")
+
+ val proc_left = (new proc_factory)#make _exp_left
+ val proc_right = (new proc_factory)#make _exp_right
+
+ val _dim = (proc_left#dim)#par proc_right#dim
+ val _delay = max proc_left#delay proc_right#delay
+
+ method exp = _exp
+ method dim = _dim
+ method delay = _delay
+
+ method eval : beam_type -> beam_type =
+ fun (input : beam_type) ->
+ let (sub_input1, sub_input2) = input#cut proc_left#dim#input in
+ let sub_output1 = proc_left#eval sub_input1 in
+ let sub_output2 = 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)
+ val _exp = exp_init
+ val _exp_left =
+ match exp_init with
+ | Split (e1, e2) -> e1
+ | _ -> raise (Process_error "par process constructor.")
+ val _exp_right =
+ match exp_init with
+ | Split (e1, e2) -> e2
+ | _ -> raise (Process_error "par process constructor.")
+
+ val proc_left = (new proc_factory)#make _exp_left
+ val proc_right = (new proc_factory)#make _exp_right
+
+ val _dim = (proc_left#dim)#split proc_right#dim
+ val _delay = proc_left#delay + proc_right#delay
+
+ method exp = _exp
+ method dim = _dim
+ method delay = _delay
+
+ method eval : beam_type -> beam_type =
+ fun (input : beam_type) ->
+ let mid_output = proc_left#eval input in
+ let mid_input = mid_output#matching proc_right#dim#input in
+ proc_right#eval mid_input
+ end
+
+
+and proc_merge : faust_exp -> process_type =
+ fun (exp_init : faust_exp) ->
+ object (self)
+ val _exp = exp_init
+ val _exp_left =
+ match exp_init with
+ | Merge (e1, e2) -> e1
+ | _ -> raise (Process_error "merge process constructor.")
+ val _exp_right =
+ match exp_init with
+ | Merge (e1, e2) -> e2
+ | _ -> raise (Process_error "merge process constructor.")
+
+ val proc_left = (new proc_factory)#make _exp_left
+ val proc_right = (new proc_factory)#make _exp_right
+
+ val _dim = (proc_left#dim)#merge proc_right#dim
+ val _delay = proc_left#delay + proc_right#delay
+
+ method exp = _exp
+ method dim = _dim
+ method delay = _delay
+
+ method eval : beam_type -> beam_type =
+ fun (input : beam_type) ->
+ let mid_output = proc_left#eval input in
+ let mid_input = mid_output#matching proc_right#dim#input in
+ proc_right#eval mid_input
+
+ end
+
+and proc_seq : faust_exp -> process_type =
+ fun (exp_init : faust_exp) ->
+ object (self)
+ val _exp = exp_init
+ val _exp_left =
+ match exp_init with
+ | Seq (e1, e2) -> e1
+ | _ -> raise (Process_error "seq process constructor.")
+ val _exp_right =
+ match exp_init with
+ | Seq (e1, e2) -> e2
+ | _ -> raise (Process_error "seq process constructor.")
+
+ val proc_left = (new proc_factory)#make _exp_left
+ val proc_right = (new proc_factory)#make _exp_right
+
+ val _dim = (proc_left#dim)#seq proc_right#dim
+ val _delay = proc_left#delay + proc_right#delay
+
+ method exp = _exp
+ method dim = _dim
+ method delay = _delay
+
+ method eval : beam_type -> beam_type =
+ fun (input : beam_type) ->
+ let mid_output = proc_left#eval input in
+ proc_right#eval mid_output
+ end
+
+and proc_rec : faust_exp -> process_type =
+ fun (exp_init : faust_exp) ->
+ object (self)
+ val _exp = exp_init
+ val _exp_left =
+ match exp_init with
+ | Rec (e1, e2) -> e1
+ | _ -> raise (Process_error "rec process constructor.")
+ val _exp_right =
+ match exp_init with
+ | Rec (e1, e2) -> e2
+ | _ -> raise (Process_error "rec process constructor.")
+
+ val proc_left = (new proc_factory)#make _exp_left
+ val proc_right = (new proc_factory)#make _exp_right
+
+ val _dim = (proc_left#dim)#_rec proc_right#dim
+ val _delay = proc_left#delay
+
+ method exp = _exp
+ method dim = _dim
+ method delay = _delay
+
+ method eval : beam_type -> beam_type =
+ fun (input : beam_type) ->
+ let mid_output = proc_left#eval input in
+ proc_right#eval mid_output
+
+
+ end
+
+and proc_factory =
+ object
+ 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;;
-(* EXCEPTIONS *)
-(** Exception raised in beam matching of faust expressions.*)
-exception Beam_Matching_Error of string;;
-(** Exception raised in case that the branch under call hasn't yet been programed.*)
-exception NotYetDone;;
(* PROCESS DELAY ESTIMATION *)
|Pass -> 0
|Stop -> 0
|Mem -> 1
- |Delay -> 100000 (* danger! *)
+ |Delay -> 100000
|Floor -> 0
|Int -> 0
|Sin -> 0
- |Cos -> 0
- |Atan -> 0
- |Atantwo -> 0
- |Sqrt -> 0
- |Rdtable -> 100000 (* danger! *)
+ |Rdtable -> 100000
|Mod -> 0
|Larger -> 0
|Smaller -> 0
- |Vectorize -> 100 (* danger! *)
+ |Vectorize -> 100
|Concat -> 0
|Nth -> 0
|Serialize -> 0
(** val subtree_right : dimension -> dimension, returns the right subtree of dimension tree.*)
let subtree_right = fun d_tree -> subtree d_tree 1;;
-
-(** val d_par : int * int -> int * int -> int * int, process dimension for constructor "par(,)",
-which is the addition of two dimensions.*)
-let d_par a b = (((fst a) + (fst b)), ((snd a) + (snd b)));;
-
-
-(** val d_seq : int * int -> int * int -> int * int, process dimension for constructor "seq(:)",
-which is (size of input beam of first exp, size of output beam of second exp)
-along with beam matching.*)
-let d_seq a b = if (snd a) = (fst b) then (fst a, snd b) else raise (Beam_Matching_Error "seq");;
-
-
-(** val d_split : int * int -> int * int -> int * int, process dimension for constructor "split(<:)",
-which is (size of input beam of first exp, size of output beam of second exp)
-along with beam matching.*)
-let d_split a b =
- if ((fst b) mod (snd a)) = 0 then
- (fst a, snd b)
- else raise (Beam_Matching_Error "split");;
-
-
-(** val d_merge : int * int -> int * int -> int * int, process dimension for constructor "merge(:>)",
-which is (size of input beam of first exp, size of output beam of second exp)
-along with beam matching. *)
-let d_merge a b =
- if ((snd a) mod (fst b)) = 0 then
- (fst a, snd b)
- else raise (Beam_Matching_Error "merge");;
-
-
-(** val d_rec : int * int -> int * int -> int * int, process dimension for constructor "rec(~)",
-which is (size of input beam of first exp - size of output beam of second exp,
-size of output beam of first exp)
-along with beam matching.*)
-let d_rec a b =
- if (fst a) >= (snd b) && (snd a) >= (fst b) then
- ((fst a) - (snd b), snd a)
- else raise (Beam_Matching_Error "rec");;
-
-
(** val dim : faust_exp -> int * int, returns dimension for faust expression,
along with beam matching.*)
let rec dim exp_faust =
|Floor -> End (1, 1)
|Int -> End (1, 1)
|Sin -> End (1, 1)
- |Cos -> End (1, 1)
- |Atan -> End (1, 1)
- |Atantwo -> End (2, 1)
- |Sqrt -> End (1, 1)
|Rdtable -> End (3, 1)
|Mod -> End (2, 1)
|Vectorize -> End (2, 1)