SUBROUTINE Critical(rvals, vp, nmax, jval, vasy, re, v0re, v1re, v2re, rc, v0rc, v1rc, v2rc, mu, ichanl) USE Numeric_Kinds_Module IMPLICIT NONE !============================================================================== !this subroutine finds all critical points of the potential function v for !the specified jval !============================================================================== LOGICAL :: root INTEGER :: i, nmax, jval, ichanl REAL(dp) :: r, v0, v1, v2 REAL(dp) :: rvals(nmax), vp(nmax) REAL(dp) :: vasy, re, v0re, v1re, v2re, rc, v0rc, v1rc, v2rc, mu !============================================================================== ! Zero all variables r=0.d0 v0=0.d0 v1=0.d0 v2=0.d0 re=0.d0 v0re=0.d0 v1re=0.d0 v2re=0.d0 rc=0.d0 v0rc=0.d0 v1rc=0.d0 v2rc=0.d0 !============================================================================== ! Find points at which the potential is equal to vasy grid_loop: DO i=2,nmax !============================================================================ ! Find points at which the potential is a maxiumum or minimum ! Findextreme sets root to .true. if it finds a maximum or minumum CALL findextreme(i, nmax, rvals, vp, jval, r, v0, v1, v2, root, mu, ichanl) IF(re.eq.0.d0.and.root)THEN re=r !sets re to r value just determined if this is the first maximum/minimum findextreme has found v0re=v0 !also stores potential at this point and its derivatives v1re=v1 v2re=v2 ELSE IF(root)THEN rc=r !sets rc to r value just determined if this is the second maximum/minimum findextreme has found v0rc=v0 !also stores potential at this point and its derivatives v1rc=v1 v2rc=v2 ENDIF ENDDO grid_loop IF (v0rc.eq.0.d0) THEN v0rc=vasy ENDIF RETURN END SUBROUTINE Critical