@@ -81,7 +81,7 @@ contains
8181 ! s_compute_finite_difference_coefficients.
8282
8383 ! Allocating centered finite- difference coefficients in x- direction
84- if (omega_wrt(2 ) .or. omega_wrt(3 ) .or. schlieren_wrt .or. liutex_wrt) then
84+ if (omega_wrt(2 ) .or. omega_wrt(3 ) .or. schlieren_wrt .or. liutex_wrt) then
8585 allocate (fd_coeff_x(- fd_number:fd_number, &
8686 - offset_x%beg:m + offset_x%end))
8787 end if
@@ -558,7 +558,7 @@ contains
558558 end subroutine s_derive_qm
559559
560560 !> This subroutine gets as inputs the primitive variables. From those
561- !! inputs, it proceeds to calculate the Liutex vector and its
561+ !! inputs, it proceeds to calculate the Liutex vector and its
562562 !! magnitude based on Xu et al. (2019).
563563 !! @param q_prim_vf Primitive variables
564564 !! @param liutex_mag Liutex magnitude
@@ -588,9 +588,9 @@ contains
588588 real(wp), dimension(nm, nm) :: vgt !< velocity gradient tensor
589589 real(wp), dimension(nm) :: lr, li !< real and imaginary parts of eigenvalues
590590 real(wp), dimension(nm, nm) :: vl, vr !< left and right eigenvectors
591- integer, parameter :: lwork = 4*nm !< size of work array (4*nm recommended)
591+ integer, parameter :: lwork = 4*nm !< size of work array (4*nm recommended)
592592 real(wp), dimension(lwork) :: work !< work array
593- integer :: info
593+ integer :: info
594594
595595 real(wp), dimension(nm) :: eigvec !< real eigenvector
596596 real(wp) :: eigvec_mag !< magnitude of real eigenvector
@@ -607,7 +607,7 @@ contains
607607
608608 ! Get velocity gradient tensor (VGT)
609609 vgt(:, :) = 0._wp
610-
610+
611611 do r = -fd_number, fd_number
612612 do i = 1, 3
613613 ! d()/dx
@@ -629,38 +629,38 @@ contains
629629 end do
630630
631631 ! Compute vorticity
632- omega(1) = vgt(3,2) - vgt(2,3)
633- omega(2) = vgt(1,3) - vgt(3,1)
634- omega(3) = vgt(2,1) - vgt(1,2)
632+ omega(1) = vgt(3, 2) - vgt(2, 3)
633+ omega(2) = vgt(1, 3) - vgt(3, 1)
634+ omega(3) = vgt(2, 1) - vgt(1, 2)
635635
636636 ! Call appropriate LAPACK routine based on precision
637637#ifdef MFC_SINGLE_PRECISION
638- call cgeev(ivl,ivr,nm,vgt,nm,lr,li,vl,nm,vr,nm,work,lwork,info)
638+ call cgeev(ivl, ivr, nm, vgt, nm, lr, li, vl, nm, vr, nm, work, lwork, info)
639639#else
640- call dgeev(ivl,ivr,nm,vgt,nm,lr,li,vl,nm,vr,nm,work,lwork,info)
640+ call dgeev(ivl, ivr, nm, vgt, nm, lr, li, vl, nm, vr, nm, work, lwork, info)
641641#endif
642642
643643 ! Find real eigenvector
644644 idx = 1
645645 do r = 2, 3
646- if (abs(li(r)) .lt. abs(li(idx))) then
646+ if (abs(li(r)) < abs(li(idx))) then
647647 idx = r
648648 end if
649649 end do
650- eigvec = vr(:,idx)
650+ eigvec = vr(:, idx)
651651
652652 ! Normalize real eigenvector if it is effectively non-zero
653653 eigvec_mag = sqrt(eigvec(1)**2._wp &
654- + eigvec(2)**2._wp &
655- + eigvec(3)**2._wp)
654+ + eigvec(2)**2._wp &
655+ + eigvec(3)**2._wp)
656656 if (eigvec_mag /= 0._wp) then
657- eigvec = eigvec / eigvec_mag
657+ eigvec = eigvec/ eigvec_mag
658658 end if
659659
660660 ! Compute vorticity projected on the eigenvector
661661 omega_proj = omega(1)*eigvec(1) &
662- + omega(2)*eigvec(2) &
663- + omega(3)*eigvec(3)
662+ + omega(2)*eigvec(2) &
663+ + omega(3)*eigvec(3)
664664
665665 ! As eigenvector can have +/- signs, we can choose the sign
666666 ! so that omega_proj is positive
@@ -673,8 +673,8 @@ contains
673673 lci = li(mod(idx, 3) + 1)
674674
675675 ! Compute Liutex magnitude
676- alpha = omega_proj**2._wp - 4._wp*lci**2._wp ! (2*alpha)^2
677- if (alpha .gt. 0._wp) then
676+ alpha = omega_proj**2._wp - 4._wp*lci**2._wp ! (2*alpha)^2
677+ if (alpha > 0._wp) then
678678 liutex_mag(j, k, l) = omega_proj - sqrt(alpha)
679679 else
680680 liutex_mag(j, k, l) = omega_proj
0 commit comments