:-object action : [bcilib, do_script, gesturelib].

  action(Name, Queue):-
    script_threads,
    repeat,
      get_queue(Queue, Event),
      proces_event(Name, Event),
    fail.
  
  proces_event(Name, rot(R)) :-
    setRotation(Name, 0.0,1.0,0.0, R).
  
  proces_event(Name, walk(X,Y,Z)) :-
    process_script(walk(Name, X,Y,Z)).

  proces_event(Name, stand) :-
    process_script(stand(Name)).
    
  select_script(Name, Script) :-
    script(Name, Script).

  turn_body_part(Agent,Body,Direction,Speed):-
    getBodyObjectName(Agent,Body,Object),
    getRotationParameter(Body,Direction,Rotation),
    getSpeedParameter(Body,Speed,Beat,Interpolation),
    !,
    turn_object(Object,Rotation,Beat,Interpolation).

  turn_body_part_init(Agent,Body,Direction):-
    getBodyObjectName(Agent,Body,Object),
    getRotationParameter(Body,Direction,rotation(X,Y,Z,_R)),
    !,
    setRotation(Object,X,Y,Z,0.0).


  move_body(Agent,Body,Direction,Speed):-
    getBodyObjectName(Agent,Body,_),
    getPositionParameter(Body,Direction,Position),
    getSpeedParameter(Body,Speed,Beat,Interpolation),
    !,  
    move_object(Agent,Position,Beat,Interpolation).

:-end_object action.

:-object do_script : [bcilib].
  var count = 0.
  var repcnt = 0.
  var max_threads = 12.
  var incrementr = 0.
  var sleeptime = 0.
  var incrementx = 0.
  var incrementy = 0.
  var incrementz = 0.
  var tempo = 60.
  script_threads :-
    set_field(answer_entry, free),
    set_field(thread_entry, free),
    new_array(script, thread_entry, max_threads),
    new_array(script, answer_entry, max_threads),
    script_threads(max_threads).
  script_threads(0) :-
                !.
  script_threads(I) :-
                N is I - 1,
    set_array(script, thread_entry, N, free),
    set_array(script, answer_entry, N, free),
                new(do_action(N), _),
                script_threads(N).
  select_entry(ArrayName, ThreadID) :-
    get_field_event(ArrayName, _Flag),
    NextThread is max_threads - 1,
    select_entry(NextThread, ArrayName, ThreadID),
    set_field(ArrayName, free).
  select_entry(I, ArrayName, _) :-
    I < 0,
    !,
    true.
    
  select_entry(I, ArrayName, ThreadID) :-
    get_array(script, ArrayName, I, State),
    State = free,
    !,
    set_array(script, ArrayName, I, lock),
    ThreadID = I.
  select_entry(I, ArrayName, Thread) :-
    N is I - 1,
    select_entry(N, ArrayName, Thread).
  release_entry(I, ArrayName) :-
    get_field_event(ArrayName, Flag),
    set_array(script, ArrayName, I, free),
    set_field(ArrayName, free).
  repeat_script(ScriptName, MaxCount) :-
    repcnt := 1,
    repeat,
      process_script(ScriptName),
      ++ repcnt,        
    repcnt > MaxCount,
    !.
  process_script(ScriptName):-
    select_script(ScriptName, ScriptCode),
    do_script(ScriptCode).
  do_script([]) :-
    !.
  do_script([Action | Y]) :-
    Action = turn(Agent,Object,Direction,Speed),
    !,
    turn_body_part(Agent,Object,Direction,Speed),
    do_script(Y).

  do_script([Action | Y]) :-
    Action = turn_init(Agent,Object,Direction),
    !,
    turn_body_part_init(Agent,Object,Direction),
    do_script(Y).


  do_script([Action | Y]) :-
    Action = [SubAction | SubActionList],
    !,
    do_script([SubAction]),
    do_script(SubActionList),
    do_script(Y).

  do_script([Action | Y]) :-
    Action = move(Agent,Direction,Speed),
    !,
    move_body(Agent,humanoidroot,Direction,Speed),
    do_script(Y).
  do_script([Action | Y]) :-
    Action = set_tempo(Tempo),
    !,
    format('gesture action: ~w~n', [Action]),
    tempo := Tempo,
    do_script(Y).
  do_script([Action | Y]) :-
    Action = wait(Time),
    !,
    SleepTime is Time * 1000,
    sleep(SleepTime),
    do_script(Y).
  do_script([Action | Y]) :-
    Action = skip(_Action),
    !,
    do_script(Y),
    true.
  do_script([Action | Y]) :-
    Action = skip,
    !,
    do_script(Y),
    true.
  do_script([Action | Y]) :-
    Action = parallel(ActionList),
    !,
%   format('parallel action list: ~w~n', [ActionList]),
    length(ActionList, ActionListLength),
    %% select a free answer slot :
    select_entry(answer_entry, Answer),
    count_down_init(Answer, ActionListLength),
%               format('ActionListLength : ~w~n', [ActionListLength]),
    process_parallel_action(ActionList, Answer),
    format_to_atom(Parent, 'parent_~w', [Answer]),
    get_field_event(Parent, ReplyValue),
%   format('all worker threads done : ~w (answer id ~w)~n', [ReplyValue, Answer]),
    release_entry(Answer, answer_entry),
    do_script(Y).
  do_script([Action | Y]) :-
    Action = script(ScriptName),
    !,
    process_script(ScriptName),
    do_script(Y).
  do_script([Action | Y]) :-
    Action = repeat(Script,Times),
    !,
    repeat_script(Script, Times),
    do_script(Y).

  do_script([Action | Y]) :-
    Action = choice([Actions]),
    !,
    process_choice([Actions]),
    do_script(Y).

  do_script([Action | Y]) :-
    Action = do(Goal),
    !,
