Silverfrost Forums

Welcome to our forums

AMD Backend Failure

8 Mar 2020 11:39 #25053

We have see in the past some examples of source code given which FTN95 /64 runs into an 'AMD backend failure'. Here is another example, which is fairly short and contains only one line with a matrix expression using user defined matrix multiply and matrix-transpose multiply operators.

The code compiles fine with FTN95 8.51, 32-bit, and other compilers such as Gfortran. FTN95 8.51 fails with /64.

*** AMD backend failure:Failed to do memory-register emit for MOVSS at 754

The source code:

   module linear_oper
   implicit none

   interface operator(.x.)
      module procedure MultAB, MultAv
   end interface

   interface operator(.tx.)
      module procedure MultATB, MultATv
   end interface

   interface
      subroutine gemv(A,b,v,trans)
         real :: A(:,:), b(:), v(:)
         character(1), optional :: trans
      end subroutine

      subroutine gemm(A,B,C,transa)
         real :: A(:,:), B(:,:), C(:,:)
         character(1), optional :: transa
      end subroutine
   end interface

   contains
      function MultAB(a, b)
         real, dimension(:,:), intent(in) :: a,b
         real, dimension(size(a,1),size(b,2)) :: MultAB
         call gemm(a,b, MultAB)
      end function MultAB

      function MultAv(a, b)
         real, dimension(:,:), intent(in) :: a
         real, dimension(:),   intent(in) :: b
         real, dimension(size(a,1)) :: MultAv
         call gemv(a,b, MultAv)
      end function MultAv

      function MultATB(a, b)
         real, dimension(:,:), intent(in) :: a,b
         real, dimension(size(a,2),size(b,2)) :: MultATB
         call gemm(a,b, MultATB, transa='T')
      end function MultATB

      function MultATv(a, b)
         real, dimension(:,:), intent(in) :: a
         real, dimension(:),   intent(in) :: b
         real, dimension(size(a,2)) :: MultATv
         call gemv(a,b, MultATv,trans='T')
      end function MultATv

   end module linear_oper

subroutine tor_modal_dec(eigvec,mtt,mmt,n)

   use linear_oper
   implicit none
   integer :: n
   real :: mtt(n,n), mmt(n,n), eigvec(n,n)

   mmt(:,:) = eigvec(:,1:n) .tx. mtt .x. eigvec(:,1:n)

end subroutine tor_modal_dec
9 Mar 2020 8:26 #25057

mecej4

Thank you for the bug report which I have logged for investigation.

14 Mar 2020 4:43 #25091

mecej4

This bug has now been fixed. Do you have some code for GEMV and GEMM so that I can test to see if the results are compatible with 32 bits etc.?

14 Mar 2020 6:13 #25092

Paul,

Here is some fake GEMV and GEMM code (the fake subroutines do not have the standard BLAS or BLAS95 interfaces), and a driver, just to enable you to build and run.

BLAS.f90:

      subroutine gemv(A,b,v,trans)
         real :: A(:,:), b(:), v(:)
         character(1), optional :: trans
         integer m, n, i
         m = size(A,1); n = size(A,2)
         if (.not. present(trans)) then
            do i=1,m
               v(i) = dot_product(A(i,:),b)
            end do
            return
         end if
         if (trans.ne.'T' .and. trans.ne.'t') then
            do i=1,m
               v(i) = dot_product(A(i,:),b)
            end do
            return
         else
            do i = 1, n
               v(i) = dot_product(A(:,i),b)
            end do
         endif
         return
       end subroutine gemv

       subroutine gemm(A,B,C,transa)
          real :: A(:,:), B(:,:), C(:,:)
          character(1), optional :: transa
          integer m, n, k, i, j
          if(present(transa)) then
             if(transa.eq.'t'.or.transa.eq.'T')goto 100
          endif
          m = size(A,1); n = size(A,2); k= size(B,2)
          do i=1,m
             do j=1,k
                C(i,j) = dot_product(A(i,:),B(:,j))
             end do
          end do
          return
   100 continue
          m = size(A,2); n = size(A,1); k = size(B,2)
          do i=1,m
             do j=1,k
                C(i,j) = dot_product(A(:,i),B(:,j))
             end do
          end do
          return

       end subroutine

DRIVER.f90:

program testxtAx

implicit none
integer i
real :: A(3,3),X(3,3),M(3,3)

A = reshape((/ 2.,-1.,1.5,-1.,2.,-1.,1.5,-1.,2. /), (/3,3/))
X = reshape((/2.,-1.,3.,-1.,2.,-1.,3.,-1.,2./),(/3,3/))

call tor_modal_dec(X,A,M,3)

print 10,(M(i,:),i=1,3)

10 format(1x,3ES15.5)
end program

The expected output:

     5.60000E+01   -3.35000E+01    5.55000E+01
    -3.35000E+01    2.30000E+01   -3.35000E+01
     5.55000E+01   -3.35000E+01    5.60000E+01

For this example, FTN95 V8.51 and 7.20 give 32-bit EXEs that produce an X87 stack fault. The fault occurs after the r.h.s. of the only executable statement in TOR_MODEL_DEC() has been evaluated and when the result is being copied to the l.h.s.

29 Apr 2020 9:16 #25306

This failure has now been fixed for the next release of FTN95.

The failure can be avoided by removing the redundant sections in

mmt(:,:) = eigvec(:,1:n) .tx. mtt .x. eigvec(:,1:n)
Please login to reply.