A20_548

download A20_548

of 8

Transcript of A20_548

  • 7/25/2019 A20_548

    1/8

    13th World Congress in Mechanism and Machine Science, Guanajuato, Mexico, 19-25 June, 2011 A20_548

    The Spherical Four-Bar Mechanism: Optimum Synthesis with DE Algorithm

    and Animation Using Mathematica R

    R. Peon-Escalante C. Villanueva F. Penunuri

    Universidad Autonoma de Yucatan Universidad Autonoma de Yucatan Universidad Autonoma de Yucatan

    Merida, Mexico. Merida, Mexico. Merida, Mexico.

    Abstract In this work an easy way to make optimum

    synthesis and animations of spherical four bar mechanisms

    is presented. We provide the necessary mathematical bag-

    gage and the original Differential evolution method which

    will be used for the optimization of the structural error. The

    animations are provided inM athematicaR although, the

    treatment is done in such a way that almost any interpreterprogram (MATLAB R, Octave, sage, etc) can be used.

    Keywords: Spherical mechanism, Path generation, Differential

    Evolution, Kinematic Synthesis.

    I. Introduction

    A spherical four-bar mechanism is a closed chain, con-

    sists of four links and four revolute pairs. These linkages

    have the property that every link in the system rotates about

    the same fixed point [1]. Thus in a spherical mechanism

    any point in a moving body is confined to move within a

    spherical surface, and all spherical surfaces of motion are

    concentric [2].Some relevant papers on kinematic synthesis of spherical

    mechanisms are described briefly:

    Denavit used matrix of homogeneous transformation [3],

    and Suh displacement matrix, addressing the three prob-

    lems of analytical synthesis [4]. Suh studied the feasibility

    of constructing an external mechanical linkage that might

    serve as an orthopedic brace for guidance of the femur rel-

    ative to the pelvis, since the relative motion at the human

    hip joint approximates spherical motion [5] . Chiang re-

    view some of important knowledge and techniques about

    this issue [2].

    Gupta presents algebraic-geometrical methods to elimi-

    nate branch and circuit defects in the synthesis [6]. Sunemployed the Fourier method offers a practical approach to

    the design of spherical four-bar linkages function generator

    [7].

    In [8] a robust geometric approach was proposed for

    solving the inputoutput equations of planar, spherical and

    spatial four-bar linkages was presented. Within this ap-

    proach, the well-known singularity-prone tan-half-angle

    transformation is avoided. This is done by resorting to a

    geometric representation of the I/O equation of the planar

    [email protected]@uady.mx

    [email protected]

    and spherical four-bar linkages, which leads to the problem

    of finding the intersection of a line and a unit circle whose

    plane contains the line.

    Recently, Cervantes proposed a careful definition of the

    design coefficients may improve the kinematic synthesis of

    spherical 4R linkages intended for function generation for

    three and four precision points [9]. As a result, the de-sign process is based on a simple system of linear equations

    whose solution is obtained in closed form.

    Although there are published articles on synthesis and

    analysis of spherical mechanisms, the aim of this document

    is to explain in detail the steps necessary to carry out the

    kinematic study of a spherical mechanism.

    In Section II the necessary mathematical background is

    presented: the rotation matrix, spherical geodesics, and

    parametric equations for the links. The synthesis of spher-

    ical mechanisms for path generation problem is treated in

    Section III. The original version of the DE method is re-

    produced in the Section IV. In Section V required functions

    are built to make the animation inMathematica R. An ex-

    ample of the method proposed in this paper is resolved in

    Section VI. In Section VII conclusions are presented. Fi-

    nally, in Appendices A and B the DE program code and

    MathematicaR for animation are shown.

    II. Mathematical baggage

    In this section, relevant concepts and useful formulas

    involved in synthesis and animations of spherical mecha-

    nisms are presented. In particular, a rotation matrix is used

    in order to construct the parametric equation for spherical

    geodesics, so we hope that concepts should not be difficult

    to understand and their treatment should be clear. Some ofthe elements presented in this section can be found in [10],

    [11], [12].

    A. The rotation matrix

    When the synthesis of spherical four bar mechanism are

    studied, one kind of transformation is extremely important.

    It is known that rotations on the coordinate system or ro-

    tations on the vector by itself keep the length invariant,

    both transformations are carried out by orthogonal matrices

    (ATA=

    ; T means the transpose operation). If we rotate

    the coordinate system, we are talking about a passive rota-

    tion; if the rotation is performed on the vector, the term ac-

    1

  • 7/25/2019 A20_548

    2/8

    13th World Congress in Mechanism and Machine Science, Guanajuato, Mexico, 19-25 June, 2011 A20_548

    tive rotation is used. In the passive case, we keep the vector

    static and rotations are made around the coordinate axes, in

    this context is where the entity of vector (in a more physical

    context instead of algebraic one) gets its name; a vector, or

    more generally a tensor, is a quantity that remains invariantunder orthogonal transformations of the coordinate system.

    In the active case, the vector is rotated while the coordinate

    axes are held fixed. The latter transformation is especially

    important to us, although is clear that we can pass from one

    to the other, see Eq (5).

    Finding a representation for the SO(3) group (the set of

    3 3orthogonal matrices with determinant 1) is when weobtain the rotation matrix. In order to find a representa-

    tion for SO(3) we recall the representation for the rotations

    around each coordinate axis is given by

    Rx = 1 0 0

    0 cos x sin x0 sin x cos x

    ,

    Ry =

    cos y 0 sin y0 1 0

    sin y 0 cos y

    , (1)

    Rz =

    cos z sin z 0 sin z cos z 0

    0 0 1

    .

    The generators of the SO(3) group (i.e. infinitesimal rota-

    tions are performed until a finite rotation is reached) are:

    k = iRk

    kk=0

    , k= x, y,z (2)

    which give

    x = i

    0 0 00 0 1

    0 1 0

    ,

    y =i

    0 0 10 0 0

    1 0 0

    , (3)

    z =i0 1 0

    1 0 0

    0 0 0 .

    With generators we can perform any rotation of angle

    around a unitary vectornusing the rotation matrix:

    Rpassive(,n) =E xp

    i

    zk=x

    knk

    , (4)

    and the active version:

    R(,n) =Rpassive(,n). (5)

    Calculating such a matrix is not difficult (expanding the ex-

    ponential in a Mclaurin series and rearranging terms, or us-

    ing the MatrixExp function ofM athematicaR, or the

    expm function of MATLAB R). For the sake of brevity Eq.

    (6) shows the R11and R12components

    R11= n2x+ (n

    2y+ n

    2z)cos ,

    (6)

    R12= 2 sin

    2

    nxnysin

    2 nzcos

    2

    .

    B. Spherical geodesics

    All the treatment is done assuming we are in the R3 linear

    vector space, the vectors are assumed to be3 1matricesand we suppose an unitary spherical surface.

    A trajectory is a function : A RB R3 and itwill be used the following notation:

    (t) = (x(t) y(t) z(t))T. (7)

    We denote the derivative of the (t)trajectory as its veloc-ity

    v(t) = d(t)

    dt . (8)

    Although v(t)is by definition a trajectory, we will use theterm velocity for it and the term trajectory will be used, in

    a more restrictive way, to denote the curve that is gener-

    ated by the end point of the position vector r(t), frequentlycalled the parametric equation of the curve. We will use

    v(t) = dr(t)

    dt to denote the velocity vector. From the def-

    inition ofv(t)it is clear that it will be a tangent vector forthe trajectory at the point r(t).

    In order to construct the geodesics on the spherical sur-

    face, consider two vectors h1 and h2with their ends on the

    spherical surface, from now on just called two points on the

    spherical surface. The parametric equation for the spherical

    geodesic from the point h1 to h2 is constructed by rotating

    the vectorh1an angle cos1(h1h2) around of their unitary

    cross product h1 h2|h1 h2|

    , that is,

    rg() =R(,nh12)h1, (9)

    where rg is the trajectory of the geodesic, nh12 =h1 h2

    |h1 h2|, and as parameter of the trajectory varying

    from = 0 up to = cos1(h1 h2) . Eq. (9) is ofgreat importance, basically all trajectories involved will be

    obtained using this equation.

    C. Parametric equations for the links

    Let there bex1, x2, x3 andx4 four arbitrary points on

    the spherical surface. We will take the crank as the geodesic

    connecting the points x1 and x2, the coupler link as the

    geodesic connecting the points x2 and x3, the oscillator

    link as the geodesic connecting the points x3and x4, finally

    the frame will be the geodesic connectingx4 andx1. The

    2

  • 7/25/2019 A20_548

    3/8

    13th World Congress in Mechanism and Machine Science, Guanajuato, Mexico, 19-25 June, 2011 A20_548

    lengths for the links will be the angles between the vectors

    defining the links. We will call 1,2,3,4the lengths of

    the crank, coupler, oscillator and frame respectivelly. The

    crank and Grashof conditions are stated as:

    1= min(1, 2, 3, 4) (10)

    1+max(2, 3, 4) sum of remainding links (11)

    respectively.

    From our convention, the parametric trajectory for the

    extreme of the crank will be:

    r2() =R(, x1)x2 (12)

    and for the oscillator

    r3(()) =R((),x4)x3. (13)

    Since the length of the coupling is constant, i.e.,

    r2() r3(()) =constant= x2 x3. (14)

    we can determine (). The solution for Eq. (14) can beobtained numerically or analytically, nevertheless, is not an

    easy task. The problems is due to the branch defect. An

    excellent treatment of this technicality along with the ana-

    lytical solution for the angle,

    () =2tan1 A

    A2 +B2 C2

    C B

    with (15)

    A= sin 1sin 3sin

    B=cos 1sin 3sin 4 sin 1sin 3cos 4cos

    C=sin 1cos 3sin 4cos +

    cos 1cos 3cos 4 cos 2,

    can be found in [9].

    The links are constructed as function of as follow: the

    geodesic connecting r2()and r3(())given by Eqs. (12)and (13) will be the coupler link, the geodesic connecting

    x1 andr2()will be the crank, finally, the oscillator is ob-tained whit the geodesic connecting x4 and r3(()).

    Using the methodology just described we can proceed

    to the synthesis and the animation for the spherical four-bar

    mechanism in a clean manner. The following sections show

    how the animation can be done usingMathematica R and

    how the optimization for the structural error can be done

    using DE.

    III. Path generation

    With the purpose of applying what we have been intro-

    duced in the previous section, an spherical mechanism for

    path generation is used. Function generation and motion

    generation can be done in a similar manner.

    The main point is to construct the objective function

    (f ob) for the structural error.

    f ob=i

    |rd rgen|2i (16)

    where rd are the desired points (or the desired trajectory)

    and rgen the generated points, the sum is over all the points.In order to make the path generation task, we use the

    architecture of Fig 1. Where the extension of the coupler

    link is what is used for generating the desired trajectory.

    1.0

    0.5

    0.0

    0.5

    1.0

    1.0

    0.5

    0.0

    0.5

    1.0

    1.0

    0.5

    0.0

    0.5

    1.0

    Fig. 1. Spherical four bar mechanism. Black link is the crank, blue is the

    oscillator.

    In the previous section the vectors xk,k = 1, 2, 3, 4wassupposed to be known but now they are adjustable parame-

    ters.The vector rgen(; , xk) can be generated rotating thevector r2(;x1,x2) an angle , also an adjust parame-ter (the length of the geodesic connecting r2(;x1,x2)and rgen(; , xk)), around the orthogonal vector tor2(;x1,x2)and r3(();x3,x4), explicitly, using Eq. (9)we have:

    rgen(; , xk) =R(, n23(;xk))r2(;x1,x2) (17)

    wheren23(;xk) = r2(;x1,x2) r3(();x3,x4)

    |r2(;x1,x2) r3(();x3,x4)|.

    As a matter of illustration, consider 7 desired points on

    the spherical surface, we need to generate 7 points in such away thatf obgiven by Eq. (16) be a minimum. So we need

    7 input angles i; i = 1, ... , 7. Such angles can be pre-scribed or not, the first case is the easy one, the only thing

    to do is to evaluate Eq. (17) for each one of the given an-

    gles and to proceed to the minimization off ob in order to

    find the initial four points for the links and the angle. For

    the second case, usually called non prescribed timing, we

    need to introduce 7 parameters extra; the possible angles,

    and then to proceed to the minimization. Clearly the non-

    prescribed timing synthesis is more difficult to do, we need

    to introduce as many parameters as points to fit, but there is

    another important thing to consider, the order defect prob-

    lem. Because we are going to use the DE method, the order

    3

  • 7/25/2019 A20_548

    4/8

    13th World Congress in Mechanism and Machine Science, Guanajuato, Mexico, 19-25 June, 2011 A20_548

    defect problem is solved by discretizing the searching space

    (as far as the angles is concern) for the individuals instead

    of penalizing them, such an approach can be found in [13].

    Apparently Eq. (17) suggest 3 parameters for each point,

    is clear that only two are required, instead of talking aboutthe tree coordinates of the point on the unitary spherical

    surface we can use the polar angle and the azimuthal angle

    as parameters, the radium is 1.

    IV. Differential Evolution Method

    Once that the objective function has been constructed,

    they shall be minimized using the DE method. The original

    version of the DE method is surprisingly easy and highly

    efficient. Such a version it is known as DE/Rand/1/bin and

    can be found in [14]. Here we reproduce the essential parts

    of the method.

    1. The population

    Px,g = (xi,g), i= 1, ...m; g= 0, ...gmax

    xi;g = (xji;g), j = 1,...D; (18)

    whereD represents the dimensionality ofx, m represents

    the number of individuals, andg is the generation.

    2. Initialization of population

    xji;0= rand

    j(0, 1) (bjU bjL).

    Vectors bUand bLare the limits of parameters.randj(0, 1)

    represents uniformly distributed random number in [0, 1).Superscriptjmeans that a random value for each parameter

    is generated.

    3. Mutation

    vi;g =xr0;g+ F (xr1;g xr2;g). (19)

    xr0;g is called base vector which is perturbed by the differ-

    ence of other two vectors. r0, r1, r2 {1, 2, ...m}, r0=r1 = r2 = i . F is a scale factor greater than zero. Evenupper limit does not exist for F. Empirically it has been

    shown that values greater than one are rarely required.

    4. Crossover

    It uses a dual recombination of vector to generate the trial

    vector:

    ui;g = uji;g =

    v

    ji;g if(rand

    j(0, 1) Cr or j =jrand)

    xji;g otherwise.

    (20)

    The crossover probability, Cr [0, 1], is a user-definedvalue.

    5. Selection

    The selection is made according to

    xi;g+1=

    ui;g iff(ui;g) f(xi;g)xi;g otherwise

    (21)

    In this work the DE method is coded in FORTRAN 90

    using the version know as dither which mean that the F

    factor of the Eq. (19) is taken as a random number between

    0 and 1. In Appendix-A it is shown an example of how to

    code the DE algorithm. For an introduction to FORTRAN

    90 we suggest [15] and [16].

    V. On the animation

    This section shows the construction of the func-

    tions that are requiered for making the animations in

    Mathematica R. For an introduction to M athematica R

    we recomend [17] and of course, the help provided with the

    software. Apendix-B show an animation of the example

    solved in Section VI.

    We need to code the equation (9). First we make the

    function for Eq. (5).

    RotU[theta_, {n1_, n2_, n3_}] =

    Module[{t1, t2, t3, Vt, Vru},

    (t1 = {{0, 0, 0},{0, 0, 1},{0, -1, 0}};

    t2 = { {0, 0, -1},{0, 0, 0},{1, 0, 0}};

    t3 = {{0, 1, 0},{-1, 0, 0},{0, 0, 0}};

    Vt = {t1, t2, t3}; Vru = {n1, n2, n3};

    FullSimplify[MatrixExp[-theta

    (Vt.Vru)]/.{n12+n22+n32->1,

    -n12-n22-n32->-1}])];

    This function can be coded in many different ways, but

    with the Module function is constructed directly.

    Now we proceed to construct the function for the para-

    metric equation when the vector y is rotated an angle theta

    around the unitary vector vr .

    fr[theta_,{vr1_,vr2_,vr3_},{y1,y2,y3}]=

    Flatten[FullSimplify[RotU[theta,

    {vr1,vr2,vr3}].{{y1}, {y2}, {y3}}]];

    The Eq. (9) is coded using the fr function just described.

    rg[theta_,X_,Y_]:=fr[theta,Cross[X,Y]/

    Norm[Cross[X,Y]],X]

    Although the geodesics between two points in the unitary

    spherical surface can be plotted using the rg function, we

    used explicitly the following function to do this.

    Geodesic[X_,Y_,Color_]:=

    ParametricPlot3D[fr[theta,

    Cross[ X,Y]/Norm[Cross[X,Y]],X],

    {theta,0,ArcCos[X.Y]},

    PlotStyle->{Thick,Color}]

    All we need is to use appropriately the function above con-

    structed in order to make the animation. For instance the

    end position of the crank is (for the animation the vectors

    xk are supposed to be know):

    r2[angle_]:=fr[angle,x1,x2]

    and the position for the oscillator:

    r3[angle_]:=fr[phiangle,x1,x2]

    4

  • 7/25/2019 A20_548

    5/8

    13th World Congress in Mechanism and Machine Science, Guanajuato, Mexico, 19-25 June, 2011 A20_548

    In our parametrization the argument for r2 is not exactly ,

    the cranks angle, but 0 where 0 is the initial anglebetween the crank and the frame, which can be calculated

    by the scalar product of their velocity vectors; Eq. (8) must

    be used for that purpose. A similar argument is applied tothe angle; phiangle= () 0. with0 the initialangle between the oscillator and the frame. The election of

    the+or sign must be combined with the branches of Eq.(15) in such a way that the problem be consistent. Math-

    ematically: Eq. (14) must be fulfill and(0) = 0. Allthis considerations must be also taken into account when

    the objective function is constructed.

    VI. An example

    This section shows the synthesis of path generation for

    four points, it is know that the problem admit analytical

    solution but the example is only for illustrative purpose.

    A. The problem

    We choose 4 random numbers on the unitary sphere.

    Then we proceed using DE to find the optimal mechanism.

    The design variable vector is

    X= (1, 2, 3, 4, , pk, k); k= 1, 2, 3, 4. (22)

    The parameters are due to the non prescribed situation,

    pk are the polar angles andk represent the azimuthal an-

    gles.

    The random points to adjust was

    P =

    0.89383 0.354598 0.274461

    0.598329 0.799403 0.0543790.345166 0.692654 0.633318

    0.377746 0.804416 0.4585

    (23)where the rowi represent the point i.

    After the DE algorithm we get= 3.71161and the fol-lowing values for the positions of the juntas:

    X=

    0.538613 0.558391 0.630948

    0.969 0.236593 0.07114890.341775 0.584733 0.735716

    0.820808 0.504138 0.26855

    (24)

    As was mentioned, the crank will be the geodesic connect-

    ingX(1) withX(2), the coupler link will be the geodesicconectingX(2)withX(3)etc. X(i)represent the rowiofX. The value of the objective function was practically0,f ob 1031.

    VII. Conclusions

    We present a concise methodology for making anima-

    tions for spherical four bar mechanisms. All the elements

    necessary in order to make the optimum synthesis and the

    animations of the mechanisms are provided. Using evolu-

    tion differential we solve the problem of path generation.

    We provided the main Mathematica R functions and an

    example of how to code the DE method in F ORTRAN 9 0.

    Appendix

    A. Coding the DE algorithm

    We decided to use FORTRAN 90 to implement the DE

    algorithm. Any programming language can be used but it

    is know that FORTRAN 90 is specially suited for this kind

    of problem, is easy, and powerful. The used compiler was

    ifort of the free Linux version.

    Let there be m the population number, NDim the num-

    ber of parameters, bU and bL the limits for the parameter,

    nit the number of iterations, X the matrix where the initial

    population is stored, u the matrix for the individuals afther

    the mutation and the crossover (the k-generation until nit is

    reached). The algorithm can be coded as follows:

    ! initial population

    do i=1,m

    do j=1,NDim

    X(i,j)=Rand()*(bU(j)-bL(j))+bL(j)

    end do

    end do

    !**************************************Loop1: do it=1,nit !loop for iterations

    Loop2: do i=1,m!Loop for doing mutation

    !crossover and selection

    3 r0=aint(rand()*m+1)

    if(r0.eq.i) go to 3

    4 r1=aint(rand()*m+1)if(r1.eq.i.or.r1.eq.r0) go to 4

    5 r2=aint(rand()*m+1)

    if(r2.eq.i.or.r2.eq.r1.or.r2.eq.r0)&

    go to 5&

    jrand=aint(rand()*m+1) !a little

    ! modification; in this way, the

    !mutation is certainly done

    do j=1,NDim

    ! jrand=aint(rand()*m+1) ! inside the

    !do loop there is a probability that

    !mutation never occurs; this is

    !the original version

    if(rand().Le.cr.or.j.eq.jrand)then

    u(i,j)=X(r0,j)+rand()*&

    (X(r1,j)-X(r2,j))

    else

    u(i,j) = X(i,j)

    end if

    end do

    ! Selection

    Nu=u(i,:)

    NX=X(i,:)

    if(fob(Nu).Lt.fob(NX)) X(i,:)=u(i,:)

    Vmen=X(i,:)

    vecvals(i)=fob(Vmen) !vector of

    5

  • 7/25/2019 A20_548

    6/8

    13th World Congress in Mechanism and Machine Science, Guanajuato, Mexico, 19-25 June, 2011 A20_548

    ! the fob values

    end do Loop2

    !**************************************! extracting the minimum

    menor=minval(vecvals)tem=minloc(vecvals)

    minpos=tem(1)

    end do Loop1

    !**************************************

    The termination criteria for this program is until the total

    number of iterations is reached and it is assumed that the

    variable for f ob is a vector (the design variable vector).

    Needles to say, all the involved variables must be appropri-

    ately defined. Of course, improvements for the the above

    program can be done, but the easy of the presented, allow a

    fast understanding of the DE method, once that understand-

    ing has been acquired, the user can make his own programas better as he likes.

    B. Mathematica R animation

    RotU[thetap_, {n1_, n2_, n3_}] =

    Module[{t1, t2, t3, Vt, Vru}, (t1 = ({

    {0, 0, 0},

    {0, 0, 1},

    {0, -1, 0}

    }); t2 = ({

    {0, 0, -1},

    {0, 0, 0},

    {1, 0, 0}}); t3 = ({

    {0, 1, 0},

    {-1, 0, 0},

    {0, 0, 0}

    }); Vt={t1,t2,t3};Vru={n1, n2, n3};

    FullSimplify[

    MatrixExp[-thetap(Vt. Vru)]/.

    {n12+n22+n32 ->

    1,-n12-n22-n32->-1}])];

    fr[thetap_, {vr1_, vr2_, vr3_},

    {r1a_, r2a_, r3a_}] =

    Flatten[FullSimplify[

    RotU[thetap,{vr1,vr2,vr3}].

    {{r1a},{r2a},{r3a}}]];

    vel[thetap_, {vr1_, vr2_, vr3_},

    {r1a_, r2a_, r3a_}] =

    FullSimplify[

    D[fr[x, {vr1, vr2, vr3},

    {r1a, r2a, r3a}], x] /. x -> thetap];

    Geodesica[X_, Y_, Color_] :=

    ParametricPlot3D[

    fr[thetap, Cross[ X, Y ]/Norm[

    Cross[ X, Y ]], X ] , {thetap, 0,

    ArcCos[X.Y]}, PlotStyle ->

    {Thick, Color}]

    extbet = 3.711618424122518

    GeodesicaX[X_, Y_, Color_] :=

    ParametricPlot3D[

    fr[thetap, Cross[ X, Y ]/Norm[

    Cross[ X, Y ]], X ] , {thetap, 0,

    extbet}, PlotStyle -> {Thick, Color}]

    Adat = {{-0.5386129123588165,

    0.5583914331833824,

    -0.6309478092423828},

    {-0.969000200194567,

    0.236593428174166, 0.0711488704596420},

    {0.34177472827299,

    0.5847325184016489,

    0.7357159214245597},

    {0.8208078851631664,

    0.5041382206729008,

    -0.2685499396960122}}(*The solution*);

    (*Probing the crank grashof condition*)

    Avec = {ArcCos[Adat[[1]].Adat[[2]]],

    ArcCos[Adat[[2]].Adat[[3]]],

    ArcCos[Adat[[3]].Adat[[4]]],

    ArcCos[Adat[[4]].Adat[[1]]]};AvecSort = Sort[Avec];

    Which[AvecSort[[1]] +

    AvecSort[[4]]-(AvecSort[[2]]+

    AvecSort[[3]])

  • 7/25/2019 A20_548

    7/8

    13th World Congress in Mechanism and Machine Science, Guanajuato, Mexico, 19-25 June, 2011 A20_548

    a3 = Avec[[3]]; a4 = Avec[[4]]; A =

    Sin[a1] Sin[a3] Sin[theta];

    B = Cos[a1] Sin[a3] Sin[a4] -

    Sin[a1] Sin[a3] Cos[a4] Cos[theta];

    Cc = Cos[a1] Cos[a3] Cos[a4] +Sin[a1] Cos[a3] Sin[a4] Cos[theta]

    - Cos[a2];

    2 ArcTan[(-A + (-1)s Sqrt[A2 + B2 -

    Cc2])/(Cc - B)])];

    Ang14x[s_]=(-1)s ArcCos[(velmaniv[0].

    velbanca[0])];

    Ang34x[s_]=(-1)s ArcCos[veloscila[0].

    -velbanca[Avec[[4]]]];

    r2t[theta_,s_]:=fr[theta-Ang14x[s],

    Adat[[1]],

    Adat[[2]]]

    r3t[theta_, s_, z_] :=

    fr[-phit[theta,s]+Ang34x[z],Adat[[4]],

    Adat[[3]]]

    xt = Re[Table[

    r2t[1, j].r3t[1,l,z],{j,1,2},

    {l,1,2},{z,1,2}]];

    fs[{j_, l_, z_}] := xt[[j, l, z]] ==

    Adat[[2]].Adat[[3]]

    xs = Partition[

    Flatten[Table[{j, l, z}, {j, 1, 2},{l, 1, 2}, {z, 1, 2}]], 3];

    pmel = Select[xs, fs];

    eps = 1*10-8;(*neglecting

    small complex parts*)

    sel2[j_] :=

    Abs[phit[Ang14x[pmel[[j, 1]]],

    pmel[[j, 2]]] -

    Ang34x[pmel[[j, 3]]]] True, AxesOrigin ->

    {0, 0, 0}];

    g1 = Graphics3D[{{Opacity[0.5],

    sferita}, sx}, Axes -> True,

    AxesOrigin -> {0, 0, 0}];

    manivela[theta_] :=

    Geodesica[Adat[[1]],

    r2[theta], Black]

    acoplador[theta_]:=Geodesica[r2[theta],

    r3[theta], Red]acopladorX[theta_]:=GeodesicaX[r2[theta],

    r3[theta], Red]

    oscilador[theta_]:=Geodesica[Adat[[4]],

    r3[theta], Blue]

    rp[theta_, ap_] :=

    Re[Flatten[

    RotU[ap,

    Cross[r2[theta],

    r3[theta]]/(Norm[Cross[r2[theta],

    r3[theta]]])].Map[List,

    r2[theta]] ]]

    circm =

    ParametricPlot3D[r2[theta],

    {theta, 0, 2 Pi},

    PlotStyle -> {Thick,

    RGBColor[1, 1, 0]}];

    (*crank trajectory*)

    circo =

    ParametricPlot3D[r3[theta],

    {theta, 0, 2 Pi},

    PlotStyle ->

    {Thick, RGBColor[0, 1, 1]}];

    (*oscillator trajectory*)

    7

  • 7/25/2019 A20_548

    8/8

    13th World Congress in Mechanism and Machine Science, Guanajuato, Mexico, 19-25 June, 2011 A20_548

    seguidor =

    ParametricPlot3D[rp[theta, extbet],

    {theta, 0, 2 Pi},PlotStyle->{Thick,RGBColor[1,0,1]}];

    (*The follower*)

    Animate[

    Show[g0, seguidor, circm, manivela[t],

    oscilador[t], acoplador[t],

    acopladorX[t], circo], {t, 0, 2 Pi}]

    References

    [1] J. Michael McCarthy. Geometric Design of Linkages. Springer, New

    York, 2000.[2] C. H. Chiang. Kinematics of Spherical Mechanisms. Cambridge

    University Press, 1988.[3] Richard S. Hartenberg and Jacques Denavit Kinematic Synthesis of

    Linkages McGraw-Hill Book Company, 1964.[4] C. H. Suh and C. W. Radcliffe Synthesis of Spherical Linkages with

    Useof theDisplacement Matrix, Journal of Engineering forIndustry89 B 215222, 1967.

    [5] C. H. Suh and C. W. Radcliffe. Kinematics and Mechanisms Design.John Wiley & Sons, 1978.

    [6] K. C. Gupta and A. S. Beloiu Branch and Circuit Defect Eliminationin Spherical Four-Bar Linkages Mechanism and Machine Theory33 (5) 491504, 1998.

    [7] Jianwei Sun and Jinkui Chu Synthesis of Spherical Four-bar Func-tion Generator by Means of Fourier Method. 12th IFToMM WorldCongress, Besanon (France), June18-21, 2007.

    [8] Shaoping Bai and Jorge Angeles A unified inputoutput anal-

    ysis of four-bar linkages. Mechanism and Machine Theory,43 (2): 240-251, 2008.

    [9] J . Jesus Cervantes-Sanchez, Hugo I. Medelln-Castillo, Jose M.Rico-Martneza, Emilio J. Gonzalez-Galvanb. Some improvementson the exact kinematic synthesis of spherical 4R function generators.

    Mechanism and Machine Theory, 44:103121, 2009.[10] J. F. Cornwell. Group Theory in Physics; An Introduction. Academic

    Press, 1997.[11] G. B. Arfken and H. J. Weber. Mathematical Methods for Physicists,

    6th Edition, Elsevier Academic Press, 2005. Academic Press, 1997.[12] J. E. Marsden and A. J. Tromba. Vector Calculus, Fifth Edition.

    W.H. Freeman and Company, New York, 2008.[13] A. Smaili, N. Diab. Optimum synthesis of hybrid-task mechanisms

    using ant-gradient search method. Mechanism and Machine Theory,42 (1): 115-130, 2007.

    [14] K. V. Price, R. M. Storn, J. A. Lampinen. Differential Evolution:A Practical Approach to Global Optimization. Springer, Germany,

    2005.[15] Michael Kupferschmid. Classical FORTRAN; PROGRAMMING FOR

    ENGINEERING AND SCIENTIFIC APPLICATIONS. Marcel Dekker,2002.

    [16] Ian D. Chivers and Jane Sleightholme. Introduction to Programmingwith Fortran. Springer-Verlag London Limited 2006.

    [17] Paul R. Wellin, Richard J. Gaylord, Samuel N. Kamin. An Introduc-tion to Programming with M athematicaR. Third Edition. Cam-bridge University press, 2005.

    8