external_interfaces.f90 Source File


Files dependent on this one

sourcefile~~external_interfaces.f90~~AfferentGraph sourcefile~external_interfaces.f90 external_interfaces.f90 sourcefile~forsolver.f90 forsolver.f90 sourcefile~forsolver.f90->sourcefile~external_interfaces.f90 sourcefile~test_solver1.f90 test_solver1.f90 sourcefile~test_solver1.f90->sourcefile~forsolver.f90 sourcefile~test_solver10.f90 test_solver10.f90 sourcefile~test_solver10.f90->sourcefile~forsolver.f90 sourcefile~test_solver11.f90 test_solver11.f90 sourcefile~test_solver11.f90->sourcefile~forsolver.f90 sourcefile~test_solver12.f90 test_solver12.f90 sourcefile~test_solver12.f90->sourcefile~forsolver.f90 sourcefile~test_solver13.f90 test_solver13.f90 sourcefile~test_solver13.f90->sourcefile~forsolver.f90 sourcefile~test_solver14.f90 test_solver14.f90 sourcefile~test_solver14.f90->sourcefile~forsolver.f90 sourcefile~test_solver15.f90 test_solver15.f90 sourcefile~test_solver15.f90->sourcefile~forsolver.f90 sourcefile~test_solver16.f90 test_solver16.f90 sourcefile~test_solver16.f90->sourcefile~forsolver.f90 sourcefile~test_solver17.f90 test_solver17.f90 sourcefile~test_solver17.f90->sourcefile~forsolver.f90 sourcefile~test_solver2.f90 test_solver2.f90 sourcefile~test_solver2.f90->sourcefile~forsolver.f90 sourcefile~test_solver3.f90 test_solver3.f90 sourcefile~test_solver3.f90->sourcefile~forsolver.f90 sourcefile~test_solver4.f90 test_solver4.f90 sourcefile~test_solver4.f90->sourcefile~forsolver.f90 sourcefile~test_solver5.f90 test_solver5.f90 sourcefile~test_solver5.f90->sourcefile~forsolver.f90 sourcefile~test_solver6.f90 test_solver6.f90 sourcefile~test_solver6.f90->sourcefile~forsolver.f90 sourcefile~test_solver7.f90 test_solver7.f90 sourcefile~test_solver7.f90->sourcefile~forsolver.f90 sourcefile~test_solver8.f90 test_solver8.f90 sourcefile~test_solver8.f90->sourcefile~forsolver.f90 sourcefile~test_solver9.f90 test_solver9.f90 sourcefile~test_solver9.f90->sourcefile~forsolver.f90

Source Code

module external_interfaces_solver

    use kinds

    implicit none

    interface gesv
#if defined(REAL64)
        pure subroutine dgesv(fn, fnrhs, fa, flda, fipiv, fb, fldb, finfo)
            import rk
            integer,  intent(in)    :: fn, fnrhs, flda, fldb
            real(rk), intent(inout) :: fa(flda,fn), fb(fldb,fnrhs)
            integer,  intent(out)   :: finfo
            integer,  intent(out)   :: fipiv(fn)
        end subroutine dgesv
#elif defined(REAL32)
        pure subroutine sgesv(fn, fnrhs, fa, flda, fipiv, fb, fldb, finfo)
            import rk
            integer,  intent(in)    :: fn, fnrhs, flda, fldb
            real(rk), intent(inout) :: fa(flda,fn), fb(fldb,fnrhs)
            integer,  intent(out)   :: finfo
            integer,  intent(out)   :: fipiv(fn)
        end subroutine sgesv
#else
        pure subroutine dgesv(fn, fnrhs, fa, flda, fipiv, fb, fldb, finfo)
            import rk
            integer,  intent(in)    :: fn, fnrhs, flda, fldb
            real(rk), intent(inout) :: fa(flda,fn), fb(fldb,fnrhs)
            integer,  intent(out)   :: finfo
            integer,  intent(out)   :: fipiv(fn)
        end subroutine dgesv
#endif
    end interface

    interface gels
#if defined(REAL64)
        pure subroutine dgels(ftrans, fm, fn, fnrhs, fa, flda, fb, fldb, fwork, flwork, finfo)
            import :: rk
            character(len=1), intent(in)    :: ftrans
            integer,          intent(in)    :: fm, fn, fnrhs, flda, fldb, flwork
            real(rk),         intent(inout) :: fa(flda,*), fb(fldb,*)
            real(rk),         intent(in)    :: fwork(*)
            integer,          intent(out)   :: finfo
        end subroutine dgels
#elif defined(REAL32)
        pure subroutine sgels(ftrans, fm, fn, fnrhs, fa, flda, fb, fldb, fwork, flwork, finfo)
            import :: rk
            character(len=1), intent(in)    :: ftrans
            integer,          intent(in)    :: fm, fn, fnrhs, flda, fldb, flwork
            real(rk),         intent(inout) :: fa(flda,*), fb(fldb,*)
            real(rk),         intent(in)    :: fwork(*)
            integer,          intent(out)   :: finfo
        end subroutine sgels
#else
        pure subroutine dgels(ftrans, fm, fn, fnrhs, fa, flda, fb, fldb, fwork, flwork, finfo)
            import :: rk
            character(len=1), intent(in)    :: ftrans
            integer,          intent(in)    :: fm, fn, fnrhs, flda, fldb, flwork
            real(rk),         intent(inout) :: fa(flda,*), fb(fldb,*)
            real(rk),         intent(in)    :: fwork(*)
            integer,          intent(out)   :: finfo
        end subroutine dgels
#endif
    end interface

end module external_interfaces_solver