@@ -163,8 +163,8 @@ subroutine cbal(nm, nl, ar, ai, low, igh, scale)
163163
164164 do 200 j = k, l
165165 if (j == i) go to 200
166- c = c + dabs (ar(j, i)) + dabs (ai(j, i))
167- r = r + dabs (ar(i, j)) + dabs (ai(i, j))
166+ c = c + abs (ar(j, i)) + abs (ai(j, i))
167+ r = r + abs (ar(i, j)) + abs (ai(i, j))
168168200 end do
169169! .......... guard against zero c or r due to underflow ..........
170170 if (c == 0.0_wp .or. r == 0.0_wp ) go to 270
@@ -243,7 +243,7 @@ subroutine corth(nm, nl, low, igh, ar, ai, ortr, orti)
243243 scale = 0.0_wp
244244! .......... scale column (algol tol then not needed) ..........
245245 do 90 i = ml, igh
246- scale = scale + dabs (ar(i, ml - 1 )) + dabs (ai(i, ml - 1 ))
246+ scale = scale + abs (ar(i, ml - 1 )) + abs (ai(i, ml - 1 ))
24724790 end do
248248 if (scale == 0._wp ) go to 180
249249 mp = ml + igh
@@ -255,7 +255,7 @@ subroutine corth(nm, nl, low, igh, ar, ai, ortr, orti)
255255 h = h + ortr(i)* ortr(i) + orti(i)* orti(i)
256256100 end do
257257!
258- g = dsqrt (h)
258+ g = sqrt (h)
259259 call pythag(ortr(ml), orti(ml), f)
260260 if (f == 0._wp ) go to 103
261261 h = h + f* g
@@ -375,8 +375,8 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
375375! .......... for i=igh-1 step -1 until low+1 do -- ..........
376376105 do 140 ii = 1 , iend
377377 i = igh - ii
378- if (dabs (ortr(i)) == 0._wp .and. dabs (orti(i)) == 0._wp ) go to 140
379- if (dabs (hr(i, i - 1 )) == 0._wp .and. dabs (hi(i, i - 1 )) == 0._wp ) go to 140
378+ if (abs (ortr(i)) == 0._wp .and. abs (orti(i)) == 0._wp ) go to 140
379+ if (abs (hr(i, i - 1 )) == 0._wp .and. abs (hi(i, i - 1 )) == 0._wp ) go to 140
380380! .......... norm below is negative of h formed in corth ..........
381381 norm = hr(i, i - 1 )* ortr(i) + hi(i, i - 1 )* orti(i)
382382 ip1 = i + 1
@@ -411,7 +411,7 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
411411!
412412 do 170 i = l, igh
413413 ll = min0(i + 1 , igh)
414- if (dabs (hi(i, i - 1 )) == 0._wp ) go to 170
414+ if (abs (hi(i, i - 1 )) == 0._wp ) go to 170
415415 call pythag(hr(i, i - 1 ), hi(i, i - 1 ), norm)
416416 yr = hr(i, i - 1 )/ norm
417417 yi = hi(i, i - 1 )/ norm
@@ -456,9 +456,9 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
456456240 do 260 ll = low, en
457457 l = en + low - ll
458458 if (l == low) go to 300
459- tst1 = dabs (hr(l - 1 , l - 1 )) + dabs (hi(l - 1 , l - 1 )) &
460- + dabs (hr(l, l)) + dabs (hi(l, l))
461- tst2 = tst1 + dabs (hr(l, l - 1 ))
459+ tst1 = abs (hr(l - 1 , l - 1 )) + abs (hi(l - 1 , l - 1 )) &
460+ + abs (hr(l, l)) + abs (hi(l, l))
461+ tst2 = tst1 + abs (hr(l, l - 1 ))
462462 if (tst2 == tst1) go to 300
463463260 end do
464464! .......... form shift ..........
@@ -481,7 +481,7 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
481481 si = si - xxi
482482 go to 340
483483! .......... form exceptional shift ..........
484- 320 sr = dabs (hr(en, enm1)) + dabs (hr(enm1, en - 2 ))
484+ 320 sr = abs (hr(en, enm1)) + abs (hr(enm1, en - 2 ))
485485 si = 0.0_wp
486486!
487487340 do 360 i = low, en
@@ -523,7 +523,7 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
523523500 end do
524524!
525525 si = hi(en, en)
526- if (dabs (si) == 0._wp ) go to 540
526+ if (abs (si) == 0._wp ) go to 540
527527 call pythag(hr(en, en), si, norm)
528528 sr = hr(en, en)/ norm
529529 si = si/ norm
@@ -568,7 +568,7 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
568568590 end do
569569600 end do
570570!
571- if (dabs (si) == 0._wp ) go to 240
571+ if (abs (si) == 0._wp ) go to 240
572572!
573573 do 630 i = 1 , en
574574 yr = hr(i, en)
@@ -598,7 +598,7 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
598598!
599599 do i = 1 , nl
600600 do j = i, nl
601- tr = dabs (hr(i, j)) + dabs (hi(i, j))
601+ tr = abs (hr(i, j)) + abs (hi(i, j))
602602 if (tr > norm) norm = tr
603603 end do
604604 end do
@@ -635,7 +635,7 @@ subroutine comqr2(nm, nl, low, igh, ortr, orti, hr, hi, wr, wi, zr, zi, ierr)
635635765 continue
636636 call cdiv(zzr, zzi, yr, yi, hr(i, en), hi(i, en))
637637! .......... overflow control ..........
638- tr = dabs (hr(i, en)) + dabs (hi(i, en))
638+ tr = abs (hr(i, en)) + abs (hi(i, en))
639639 if (tr == 0.0_wp ) go to 780
640640 tst1 = tr
641641 tst2 = tst1 + 1.0_wp / tst1
@@ -709,12 +709,12 @@ end subroutine comqr2
709709 ! ! transformed in their first ml columns
710710 subroutine cbabk2 (nm , nl , low , igh , scale , ml , zr , zi )
711711 integer , intent (in ) :: nm, nl, low, igh
712- double precision , intent ( in ) :: scale (nl)
712+ real (wp ) :: scale (nl)
713713 integer , intent (in ) :: ml
714- double precision , intent ( inout ) :: zr(nm, ml), zi(nm, ml)
714+ real (wp ) :: zr(nm, ml), zi(nm, ml)
715715
716716 integer :: i, j, k, ii
717- double precision :: s
717+ real (wp) :: s
718718
719719 if (ml == 0 ) go to 200
720720 if (igh == low) go to 120
@@ -757,14 +757,14 @@ subroutine csroot(xr, xi, yr, yi)
757757 real (wp), intent (in ) :: xr, xi
758758 real (wp), intent (out ) :: yr, yi
759759!
760- ! (yr,yi) = complex dsqrt (xr,xi)
760+ ! (yr,yi) = complex sqrt (xr,xi)
761761! branch chosen so that yr .ge. 0.0 and sign(yi) .eq. sign(xi)
762762!
763763 real (wp) :: s, tr, ti, c
764764 tr = xr
765765 ti = xi
766766 call pythag(tr, ti, c)
767- s = dsqrt (0.5_wp * (c + dabs (tr)))
767+ s = sqrt (0.5_wp * (c + abs (tr)))
768768 if (tr >= 0.0_wp ) yr = s
769769 if (ti < 0.0_wp ) s = - s
770770 if (tr <= 0.0_wp ) yi = s
@@ -786,7 +786,7 @@ subroutine cdiv(ar, ai, br, bi, cr, ci)
786786 ! cr = (ar*br + ai*bi) / (br**2._wp + bi**2._wp)
787787 ! ci = (ai*br - ar*bi) / (br**2._wp + bi**2._wp)
788788
789- s = dabs (br) + dabs (bi)
789+ s = abs (br) + abs (bi)
790790 ars = ar/ s
791791 ais = ai/ s
792792 brs = br/ s
@@ -801,12 +801,12 @@ subroutine pythag(a, b, c)
801801 real (wp), intent (in ) :: a, b
802802 real (wp), intent (out ) :: c
803803!
804- ! finds dsqrt (a**2+b**2) without overflow or destructive underflow
804+ ! finds sqrt (a**2+b**2) without overflow or destructive underflow
805805!
806806 real (wp) :: p, r, s, t, u
807- p = dmax1(dabs (a), dabs (b))
807+ p = dmax1(abs (a), abs (b))
808808 if (p == 0.0_wp ) go to 20
809- r = (dmin1(dabs (a), dabs (b))/ p)** 2
809+ r = (dmin1(abs (a), abs (b))/ p)** 2
81081010 continue
811811 t = 4.0_wp + r
812812 if (t == 4.0_wp ) go to 20
0 commit comments