Novice tries using AI code generators

There was a long thread in this forum on cubic equations a couple of years ago. Here is a short program that assumes that the cubic equation has been scaled to have a leading coefficient of 1. Test it using input coefficients 1, 2, 3 (one real root) and -6,11,-6 (three real roots).

cubic.f90
program cubic
implicit none
complex y2,y3
real b,c,d,Q,R,Dd2,Dd,s,T,alpha,pi,v(3),y1,rt3
read *,b,c,d !solve x^3 + b x^2 + c x + d = 0
Q = (3*c-b*b)/9; R = (9*b*c-27*d-2*b*b*b)/54
Dd2 = Q*Q*Q + R*R   ! discriminant
if (Dd2 < 0) then     ! All three roots are real
   s = -2*sqrt(-Q)
   alpha = acos(-R/(-Q)**1.5)
   pi =  acos(-1.0) !3.14159265
   v  =  (/ s,-s,-s /) * cos((alpha + (/ 0,1,-1 /)*pi)/3) - b/3.0
   print '(A,2x,3F10.5)','Three real roots:',v
else            ! One real root and a complex pair
   Dd = sqrt(Dd2)
   S  = cubrt(R+Dd); T = cubrt(R-Dd); rt3 = sqrt(3.0)
   y1 = S+T
   y2 = cmplx(-y1/2 ,  (S-T)*rt3/2)
   y3 = cmplx(-y1/2 , -(S-T)*rt3/2)
   print '(A,2x,F8.5, 2(", (",F8.5,", ",F8.5,")"))', &
      'One real root and one complex pair:',y1-b/3,y2-b/3,y3-b/3
endif
contains
real function cubrt(x)
   real x
   cubrt = sign(abs(x)**(1.0/3),x)
end function
end program

We can find any number of codes for solving cubic equations in various programming languages, including in languages such as Pascal that do not have a built-in complex type.

1 Like