Sun Studio 12 Update 1:使用 dbx 调试程序

第 16 章 使用 dbx 调试 Fortran

本章介绍可能会用于 Fortran 的 dbx 功能。另外还提供了一些 dbx 请求样例,以便为您在使用 dbx 调试 Fortran 代码时提供帮助。

本章包括以下主题:

调试 Fortran

以下是一些有助于您调试 Fortran 程序的提示和一般性概念。有关使用 dbx 调试 Fortran OpenMP 代码的信息,请参见与事件交互

当前过程和文件

调试会话期间,dbx 会将过程和源文件定义为当前过程和源文件。设置断点及打印或设置变量的请求都相对于当前函数和文件来解释。因此,stop at 5 会根据哪一个文件是当前文件来设置不同的断点。

大写字母

程序的标识符中有大写字母时,dbx 会识别出它们。无需提供区分大小写或不区分大小写的命令,而某些早期版本中需要提供。

Fortran 95 和 dbx 必须都处于区分大小写模式或不区分大小写模式下:

dbx 会话样例

下面的示例中使用称为 my_program 的样例程序。

用于调试的主程序 a1.f:


    PARAMETER ( n=2 )
    REAL twobytwo(2,2) / 4 *-1 /
    CALL mkidentity( twobytwo, n )
    PRINT *, determinant( twobytwo )
    END

用于调试的子例程 a2.f:


    SUBROUTINE mkidentity ( array, m )
    REAL array(m,m)
    DO 90 i = 1, m
        DO 20 j = 1, m
            IF ( i .EQ. j ) THEN
            array(i,j) = 1.
            ELSE
            array(i,j) = 0.
            END IF
20        CONTINUE
90    CONTINUE
    RETURN
    END

用于调试的函数 a3.f


    REAL FUNCTION determinant ( a )
    REAL a(2,2)
    determinant = a(1,1) * a(2,2) - a(1,2) / a(2,1)
    RETURN
    END

Procedure运行 dbx 会话样例

  1. 使用 - g 选项进行编译和链接。

    可以通过一两个步骤来完成此操作。

    使用 -g 一步完成编译和链接:


     demo% f95 -o my_program -g a1.f a2.f a3.f
    

    或分步完成编译和链接:


     demo% f95 -c -g a1.f a2.f a3.f
     demo% f95 -o my_program a1.o a2.o a3.o
    
  2. 对名为 my_program 的可执行文件启动 dbx


     demo% dbx my_program
     Reading symbolic information…
  3. 键入 stop in subnam 来设置简单断点,其中 subnam 是子例程、函数或块数据子程序的名称。

    在主程序的第一个可执行语句处停止。


     (dbx) stop in MAIN
     (2) stop in MAIN

    尽管 MAIN 必须全部为大写字母,但 subnam 大小写均可。

  4. 键入 run 命令,它会运行启动 dbx 时指定的可执行文件中的程序。


     (dbx) run
     Running: my_program
     stopped in MAIN at line 3 in file "a1.f"
         3         call mkidentity( twobytwo, n )

    到达断点时,dbx 会显示一条消息,指出其停止位置(本例中为文件 a1.f 的第 3 行)。

  5. 要打印值,请键入 print 命令。

    打印 n 的值:


     (dbx) print n
     n = 2

    打印矩阵 twobytwo,格式可能会有所不同:


     (dbx) print twobytwo
     twobytwo =
        (1,1)       -1.0
        (2,1)       -1.0
        (1,2)       -1.0
        (2,2)       -1.0

    打印矩阵 array


    (dbx) print array
    dbx: "array" is not defined in the current scope
    (dbx)

    打印失败的原因是此处未定义 array,而只是在 mkidentity 中进行了定义。

  6. 要继续执行到下一行,请键入 next 命令。

    继续执行到下一行:


    (dbx) next
    stopped in MAIN at line 4 in file "a1.f"
        4             print *, determinant( twobytwo )
    (dbx) print twobytwo
    twobytwo =
        (1,1)       1.0
        (2,1)       0.0
        (1,2)       0.0
        (2,2)       1.0
    (dbx) quit
    demo%

    next 命令会执行当前源代码行并在下一行处停止。它将各次子程序调用按独立的语句来计数。

    next 命令与 step 命令不同。step 命令会执行下一个源代码行或进入子程序的下一步。如果下一个可执行源代码语句是一个子例程或函数调用,则:

    • step 命令在子程序的第一个源代码语句处设置断点。

    • next 命令在调用后的第一个源代码语句处但仍在调用程序中设置断点。

  7. 要退出 dbx,请键入 quit 命令。


    (dbx)quit        
    demo%