%%    format('~w~n',[Action]),
    inspect_goal(Goal),
    do_script(Y),
    true.

  do_script([Action | Y]) :-
    Action = test(State),
    !,
    inspect_goal(State),
    do_script(Y),
    true.

  do_script([Action | Y]) :-
    Action = star(Action1),
    !,
    process_star(Action1),
    do_script(Y),
    true.

  do_script([Action |Y]) :-
    !,
    format('unknown gesture action: ~w~n', [Action]),
    do_script(Y).
  do_script(Action) :-
    format('unknown gesture action:~w (not a list)~n', [Action]).

     

  process_choice([]):-!.

  process_choice([Action|_Y]):-
      do_script(Action),
      !.

  process_choice([_Action|Y]):-
      process_choice(Y),
      !.
  process_star(Action):-
      do_script(Action),
      !.

  process_star(Action):-
      !,
      process_star(Action),
      true.


  inspect_goal((Goal1,Goal2)) :-
    !,
    do_goal(Goal1),
    inspect_goal(Goal2).
  inspect_goal(Goal) :-
    do_goal(Goal).
  do_goal(setRotation(O,X,Y,Z,R)) :-
    !,
    setRotation(O,X,Y,Z,R).
  do_goal(getRotation(O,X,Y,Z,R)) :-
    !,
    getRotation(O,X,Y,Z,R).

  do_goal(setPosition(O,X,Y,Z)) :-
    !,
    setPosition(O,X,Y,Z).

  do_goal(getPosition(O,X,Y,Z)) :-
    !,
    getPosition(O,X,Y,Z).

  do_goal(getBodyObjectName(A,O,N)) :-
    !,
    gesturelib <- getBodyObjectName(A,O,N).

  do_goal(Goal):-
    call(Goal).
    
  count_down_init(Answer, Counter) :-
    set_array(script, answer_entry, Answer, Counter).
  count_down_join(Answer, ThreadID) :-
    get_field_event(answer_entry, _Flag),
    get_array(script, answer_entry, Answer, C),
%   format('count_down_join : a = ~w, c = ~w, t = ~w~n', [Answer,C,ThreadID]),
                C1 is C - 1,
                set_array(script, answer_entry, Answer, C1),
    set_field(answer_entry, free),
                count_down_last(C1, Answer).
        count_down_last(C, Answer) :-
                C =< 0,
                !,
    format_to_atom(Parent, 'parent_~w', [Answer]),
                %% set_queue(Parent, done).
    %% use field instead :
                set_field(Parent, done).
        count_down_last(_, _).
  turn_object(Object, rotation(X,Y,Z,R), Time, Interpolation):-
    getRotation(Object,X1,Y1,Z1,R1),
    %% format('start Rotation:<~w,~w,~w,~w>~n',[X1,Y1,Z1,R1]),
    count := 0,
    incrementr := (R-R1)/Interpolation,
    incrementx := (X-X1)/Interpolation,
    incrementy := (Y-Y1)/Interpolation,
    incrementz := (Z-Z1)/Interpolation,
    sleeptime := (60/tempo)*Time*1000/Interpolation,
    repeat,
      Rnew is R1+incrementr*(count+1),
      Xnew is X1+incrementx*(count+1),
      Ynew is Y1+incrementy*(count+1),
      Znew is Z1+incrementz*(count+1),      
      setRotation(Object,Xnew,Ynew,Znew,Rnew),
      sleep(sleeptime),
      ++count,
    abs(Rnew-R) =< abs(incrementr),
    setRotation(Object,X,Y,Z,R),
    !.
  
  move_object(Object, increment(X,Y,Z), Time, Interpolation):-
    getSFVec3f(Object,translation,X1,Y1,Z1),
    count:=0,
    X_increment is X/Interpolation,
    Y_increment is Y/Interpolation,
    Z_increment is Z/Interpolation,
    SleepTime is (60/tempo)*Time*1000/Interpolation,
    repeat,
      Xnew is X1 + X_increment*(count+1),
      Ynew is Y1 + Y_increment*(count+1),
      Znew is Z1 + Z_increment*(count+1),
      setSFVec3f(Object,translation, Xnew,Ynew,Znew),
      sleep(SleepTime),
      ++count,
    count >= Interpolation,
    !.
  process_parallel_action([], _Answer) :-
    !.
  process_parallel_action([Action | List], Answer) :-
    select_entry(thread_entry, I),
    %% format('parallel : thread = ~w, answer = ~w, action = ~w~n', [I,Answer,Action]),
    format_to_atom(Queue, 'queue_~w', [I]),
                set_queue(Queue, task(Action,Answer)),
                process_parallel_action(List, Answer).
  look_at_audience(Agent,Viewpoint):-
    getSFVec3f(Viewpoint,position,X,_Y,Z),
    look_at_position(Agent,X,Z),
    true.
  look_at_position(Agent,X1,Z1) :-
    getSFVec3f(Agent,translation, X,_,Z),
    X =\= X1,
    !,  %% RS: added
    Xdif is X-X1,
    Zdif is Z1-Z,
    R is atan(Zdif/Xdif) - sign(X-X1)*1.5708,
    setRotation(Agent,0.0, 1.0, 0.0, R).
  look_at_position(_, _, _).
:-end_object do_script.

:-object do_action : [bcilib, do_script, gesturelib].
  do_action(ThreadID) :-
    format_to_atom(Queue, 'queue_~w', [ThreadID]),
    repeat,
      get_queue(Queue, task(Action, Answer)),
      %% format('~w gets action ~w (answer = ~w)~n', [Queue,Action,Answer]),
      do_script([Action]),
      count_down_join(Answer, ThreadID),
      release_entry(ThreadID, thread_entry),
    fail.
  select_script(Name, Script) :-
    script(Name, Script).
  turn_body_part(Agent,Body,PoserR,Speed):-
    %% format('turn_body_part : A=~w, B=~w, P=~w, S=~w~n', [Agent,Body,PoserR,Speed]),
    getBodyObjectName(Agent,Body,Object),
    getRotationParameter(Body,PoserR,Rotation),
    getSpeedParameter(Body,Speed,Time,Interpolation),
    !,
    turn_object(Object,Rotation,Time,Interpolation).

  turn_body_part_init(Agent,Body,Direction):-
    getBodyObjectName(Agent,Body,Object),
    getRotationParameter(Body,Direction,rotation(X,Y,Z,_R)),
    !,
    setRotation(Object,X,Y,Z,0.0).

  move_body(Agent,Body,Direction,Speed):-
    getBodyObjectName(Agent,Body,_),
    getPositionParameter(Body,Direction,Position),
    getSpeedParameter(Body,Speed,Time,Interpolation),
    !,  
    move_object(Agent,Position,Time,Interpolation).

:-end_object do_action.

