Software Archive
Read-only legacy content
17061 Discussions

using dgemm causes offload error

Bobo_S_
Beginner
546 Views

Hi all,

Why I am getting error when I use dgemm inside offload section?

      PROGRAM   MAIN
      IMPLICIT NONE

      DOUBLE PRECISION ALPHA, BETA
      INTEGER          I, J
      INTEGER           M,K,N
      PARAMETER        (N=10)
      DOUBLE PRECISION, allocatable:: A(:), B(:)
      DOUBLE PRECISION, allocatable:: C(:)

      allocate(A(N*N*4), B(4*N*N), C(4*N*N))

      ALPHA=1.0d0
      BETA=1.0d0
      DO I = 1, N*2
         DO J = 1, N*2
            A(10*(I-1) + J) = 0.1*(I+J)
            B(10*(I-1) + J) = 0.1*(I+J)
            C(10*(I-1) + J) = 0.1*(I+J)
         END DO
      END DO
      call mydgemm_offload(2, A, B, C, ALPHA, BETA)

      STOP

      END

      SUBROUTINE mydgemm_offload(n, a, b, c, alpha, beta)
      INTEGER n
      DOUBLE PRECISION a(*), b(*), c(*)
      target a, b
      DOUBLE PRECISION alpha, beta
      DOUBLE PRECISION, pointer :: pa(:), pb(:)
C      !dir$ attributes offload:mic :: a, b, c
      !dir$ attributes offload:mic :: DGEMM
      pa=>a(2:2+n*n-1)
      pb=>b(2:2+n*n-1)

      !dir$ offload_transfer target(mic) in(c:length(100)
     &     alloc_if(.TRUE.) free_if(.FALSE.))
      !dir$ offload_transfer target(mic) in(pa:length(n*n)
     &     alloc_if(.TRUE.) free_if(.FALSE.))
      !dir$ offload_transfer target(mic) in(pb:length(n*n)
     &     alloc_if(.TRUE.) free_if(.FALSE.))

      !dir$ offload begin target(mic) nocopy(pa:length(n*n)) nocopy(pb:
     &     length(n*n)) nocopy(c(1:100))
      write(*,*) "before dgemm: c:"
      write(*,*) c(1:10)
      write(*,*) "pa:", pa
      write(*,*) "pb:", pb
      call DGEMM('N','T', n, n, n, alpha, pa, n, pb, n, beta, c(3), n)
      write(*,*) "after dgemm: c:"
      write(*,*) c(1:10)
      write(*,*) "pa:", pa
      write(*,*) "pb:", pb
      write(*,*) "bobo1:"
      !dir$ end offload

      write(*,*) "before out(c): c:"
      write(*,*) c(3:n*n+2)
      !dir$ offload_transfer target(mic) out(c:length(100)
     &     alloc_if(.FALSE.) free_if(.TRUE.))
      write(*,*) "after out(c): c:"
      write(*,*) c(3:n*n+2)

      RETURN
      END

ifort -mkl dgemm_example-offload-5.f

./a.out

 before dgemm: c:
  0.200000002980232       0.300000011920929       0.400000005960464
  0.500000000000000       0.600000023841858       0.699999988079071
  0.800000011920929       0.900000035762787        1.00000000000000
   1.10000002384186
 pa:  0.300000011920929       0.400000005960464       0.500000000000000
  0.600000023841858
 pb:  0.300000011920929       0.400000005960464       0.500000000000000
  0.600000023841858
 after dgemm: c:
  0.200000002980232       0.300000011920929       0.740000013113022
  0.920000018477440        1.02000004231930        1.22000002145767
  0.800000011920929       0.900000035762787        1.00000000000000
   1.10000002384186
 pa:  0.300000011920929       0.400000005960464       0.500000000000000
  0.600000023841858
 pb:  0.300000011920929       0.400000005960464       0.500000000000000
  0.600000023841858
 bobo1:
offload error: process on the device 0 unexpectedly exited with code 0

The thing is if I do not use DGEMM inside the offload section, the code works fine. But when there is DGEMM, I got offload error.

Anybody can help? Thanks,

 

0 Kudos
1 Solution
Rajiv_D_Intel
Employee
546 Views

Add a in(n) clause to the offload on line 46.

When you call dgemm, the variables alpha, beta and n are referenced in the code and by default become inout.

Alpha and beta are variables passed as parameters, and can be dealt with. "n" is a parameter, in other words, a constant. When a write operation is attempted on it you get an error. The write is caused by the default inout of n.

View solution in original post

0 Kudos
2 Replies
Rajiv_D_Intel
Employee
547 Views

Add a in(n) clause to the offload on line 46.

When you call dgemm, the variables alpha, beta and n are referenced in the code and by default become inout.

Alpha and beta are variables passed as parameters, and can be dealt with. "n" is a parameter, in other words, a constant. When a write operation is attempted on it you get an error. The write is caused by the default inout of n.

0 Kudos
Bobo_S_
Beginner
546 Views

Hi Rajiv,

I see. Thank you very much.

Bobo

0 Kudos
Reply