Graphing.mws

Graphing

>    restart;
with( plots ):
with( Student[Calculus1] ):

Warning, the name changecoords has been redefined

>   

Auxiliary Procedures

>    InInterval := proc(x,S::list(numeric))
  if has(x,I) then return false end if;
  return evalb( evalf(x)>=op(1,S) and evalf(x)<=op(2,S) )
end proc:

>    TestIncrDecr := proc( df, pts )
  local c, m, fmt1, fmt2;
  Digits := 4;
  fmt1 := "f'(%a)=%a; the function is %a on the subinterval containing %a";
  fmt2 := "f'(%a)=%a; the function has a stationary point at x = %a";
  for c in evalf(pts) do
    m := eval( df, x=c );
    if m>0 then
      print( printf(fmt1, c, m, `increasing`, c) );
    elif m<0 then
      print( printf(fmt1, c, m, `decreasing`, c) );
    else
      print( printf(fmt2, c) );
    end if;
  end do:
end proc:

>    TestConcavity := proc( d2f, pts )
  local a, c, fmt1, fmt2;
  Digits := 4;
  fmt1 := "f''(%a)=%a; the function is concave %a on the subinterval containing %a";
  fmt2 := "f''(%a)=%a; the function has a possible inflection point at x = %a";
  for c in evalf(pts) do
    a := eval( d2f, x=c );
    if a>0 then
      print( printf(fmt1, c, a, `up`, c) );
    elif a<0 then
      print( printf(fmt1, c, a, `down`, c) );
    else
     print( printf(fmt2, c, a, c) );
    end if
  end do:
end proc:

>    SignPlot := proc( f, dom, desc, Y, C )
  local char_fn, neg_part, pos_part, P1, P2, x, xhi, xlo;
  char_fn := proc( test, value )
    local val;
    if nargs=1 then val := 1 else val := value end if;
    proc(f,y)
      local v;
      if nargs=1 then v := val else v := y end if;
      if type(f,numeric) then
        return `if`( test(f), v, undefined )
      else
        return 'procname'( 'args' )
      end if;
    end proc
  end proc;
  pos_part := char_fn( v->signum(v)= 1 );
  neg_part := char_fn( v->signum(v)=-1 );
  x, xlo, xhi := lhs(dom), op(evalf(rhs(dom)));
  P1 := plot( [pos_part(f,Y),neg_part(f,Y)], dom, color=C, thickness=3 );
  P2 := plots[textplot]( [(xlo+39*xhi)/40, Y, desc], align=ABOVE );
  return plots[display]( [P1, P2] );
end proc:

>    SignChart := proc( f, dom, orders )
  local F, L, ORDERS, Y;
  if type(orders,list) then
    ORDERS := seq(ord+1,ord=orders)
  else
    ORDERS := [orders+1]
  end if;
  F := [ f, diff(f,x), diff(f,x,x) ];
  L := [ `y`, `y'`, `y''` ];
  Y := [ -1/4, -1/2, -3/4 ];
  return
     plots[display](
      [seq( SignPlot( F[i], dom, L[i], Y[i], [pink,cyan] ), i=ORDERS )],
            view=[DEFAULT,-1..0], ytickmarks=0 )
end proc:

>   

Lesson Overview

The Global Analysis and Local Analysis lessons have introduced all of the tools needed to graph almost any function that you will encounter. While the FunctionChart  command, in the Student[Calculus1]  package, can produce excellent graphs, the ability to graph a function by hand is important for many reasons, including:

A general approach to graphing a function will be given and then demonstrated on a varied collection of functions. Some of the functions considered in these examples are somewhat more complicated than the typical functions considered in examples and exercises. These functions have been chosen to emphasize the general techniques and approach and to let Maple do some of the tedious calculations. In support of this approach, this worksheet introduces the SignChart  command (defined at the top of this worksheet). The general usage of this command is

    SignChart( f, domain, orders );    