:-object gesturelib.

  var unit_interpolation = 6.0.

  script(walk(Agent), ActionList) :-
    ActionList = [
        parallel([turn(Agent,r_shoulder,back_down2,fast),
        turn(Agent,r_hip,front_down2,fast),
    turn(Agent,l_shoulder,front_down2,fast),
    turn(Agent,l_hip,back_down2,fast)]),
    parallel([turn(Agent,l_shoulder,back_down2,fast),
    turn(Agent,l_hip,front_down2,fast),
    turn(Agent,r_shoulder,front_down2,fast),
    turn(Agent,r_hip,back_down2,fast)])
    ],
    !.

script(walk(Agent, X,Y,Z), ActionList) :-
    ActionList = [
      parallel([
        turn(Agent,r_shoulder,back_down2,fast),
        turn(Agent,r_hip,front_down2,fast),
        move(Agent,increment(X,Y,Z),fast),
        turn(Agent,l_shoulder,front_down2,fast),
        turn(Agent,l_hip,back_down2,fast)]),
      parallel([
        turn(Agent,l_shoulder,back_down2,fast),
        turn(Agent,l_hip,front_down2,fast),
        move(Agent,increment(X,Y,Z),fast),
        turn(Agent,r_shoulder,front_down2,fast),
        turn(Agent,r_hip,back_down2,fast)])
    ],
    !.


script(walk(Agent, StepLength), ActionList) :-
    ActionList = [
      parallel([
        turn(Agent,r_shoulder,back_down2,fast),
        turn(Agent,r_hip,front_down2,fast),
        move(Agent,increment(0.0,0.0,StepLength),fast),
        turn(Agent,l_shoulder,front_down2,fast),
        turn(Agent,l_hip,back_down2,fast)]),
      parallel([
        turn(Agent,l_shoulder,back_down2,fast),
        turn(Agent,l_hip,front_down2,fast),
        move(Agent,increment(0,0,StepLength),fast),
        turn(Agent,r_shoulder,front_down2,fast),
        turn(Agent,r_hip,back_down2,fast)])
    ],
    !.

script(get_adjustY(Agent, Y), ActionList) :-
    ActionList = [ do(getBodyObjectName(Agent, l_ankle, ObjectName)),
           do(getPosition(ObjectName,_X1,Y1,_Z1)),
           turn(Agent,l_hip,back_down2,fast),
           do(getPosition(ObjectName,_X2,Y2,_Z2)),
           do(Y is Y2-Y1),
           turn(Agent,l_hip,down,fast)
           ],
           !.


script(walk_adjustY(Agent,Y,StepLength), ActionList) :-
    ActionList = [do(Y1 is -Y),
          parallel([script(walk(Agent)),
         [move(Agent,increment(0.0,Y,StepLength),very_fast),
          move(Agent,increment(0.0,Y1,StepLength),very_fast)]
            ])
        
        ],
    !.




  script(fast_walk(Agent), ActionList) :-
    ActionList = [
      set_tempo(300),
      parallel([turn(Agent,r_shoulder,back_down2,fast),
    turn(Agent,r_hip,front_down2,fast),
    turn(Agent,l_shoulder,front_down2,fast),
    turn(Agent,l_hip,back_down2,fast)]),
    parallel([turn(Agent,l_shoulder,back_down2,fast),
    turn(Agent,l_hip,front_down2,fast),
    turn(Agent,r_shoulder,front_down2,fast),
    turn(Agent,r_hip,back_down2,fast)])
    ],
    !.

  script(walk_front(Agent), ActionList) :-
    ActionList = [
    parallel([turn(Agent,r_shoulder,back_down2,fast),
        turn(Agent,r_hip,front_down2,fast),
        move(Agent,front,fast),
        turn(Agent,l_shoulder,front_down2,fast),
        turn(Agent,l_hip,back_down2,fast)]),
    parallel([turn(Agent,l_shoulder,back_down2,fast),
        turn(Agent,l_hip,front_down2,fast),
        move(Agent,front,fast),
        turn(Agent,r_shoulder,front_down2,fast),
        turn(Agent,r_hip,back_down2,fast)])
    ],
    !.
  script(jump(Agent), ActionList) :-
    ActionList = [
    turn_init(Agent,l_shoulder,up),
    parallel([turn(Agent,r_knee,back,fast),
        turn(Agent,r_hip,front_down,fast),
        move(Agent,down,fast),
        turn(Agent,r_shoulder,up,fast),
        turn(Agent,l_shoulder,up,fast),
        turn(Agent,l_knee,back,fast),
        turn(Agent,l_hip,front_down,fast)]),
    turn_init(Agent,l_shoulder,left),
    parallel([turn(Agent,l_knee,down,fast),
        turn(Agent,l_hip,down,fast),
        move(Agent,up,fast),
        turn(Agent,r_shoulder,right,fast),
        turn(Agent,l_shoulder,left,fast),
        turn(Agent,r_knee,down,fast),
        turn(Agent,r_hip,down,fast)]),
    turn_init(Agent,l_shoulder,down_from_front),
    parallel([move(Agent,up,fast),
         turn(Agent,r_shoulder,down_from_front,fast),
         turn(Agent,l_shoulder,down_from_front,fast)]),
    
    move(Agent,down,fast)
    ],
    !.
  
