home *** CD-ROM | disk | FTP | other *** search
-
- (* Copyright 1988 Wolfram Research Inc. *)
-
- (*:Version: Mathematica 2.0 *)
-
- (*:Title: Trigonometric Simplifications *)
-
- (*:Author: Roman Maeder *)
-
- (*:Keywords:
- trigonometry, simplification, reduction, expansion
- *)
-
- (*:Requirements: none. *)
-
- (*:Warnings: none. *)
-
- (*:Summary:
- This package provides all kinds of trigonometric simplifications.
- *)
-
- (* import Global`, as we anticipate these routines to be called
- frequently by mistake before reading the file. *)
-
- BeginPackage["Algebra`Trigonometry`", "Global`"]
-
- TrigCanonical::usage = "TrigCanonical[expr] is obsolete.
- Its functionality is now built-in."
-
- TrigExpand::usage = "TrigExpand[expr] is obsolete.
- Its functionality is provided by Expand[expr, Trig->True]."
-
- TrigFactor::usage = "TrigFactor[expr] tries to write sums of trigonometric
- functions as products."
-
- TrigReduce::usage = "TrigReduce[expr] writes trigonometric functions of
- multiple angles as sums of products of trigonometric functions of
- that angle."
-
- TrigReduce::notes = "TrigReduce simplifies the arguments of trigonometric
- functions. It is, in a way, the inverse of TrigExpand."
-
- TrigToComplex::usage = "TrigToComplex[expr] writes trigonometric functions
- in terms of complex exponentials."
-
- ComplexToTrig::usage = "ComplexToTrig[expr] writes complex exponentials
- as trigonometric functions of a real angle."
-
-
- Begin["`Private`"]
-
- (* explicitly create all local variables to avoid name clashes,
- since Global` is on the search path. *)
-
- {`x, `y, `r, `n, `m, `a, `b, `c, `i, `e};
-
- TrigCanonical[e_] := e
-
- TrigExpand[___] := $Failed /;
- Message[TrigExpand::obsfn, TrigExpand, Expand]
-
- TrigExpand[e_]:=Expand[e,Trig->True]
-
- `TrigFactorRel = {
- a_. Sin[x_] + a_. Sin[y_] :> 2 a Sin[x/2+y/2] Cos[x/2-y/2],
- a_. Sin[x_] + b_. Sin[y_] :> 2 a Sin[x/2-y/2] Cos[x/2+y/2] /; a+b == 0,
- a_. Cos[x_] + a_. Cos[y_] :> 2 a Cos[x/2+y/2] Cos[x/2-y/2],
- a_. Cos[x_] + b_. Cos[y_] :> 2 a Sin[x/2+y/2] Sin[y/2-x/2] /; a+b == 0,
- a_. Tan[x_] + a_. Tan[y_] :> a Sin[x+y]/(Cos[x] Cos[y]),
- a_. Tan[x_] + b_. Tan[y_] :> a Sin[x-y]/(Cos[x] Cos[y]) /; a+b == 0,
-
- a_. Sin[x_] Cos[y_] + a_. Sin[y_] Cos[x_] :> a Sin[x + y],
- a_. Sin[x_] Cos[y_] + b_. Sin[y_] Cos[x_] :> a Sin[x - y] /; a+b == 0,
- a_. Cos[x_] Cos[y_] + b_. Sin[x_] Sin[y_] :> a Cos[x + y] /; a+b == 0,
- a_. Cos[x_] Cos[y_] + a_. Sin[x_] Sin[y_] :> a Cos[x - y]
-
- }
- TrigFactorRel = Dispatch[TrigFactorRel]
- Protect[TrigFactorRel]
-
- TrigFactor[e_] := FixedPoint[(# /. TrigFactorRel)&, e]
-
- `TrigReduceRel = {
-
- (* the following two formulas are chosen to allow easy
- reconstruction of TrigExpand[Sin[x]^n] or TrigExpand[Cos[x]^n].
- In these cases, Sin[n x] with even n does not occur.
- There we use another formula. *)
-
- Cos[n_Integer x_] :> 2^(n-1) Cos[x]^n +
- Sum[ Binomial[n-i-1, i-1] (-1)^i n/i 2^(n-2i-1) Cos[x]^(n-2i),
- {i, 1, n/2} ] /; n > 0,
-
- Sin[m_Integer?OddQ x_] :>
- Block[{`p = -(m^2-1)/6, `s = Sin[x], `k},
- Do[s += p Sin[x]^k;
- p *= -(m^2 - k^2)/(k+2)/(k+1),
- {k, 3, m, 2}];
- m s] /; m > 0,
-
- Sin[n_Integer?EvenQ x_] :>
- Sum[ Binomial[n, i] (-1)^((i-1)/2) Sin[x]^i Cos[x]^(n-i),
- {i, 1, n, 2} ] /; n > 0,
-
- Tan[n_Integer x_] :> Sin[n x]/Cos[n x],
-
- Sin[x_ + y_] :> Sin[x] Cos[y] + Sin[y] Cos[x],
- Cos[x_ + y_] :> Cos[x] Cos[y] - Sin[x] Sin[y],
- Tan[x_ + y_] :> (Tan[x] + Tan[y])/(1 - Tan[x] Tan[y]),
-
- (* rational factors, "symb" does not have a value *)
- Sin[r_Rational x_] :> (Sin[Numerator[r] `symb] /. TrigReduceRel /.
- `symb -> x/Denominator[r]) /; Numerator[r] != 1,
- Cos[r_Rational x_] :> (Cos[Numerator[r] `symb] /. TrigReduceRel /.
- `symb -> x/Denominator[r]) /; Numerator[r] != 1,
-
- (* half angle args *)
- Tan[x_/2] :> (1 - Cos[x])/Sin[x],
- Cos[x_/2]^(n_Integer?EvenQ) :>
- ((1 + Cos[x])/2)^(n/2),
- Sin[x_/2]^(n_Integer?EvenQ) :>
- ((1 - Cos[x])/2)^(n/2),
- Sin[x_/2]^n_. Cos[x_/2]^m_. :> Tan[x/2]^n /; m == -n,
- Sin[r_ x_.] Cos[r_ x_.] :> Sin[2 r x]/2 /; IntegerQ[2r]
-
- }
- TrigReduceRel = Dispatch[TrigReduceRel]
-
- TrigReduce[e_] := e //. TrigReduceRel
-
- `TrigToComplexRel = {
- Sin[x_] :> -I/2*(-E^(-I*x) + E^(I*x)),
- Cos[x_] :> (E^(-I*x) + E^(I*x))/2,
- Tan[x_] :> (-I*(-E^(-I*x) + E^(I*x)))/(E^(-I*x) + E^(I*x)),
- Csc[x_] :> (2*I)/(-E^(-I*x) + E^(I*x)),
- Sec[x_] :> 2/(E^(-I*x) + E^(I*x)),
- Cot[x_] :> (I*(E^(-I*x) + E^(I*x)))/(-E^(-I*x) + E^(I*x)),
- Si[x_] :> -I/2(ExpIntegralE[1, I x] - ExpIntegralE[1, -I x]) + Pi/2,
- Ci[x_] :> -1/2(ExpIntegralE[1, I x] + ExpIntegralE[1, -I x])
- }
- TrigToComplexRel = Dispatch[TrigToComplexRel]
-
- TrigToComplex[e_] := e //. TrigToComplexRel
-
- `ComplexToTrigRel = {
- Exp[a_ b_Plus] :> Exp[Expand[a b]],
- Exp[c_Complex x_. + y_.] :> Exp[Re[c] x + y] (Cos[Im[c] x] + I Sin[Im[c] x])
- }
- ComplexToTrigRel = Dispatch[ComplexToTrigRel]
-
- ComplexToTrig[e_] := Cancel[e //. ComplexToTrigRel]
-
- End[] (* Algebra`Trigonometry`Private` *)
-
- Protect[ TrigCanonical, TrigExpand, TrigFactor, TrigReduce,
- TrigToComplex, ComplexToTrig ]
-
- EndPackage[] (* Algebra`Trigonometry` *)
-
- (*:Limitations: none known. *)
-
-
- (*:Examples:
-
- TrigExpand[ Sin[x]^2 ]
-
- TrigFactor[ Sin[x] + Sin[y] ]
-
- TrigReduce[ Sin[5 x] ]
-
- TrigToComplex[ Cos[x] ]
-
- ComplexToTrig[ Exp[I] ]
-
- *)
-