调试段故障

如果程序出现段故障 (SIGSEGV),便会引用其可用内存外的内存地址。

导致段故障的最常见原因:

使用 dbx 找出问题

可使用 dbx 找到出现段故障的源代码行。

使用程序来生成段故障:


demo% cat WhereSEGV.f
    INTEGER a(5)
    j = 2000000
    DO 9 i = 1,5
        a(j) = (i * 10)
9    CONTINUE
    PRINT *, a
    END
demo%

可使用 dbx 找到 dbx 段故障的行号:


demo% f95 -g -silent WhereSEGV.f
demo% a.out
Segmentation fault
demo% dbx a.out
Reading symbolic information for a.out
program terminated by signal SEGV (segmentation violation)
(dbx) run
Running: a.out
signal SEGV (no mapping at the fault address)
    in MAIN at line 4 in file "WhereSEGV.f"
    4                   a(j) = (i * 10)
(dbx)

定位异常

有许多原因可导致程序异常。一种定位故障的方法是在源程序中找到发生异常的行号,然后在该处寻找线索。

编译时使用 -ftrap=common 可强制捕获所有常见异常。

查找异常发生位置:


demo% cat wh.f
                 call joe(r, s)
                 print *, r/s
                 end
                 subroutine joe(r,s)
                 r = 12.
                 s = 0.
                 return
                 end
demo% f95 -g -o wh -ftrap=common wh.f
demo% dbx wh
Reading symbolic information for wh
(dbx) catch FPE
(dbx) run
Running: wh
(process id 17970)
signal FPE (floating point divide by zero) in MAIN at line 2 in file “wh.f”
   2                     print *, r/s
(dbx)

跟踪调用

有时程序会因核心转储而停止,此时便需要知道将程序引至该处的调用的序列。此序列称为栈跟踪

where 命令显示程序流中执行停止位置以及执行到达此点的过程,即被调用例程的栈跟踪

ShowTrace.f 是专门用于使核心转储深入调用序列中的若干层来显示栈跟踪的程序。


Note the reverse order:
demo% f77 -silent -g ShowTrace.f
demo% a.out
MAIN called calc, calc called calcb.
*** TERMINATING a.out
*** Received signal 11 (SIGSEGV)
Segmentation Fault (core dumped)
quil 174% dbx a.out
Execution stopped, line 23
Reading symbolic information for a.out
...
(dbx) run
calcB called from calc, line 9
Running: a.out
(process id 1089)
calc called from MAIN, line 3
signal SEGV (no mapping at the fault address) in calcb at line 23 in file "ShowTrace.f"
   23                   v(j) = (i * 10)
(dbx) where -V
=>[1] calcb(v = ARRAY , m = 2), line 23 in "ShowTrace.f"
  [2] calc(a = ARRAY , m = 2, d = 0), line 9 in "ShowTrace.f"
  [3] MAIN(), line 3 in "ShowTrace.f"
(dbx)
Show the sequence of calls, starting at where the execution stopped:

处理数组

dbx 可识别数组并打印它们。


demo% dbx a.out
Reading symbolic information…
(dbx) list 1,25
    1           DIMENSION IARR(4,4)
    2           DO 90 I = 1,4
    3                   DO 20 J = 1,4
    4                           IARR(I,J) = (I*10) + J
    5   20              CONTINUE
    6   90      CONTINUE
    7           END
(dbx)  stop at 7
(1) stop at "Arraysdbx.f":7
(dbx) run
Running: a.out
stopped in MAIN at line 7 in file "Arraysdbx.f"
    7           END
(dbx) print IARR
iarr =
    (1,1) 11
    (2,1) 21
    (3,1) 31
    (4,1) 41
    (1,2) 12
    (2,2) 22
    (3,2) 32
    (4,2) 42
    (1,3) 13
    (2,3) 23
    (3,3) 33
    (4,3) 43
    (1,4) 14
    (2,4) 24
    (3,4) 34
    (4,4) 44
(dbx) print IARR(2,3)
    iarr(2, 3) = 23  - Order of user-specified subscripts ok
(dbx) quit

有关 Fortran 中数组分片的信息,请参见Fortran 数组分片语法

Fortran 95 可分配数组

以下示例说明如何在 dbx 中处理分配的数组。