script(stand(Agent), ActionList) :-
    ActionList = [
	parallel([
	  turn(Agent,l_shoulder,down,fast),
    	  turn(Agent,r_shoulder,down,fast),
    	  turn(Agent,l_hip,down,fast),
    	  turn(Agent,r_hip,down,fast)
	])
    ],
    !.

  script(stand2(Agent), ActionList) :-
    ActionList = [
    turn_init(Agent,r_shoulder,down),
    parallel([turn(Agent,l_shoulder,down,fast),
    turn(Agent,r_shoulder,down,fast),
    turn(Agent,skullbase,front,fast),
    turn(Agent,l_hip,down,fast),
    turn(Agent,r_hip,down,fast)]),
    parallel([turn(Agent,l_knee,down,fast),
    turn(Agent,r_knee,down,fast)])
    ],
    !.
  script(kicking(Agent), ActionList) :-
    ActionList = [
      parallel([turn(Agent,r_hip,back_down,fast),
          turn(Agent,r_knee,back,fast),
          turn(Agent,r_shoulder,front_down2,fast),
          turn(Agent,l_shoulder,back_down2,fast)
          ]),
      parallel([turn(Agent,r_hip,front,fast),
          turn(Agent,r_knee,front_down2,fast),
          turn(Agent,l_shoulder,front_down2,fast),
          turn(Agent,r_shoulder,back_down2,fast)
          ])
    ],
    !.
  
  
        
  script(kneeing(Agent), ActionList) :-
    ActionList = [parallel([turn(Agent, r_elbow, front, fast), 
        turn(Agent, l_elbow, front, fast)]),
        parallel([turn(Agent, l_hip, front_down2, fast),
        turn(Agent, r_hip, front_down2, fast),
        turn(Agent, l_knee, back, fast),
        turn(Agent, r_knee, back, fast)])
    ],
    !.
  script(start_run(Agent), ActionList) :-
    ActionList = [parallel([turn(Agent, r_elbow, front, fast), 
        turn(Agent, l_elbow, front, fast)]),
        parallel([turn(Agent, l_hip, front_down2, fast),
        turn(Agent, r_hip, front_down2, fast),
        turn(Agent, l_knee, back_down, fast),
        turn(Agent, r_knee, back_down, fast)])
    ],
    !.
  script(run1(Agent), ActionList) :-
    ActionList = [parallel([turn(Agent,r_shoulder,back_down2,fast),
    turn(Agent,r_hip,front,fast),
    turn(Agent,l_shoulder,front_down2,fast),
    turn(Agent,l_hip,back_down2,fast)]),
    parallel([turn(Agent,l_shoulder,back_down2,fast),
    turn(Agent,l_hip,front,fast),
    turn(Agent,r_shoulder,front_down2,fast),
    turn(Agent,r_hip,back_down2,fast)])
    ],
    !.
  script(run(Agent), ActionList) :-
    ActionList = [parallel([turn(Agent,r_shoulder,back_down2,fast),
    turn(Agent,r_hip,front_down,fast),
    turn(Agent,l_shoulder,front_down2,fast),
    turn(Agent,l_hip,back_down2,fast)]),
    parallel([turn(Agent,l_shoulder,back_down2,fast),
    turn(Agent,l_hip,front_down,fast),
    turn(Agent,r_shoulder,front_down2,fast),
    turn(Agent,r_hip,back_down2,fast)])
    ],
    !.
  script(l_wave(Agent), ActionList) :-
    ActionList = [turn(Agent,l_shoulder,left_front_up,fast),
    turn(Agent,l_shoulder,left_front2_up,fast)],
    !.
  script(l_wave2(Agent), ActionList) :-
    ActionList = [turn(Agent,l_shoulder,left_front_up,fast),
    turn(Agent,l_shoulder,up_turn_90,fast)],
    !.
  script(r_wave(Agent), ActionList) :-
    ActionList = [turn(Agent,r_shoulder,right_front_up,fast),
    turn(Agent,r_shoulder,right_front2_up,fast)],
    !.
  script(r_wave2(Agent), ActionList) :-
    ActionList = [turn(Agent,r_shoulder,right_front_up,fast),
    turn(Agent,r_shoulder,up_turn_90,fast)],
    !.
  script(greeting(Agent), ActionList) :-
    ActionList = [parallel([
        turn_init(Agent,r_shoulder,right_front_up),
        repeat(l_wave2(Agent),8),
        repeat(r_wave2(Agent),8)]),
          script(stand2(Agent)),
          wait(1.0)
    ],
    !.
  script(open_leg1(Agent), ActionList) :-
    ActionList = [parallel([turn(Agent,l_hip,side1_down,fast),
        turn(Agent,r_hip,side1_down,fast)])],
    !.
  
  
  script(test(Agent), ActionList) :-
    ActionList = [
    do(format('Agent action: walking~n')),
    repeat(walk(Agent), 6),
    do(format('Agent action: kicking~n')),
    repeat(kicking(Agent), 6),
    script(stand1(Agent)),
    do(format('Agent action: running~n')),
    script(start_run(Agent)),
    repeat(run(Agent), 6),
    script(stand1(Agent)),
    do(format('Agent action: jumping~n')),
    repeat(jump(Agent), 6),
    script(stand1(Agent)),
    do(format('Agent action: greeting~n')),
    repeat(greeting(Agent), 3),
    script(stand1(Agent))
    ],
    !.

  script(taichi(Agent), ActionList) :-
    ActionList = [
    do(format('Agent action: taichi~n')),
    script(taichi(Agent, stage1)),
  % script(taichi(Agent, stage2)),
  % turn(Agent,humanoidroot,turn_45,very_slow),
    script(stand1(Agent))
  % turn(Agent,humanoidroot,turn_45,very_slow)
    ],
    !.


script(taichi(Agent, stage1), ActionList) :-
    ActionList = [
    turn(Agent,l_hip,side1_down,fast),
    turn(Agent,r_hip,side1_down,fast),
    turn_init(Agent,l_shoulder,front),
    turn_init(Agent,r_shoulder,front),
    parallel([turn(Agent,l_shoulder,front,slow),
          turn(Agent,r_shoulder,front,slow)]),
    turn_init(Agent,l_elbow,front_right2),
    parallel([turn(Agent,l_shoulder,front_down,slow),
          turn(Agent,r_shoulder,front_down,slow),
          turn(Agent,l_elbow,front_right2,slow),
          turn(Agent,r_elbow,front_left2,slow)]),
    turn_init(Agent,l_hip,left_front_down),
    turn_init(Agent,r_hip,right_front_down),
    turn_init(Agent,l_knee,back2_down),
    turn_init(Agent,r_knee,back2_down),
    turn_init(Agent,l_elbow,right_front_down),
    parallel([
          move(Agent,increment(0.0,-0.1,0.0),slow),
          turn(Agent,l_hip,left_front_down,slow),
          turn(Agent,r_hip,right_front_down,slow),
          turn(Agent,l_elbow,right_front_down,slow),
          turn(Agent,r_shoulder,front_down2,slow),
          turn(Agent,l_knee,back2_down,slow),
          turn(Agent,r_knee,back2_down,slow)]),
    turn_init(Agent,l_shoulder,left_front_up2),
    turn_init(Agent,r_elbow,front),
    parallel([turn(Agent,l_shoulder,left_front_up2,very_slow),
        turn(Agent,r_wrist,turn_n45,slow),
        turn(Agent,r_elbow,front,slow),
          turn(Agent,r_shoulder,front_left,very_slow)]),
    parallel([turn(Agent,l_wrist,turn_90,slow),
          turn(Agent,r_wrist,turn_90,slow)])
    ],
    !.

