f2py and Fortran90 gfortran_filename error

Tyler hayes.tyler at gmail.com
Wed Feb 28 00:15:55 EST 2007


Hello All:

Since my last post I have attempted to use the f2py program which
comes with numpy. I am able to create a <module_name>.so file fine;
however, when I import it into Python, I receive the following
message:



>>> import matsolve2
Traceback (most recent call last):
  File "<stdin>", line 1, in ?
ImportError: ./matsolve2.so: undefined symbol: _gfortran_filename


The steps I used to create the matsolve2.so file are as follows:

(1) Created a Fortran90 program matsolve.f90

Note: The program compiles fine and prints the proper output for the
simple matrix specified. I have also attached below the file
matsolve.f90 if it helps at all.

(2) f2py matsolve.f90 -m matsolve2 -h matsolve2.pyf
(3) f2py -c matsolve2.pyf --f90exec=/usr/bin/gfortran matsolve.f90

Note: I had to specify the f90 path as f2py did not automatically find
it.

Any  suggestions are greatly appreciated.

Cheers,

t.

! MATSOLVE.f90
!
! Start main program
PROGRAM MATSOLVE
  IMPLICIT NONE
  INTEGER,PARAMETER :: n=3
  INTEGER :: i,j
  REAL,DIMENSION(n) :: x,b
  REAL,DIMENSION(n,n) :: A,L,U
! Initialize the vectors and matrices with a test case from text
! Using the one given in Appendix A from Thompson.
! Known vector "b"
  b(1) = 12.
  b(2) = 11.
  b(3) =  2.

! Known coefficient matrix "A", and initialize L and U
  DO i=1,n
     DO j=1,n
        L(i,j) = 0.
        U(i,j) = 0.
     END DO
  END DO

  A(1,1) =  3.
  A(1,2) = -1.
  A(1,3) =  2.

  A(2,1) = 1.
  A(2,2) = 2.
  A(2,3) = 3.

  A(3,1) =  2.
  A(3,2) = -2.
  A(3,3) = -1.


! Call subroutine to create L and U matrices from A
  CALL lumake(L,U,A,n)
! Print results
  PRINT *, '-----------------------'
  DO i=1,n
     DO j=1,n
        PRINT *, i, j, A(i,j), L(i,j), U(i,j)
     END DO
  END DO
  PRINT *, '-----------------------'

! Call subroutine to solve for "x" using L and U
  CALL lusolve(x,L,U,b,n)

! Print results
  PRINT *, '-----------------------'
  DO i=1,n
     PRINT *, i, x(i)
  END DO
  PRINT *, '-----------------------'

END PROGRAM MATSOLVE


! Create subroutine to make L and U matrices
SUBROUTINE lumake(LL,UU,AA,n1)
  IMPLICIT NONE
  INTEGER,PARAMETER :: n=3
  INTEGER :: i,j,k
  REAL :: LUSUM
  INTEGER,INTENT(IN) :: n1
  REAL,DIMENSION(n,n),INTENT(IN) :: AA
  REAL,DIMENSION(n,n),INTENT(OUT) :: LL,UU

! We first note that the diagonal in our UPPER matrix is
! going to be UU(j,j) = 1.0, this allows us to initialize
! the first set of expressions
  UU(1,1) = 1.

! Find first column of LL
  DO i = 1,n1
     LL(i,1) = AA(i,1)/UU(1,1)
  END DO

! Now find first row of UU
  DO j = 2,n1
     UU(1,j) = AA(1,j)/LL(1,1)
  END DO

! Now find middle LL elements
  DO j = 2,n1
     DO i = j,n1
        LUSUM = 0.
        DO k = 1,j-1
           LUSUM = LUSUM + LL(i,k)*UU(k,j)
        END DO
        LL(i,j) = AA(i,j) - LUSUM
     END DO

! Set Diagonal UU
     UU(j,j) = 1.

! Now find middle UU elements
     DO i = j+1,n1
        LUSUM = 0.
        DO k = 1,j-1
           LUSUM = LUSUM + LL(j,k)*UU(k,i)
        END DO
        UU(j,i) = (AA(j,i) - LUSUM)/LL(j,j)
     END DO
  END DO
END SUBROUTINE lumake


! Make subroutine to solve for x
SUBROUTINE lusolve(xx,L2,U2,bb,n2)
  IMPLICIT NONE
  INTEGER,PARAMETER :: n=3
  INTEGER :: i,j,k
  REAL :: LYSUM,UXSUM
  REAL,DIMENSION(n):: y
  INTEGER,INTENT(IN) :: n2
  REAL,DIMENSION(n),INTENT(IN) :: bb
  REAL,DIMENSION(n,n),INTENT(IN) :: L2,U2
  REAL,DIMENSION(n),INTENT(OUT) :: xx

! Initialize
  DO i=1,n2
     y(i)  = 0.
     xx(i) = 0.
  END DO

! Solve L.y = b
  y(1) = bb(1)/L2(1,1)
  DO i = 2,n2
     LYSUM = 0.
     DO k = 1,i-1
        LYSUM = LYSUM + L2(i,k)*y(k)
     END DO
     y(i) = (bb(i) - LYSUM)/L2(i,i)
  END DO

! Now do back subsitution for U.x = y
  xx(n2) = y(n2)/U2(n2,n2)
  DO j = n2-1,1,-1
     UXSUM = 0.
     DO k = j+1,n2
        UXSUM = UXSUM + U2(j,k)*xx(k)
     END DO
     xx(j) = y(j) - UXSUM
  END DO
END SUBROUTINE lusolve




More information about the Python-list mailing list