dbcsr_printmat_matlab_s Subroutine

private subroutine dbcsr_printmat_matlab_s(matrix, rows, cols, r_offset, c_offset, iunit, tr, variable_name)

Arguments

Type IntentOptional Attributes Name
real(kind=real_4), intent(in), DIMENSION(:) :: matrix
integer, intent(in) :: rows
integer, intent(in) :: cols
integer, intent(in) :: r_offset
integer, intent(in) :: c_offset
integer, intent(in) :: iunit
logical, intent(in), optional :: tr
character(len=*), intent(in), optional :: variable_name

Source Code

   SUBROUTINE dbcsr_printmat_matlab_s(matrix, rows, cols, r_offset, c_offset, iunit, tr, variable_name)
      REAL(KIND=real_4), DIMENSION(:), INTENT(IN)        :: matrix
      INTEGER, INTENT(IN)                                :: rows, cols, r_offset, c_offset, iunit
      LOGICAL, INTENT(IN), OPTIONAL                      :: tr
      CHARACTER(len=*), INTENT(in), OPTIONAL             :: variable_name

      INTEGER                                            :: c, c_off, m, n, r, r_off
      LOGICAL                                            :: t

!   ---------------------------------------------------------------------------

      m = rows
      n = cols
      r_off = r_offset
      c_off = c_offset
      t = .FALSE.
      IF (PRESENT(tr)) THEN
         IF (tr) THEN
            t = .TRUE.
            m = cols
            n = rows
            r_off = c_offset
            c_off = r_offset
         END IF
      END IF

      DO c = 1, cols
      DO r = 1, rows
         IF (.NOT. t) THEN
            IF (PRESENT(variable_name)) THEN
               WRITE (iunit, '(A,I4,A,I4,A,E15.7,A)') &
                  variable_name//'(', r + r_offset - 1, ',', c + c_offset - 1, ')=', matrix(r + (c - 1)*rows), ';'
            ELSE
               WRITE (iunit, '(A,I4,A,I4,A,E15.7,A)') 'a(', r + r_offset - 1, ',', &
                  c + c_offset - 1, ')=', matrix(r + (c - 1)*rows), ';'
            END IF
         ELSE
            IF (PRESENT(variable_name)) THEN
               WRITE (iunit, '(A,I4,A,I4,A,E15.7,A)') &
                  variable_name//'(', r + r_offset - 1, ',', c + c_offset - 1, ')=', matrix((r - 1)*cols + c), ';'
            ELSE
               WRITE (iunit, '(A,I4,A,I4,A,E15.7,A)') 'a(', r + r_offset - 1, ',', &
                  c + c_offset - 1, ')=', matrix((r - 1)*cols + c), ';'
            END IF
         END IF
      END DO
      END DO
   END SUBROUTINE dbcsr_printmat_matlab_s