script(taichi(Agent, stage2), ActionList) :-
    ActionList = [
    turn_init(Agent,humanoidroot,turn_n45),
    parallel([turn(Agent,humanoidroot,turn_n45,very_slow),
    turn(Agent,r_shoulder,right_front_down,very_slow),
    turn(Agent,r_knee,back_down2,very_slow)]),
    parallel([turn(Agent,l_shoulder,right_front_down,fast),
    turn(Agent,l_elbow,front,fast)]),
    turn_init(Agent,l_hip,front_down1),
    parallel([turn(Agent,r_knee,back,slow),
    turn(Agent,l_knee,back,slow),
    turn(Agent,l_hip,front_down1,slow)]),
    parallel([turn(Agent,l_hip,left_down,slow),
    turn(Agent,l_shoulder,front,slow),
    turn(Agent,r_shoulder,front,slow),
    turn(Agent,l_elbow,down,slow),
    turn(Agent,r_elbow,down,slow),
    turn(Agent,l_knee,down,slow)]),
    parallel([turn(Agent,l_hip,front_down,slow),
    turn(Agent,l_shoulder,front_down,slow),
    turn(Agent,r_shoulder,front_down,slow),
    turn(Agent,l_elbow,front,slow),
    turn(Agent,r_elbow,front,slow),
    turn(Agent,l_knee,back,slow)])
    ],
    !.



%high level interaction operator definitions

script(if_then_else(Condition,Then,Else),ActionList):-
    ActionList =[
         choice([[test(Condition),Then],[test(not(Condition)),Else]])
        ],
        !.

script(if_then(Condition,Then),ActionList):-
    ActionList =[
         choice([[test(Condition),Then],[test(not(Condition)),skip]])
        ],
        !.


