MC01VD

Roots of a quadratic equation with real coefficients

[Specification] [Arguments] [Method] [References] [Comments] [Example]

Purpose

  To compute the roots of a quadratic equation with real
  coefficients.

Specification
      SUBROUTINE MC01VD( A, B, C, Z1RE, Z1IM, Z2RE, Z2IM, INFO )
C     .. Scalar Arguments ..
      INTEGER           INFO
      DOUBLE PRECISION  A, B, C, Z1IM, Z1RE, Z2IM, Z2RE

Arguments

Input/Output Parameters

  A       (input) DOUBLE PRECISION
          The value of the coefficient of the quadratic term.

  B       (input) DOUBLE PRECISION
          The value of the coefficient of the linear term.

  C       (input) DOUBLE PRECISION
          The value of the coefficient of the constant term.

  Z1RE    (output) DOUBLE PRECISION
  Z1IM    (output) DOUBLE PRECISION
          The real and imaginary parts, respectively, of the largest
          root in magnitude.

  Z2RE    (output) DOUBLE PRECISION
  Z2IM    (output) DOUBLE PRECISION
          The real and imaginary parts, respectively, of the
          smallest root in magnitude.

Error Indicator
  INFO    INTEGER
          = 0:  successful exit;
          = 1:  if on entry, either A = B = 0.0 or A = 0.0 and the
                root -C/B overflows; in this case Z1RE, Z1IM, Z2RE
                and Z2IM are unassigned;
          = 2:  if on entry, A = 0.0; in this case Z1RE contains
                BIG and Z1IM contains zero, where BIG is a
                representable number near the overflow threshold
                of the machine (see LAPACK Library Routine DLAMCH);
          = 3:  if on entry, either C = 0.0 and the root -B/A
                overflows or A, B and C are non-zero and the largest
                real root in magnitude cannot be computed without
                overflow; in this case Z1RE contains BIG and Z1IM
                contains zero;
          = 4:  if the roots cannot be computed without overflow; in
                this case Z1RE, Z1IM, Z2RE and Z2IM are unassigned.

Method
  The routine computes the roots (r1 and r2) of the real quadratic
  equation
          2
     a * x  + b * x + c = 0

  as
          - b - SIGN(b) * SQRT(b * b - 4 * a * c)             c
     r1 = ---------------------------------------  and r2 = ------
                           2 * a                            a * r1

  unless a = 0, in which case

          -c
     r1 = --.
           b

  Precautions are taken to avoid overflow and underflow wherever
  possible.

Numerical Aspects
  The algorithm is numerically stable.

Further Comments
  None
Example

Program Text

*     MC01VD EXAMPLE PROGRAM TEXT
*     Copyright (c) 2002-2017 NICONET e.V.
*
*     .. Parameters ..
      INTEGER          NIN, NOUT
      PARAMETER        ( NIN = 5, NOUT = 6 )
*     .. Local Scalars ..
      DOUBLE PRECISION A, B, C, Z1IM, Z1RE, Z2IM, Z2RE
      INTEGER          INFO
*     .. External Subroutines ..
      EXTERNAL         MC01VD
*     .. Executable Statements ..
*
      WRITE ( NOUT, FMT = 99999 )
*     Skip the heading in the data file and read the data.
      READ ( NIN, FMT = '()' )
      READ ( NIN, FMT = * ) A, B, C
*     Solve the quadratic equation A*x**2 + B*x + C = 0.
      CALL MC01VD( A, B, C, Z1RE, Z1IM, Z2RE, Z2IM, INFO )
*
      IF ( INFO.NE.0 ) THEN
         WRITE ( NOUT, FMT = 99998 ) INFO
      ELSE
         WRITE ( NOUT, FMT = 99997 )
         WRITE ( NOUT, FMT = 99996 ) Z1RE, Z1IM, Z2RE, Z2IM
      END IF
*
      STOP
*
99999 FORMAT (' MC01VD EXAMPLE PROGRAM RESULTS',/1X)
99998 FORMAT (' INFO on exit from MC01VD = ',I2)
99997 FORMAT (' The roots of the quadratic equation are ')
99996 FORMAT (/' x = ',F8.4,2X,SP,F8.4,'*j',SS,/' x = ',F8.4,2X,SP,F8.4,
     $       '*j')
      END
Program Data
 MC01VD EXAMPLE PROGRAM DATA
   0.5  -1.0  2.0
Program Results
 MC01VD EXAMPLE PROGRAM RESULTS

 The roots of the quadratic equation are 

 x =   1.0000   +1.7321*j
 x =   1.0000   -1.7321*j

Return to index