where f  is the expression containing the function to be analyzed, domain  is an equation of the form var = left .. right  where var  is the variable in f  and left  and right  are the left and right endpoints of the interval for which the sign chart is requested, and orders  is a single integer or a list of integers indicating the order of the derivative(s) to include in the sign chart (use 0  for the f, 1  for f ', and 2  for f ''). Each sign chart is labeled and uses pink to indicate intervals where the function (or derivative) is positive and cyan to indicte regions where the function (or derivative) is negative.

Because the emphasis is on obtaining the information needed to construct the graph of a function, the FunctionAnalyzer  maplet [ Maplet Viewer][ MapleNet] is recommended over the CurveAnalysis  [ Maplet Viewer][ MapleNet] and DerivativePlot  [ Maplet Viewer][ MapleNet] maplets. To display a function in a Maple worksheet, the FunctionChart  command in the Student[Calculus1]  package is recommended.

>   

General Approach to Graphing a Function y = f(x)  

The process of creating a good graph of a function depends on the specific function to be graphed. The following list of steps can be used for most functions you are likely to encounter. Some of the steps can be omitted for some problems, but the decision to skip a step, or a part of a step,  needs to be a conscious decision rather than one of omission.

>   

Steps 1-3: Analysis Based on the Function

Step 1: Domain, Range, Symmetry, Periodicity

  • Domain
    If an interval is provided, use this as the domain.
    Otherwise, determine the function's natural domain.
  • Range
    Attempt to determine the range of the function.
    In particular, is the range bounded or unbounded?
    (Sometimes this becomes clearer after completing Step 2.)
  • Periodicity
    If the function is periodic, find its period.
  • Symmetry
    Is the function even (symmetric about the y-axis)? odd (symmetric about the origin)?

>   

Step 2: Intercept, Zeroes, Endpoints

  • Intercept
    Determine the point ( 0,
    f(0)  ).
  • Zeroes
    Attempt to locate all solutions to
    f(x) = 0 .
    Put all points (
    x , 0 ) where f(x) = 0 .
  • Endpoints
    Collect information for each finite endpoint.
    Note : For an endpoint not in the domain, use an appropriate one-sided limit.
  • Sign Chart for y = f(x)  
    Determine intervals of the domain where the function is positive and where the function is negative.

>   

Step 3 Asymptotes

  • Horizontal
    If the domain includes
    infinity  or -infinity , compute the corresponding limit at infinity.
    If this limit is finite, then this value is a horizontal asymptote.
    E.g., if
    Limit(f(x),x = infinity) = L , then y = L  is a horizontal asymptote.
  • Vertical
    For any finite number
    a , if either one-sided limit of f at a  is infinite, then x = a  is a vertical asymptote.
  • Oblique
    If there are values of
    a  and b  such that either
        
    Limit(``,x = infinity) ``*(f(x)-(a*x+b))  = 0   or    Limit(``,x = -infinity) ``*(f(x)-(a*x+b))  = 0,    
    then
    y = a*x+b  is an oblique asymptote.

Note : After computing the asymptotes, check that this information is consistent with the range found in Step 0.

>   

Step 4: Analysis Based on the First Derivative

  • Critical Points
    Find all stationary points, singular points, and endpoints.
  • Sign Chart for `y'` = `f '`(x)  
    Determine the intervals of the domain where the function is increasing and where the function is decreasing.
  • Local Extrema
    Use the First Derivative Test to classify all local maxima and local minima.
    Be sure to record both the extreme value and the point in the domain where it is attained.
  • Global Extrema
    Identify the global maximum,
    M , and minimum, m .
    (Check that the global extrema are consistent with the range found in Step 1.)
    Identify any values of
    x  in the domain of the function that satisfy f(x) = M  or f(x) = m .

Note : Classification of local extrema can be omitted from Step 3 if the Second Derivative Test is used in Step 4.

>   

Step 5: Analysis Based on the Second Derivative

  • Sign Chart for `y''` = `f ''`(x)  
    Use the possible inflection points to determine intervals of the domain where the function is concave up and where the function is concave down.
  • Local Extrema
    Use the Second Derivative Test to classify all local maxima and local minima.
    Be sure to record both the extreme value and the point in the domain where it is attained.
  • Inflection Points
    Identify any point where the second derivative changes sign.

Note : Classification of local extrema can be omitted from Step 4 if the First Derivative Test is used in Step 3.

>   

Step 6: Graph the Function

  • Plot the special points identified in Steps 1-5.
  • Draw all asymptotes found in Step 3.
  • Use the sign charts to ``connect the dots''.
  • Verify that the graph is consistent with all analysis.

>   

Example 1: Polynomial

Let

>    f1 := x^6-10*x^5-15*x^4+140*x^3+160*x^2-528*x-800:
F1 := unapply( f1, x ):
f(x) = f1;

f(x) = x^6-10*x^5-15*x^4+140*x^3+160*x^2-528*x-800

Create a graph of y = f(x)  that shows all significant behavior on the entire real line.

>   

Steps 1-3: Analysis Based on the Function

This function is defined for all real numbers. The range is difficult to determine. Note that

>    q1 := Limit( f1, x=infinity ):
q1 = value( q1 );

Limit(x^6-10*x^5-15*x^4+140*x^3+160*x^2-528*x-800,x = infinity) = infinity

>    q2 := Limit( f1, x=-infinity ):
q2 = value( q2 );

Limit(x^6-10*x^5-15*x^4+140*x^3+160*x^2-528*x-800,x = -infinity) = infinity

so the global maximum is + infinity . There must be a global minimum, but we do not yet have enough information to even estimate it.

This function is neither even nor odd and is definitely not periodic. There are no endpoints to consider.

The intercept is y  = -800, so one point on the graph is ( 0, -900 ). This information will be collected for reporting in a table immediately prior to creating the graph.

>    int1 := [ 0, F1(0), `intercept` ]:
int1;

[0, -800, intercept]

(Note that we already have significant information suggesting that the range of this function will be very large.)

Finding roots is not possible to do by hand. As a sixth-degree polynomial, there are six zeroes but there is no general formula for these roots. Maple's solve  command provides approximations to all six zeroes of this polynomial:

>    q3 := solve( f1=0., x ):
q3;

-2.588203081, -1.726727941-.6110506992*I, -1.726727941+.6110506992*I, 3.020357309-.2993429264*I, 3.020357309+.2993429264*I, 10.00094434
-2.588203081, -1.726727941-.6110506992*I, -1.726727941+.6110506992*I, 3.020357309-.2993429264*I, 3.020357309+.2993429264*I, 10.00094434

The two real-valued roots are, approximately,

>    q4 := op(remove( has, [q3], I )):
evalf[4]( q4 );

-2.588, 10.00

The corresponding point on the graph are ( -2.588, 0 ) and ( 10, 0 ). The information needed for the summary table is

>    zero1 := seq( [x,0, `zero`], x=q4 ):
evalf[4]( zero1 );

[-2.588, 0., zero], [10.00, 0., zero]

Because the function is continuous and has only these two zeroes, the sign of the function can change only at these two points. The SignChart  command (defined at the top of this worksheet) can be used to create a sign chart showing where the function is positive (pink) and negative (cyan).

>    SignChart( f1, x=-10..15, 0 );

[Maple Plot]

Observe that we now know the global minimum must occur somewhere between -2.588 and 10.00.

There are no asymptotes.

>   

Step 4: Analysis Based on the First Derivative

The first derivative is

>    df1 := diff( f1, x ):
`f '`(x) = df1;

`f '`(x) = 6*x^5-50*x^4-60*x^3+420*x^2+320*x-528

The stationary points are

>    stat1 := solve( df1=0., x ):
evalf[4]( stat1 );

3., -2., -2., 8.467, .8661

There are no endpoints and no singular points

>    end1 := NULL:
sing1 := NULL:

The critical points of this function are

>    crit1 := [ stat1, sing1, end1 ]:
evalf[4]( crit1 );

[3., -2., -2., 8.467, .8661]

The critical points divide the domain into intervals on which the derivative does not change sign. (In the following sign chart the first derivative is positive on pink intervals and negative on cyan intervals. Note that the third argument is the order of the derivative.)

>    SignChart( f1, x=-10..15, 1 );

[Maple Plot]

From this sign chart, and the First Derivative Test, it is clear the function has local minima where the sign chart changes from cyan to pink, i.e., at x  = 0.8661 and x  = 8.467, and has local maxima where the sign chart changes from pink to cyan, i.e., at x  = 3. The corresponding points on the graph of the function are

>    cp1 := seq( [ x, F1(x), `critical point` ], x=crit1 ):
evalf[4]( cp1 );

[3., -80., `critical point`], [-2., -80., `critical point`], [-2., -80., `critical point`], [8.467, -.5262e5, `critical point`], [.8661, -1059., `critical point`]
[3., -80., `critical point`], [-2., -80., `critical point`], [-2., -80., `critical point`], [8.467, -.5262e5, `critical point`], [.8661, -1059., `critical point`]

The global minimum can now be determined by comparison of the function values for the local minima; hence, the global minimum is -52620 and occurs near x  = 8.467.

>   

Step 5: Analysis Based on the Second Derivative

The second derivative is

>    ddf1 := diff( f1, x,x ):
`f ''`(x) = ddf1;

`f ''`(x) = 30*x^4-200*x^3-180*x^2+840*x+320

The possible inflection points are

>    possinfl1 := solve( ddf1=0., x ):
evalf[4]( possinfl1 );

-2., -.3646, 2.115, 6.917

The concavity on the five intervals defined by these four points is easiest to display in terms of a sign chart for the second derivative. (Intervals where the function is concave up are shown in pink; concave down in cyan.)

>    SignChart( f1, x=-10..15, 2 );

[Maple Plot]

There is a sign change in the second derivative at each zero of the second derivative. The coordinates of the four inflection points are

>    ip1 := seq( [ x, F1(x), `inflection point` ], x=[possinfl1] ):
evalf[4]( ip1 );

[-2., -80., `inflection point`], [-.3646, -593.2, `inflection point`], [2.115, -510.6, `inflection point`], [6.917, -.3361e5, `inflection point`]
[-2., -80., `inflection point`], [-.3646, -593.2, `inflection point`], [2.115, -510.6, `inflection point`], [6.917, -.3361e5, `inflection point`]

>   

Step 6: Graph the Function

The important points identified in Steps 1-5 include the intercept, the zeroes, the critical points, and the inflection points. These can be collected in a table (sorted by increasing value of x ):

>    important1 := sort( [ int1, zero1, cp1, ip1 ], (a,b)->a[1]<b[1] ):
tab1 := [ [`x`, `y`, `description`], [`-----`, `-----`, `---------------`], op(important1) ]:
matrix( evalf[4]( tab1 ) );

matrix([[x, y, `description`], [`-----`, `-----`, `---------------`], [-2.588, 0., zero], [-2., -80., `inflection point`], [-2., -80., `critical point`], [-2., -80., `critical point`], [-.3646, -593.2,...

Our sketch of the function begins by plotting these points

>    pts1 := [seq( P[1..2], P=important1 )]:
Ppts1 := plot( pts1, color=blue, style=point, symbolsize=20 ):
display( Ppts1, view=[-10..15,DEFAULT],
         title=sprintf("Important Points for\n y=%a",f1) );

[Maple Plot]

The sign charts for the function and its first two derivatives are used to ``connect the dots''. (Note how a list is used in the third argument to plot multiple sign charts in one Maple plot.)

>    SignChart( f1, x=-10..15, [0,1,2] );

[Maple Plot]

Remember that the global maximum of the function is M = infinity  and the global minimum is m = -52620 ; this means the function is going to increase very rapidly as abs(x)  increases.

>    Pfn1 := plot( f1, x=-10..15, view=[DEFAULT,-53000..53000], numpoints=250 ):
display( [Ppts1, Pfn1],
         title=sprintf("Important Points and Graph for\n y=%a",f1) );

[Maple Plot]

On this scale it is difficult to clearly see the local extrema and inflection points. Since all but three of the ``interesting points'' are contained in the interval [-3,4], it makes sense to zoom in on that region of the function.To select a viewing window, identify the largest and smallest y-coordinate from the critical points that are to be displayed and the endpoints of the bounded interval

>    f(-3) = F1(-3);
f(4) = F1(4);

f(-3) = 388

f(4) = -1376

On this viewing window, the important points are

>    display( Ppts1, view=[-3..4,-1500..500],
         title=sprintf("Important Points for\n y=%a",f1) );

[Maple Plot]

and the corresponding sign chart are

>    SignChart( f1, x=-3..4, [0,1,2] );

[Maple Plot]

With this information it is a straightforward task to complete the graph of the function. The result is

>    display( [Ppts1,Pfn1], view=[-3..4,-1500..500],
         title=sprintf("Important Points and Graph for\n y=%a",f1) );

[Maple Plot]

>   

To conclude, it is interesting to compare our graphs with the ones produced by Maple's FunctionChart  command. First, on the interval [-10,15]

>    FunctionChart( f1, -10..15, view=[DEFAULT,-53000..53000],
               pointoptions=[symbolsize=20],
               slope=[thickness(2,2), color(red,blue)],
               concavity=[filled(pink,cyan)] );

[Maple Plot]

and also on [ -3, 4 ]

>    FunctionChart( f1, -3..4, view=[DEFAULT,-1500..500],
               pointoptions=[symbolsize=20],
               slope=[thickness(2,2), color(red,blue)],
               concavity=[filled(pink,cyan)] );

[Maple Plot]

>   

Example 2: Rational Function

Let

>    f2 := (-x^3+3*x^2-5*x+6)/(x^2-4*x+3):
F2 := unapply( f2, x ):
f(x) = f2;

f(x) = (-x^3+3*x^2-5*x+6)/(x^2-4*x+3)

Create a graph of y = f(x)  that shows all significant behavior on the entire real line.

>   

Steps 1-3: Analysis Based on the Function

Because the denominator of has zeroes at

>    q1 := solve( denom(f2)=0, x ):
q1;

3, 1

but, except for these points, the function is defined and continuous for all real numbers.

The range is ( -infinity , infinity  ) because

>    q2 := Limit( f2, x=infinity ):
q2 = value( q2 );

Limit((-x^3+3*x^2-5*x+6)/(x^2-4*x+3),x = infinity) = -infinity

>    q3 := Limit( f2, x=-infinity ):
q3 = value( q3 );

Limit((-x^3+3*x^2-5*x+6)/(x^2-4*x+3),x = -infinity) = infinity

All interesting extrema will be local.

This function is neither even nor odd and is definitely not periodic. There are no endpoints to consider.

The intercept is y = 6/5 , so one point on the graph is

>    int2 := [ 0, F2(0), `intercept` ]:
int2;

[0, 2, intercept]

The zeroes of the numerator of f are not obvious, but Maple reports

>    q4 := solve( numer(f2)=0, x );

q4 := 2, 1/2+1/2*I*11^(1/2), 1/2-1/2*I*11^(1/2)

so the real-valued zero of f are

>    q5 := remove( has, [q4], I ):
op(q5);

2

The corresponding point on the graph are

>    zero2 := seq( [x,0, `zero`], x=q5 ):
evalf[4]( zero2 );

[2., 0., zero]

The sign chart for the function on [ -3, 4 ] is

>    SignChart( f2, x=-3..4, 0 );

[Maple Plot]

Notice how the function changes sign at the holes in the domain and the zero of the numerator.

There are no horizontal asymptotes.

>    horiz2 := NULL:

Vertical asymptotes could possibly exist at x = 1  and x = 3 . To test both points, compute the four limits

>    q6 := Limit( f2, x=1, right ):
q6 = value( q6 );

Limit((-x^3+3*x^2-5*x+6)/(x^2-4*x+3),x = 1,right) = -infinity

>    q7 := Limit( f2, x=1, left ):
q7 = value( q7 );

Limit((-x^3+3*x^2-5*x+6)/(x^2-4*x+3),x = 1,left) = infinity

>    q8 := Limit( f2, x=3, right ):
q8 = value( q8 );

Limit((-x^3+3*x^2-5*x+6)/(x^2-4*x+3),x = 3,right) = -infinity

>    q9 := Limit( f2, x=3, left ):
q9 = value( q9 );

Limit((-x^3+3*x^2-5*x+6)/(x^2-4*x+3),x = 3,left) = infinity

There are two vertical asymptotes:

>    vert2 := x=1, x=3:
vert2;

x = 1, x = 3

The search for an oblique asymptote is somewhat complicated. But, it is simplest to see by observing that long division yields

>    q10 := quo(numer(f2),denom(f2),x, 'q11'):

>    f(x) = f2;
`` = q10 + q11/denom(h2);

f(x) = (-x^3+3*x^2-5*x+6)/(x^2-4*x+3)

`` = -7*x+8

This suggests y = -x-1  is a candidate for an asymptote of f. To confirm this

>    q12 := Limit( f2-q10, x=infinity ):
q12 = value( q12 );

Limit((-x^3+3*x^2-5*x+6)/(x^2-4*x+3)+x+1,x = infinity) = 0

>    q13 := Limit( f2-q10, x=-infinity ):
q13 = value( q13 );

Limit((-x^3+3*x^2-5*x+6)/(x^2-4*x+3)+x+1,x = -infinity) = 0

The oblique asymptote for this function is

>    obliq2 := y = q10:
obliq2;

y = -x-1

The complete set of asymptotes for this problem is

>    asymp2 := horiz2, vert2, obliq2:
asymp2;

x = 1, x = 3, y = -x-1

>   

Step 4: Analysis Based on the First Derivative

The first derivative is

>    df2 := simplify(diff( f2, x )):
`f '`(x) = df2;

`f '`(x) = -(x^4-8*x^3+16*x^2-6*x-9)/(x^2-4*x+3)^2

The stationary points are the real zeroes of the first derivative

>    q14 := solve( df2=0., x ):
stat2 := op(remove( has, [q14], I )):
evalf[4]( stat2 );

-.5318, 5.217

The holes in the domain are neither singular points nor endpoints.

>    sing2 := NULL:
end2 := NULL:

The critical points of this function are

>    crit2 := [ stat2, sing2, end2 ]:
evalf[4]( crit2 );

[-.5318, 5.217]

The critical points divide the domain into intervals on which the derivative does not change sign. (In the following sign chart the first derivative is positive on pink intervals and negative on cyan intervals.)

>    SignChart( f2, x=-10..10, 1 );

[Maple Plot]

From this sign chart, and the First Derivative Test, it is clear the function has a local minimum where the sign chart changes from cyan to pink, i.e., at x  = -0.5318, and has a local maximum where the sign chart changes from pink to cyan, i.e., at x  = 5.217. The corresponding points on the graph of the function are

>    cp2 := seq( [ x, F2(x), `critical point` ], x=crit2 ):
evalf[4]( cp2 );

[-.5318, 1.785, `critical point`], [5.217, -8.602, `critical point`]

The global minimum can now be determined by comparison of the function values for the local minima; hence, the global minimum is -52620 and occurs near x  = 8.467.

>   

Step 5: Analysis Based on the Second Derivative

The second derivative is

>    ddf2 := simplify(diff( f2, x,x )):
`f ''`(x) = ddf2;

`f ''`(x) = -6*(2*x^3-9*x^2+18*x-15)/(x^2-4*x+3)^3

The possible inflection points are the real-valued zeroes of the second derivative:

>    q15 := solve( ddf2=0., x ):
possinfl2 := op(remove( has, [q15], I )):
evalf[4]( possinfl2 );

1.819

The concavity on the five intervals defined by these four points is easiest to display in terms of a sign chart for the second derivative. (Intervals where the function is concave up are shown in pink; concave down in cyan.)

>    SignChart( f2, x=-10..10, 2 );

[Maple Plot]

There is a sign change in the second derivative at the zero -- and at each hole in the domain. The coordinates on the inflection point in the domain is

>    ip2 := seq( [ x, F2(x), `inflection point` ], x=[possinfl2] ):
evalf[4]( ip2 );

[1.819, -.8405, `inflection point`]

>   

Step 6: Graph the Function

The important points identified in Steps 1-5 include the intercept, the zeroes, the critical points, and the inflection point. These can be collected in a table (sorted by increasing value of x ):

>    important2 := sort( [ int2, zero2, cp2, ip2 ], (a,b)->a[1]<b[1] ):
tab2 := [ [`x`, `y`, `description`], [`-----`, `-----`,`---------------`], op(important2) ]:
matrix( evalf[4]( tab2 ) );

matrix([[x, y, `description`], [`-----`, `-----`, `---------------`], [-.5318, 1.785, `critical point`], [0., 2., intercept], [1.819, -.8405, `inflection point`], [2., 0., zero], [5.217, -8.602, `criti...

Our sketch of the function begins by plotting these points

>    pts2 := [seq( P[1..2], P=important2 )]:
Ppts2 := plot( pts2, color=blue, style=point, symbolsize=20 ):
display( Ppts2, view=[-10..10,DEFAULT],
         title=sprintf("Important Points for\n y=%a",f2) );

[Maple Plot]

>    SignChart( f2, x=-10..10, [0,1,2] );

[Maple Plot]

Looking at these points and the classification of each point it might appear to be impossible to ``connect the dots'' following what we know about the sign of the function and its first two derivatives. But, remember that there are two points where the function is discontinuous. When the asymptotes are added, the picture becomes a little clearer.

>    Pasym2 := implicitplot( {asymp2}, x=-10..15, y=-20..10, color=sienna ):
display( [Ppts2,Pasym2],
         title=sprintf("Important Points and Asymptotes for\n f(x)=%a", f2) );

[Maple Plot]

>   

The behavior of the function at each asymptote, combined with the local extrema and inflection point results, provides enough information to complete the graph.

>    Pfn2 := plot( f2, x=-10..15, discont=true,
              view=[DEFAULT,-20..10], numpoints=250 ):
display( [Ppts2, Pasym2, Pfn2],
         title=sprintf("Important Points, Asymptotes, and Graph for\n y=%a",f1) );

[Maple Plot]

>   

To conclude, it is interesting to compare our graphs with the ones produced by Maple's FunctionChart  command. First, on the interval [-10,15]

>    FunctionChart( f2, -10..15, view=[DEFAULT,-20..10],
               pointoptions=[symbolsize=20],
               slope=[thickness(2,2), color(red,blue)],
               concavity=[filled(pink,cyan)] );

[Maple Plot]

>   

Example 3: Plotting a Parametric Family of Functions

Let

>    f3 := 10/(x^2+6*x+c):
F3 := unapply( f3, x ):
f(x) = f3;

f(x) = 10/(x^2+6*x+c)

Determine the value of c  for where the graphs of y = f(x)  undergo a significant change in appearance. Prepare one plot containing representative graphs of each type.

>   

The key to this problem is the denominator. Completing the square on this quadratic allows the denominator to be rewritten as

>    q1 := denom( f3 ):
q1 = student[completesquare]( q1, x );

x^2+6*x+c = (x+3)^2-9+c

There are three cases to consider:

Based on this analysis it appears the critical value of the parameter is c  = 9.

>   

Steps 1-3: Analysis Based on the Function

The different domains for the three cases have already been noted:

  • for c  > 9:

>    domain3a := [-infinity,infinity]:
domain3a;

[-infinity, infinity]

  • for c  = 9:

>    domain3b := [ x<>-3 ]:
domain3b;

[x <> -3]

  • for c  < 9:

>    domain3c := [ x<>-3+sqrt(9-c), x<>-3-sqrt(9-c) ]:
domain3c;

[x <> -3+(9-c)^(1/2), x <> -3-(9-c)^(1/2)]

A table comparing properties of this function for the three different cases will be created. The following will be used to make one line of this table.

>    domain3 := [ `domain`, domain3a, domain3b, domain3c ]:

>   

To check for horizontal asymptotes, consider

>    q1 := Limit( f3, x=infinity ):
q1 = value( q1 );

Limit(10/(x^2+6*x+c),x = infinity) = 0

>    q2 := Limit( f3, x=-infinity ):
q2 = value( q2 );

Limit(10/(x^2+6*x+c),x = -infinity) = 0

Thus, all three cases have the horizontal asymptote

>    horiz3a := y = 0:
horiz3b := horiz3a:
horiz3c := horiz3a:

>    horiz3 := [ `horiz. asymp.`, horiz3a, horiz3b, horiz3c ]:

The search for vertical asymptotes produces different results for different values of c :

  • for c  > 9, there are no vertical asymptotes

>    vert3a := `none`:

  • for c  = 9, there is one vertical asymptote at

>    vert3b := x = -3:
vert3b;

x = -3

  • for c  < 9, there are two vertical asymptotes at x

>    vert3c := [ x = -3-sqrt(9-c), x=-3+sqrt(9-c) ]:
vert3c;

[x = -3-(9-c)^(1/2), x = -3+(9-c)^(1/2)]

>    vert3 := [ `vert. asymp.`, vert3a, vert3b, vert3c ]:

>   

For no value of c  is the function even or odd or periodic.

When x  = 0 is in the domain (and c <> 0 ), the intercept is y = 10/c .

>    int3a := [ 0, 10/c ]:
int3b := int3a:
int3c := int3a:
int3 := [`intercept`, int3a, int3b, int3c ]:

>   

Step 4: Analysis Based on the First Derivative

The first derivative,

>    df3 := simplify(diff( f3, x )):
`f '`(x) = df3;

`f '`(x) = -20*(x+3)/(x^2+6*x+c)^2

is defined on the same domain as the original function (regardless of the value of c ). As a result there are no singular points and no endpoints.

>    sing3 := NULL:
end3 := NULL:

The zero of the numerator of the first derivative is

>    stat3 := solve( numer(df3)=0, x ):
evalf[4]( stat3 );

-3.

Note that

  • when c <> 9   there is a single critical point

>    crit3a := [seq( x=z, z=[ stat3, sing3, end3 ] )]:
crit3c := crit3a:
crit3a;

[x = -3]

  • for c  = 9, x  = -3 is not in the domain of the function and so there are no critical points.

>    crit3b := `none`:
crit3c := `none`:

>    crit3 := [ `critical point`, crit3a, crit3b, crit3c ]:

A closer look at the first derivative indicates that `f '`(x)  > 0 for all x  < -3 (and in the domain of f) and `f '`(x)  < 0 for all x  > -3 (and in the domain of f). In particular, for c  > 9, the function is increasing to the left of x  = -3, decreasing to the right of x  = -3, and x  = -3 is a local maximum.

>    lextrema3 := [ `local extrema`, `maximum`, `none`, `maximum` ]:

>   

Step 5: Analysis Based on the Second Derivative

The second derivative is

>    ddf3 := simplify(diff( f3, x,x )):
`f ''`(x) = ddf3;

`f ''`(x) = 20*(3*x^2+18*x+36-c)/(x^2+6*x+c)^3

The possible inflection points are the real-valued zeroes of the second derivative:

>    q3 := solve( ddf3=0, x ):
q4 := [seq( x=z, z=[q3] )]:
q4;

[x = -3+1/3*(-27+3*c)^(1/2), x = -3-1/3*(-27+3*c)^(1/2)]

Once again, this depends on the parameter:

  • if c  > 9, both zeroes are real and in the domain of f is

>    possinfl3a := q4:
possinfl3a;

[x = -3+1/3*(-27+3*c)^(1/2), x = -3-1/3*(-27+3*c)^(1/2)]

  • if c  = 9, there is only one potential possible inflection point, but recall that x  = -3 is not in the domain for this value of c  

>    possinfl3b := vert3b:
possinfl3b;

x = -3

  • if c  < 9, there are no real-valued solutions to `f ''`(x)  = 0 but the concavity could change at the two vertical asymptotes

>    possinfl3c := vert3c:
possinfl3c;

[x = -3-(9-c)^(1/2), x = -3+(9-c)^(1/2)]

>   

When f '' is evaluated on each subinterval identified above, it is found that

  • for c  > 9 the function is concave up except between the two inflection points where the function is concave down

>    inflpt3a := possinfl3a:

  • for c  = 9 the function is concave up to the left and right of x  = -3

>    inflpt3b := `none`:

  • for c  < 9 the function is concave up on the two unbounded intervals and is concave down on the interval between the two singularities

>    inflpt3c := possinfl3c:

>    inflpt3 := [`infl. pt.`, inflpt3a, inflpt3b, inflpt3c ]:

>   

Step 6: Graph the Function

Steps 1-5 have revealed a number of differences between the graphs for c  > 9, c  = 9, and c  < 9. The similarities and differences are summarized in the following table.

>    matrix( [ [`category`, `c > 9`, `c = 9`, `c < 9`],
          [`-------------------`, `----------------------`,  `----------------------`, `----------------------`],
          domain3, horiz3, vert3, int3, crit3, lextrema3, inflpt3 ] );

matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...
matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...
matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...
matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...
matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...
matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...
matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...
matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...
matrix([[category, `c > 9`, `c = 9`, `c < 9`], [`-------------------`, `----------------------`, `----------------------`, `----------------------`], [domain, [-infinity, infinity], [x <> -3], [x <> -3...

>   

An animation containing plots for different values of c  shows the results very nicely.

>    Clist := [2*($0..4),8.5,9,9.5,2*($5..9)]:

>    COLORS := red,blue,green,sienna,pink,cyan:
COLORS := [COLORS,COLORS,COLORS]:

>    p1 := seq( plot( eval(f3,c=Clist[i]),
                 x=-10..6,
                 discont=true,
                 color=COLORS[i],
                 title=sprintf("Plot of 1/(x^2+6*x+c)\n for c=%a",Clist[i]) ),
           i=1..nops(Clist) ):

>    display( [p1], view=[DEFAULT,-40..30], insequence=true );

[Maple Plot]

>   

Or, with all plots in a single frame:

>    display( [p1], view=[DEFAULT,-40..30],
          title=sprintf("Plots of 1/(x^2+6*x+c)\n for c=%a",Clist) );

[Maple Plot]

>   

And, finally, an animation of the FunctionChart  plots are very informative.

>    p2 := [seq(
  FunctionChart( factor(f3), -10..6, view=[DEFAULT,-40..30],
                 pointoptions=[symbolsize=20],
                 slope=[thickness(2,2), color(red,blue)],
                 concavity=[filled(pink,cyan)] ),
           c=Clist )]:

>    display( p2, insequence=true );

[Maple Plot]

>   

Example 4: Periodic Function

Let

>    f4 := sin(4*x+1/2)*cos(x/2):
F4 := unapply( f4, x ):
f(x) = f4;

f(x) = sin(4*x+1/2)*cos(1/2*x)

>   

Create a graph of y = f(x)  that shows all significant behavior of the function..

>   

Steps 1-3: Analysis Based on the Function

This function is defined for all real numbers. Because each term in the product has range [ -1, 1 ], their product will take on values on [ -1, 1 ]. Whether the range is [ -1, 1 ] or a subset of [ -1, 1 ] is not important at this time.

This function is neither even nor odd,

>    simplify( F4(-x)-F4(x) );

-cos(1/2*x)*(sin(4*x-1/2)+sin(4*x+1/2))

>    simplify( F4(-x)+F4(x) );

cos(1/2*x)*(-sin(4*x-1/2)+sin(4*x+1/2))

but is periodic with period 4*Pi .

>    simplify( F4(x+4*Pi)-F4(x) );

0

Because the function is periodic it suffices to sketch its graph on one period. If we choose to work on the interval [ 0, 4*Pi  ], then the endpoints are

>    end4 := 0, 4*Pi:
end4;

0, 4*Pi

The intercept is y = 0 , so one point on the graph is

>    int4 := [ 0, F4(0), `intercept` ]:
int4;

[0, sin(1/2), intercept]

The function will be zero whenever either factor is zero. The solutions to sin(4*x+1/2) = 0  satisfy

>    q1 := 4*x+1/2 = i*Pi:
q1;

4*x+1/2 = i*Pi

That is,

>    q2 := isolate( q1, x ):
q2;

x = 1/4*i*Pi-1/8

for an integer i . The zeroes in [ 0, 4*Pi  ] are

>    q3 := seq( rhs(q2), i=1..16 ):
q3;

1/4*Pi-1/8, 1/2*Pi-1/8, 3/4*Pi-1/8, Pi-1/8, 5/4*Pi-1/8, 3/2*Pi-1/8, 7/4*Pi-1/8, 2*Pi-1/8, 9/4*Pi-1/8, 5/2*Pi-1/8, 11/4*Pi-1/8, 3*Pi-1/8, 13/4*Pi-1/8, 7/2*Pi-1/8, 15/4*Pi-1/8, 4*Pi-1/8
1/4*Pi-1/8, 1/2*Pi-1/8, 3/4*Pi-1/8, Pi-1/8, 5/4*Pi-1/8, 3/2*Pi-1/8, 7/4*Pi-1/8, 2*Pi-1/8, 9/4*Pi-1/8, 5/2*Pi-1/8, 11/4*Pi-1/8, 3*Pi-1/8, 13/4*Pi-1/8, 7/2*Pi-1/8, 15/4*Pi-1/8, 4*Pi-1/8

Likewise the zeroes of cos(x/2)  are

>    q4 := x/2 = Pi/2 + i*Pi:
q4;

1/2*x = 1/2*Pi+i*Pi

where i  is an integer. The zeroes in [ 0, 4*Pi  ] are

>    q5 := seq( solve(q4,x), i=0..1 ):
q5;

Pi, 3*Pi

The first points on the graph are the 18 zeroes of the product on [ 0, 4*Pi  ]:

>    zero4 := seq( [x,0, `zero`], x=[q3,q5] ):
evalf[4]( zero4 );

[.6605, 0., zero], [1.446, 0., zero], [2.231, 0., zero], [3.017, 0., zero], [3.803, 0., zero], [4.588, 0., zero], [5.373, 0., zero], [6.159, 0., zero], [6.945, 0., zero], [7.730, 0., zero], [8.515, 0.,...
[.6605, 0., zero], [1.446, 0., zero], [2.231, 0., zero], [3.017, 0., zero], [3.803, 0., zero], [4.588, 0., zero], [5.373, 0., zero], [6.159, 0., zero], [6.945, 0., zero], [7.730, 0., zero], [8.515, 0.,...
[.6605, 0., zero], [1.446, 0., zero], [2.231, 0., zero], [3.017, 0., zero], [3.803, 0., zero], [4.588, 0., zero], [5.373, 0., zero], [6.159, 0., zero], [6.945, 0., zero], [7.730, 0., zero], [8.515, 0.,...
[.6605, 0., zero], [1.446, 0., zero], [2.231, 0., zero], [3.017, 0., zero], [3.803, 0., zero], [4.588, 0., zero], [5.373, 0., zero], [6.159, 0., zero], [6.945, 0., zero], [7.730, 0., zero], [8.515, 0.,...

The sign chart for the function on [ 0, 4*Pi  ] is

>    SignChart( f4, x=0..4*Pi, 0 );

[Maple Plot]

Notice that some of the adjacent zeroes are so close that they are not visible on this sign chart.

The continuity of the function on [ 0, 4*Pi  ] means there can be no vertical asymptotes. Likewise, because the domain is bounded there are no horizontal or oblique asymptotes.

>   

Step 4: Analysis Based on the First Derivative

The first derivative is

>    df4 := simplify(diff( f4, x )):
`f '`(x) = df4;

`f '`(x) = 4*cos(4*x+1/2)*cos(1/2*x)-1/2*sin(4*x+1/2)*sin(1/2*x)

The stationary points are the real zeroes of the first derivative

>    q6 := solve( df4=0., x ):
evalf[4]( q6 );

-6.020, 5.774, -5.248, 5.003, -4.484, 4.245, -3.753, 3.546, -3.205, 3.078, -2.737, 2.530, -2.038, 1.799, -1.280, 1.035, -.5096, .2636
-6.020, 5.774, -5.248, 5.003, -4.484, 4.245, -3.753, 3.546, -3.205, 3.078, -2.737, 2.530, -2.038, 1.799, -1.280, 1.035, -.5096, .2636

Note that these zeroes are in the interval [ -2*Pi , 2*Pi  ]. By periodicity, the zeroes in [ 2*Pi , 6*Pi  ] can be obtained by adding 4*Pi  to each of the above zeroes.

>    q7 := seq(evalf(z+4*Pi),z=[q6]):
stat4 := op(select( InInterval, [q6,q7], [0,evalf(4*Pi)] )):
evalf[4]( stat4 );

5.774, 5.003, 4.245, 3.546, 3.078, 2.530, 1.799, 1.035, .2636, 6.547, 7.319, 8.083, 8.813, 9.362, 9.829, 10.53, 11.29, 12.06
5.774, 5.003, 4.245, 3.546, 3.078, 2.530, 1.799, 1.035, .2636, 6.547, 7.319, 8.083, 8.813, 9.362, 9.829, 10.53, 11.29, 12.06

>   

There are no singular points and we have already identified the endpoints.

>    sing4 := NULL:
end4;

0, 4*Pi

The critical points of this function are

>    crit4 := [ stat4, sing4, end4 ]:
evalf[4]( crit4 );

[5.774, 5.003, 4.245, 3.546, 3.078, 2.530, 1.799, 1.035, .2636, 6.547, 7.319, 8.083, 8.813, 9.362, 9.829, 10.53, 11.29, 12.06, 0., 12.57]
[5.774, 5.003, 4.245, 3.546, 3.078, 2.530, 1.799, 1.035, .2636, 6.547, 7.319, 8.083, 8.813, 9.362, 9.829, 10.53, 11.29, 12.06, 0., 12.57]

The critical points divide the domain into intervals on which the derivative does not change sign. (In the following sign chart the first derivative is positive on pink intervals and negative on cyan intervals.)

>    SignChart( f4, x=0..4*Pi, 1 );

[Maple Plot]

From this sign chart, and the First Derivative Test, it is clear the function has a local minimum at each of the nine points where the sign chart changes from cyan to pink and has a local maximum at the nine points where the sign chart changes from pink to cyan. (Only the two endpoints are not local extrema.) The corresponding points on the graph of the function are

>    cp4 := seq( [ x, F4(x), `critical point` ], x=crit4 ):
evalf[4]( cp4 );

[5.774, .9672, `critical point`], [5.003, -.7987, `critical point`], [4.245, .5136, `critical point`], [3.546, -.1715, `critical point`], [3.078, .7731e-2, `critical point`], [2.530, -.2801, `critical ...
[5.774, .9672, `critical point`], [5.003, -.7987, `critical point`], [4.245, .5136, `critical point`], [3.546, -.1715, `critical point`], [3.078, .7731e-2, `critical point`], [2.530, -.2801, `critical ...
[5.774, .9672, `critical point`], [5.003, -.7987, `critical point`], [4.245, .5136, `critical point`], [3.546, -.1715, `critical point`], [3.078, .7731e-2, `critical point`], [2.530, -.2801, `critical ...
[5.774, .9672, `critical point`], [5.003, -.7987, `critical point`], [4.245, .5136, `critical point`], [3.546, -.1715, `critical point`], [3.078, .7731e-2, `critical point`], [2.530, -.2801, `critical ...
[5.774, .9672, `critical point`], [5.003, -.7987, `critical point`], [4.245, .5136, `critical point`], [3.546, -.1715, `critical point`], [3.078, .7731e-2, `critical point`], [2.530, -.2801, `critical ...
[5.774, .9672, `critical point`], [5.003, -.7987, `critical point`], [4.245, .5136, `critical point`], [3.546, -.1715, `critical point`], [3.078, .7731e-2, `critical point`], [2.530, -.2801, `critical ...
[5.774, .9672, `critical point`], [5.003, -.7987, `critical point`], [4.245, .5136, `critical point`], [3.546, -.1715, `critical point`], [3.078, .7731e-2, `critical point`], [2.530, -.2801, `critical ...

These points show that the range is [ -0.9912, 0.9912 ]

>   

Step 5: Analysis Based on the Second Derivative

The second derivative is

>    ddf4 := simplify(diff( f4, x,x )):
`f ''`(x) = ddf4;

`f ''`(x) = -65/4*sin(4*x+1/2)*cos(1/2*x)-4*cos(4*x+1/2)*sin(1/2*x)

The possible inflection points are the real-valued zeroes of the second derivative:

>    q8 := solve( ddf4=0., x ):
evalf[4]( q8 );

6.162, -5.643, 5.402, -4.888, 4.651, -4.156, 3.935, -3.501, 3.321, -2.962, 2.783, -2.348, 2.127, -1.632, 1.395, -.8815, .6400, -.1213
6.162, -5.643, 5.402, -4.888, 4.651, -4.156, 3.935, -3.501, 3.321, -2.962, 2.783, -2.348, 2.127, -1.632, 1.395, -.8815, .6400, -.1213

Shifting these solutions by 4*Pi  then removing those outside [ 0, 4*Pi  ] yields a list of 18 possible inflection points.

>    q9 := seq(evalf(z+4*Pi),z=[q8]):
possinfl4 := op(select( InInterval, [q8,q9], [0,evalf(4*Pi)] )):
evalf[4]( possinfl4 );

6.162, 5.402, 4.651, 3.935, 3.321, 2.783, 2.127, 1.395, .6400, 6.923, 7.678, 8.410, 9.066, 9.605, 10.22, 10.93, 11.68, 12.45
6.162, 5.402, 4.651, 3.935, 3.321, 2.783, 2.127, 1.395, .6400, 6.923, 7.678, 8.410, 9.066, 9.605, 10.22, 10.93, 11.68, 12.45

The concavity on the intervals defined by these 18 points is easiest to display in terms of a sign chart for the second derivative. (Intervals where the function is concave up are shown in pink; concave down in cyan.)

>    SignChart( f4, x=0..4*Pi, 2 );

[Maple Plot]

There is a sign change in the second derivative at point where `f ''`(x) = 0 . The coordinates on the inflection point in the domain is

>    ip4 := seq( [ x, F4(x), `inflection point` ], x=[possinfl4] ):
evalf[4]( ip4 );

[6.162, -.1491e-1, `inflection point`], [5.402, .1043, `inflection point`], [4.651, -.1734, `inflection point`], [3.935, .1957, `inflection point`], [3.321, -.8434e-1, `inflection point`], [2.783, -.14...
[6.162, -.1491e-1, `inflection point`], [5.402, .1043, `inflection point`], [4.651, -.1734, `inflection point`], [3.935, .1957, `inflection point`], [3.321, -.8434e-1, `inflection point`], [2.783, -.14...
[6.162, -.1491e-1, `inflection point`], [5.402, .1043, `inflection point`], [4.651, -.1734, `inflection point`], [3.935, .1957, `inflection point`], [3.321, -.8434e-1, `inflection point`], [2.783, -.14...
[6.162, -.1491e-1, `inflection point`], [5.402, .1043, `inflection point`], [4.651, -.1734, `inflection point`], [3.935, .1957, `inflection point`], [3.321, -.8434e-1, `inflection point`], [2.783, -.14...
[6.162, -.1491e-1, `inflection point`], [5.402, .1043, `inflection point`], [4.651, -.1734, `inflection point`], [3.935, .1957, `inflection point`], [3.321, -.8434e-1, `inflection point`], [2.783, -.14...
[6.162, -.1491e-1, `inflection point`], [5.402, .1043, `inflection point`], [4.651, -.1734, `inflection point`], [3.935, .1957, `inflection point`], [3.321, -.8434e-1, `inflection point`], [2.783, -.14...

>   

Step 6: Graph the Function

The important points identified in Steps 1-5 include the intercept, the zeroes, the critical points, and the inflection points. These can be collected in a table (sorted by increasing value of x ):

>    important4 := sort( evalf([ int4, zero4, cp4, ip4 ]), (a,b)->a[1]<b[1] ):
tab4 := [ [`x`, `y`, `description`], [`-----`, `-----`,`---------------`], op(important4) ]:
matrix( evalf[4]( tab4 ) );

matrix([[x, y, `description`], [`-----`, `-----`, `---------------`], [0., .4794, `critical point`], [0., .4794, intercept], [.2636, .9912, `critical point`], [.6400, .7718e-1, `inflection point`], [.6...

This is a long list. But, each point in this table is important. When these points are plotted

>    pts4 := [seq( P[1..2], P=important4 )]:
Ppts4 := plot( pts4, color=blue, style=point, symbolsize=20 ):
display( Ppts4,
         title=sprintf("Important Points for\n y=%a",f4) );

[Maple Plot]

>    SignChart( f4, x=0..4*Pi, [0,1,2] );

[Maple Plot]

It is now a fairly simple matter to obtain an accurate graph by connecting these points in succession.

>    Pfn4 := plot( f4, x=0..4*Pi ):
display( [Ppts4, Pfn4],
         title=sprintf("Important Points, Asymptotes, and Graph for\n y=%a",f4) );

[Maple Plot]

>   

To conclude, it is interesting to compare our graphs with the ones produced by Maple's FunctionChart  command on the interval [ 0, 4*Pi ]

>    FunctionChart( f4, 0..4*Pi,
               pointoptions=[symbolsize=20],
               slope=[thickness(2,2), color(red,blue)],
               concavity=[filled(pink,cyan)] );

[Maple Plot]

>   

Example 5: Reconstructing a Function from Its First Derivative

Let f be an unspecified function with the properties that f(0)  = -10, and

>    df5 := (x-4)*(x-2)/sqrt(x):
dF5 := unapply( f5, x ):
`f '`(x) = df5;

`f '`(x) = (x-4)*(x-2)/x^(1/2)

Determine all information needed to create a graph of the function f. In particular, create the table of important points and the sign charts for the first and second derivative. Then, draw the function by hand.

>   

Steps 1-3: Analysis Based on the Function

Because we do not have an explicit formula for the function, there is not much to do in Steps 1-3.

>   

Step 4: Analysis Based on the First Derivative

The first derivative is

>    `f '`(x) = df5;

`f '`(x) = (x-4)*(x-2)/x^(1/2)

The stationary points are the real zeroes of the first derivative

>    stat5 := solve( df5=0., x ):
evalf[4]( stat5 );

2., 4.

The fact that the derivative exists only for x  > 0 means the function f must be continuous for all x  > 0 (and, possibly, x  = 0).

>    sing5 := NULL:
end5 := 0:

The critical points of this function are

>    crit5 := [ stat5, sing5, end5 ]:
evalf[4]( crit5 );

[2., 4., 0.]

The critical points divide the domain into intervals on which the derivative does not change sign. (In the following sign chart the first derivative is positive on pink intervals and negative on cyan intervals.)

>    SignChart( df5, x=0..10, 0 );

[Maple Plot]

From this sign chart, and the First Derivative Test, it is clear the function has a local minimum at x  = 4 and has a local maximum at x  = 2. Also, because the derivative is positive immediately to the right of x  = 0, this endpoint is a local minimum. (There is nothing that can be said about global extrema.) All that is known about function values at the critical points is summarized below:

>    cp5 := [ 0,     -10, `endpoint` ],
       [ 0,     -10, `local minimum` ],
       [ 2,  `>-10`, `local maximum` ],
       [ 4, `<f(2)`, `local minimum` ]:
cp5;

[0, -10, endpoint], [0, -10, `local minimum`], [2, `>-10`, `local maximum`], [4, `<f(2)`, `local minimum`]

>   

Step 5: Analysis Based on the Second Derivative

The second derivative is

>    ddf5 := simplify(diff( df5, x )):
`f ''`(x) = ddf5;

`f ''`(x) = 1/2*(3*x^2-6*x-8)/x^(3/2)

The possible inflection points are the real-valued zeroes of the second derivative:

>    q1 := solve( ddf5=0., x ):
evalf[4]( q1 );

2.915, -.9149

The only possible inflection point is the root in the domain of the function:

>    possinfl5 := op(select( InInterval, [q1], [0,10] )):
evalf[4]( possinfl5 );

2.915

The concavity on the two intervals defined by this one point is easiest to display in terms of a sign chart for the second derivative.

>    SignChart( df5, x=0..10, 1 );

[Maple Plot]

There is one inflection point. a sign change in the second derivative at the zero. The coordinates on the inflection point in the domain is not known, but because the function is decreasing on ( 2, 4 ) we know  f(2) > f(2.915) > f(4):

>    ip5 := seq( [ x, `<f(2) & >f(4)`, `inflection point` ], x=[possinfl5] ):
evalf[4]( ip5 );

[2.915, `<f(2) & >f(4)`, `inflection point`]

>   

Step 6: Graph the Function

The important points identified in Steps 4 & 5 include the intercept, the zeroes, the critical points, and the inflection point. These can be collected in a table (sorted by increasing value of x ):

>    important5 := sort( [ cp5, ip5 ], (a,b)->a[1]<b[1] ):
tab5 := [ [`x`, `y`, `description`], [`-----`, `-----`,`---------------`], op(important5) ]:
matrix( evalf[4]( tab5 ) );

matrix([[x, y, `description`], [`-----`, `-----`, `---------------`], [0., -10., `local minimum`], [0., -10., endpoint], [2., `>-10`, `local maximum`], [2.915, `<f(2) & >f(4)`, `inflection point`], [4....

This is the table of important values that is requested at the outset of the problem. It is not difficult to sketch the general shape of the function from this information and the sign charts for the first and second derivatives

>    SignChart( df5, x=0..10, [0,1] );

[Maple Plot]

>   

Lesson Summary

The task of creating the graph of a function can be subdivided into the analysis of the function, the first derivative, and the second derivative. Some of the conclusions, e.g., the classification of local extrema, can be done in more than one stage of the process. From a table of important values compiled during the analysis and the sign charts for the function and its first two derivatives, it is usually fairly easy to complete the sketch by ``connecting the dots''.

You are encouraged to use Maple at any time while solving these problems. Remember, however, to avoid using Maple to plot the function until you have discovered all of the properties of the graph. Use the FunctionChart , in the Student[Calculus1]  package, command only as a check of your work.

As for the use of maplets, the FunctionAnalyzer  maplet [ Maplet Viewer][ MapleNet] is recommended over the CurveAnalysis  [ Maplet Viewer][ MapleNet] and DerivativePlot  [ Maplet Viewer][ MapleNet] maplets.

>   

What's Next?

If you understand the material in the Global Analysis and Local Analysis lessons, you should be essentially ready to begin the online homework assignment and the textbook homework assignment for this lesson. If you are a little uncertain, you are advised to review the earlier lessons and to master a few practice problems prior to beginning the homework assignment.

The Global Analysis, Local Analysis, Optimization Problems, and Graphing lessons provide a complete discussion of the use of calculus for locating and classifying the most interesting point on the graph of a function. The Mean Value Theorem lesson is an obvious but important theoretical result that, like the Intermediate Value Theorem, is also used in a variety of applications. The Related Rates lesson develops techniques for determining rates of change between two or more dependent variables.

>   

>