script(until(Action,Condition),ActionList):-
    ActionList =[
         [star(Action),test(Condition)]
        ],
        !.

  getBodyObjectName(humanoid,l_shoulder,hanim_l_shoulder) :- !.
  getBodyObjectName(humanoid,r_shoulder,hanim_r_shoulder) :- !.
  getBodyObjectName(humanoid,l_elbow,hanim_l_elbow) :- !.
  getBodyObjectName(humanoid,r_elbow,hanim_r_elbow) :- !.
  getBodyObjectName(humanoid,l_hip,hanim_l_hip) :- !.
  getBodyObjectName(humanoid,r_hip,hanim_r_hip) :- !.
  getBodyObjectName(humanoid,l_ankle,hanim_l_ankle) :- !.
  getBodyObjectName(humanoid,r_ankle,hanim_r_ankle) :- !.
  getBodyObjectName(humanoid,l_knee,hanim_l_knee) :- !.
  getBodyObjectName(humanoid,r_knee,hanim_r_knee) :- !.
  getBodyObjectName(humanoid,l_wrist,hanim_l_wrist) :- !.
  getBodyObjectName(humanoid,r_wrist,hanim_r_wrist) :- !.
  getBodyObjectName(humanoid,vl5,hanim_vl5) :- !.
  getBodyObjectName(humanoid,skullbase,hanim_skullbase) :- !.
  getBodyObjectName(humanoid,humanoidroot,hanim_HumanoidRoot) :- !.
  getBodyObjectName(humanoid,sacroiliac,hanim_sacroiliac) :- !.
  getBodyObjectName(H, B, N) :-
    format('invalid name : H=~w, B=~w, N=~w~n', [H,B,N]).
  object_class(l, l_shoulder) :- !.
  object_class(r, r_shoulder) :- !.
  object_class(l, l_elbow) :- !.
  object_class(r, r_elbow) :- !.
  object_class(l, l_hip) :- !.
  object_class(r, r_hip) :- !.
  object_class(l, l_ankle) :- !.
  object_class(r, r_ankle) :- !.
  object_class(l, l_knee) :- !.
  object_class(r, r_knee) :- !.
  object_class(l, l_wrist) :- !.
  object_class(r, r_wrist) :- !.
  object_class(c,vl5) :- !.
  object_class(c,skullbase) :- !.
  object_class(c,root) :- !.
  object_class(c,sacroiliac) :- !.
  object_class(c,humanoidroot) :- !.
  object_class(C, B) :-
    format('object class error : C=~w, B=~w~n', [C,B]).
  getRotationParameter(_Object,rotation(X,Y,Z,R0),rotation(X,Y,Z,R0)):-
    !.
  
  getRotationParameter(Object,Direction,R):-
    object_class(ObjectClass,Object),
    rotation_parameter(ObjectClass,Direction,R),
    !.
  getRotationParameter(Object,_Poser,_R):-
    format('rotation parameter error for ~w~n', [Object]).
  
  
  rotation_parameter(l, front, rotation(1.0,0.0,0.0,-1.57)):-!.
  rotation_parameter(l, back, rotation(1.0,0.0,0.0,1.57)):-!.
  rotation_parameter(l, back_down2, rotation(1.0,0.0,0.0,0.4)):-!.
  rotation_parameter(l, front_down2, rotation(1.0,0.0,0.0,-0.4)):-!.
  rotation_parameter(l, back_down, rotation(1.0,0.0,0.0,0.77)):-!.
  rotation_parameter(l, back2_down, rotation(1.0,0.0,0.0,1.17)):-!.
  rotation_parameter(l, front_down, rotation(1.0,0.0,0.0,-0.77)):-!.
  rotation_parameter(l, front_down1, rotation(1.0,0.0,0.0,-1.37)):-!.
  rotation_parameter(l, back_up, rotation(1.0,0.0,0.0,-2.34)):-!.
  rotation_parameter(l, front_up, rotation(1.0,0.0,0.0,2.34)):-!.
  rotation_parameter(l, up_via_back, rotation(1.0,0.0,0.0,3.14)):-!.
  rotation_parameter(l, up, rotation(1.0,0.0,0.0,-3.14)):-!.
  rotation_parameter(l, turn_90, rotation(0.0,1.0,0.0,1.57)):-!.
  rotation_parameter(l, turn_n90, rotation(0.0,1.0,0.0,-1.57)):-!.
  rotation_parameter(l, turn_45, rotation(0.0,1.0,0.0,0.79)):-!.
  rotation_parameter(l, turn_n45, rotation(0.0,1.0,0.0,-0.79)):-!.
  rotation_parameter(l, turn_180, rotation(0.0,1.0,0.0,3.14)):-!.
  rotation_parameter(l, turn_n180, rotation(0.0,1.0,0.0,-3.14)):-!.
  rotation_parameter(l, turn_270, rotation(0.0,1.0,0.0,4.71)):-!.
  rotation_parameter(l, turn_n270, rotation(0.0,1.0,0.0,-4.71)):-!.
  rotation_parameter(l, turn_360, rotation(0.0,1.0,0.0,6.28)):-!.
  rotation_parameter(l, turn_n360, rotation(0.0,1.0,0.0,-6.28)):-!.
  rotation_parameter(l, turn_reset, rotation(0.0,1.0,0.0,0.0)):-!.
  rotation_parameter(l, front_right, rotation(1.0,1.0,0.0,-1.57)):-!.
  rotation_parameter(l, front_right2, rotation(1.0,1.0,0.0,-1.3)):-!.
  rotation_parameter(l, front_right1, rotation(1.0,1.0,0.0,-1.0)):-!.
  rotation_parameter(l, back_down_turn_90, rotation(1.0,1.0,0.0,1.57)):-!.
  rotation_parameter(l, left_back_down_turn_90, rotation(0.0,1.0,1.0,1.57)):-!.
  rotation_parameter(l, right_back_down_turn_n90, rotation(0.0,1.0,1.0,-1.57)):-!.
  rotation_parameter(l, left_front_down_turn_90, rotation(0.0,1.0,1.0,1.57)):-!.
  rotation_parameter(l, left_front_down, rotation(-0.97,0.09,0.23,0.79)):-!.
  rotation_parameter(l, right_front_down, rotation(-0.37,-0.86,0.35,1.13)):-!.
  rotation_parameter(l, down, rotation(0.0,0.0,1.0,0.0)):-!.
  rotation_parameter(l, down_from_front, rotation(1.0,0.0,0.0,0.0)):-!.
  rotation_parameter(l, up_via_center,rotation(0.0,0.0,1.0,3.14)):-!.
  rotation_parameter(l, up_via_right,rotation(0.0,0.0,1.0,3.14)):-!.
  rotation_parameter(l, up_via_side,rotation(0.0,0.0,1.0,-3.14)):-!.
  rotation_parameter(l, up_via_left,rotation(0.0,0.0,1.0,-3.14)):-!.
  rotation_parameter(l, side_up, rotation(0.0,0.0,1.0,2.34)):-!.
  rotation_parameter(l, side, rotation(0.0,0.0,1.0,1.57)):-!.
  rotation_parameter(l, left_up, rotation(0.0,0.0,1.0,2.34)):-!.
  rotation_parameter(l, left, rotation(0.0,0.0,1.0,1.57)):-!.
  rotation_parameter(l, side_down, rotation(0.0,0.0,1.0,0.77)):-!.
  rotation_parameter(l, left_down, rotation(0.0,0.0,1.0,0.77)):-!.
  rotation_parameter(l, side2_down, rotation(0.0,0.0,1.0,0.38)):-!.
  rotation_parameter(l, left2_down, rotation(0.0,0.0,1.0,0.38)):-!.
  rotation_parameter(l, side1_down, rotation(0.0,0.0,1.0,0.19)):-!.
  rotation_parameter(l, left1_down, rotation(0.0,0.0,1.0,0.19)):-!.
  rotation_parameter(l, center_up, rotation(0.0,0.0,1.0,-2.34)):-!.
  rotation_parameter(l, right_up, rotation(0.0,0.0,1.0,-2.34)):-!.
  rotation_parameter(l, left_front2_up, rotation(-1.0,0.0,1.0,2.34)):-!.
  rotation_parameter(l, left_front_up2, rotation(-1.0,0.0,1.0,1.57)):-!.
  rotation_parameter(l, side_front2_up, rotation(-1.0,0.0,1.0,2.34)):-!.
  rotation_parameter(l, side_front_up2, rotation(-1.0,0.0,1.0,1.57)):-!.
  rotation_parameter(l, left_front_up, rotation(-0.38,-0.16,0.91,2.4)):-!.
  rotation_parameter(l, side_front_up, rotation(-0.38,-0.16,0.91,2.4)):-!.
  rotation_parameter(l, up_turn_n90, rotation(-0.71,0,-0.71,3.14)):-!.
  rotation_parameter(l, up_turn_90, rotation(-0.71,0,0.71,3.14)):-!.
  rotation_parameter(l, front_turn_90, rotation(-0.58,0.58,-0.58,2.0)):-!.
  rotation_parameter(l, center, rotation(0.0,0.0,1.0,-1.57)):-!.
  rotation_parameter(l, right, rotation(0.0,0.0,1.0,-1.57)):-!.
  rotation_parameter(l, center_down, rotation(0.0,0.0,1.0,-0.77)):-!.
  rotation_parameter(l, right_down, rotation(0.0,0.0,1.0,-0.77)):-!.
  
  
  
  
  rotation_parameter(r, front,rotation(1.0,0.0,0.0,-1.57)):-!.
  rotation_parameter(r, back,rotation(1.0,0.0,0.0,1.57)):-!.
  rotation_parameter(r, front_down2, rotation(1.0,0.0,0.0,-0.4)):-!.
  rotation_parameter(r, back_down2, rotation(1.0,0.0,0.0,0.4)):-!.
  rotation_parameter(r, back2_down, rotation(1.0,0.0,0.0,1.17)):-!.
  rotation_parameter(r, front_down, rotation(1.0,0.0,0.0,-0.77)):-!.
  rotation_parameter(r, front_down1, rotation(1.0,0.0,0.0,-1.37)):-!.
  rotation_parameter(r, back_down, rotation(1.0,0.0,0.0,0.77)):-!.
  rotation_parameter(r, up_via_back, rotation(1.0,0.0,0.0,3.14)):-!.
  rotation_parameter(r, up, rotation(1.0,0.0,0.0,-3.14)):-!.
  rotation_parameter(r, turn_90, rotation(0.0,1.0,0.0,1.57)):-!.
  rotation_parameter(r, turn_n90, rotation(0.0,1.0,0.0,-1.57)):-!.
  rotation_parameter(r, turn_45, rotation(0.0,1.0,0.0,0.79)):-!.
  rotation_parameter(r, turn_n45, rotation(0.0,1.0,0.0,-0.79)):-!.
  rotation_parameter(r, turn_180, rotation(0.0,1.0,0.0,3.14)):-!.
  rotation_parameter(r, turn_n180, rotation(0.0,1.0,0.0,-3.14)):-!.
  rotation_parameter(r, turn_270, rotation(0.0,1.0,0.0,4.71)):-!.
  rotation_parameter(r, turn_n270, rotation(0.0,1.0,0.0,-4.71)):-!.
  rotation_parameter(r, turn_360, rotation(0.0,1.0,0.0,6.28)):-!.
  rotation_parameter(r, turn_n360, rotation(0.0,1.0,0.0,-6.28)):-!.
  rotation_parameter(r, turn_reset, rotation(0.0,1.0,0.0,0.0)):-!.
  rotation_parameter(r, front_right, rotation(1.0,1.0,0.0,-1.57)):-!.
  rotation_parameter(r, front_left, rotation(-1.0,1.0,0.0,1.57)):-!.
  rotation_parameter(r, front_left2, rotation(-1.0,1.0,0.0,1.3)):-!.
  rotation_parameter(r, front_left1, rotation(-1.0,1.0,0.0,1.00)):-!.
  rotation_parameter(r, back_down_turn_90, rotation(1.0,1.0,0.0,1.57)):-!.
  rotation_parameter(r, left_back_down_turn_90, rotation(0.0,1.0,1.0,1.57)):-!.
  rotation_parameter(r, right_back_down_turn_n90, rotation(0.0,1.0,1.0,-1.57)):-!.
  rotation_parameter(r, left_front_down_turn_90, rotation(-1.0,1.0,0.0,1.57)):-!.
  rotation_parameter(r, down,rotation(0.0,0.0,1.0,0.0)):-!.
  rotation_parameter(r, down_from_front, rotation(1.0,0.0,0.0,0.0)):-!.
  rotation_parameter(r, up_via_side,rotation(0.0,0.0,1.0,3.14)):-!.
  rotation_parameter(r, up_via_left,rotation(0.0,0.0,1.0,3.14)):-!.
  rotation_parameter(r, up_via_center,rotation(0.0,0.0,1.0,-3.14)):-!.
  rotation_parameter(r, up_via_left,rotation(0.0,0.0,1.0,-3.14)):-!.
  rotation_parameter(r, side_up,rotation(0.0,0.0,1.0,-2.34)):-!.
  rotation_parameter(r, side,rotation(0.0,0.0,1.0,-1.57)):-!.
  rotation_parameter(r, right_up,rotation(0.0,0.0,1.0,-2.34)):-!.
  rotation_parameter(r, right,rotation(0.0,0.0,1.0,-1.57)):-!.
  rotation_parameter(r, side_down, rotation(0.0,0.0,1.0,-0.77)):-!.
  rotation_parameter(r, right_down, rotation(0.0,0.0,1.0,-0.77)):-!.
  rotation_parameter(r, side2_down, rotation(0.0,0.0,1.0,-0.38)):-!.
  rotation_parameter(r, left2_down, rotation(0.0,0.0,1.0,-0.38)):-!.
  rotation_parameter(r, side1_down, rotation(0.0,0.0,1.0,-0.19)):-!.
  rotation_parameter(r, left1_down, rotation(0.0,0.0,1.0,-0.19)):-!.  
  rotation_parameter(r, center, rotation(0.0,0.0,1.0,1.57)):-!.
  rotation_parameter(r, left, rotation(0.0,0.0,1.0,1.57)):-!.
  rotation_parameter(r, center_down, rotation(0.0,0.0,1.0,0.77)):-!.
  rotation_parameter(r, left_down, rotation(0.0,0.0,1.0,0.77)):-!.
  rotation_parameter(r, center_up, rotation(0.0,0.0,1.0,2.34)):-!.
  rotation_parameter(r, left_up, rotation(0.0,0.0,1.0,2.34)):-!.
  rotation_parameter(r, right_front2_up, rotation(-1.0,0.0,-1.0,2.34)):-!.
  rotation_parameter(r, right_front_up2, rotation(-1.0,0.0,-1.0,1.57)):-!.
  rotation_parameter(r, right_front_down, rotation(-0.97,-0.09,-0.23,0.79)):-!.