demo% f95 -g Alloc.f95
  demo% dbx a.out
  (dbx) list 1,99
      1   PROGRAM TestAllocate
      2   INTEGER n, status
      3   INTEGER, ALLOCATABLE :: buffer(:)
      4           PRINT *, ’Size?’
      5           READ *, n
      6           ALLOCATE( buffer(n), STAT=status )
      7           IF ( status /= 0 ) STOP ’cannot allocate buffer’
      8           buffer(n) = n
      9           PRINT *, buffer(n)
     10           DEALLOCATE( buffer, STAT=status)
     11   END
(dbx) stop at 6
 (2) stop at "alloc.f95":6
 (dbx) stop at 9
 (3) stop at "alloc.f95":9
 (dbx) run
 Running: a.out
 (process id 10749)
  Size?
 1000
 stopped in main at line 6 in file "alloc.f95"
     6           ALLOCATE( buffer(n), STAT=status )
 (dbx) whatis buffer
 integer*4 , allocatable::buffer(:)
 (dbx) next
 continuing
 stopped in main at line 7 in file "alloc.f95"
     7           IF ( status /= 0 ) STOP ’cannot allocate buffer’
 (dbx) whatis buffer
 integer*4 buffer(1:1000)
 (dbx) cont
 stopped in main at line 9 in file "alloc.f95"
     9           PRINT *, buffer(n)
 (dbx) print n
buffer(1000) holds 1000
 n = 1000
 (dbx) print buffer(n)
 buffer(n) = 1000

显示内函数

dbx 可识别 Fortran 内函数(仅限于 SPARC 平台和 x86 平台)。

要在 dbx 中显示内函数,请键入:


demo% cat ShowIntrinsic.f
    INTEGER i
    i = -2
    END
(dbx) stop in MAIN
(2) stop in MAIN
(dbx) run
Running: shi
(process id 18019)
stopped in MAIN at line 2 in file "shi.f"
    2              i = -2
(dbx) whatis abs
Generic intrinsic function: "abs"
(dbx) print i
i = 0
(dbx) step
stopped in MAIN at line 3 in file "shi.f"
    3              end
(dbx) print i
i = -2
(dbx) print abs(1)
abs(i) = 2
(dbx)

显示复数表达式

dbx 还可识别 Fortran 复数表达式。

要在 dbx 中显示复数表达式,请键入:


demo% cat ShowComplex.f
   COMPLEX z
    z = ( 2.0, 3.0 )
    END
demo% f95 -g ShowComplex.f
demo% dbx a.out
(dbx) stop in MAIN
(dbx) run
Running: a.out
(process id 10953)
stopped in MAIN at line 2 in file "ShowComplex.f"
    2       z = ( 2.0, 3.0 )
(dbx) whatis z
complex*8  z
(dbx) print z
z = (0.0,0.0)
(dbx) next
stopped in MAIN at line 3 in file "ShowComplex.f"
    3       END
(dbx) print z
z = (2.0,3.0)
(dbx) print z+(1.0,1.0)
z+(1,1) = (3.0,4.0)
(dbx) quit
demo%

显示区间表达式

要在 dbx 中显示区间表达式,请键入:


demo% cat ShowInterval.f95
   INTERVAL v
   v = [ 37.1, 38.6 ]
   END
demo% f95 -g -xia ShowInterval.f95
demo% dbx a.out
(dbx) stop in MAIN
(2) stop in MAIN
(dbx) run
Running: a.out
(process id 5217)
stopped in MAIN at line 2 in file "ShowInterval.f95"
    2      v = [ 37.1, 38.6 ]
(dbx) whatis v
INTERVAL*16  v
(dbx) print v
v = [0.0,0.0]
(dbx) next
stopped in MAIN at line 3 in file "ShowInterval.f95"
    3      END
(dbx) print v
v = [37.1,38.6]
(dbx) print v+[0.99,1.01]
v+[0.99,1.01] = [38.09,39.61]
(dbx) quit
demo%

注 –

仅编译为在基于 SPARC 的平台上运行(如果编译时使用 -xarch={sse|sse2},则在 Solaris x86 SSE/SSE2 Pentium 4 兼容的平台上运行;如果编译时使用 -xarch=amd64,则在 x64 平台上运行)的程序中可以使用区间表达式。


显示逻辑操作符

dbx 可以找出 Fortran 逻辑操作符并打印它们。

要在 dbx 中显示逻辑操作符,请键入:


demo% cat ShowLogical.f
        LOGICAL a, b, y, z
        a = .true.
        b = .false.
        y = .true.
        z = .false.
        END
demo% f95 -g ShowLogical.f
demo% dbx a.out
(dbx) list 1,9
    1           LOGICAL a, b, y, z
    2           a = .true.
    3           b = .false.
    4           y = .true.
    5           z = .false.
    6           END
(dbx) stop at 5
(2) stop at "ShowLogical.f":5
(dbx) run
Running: a.out
(process id 15394)
stopped in MAIN at line 5 in file "ShowLogical.f"
    5           z = .false.
(dbx) whatis y
logical*4 y
(dbx) print a .or. y
a.OR.y = true
(dbx) assign z = a .or. y
(dbx) print z
z = true
(dbx) quit
demo%

查看 Fortran 95 派生类型

可以使用 dbx 显示结构,即 Fortran 95 派生类型。


demo% f95 -g DebStruc.f95
demo% dbx a.out
(dbx) list 1,99
    1   PROGRAM Struct ! Debug a Structure
    2      TYPE product
    3         INTEGER        id
    4         CHARACTER*16   name
    5         CHARACTER*8    model
    6         REAL           cost
    7 REAL price
    8      END TYPE product
    9
   10      TYPE(product) :: prod1
   11
   12      prod1%id = 82
   13      prod1%name = "Coffee Cup"
   14      prod1%model = "XL"
   15      prod1%cost = 24.0
   16      prod1%price = 104.0
   17      WRITE ( *, * ) prod1%name
   18   END
(dbx) stop at 17
(2) stop at "Struct.f95":17
(dbx) run
Running: a.out
(process id 12326)
stopped in main at line 17 in file "Struct.f95"
   17      WRITE ( *, * ) prod1%name
(dbx) whatis prod1
product prod1
(dbx) whatis -t product
type product
    integer*4 id
    character*16 name
    character*8 model
    real*4 cost
    real*4 price
end type product
(dbx) n
(dbx) print prod1
    prod1 = (
    id    = 82
    name = ’Coffee Cup’
    model = ’XL’
    cost = 24.0
    price = 104.0
)

指向 Fortran 95 派生类型的指针

可以使用 dbx 显示结构(Fortran 95 派生类型)和指针。


demo% f95 -o debstr -g DebStruc.f95
 demo% dbx debstr
 (dbx) stop in main
 (2) stop in main
 (dbx) list 1,99
     1   PROGRAM DebStruPtr! Debug structures & pointers
Declare a derived type.
     2      TYPE product
     3         INTEGER        id
     4         CHARACTER*16   name
     5         CHARACTER*8    model
     6         REAL           cost
     7         REAL           price
     8      END TYPE product
     9
Declare prod1  and prod2 targets.
    10      TYPE(product), TARGET :: prod1, prod2
Declare curr and prior pointers.
    11      TYPE(product), POINTER :: curr, prior
    12
Make curr point to prod2.
    13      curr => prod2
Make prior point to prod1.
    14      prior => prod1
Initialize prior.
    15      prior%id = 82
    16      prior%name = "Coffee Cup"
    17      prior%model = "XL"
    18      prior%cost = 24.0
    19      prior%price = 104.0
Set curr to prior.
    20      curr = prior
Print name from curr and prior.  
    21      WRITE ( *, * ) curr%name, " ", prior%name
    22   END PROGRAM DebStruPtr
 (dbx) stop at 21
 (1) stop at "DebStruc.f95":21
 (dbx) run
 Running: debstr
(process id 10972)
stopped in main at line 21 in file "DebStruc.f95"
   21      WRITE ( *, * ) curr%name, " ", prior%name
(dbx) print prod1
 prod1 = (
    id = 82
    name = "Coffee Cup"
    model = "XL"
    cost = 24.0
    price = 104.0
)

上例中,dbx 显示了派生类型的所有字段,包括字段名。

可以使用结构并查询有关 Fortran 95 派生类型的项。


Ask about the variable
(dbx) whatis prod1
 product prod1
Ask about the type (-t)
 (dbx) whatis -t product
 type product
    integer*4 id
    character*16 name
    character*8 model
    real cost
    real price
 end type product

要打印指针,请键入:


dbx displays the contents of a pointer, which is an address. This address can be different with every run.
(dbx) print prior
 prior = (
     id    = 82
     name = ’Coffee Cup’
     model = ’XL’
     cost = 24.0
     price = 104.0
 )