% rotation_parameter(r, left_front_down, rotation(0.97,-0.09,-0.23,0.79)):-!.
  rotation_parameter(r, side_front2_up, rotation(-1.0,0.0,-1.0,2.34)):-!.
  rotation_parameter(r, side_front_up2, rotation(-1.0,0.0,-1.0,1.57)):-!.
  rotation_parameter(r, right_front_up, rotation(-0.38,0.16,-0.91,2.4)):-!.
  rotation_parameter(r, side_front_up, rotation(-0.38,0.16,-0.91,2.4)):-!.
  rotation_parameter(r, up_turn_n90, rotation(-0.71,0,0.71,3.14)):-!.
  rotation_parameter(r, up_turn_90, rotation(-0.71,0,-0.71,3.14)):-!.
  
  rotation_parameter(r, front_turn_90, rotation(-0.58,-0.58,0.58,2.0)):-!.
  
  rotation_parameter(r, back_up, rotation(1.0,0.0,0.0,2.34)):-!.
  rotation_parameter(r, side_up2, rotation(1.0,0.0,0.0,-2.34)):-!.
  rotation_parameter(r, right_up2, rotation(1.0,0.0,0.0,-2.34)):-!.
  rotation_parameter(c, right, rotation(0.0,0.0,1.0,1.47)):-!.
  rotation_parameter(c, up, rotation(1.0,0.0,0.0,-1.57)):-!.
  rotation_parameter(c, right_down, rotation(0.0,0.0,1.0,3.00)):-!.
  rotation_parameter(c, left_down, rotation(0.0,0.0,1.0,-3.00)):-!.
  rotation_parameter(c, down, rotation(1.0,0.0,0.0,1.57)):-!.
  rotation_parameter(c, left_turn, rotation(0.0,1.0,0.0,1.57)):-!.
  rotation_parameter(c, right_turn, rotation(0.0,1.0,0.0,-1.57)):-!.
  rotation_parameter(c, front, rotation(0.0,0.0,1.0,0.0)):-!.
  rotation_parameter(c, right_down2, rotation(0.0,0.0,1.0,2.34)):-!.
  rotation_parameter(c, left_down2, rotation(0.0,0.0,1.0,-2.34)):-!.
  rotation_parameter(c, left_down1, rotation(0.0,0.0,1.0,-1.57)):-!.
  rotation_parameter(c, right_down1, rotation(0.0,0.0,1.0,1.57)):-!.
  rotation_parameter(c, front_down2, rotation(1.0,0.0,0.0,0.4)):-!.
  rotation_parameter(c, front_up2, rotation(1.0,0.0,0.0,-0.4)):-!.
  rotation_parameter(c, front_down, rotation(1.0,0.0,0.0,0.77)):-!.
  rotation_parameter(c, front_up, rotation(1.0,0.0,0.0,-0.77)):-!.
  rotation_parameter(c, back_up, rotation(1.0,0.0,0.0,-2.34)):-!.
  rotation_parameter(c, front_down3, rotation(1.0,0.0,0.0,2.34)):-!.
  rotation_parameter(c, front_left_down, rotation(1.0,1.0,0.0,0.77)):-!.
  rotation_parameter(c, front_right_up, rotation(1.0,1.0,0.0,-0.77)):-!.
  rotation_parameter(c, front_right_down, rotation(1.0,0.0,1.0,0.77)):-!.
  rotation_parameter(c, front_left_up, rotation(1.0,0.0,1.0,-0.77)):-!.
  rotation_parameter(c, front_left_up_turn, rotation(0.0,1.0,1.0,0.77)):-!.
  rotation_parameter(c, front_left_down_turn, rotation(0.0,1.0,1.0,-0.77)):-!.
  rotation_parameter(c, turn_22, rotation(0.0,1.0,0.0,0.38)):-!.
  rotation_parameter(c, turn_n22, rotation(0.0,1.0,0.0,-0.38)):-!.
  rotation_parameter(c, turn_45, rotation(0.0,1.0,0.0,0.79)):-!.
  rotation_parameter(c, turn_n45, rotation(0.0,1.0,0.0,-0.79)):-!.
  rotation_parameter(c, turn_90, rotation(0.0,1.0,0.0,1.57)):-!.
  rotation_parameter(c, turn_n90, rotation(0.0,1.0,0.0,-1.57)):-!.
  rotation_parameter(c, turn_180, rotation(0.0,1.0,0.0,3.14)):-!.
  rotation_parameter(c, turn_n180, rotation(0.0,1.0,0.0,-3.14)):-!.
  rotation_parameter(c, turn_270, rotation(0.0,1.0,0.0,4.71)):-!.
  rotation_parameter(c, turn_n270, rotation(0.0,1.0,0.0,-4.71)):-!.
  rotation_parameter(c, turn_360, rotation(0.0,1.0,0.0,6.28)):-!.
  rotation_parameter(c, turn_n360, rotation(0.0,1.0,0.0,-6.28)):-!.
  rotation_parameter(c, turn_reset, rotation(0.0,1.0,0.0,0.0)):-!.
% rotation_parameter(c, left_front2_up, rotation(-1.0,0.0,1.0,2.34)):-!.
% rotation_parameter(c, left_front_up2, rotation(-1.0,0.0,1.0,1.57)):-!.
% rotation_parameter(c, side_front2_up, rotation(-1.0,0.0,1.0,2.34)):-!.
% rotation_parameter(c, side_front_up2, rotation(-1.0,0.0,1.0,1.57)):-!.
% rotation_parameter(c, left_front_up, rotation(-0.38,-0.16,0.91,2.4)):-!.
  rotation_parameter(c, right_front_up, rotation(0.38,-0.16,0.91,0.4)):-!.
  rotation_parameter(c, right_back_down, rotation(-0.38,-0.16,0.91,2.4)):-!.
  rotation_parameter(c, right_front_down, rotation(0.38,0.16,0.91,2.4)):-!.
  rotation_parameter(c, left_back_up, rotation(0.38,-0.16,-0.91,0.4)):-!.
  rotation_parameter(c, right_back_up, rotation(0.38,-0.16,-0.91,-0.4)):-!.
  rotation_parameter(c, right_front_up2, rotation(1.0,1.0,1.0,0.1)):-!.


  rotation_parameter(C, Po, R):-
    format('rotation error : C=~w, Po=~w, R=~w~n', [C,Po,R]).
  position_parameter(c, front, increment(0.0,0.0,0.7)):-!.
  position_parameter(c, back, increment(0.0,0.0,-0.7)):-!.
  position_parameter(c, left, increment(0.7,0.0,0.0)):-!.
  position_parameter(c, right, increment(-0.7,0.0,0.0)):-!.
  position_parameter(c, up, increment(0.0,0.5,0.0)):-!.
  position_parameter(c, down, increment(0.0,-0.5,0.0)):-!.
  position_parameter(C, Po, P):-
    format('position error : C=~w, Po=~w, P=~w~n', [C,Po,P]).
  getPositionParameter(_Object,increment(X,Y,Z),increment(X,Y,Z)):-
  !.
  getPositionParameter(Object,Direction,Position):-
    object_class(ObjectClass,Object),
    position_parameter(ObjectClass,Direction,Position).
  getSpeedParameter(_Object,beat(Beat),Beat,Interpolation):-
    Interpolation is unit_interpolation * Beat,
    !.
  getSpeedParameter(_Object,time(Time,second),Beat,Interpolation):-
%   Beat is Time*tempo/60.0,
    Beat is Time,
    Interpolation is unit_interpolation * Beat,
    !.
  
  getSpeedParameter(Object,Speed,Beat,Interpolation):-
    object_class(ObjectClass,Object),
    speed_parameter(ObjectClass,Speed,Beat),
    Interpolation is unit_interpolation * Beat,
    !.
  getSpeedParameter(Object, _Speed, _Beat, _Interpolation):-
    format('speed parameter error for ~w~n', [Object]).
  speed_parameter(l, slow, 3):-!.
  speed_parameter(l, very_slow, 5):-!.
  speed_parameter(l, intermedia, 2):-!.
  speed_parameter(l, fast, 1):-!.
  speed_parameter(l, very_fast, 0.5):-!.
  speed_parameter(r, slow, 3):-!.
  speed_parameter(r, very_slow, 5):-!.
  speed_parameter(r, intermedia, 2):-!.
  speed_parameter(r, fast, 1):-!.
  speed_parameter(r, very_fast, 0.5):-!.
  speed_parameter(c, slow, 3):-!.
  speed_parameter(c, very_slow, 5):-!.
  speed_parameter(c, intermedia, 2):-!.
  speed_parameter(c, fast, 1):-!.
  speed_parameter(c, very_fast, 0.5):-!.
  speed_parameter(C, S, T):-
    format('spped error : C=~w, S=~w, T=~w~n', [C,S,T]).
:-end_object gesturelib.
