公共派生类型 (规范)
通过刷新单元来终结 logger_type
实体 self
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
type(logger_type), | intent(in) | :: | self |
使用 newunit
打开格式化的顺序访问输出文件 filename
,并将结果单元号添加到 self
的 log_units
数组中。如果存在,action
是 open
语句的 action
说明符,其默认值为 "write"
。如果存在,position
是 position
说明符,其默认值为 "REWIND"
。如果存在,status
是 open
语句的 status
说明符,其默认值为 "REPLACE"
。如果存在,stat
的值为 success
(如果 filename
可以打开)、read_only_error
(如果 action
为 "read"
)或 open_failure
(否则)。(规范)
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(inout) | :: | self |
要向其添加文件的记录器变量 |
||
character(len=*), | intent(in) | :: | filename |
要添加到记录器的文件名 |
||
integer, | intent(out), | optional | :: | unit |
生成的 I/O 单元号 |
|
character(len=*), | intent(in), | optional | :: | action |
`open` 语句的 |
|
character(len=*), | intent(in), | optional | :: | position |
|
|
character(len=*), | intent(in), | optional | :: | status |
|
|
integer, | intent(out), | optional | :: | stat |
退出时的错误状态,可能的值为:* 示例
|
将 unit
添加到 log_units
中的日志文件单元中。unit
必须是已打开的文件,其 form
为 "formatted"
,access
为 "sequential"
,并且 action
为 "write"
或 "readwrite"
,否则,如果存在,stat
的值将不为 success
,并且 unit
不会进入 log_units
,或者,如果 stat
不存在,则处理将停止。(规范)
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(inout) | :: | self |
要向其添加 I/O 单元的记录器变量 |
||
integer, | intent(in) | :: | unit |
输入逻辑单元号 |
||
integer, | intent(out), | optional | :: | stat |
错误代码,可能的值为:* 示例
|
报告 self
的日志记录配置。报告以下属性:1. add_blank_line
是一个逻辑标志,.true.
表示输出以空行开头,.false.
表示没有空行。2. indent
是一个逻辑标志,.true.
表示后续列将缩进 4 个空格,.false.
表示没有缩进。3. level
是打印消息的最低级别。4. max_width
是输出文本的最大列数,max_width == 0
=> 输出宽度没有限制。5. time_stamp
是一个逻辑标志,.true.
表示输出将带有时间戳,.false.
表示没有时间戳。6. log_units
是将日志输出写入的 I/O 单元号数组。(规范)
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
要报告其配置的记录器变量 |
||
logical, | intent(out), | optional | :: | add_blank_line |
添加前导空行的逻辑标志 |
|
logical, | intent(out), | optional | :: | indent |
缩进后续行的逻辑标志 |
|
integer, | intent(out), | optional | :: | level |
打印消息的最低级别 |
|
integer, | intent(out), | optional | :: | max_width |
大多数输出的最大列数 |
|
logical, | intent(out), | optional | :: | time_stamp |
添加时间戳的逻辑标志 |
|
integer, | intent(out), | optional, | allocatable | :: | log_units(:) |
输出中使用的 I/O 单元 示例
|
配置 SELF 的日志记录过程。配置以下属性:1. add_blank_line
是一个逻辑标志,.true.
表示输出以空行开头,.false.
表示没有空行。add_blank_line
的启动值为 .false.
。2. indent
是一个逻辑标志,.true.
表示后续行将缩进 4 个空格,.false.
表示没有缩进。indent
的启动值为 .true.
。3. level
是打印消息的最低级别。4. max_width
是输出文本的最大列数,max_width == 0
=> 输出宽度没有限制。max_width
的启动值为 0。5. time_stamp
是一个逻辑标志,.true.
表示输出将带有时间戳,.false.
表示没有时间戳。time_stamp
的启动值为 .true.
。(规范)
program main
use stdlib_logger
...
call global_logger % configure( indent=.false., max_width=72 )
...
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(inout) | :: | self | |||
logical, | intent(in), | optional | :: | add_blank_line | ||
logical, | intent(in), | optional | :: | indent | ||
integer, | intent(in), | optional | :: | level | ||
integer, | intent(in), | optional | :: | max_width | ||
logical, | intent(in), | optional | :: | time_stamp |
将字符串 message
写入 self % log_units
,并可选地添加其他文本。(规范)
如果时间戳处于活动状态,则写入时间戳,如果存在,则随后写入 module
和 procedure
,然后以 'DEBUG: ' 为前缀写入 message
。
module example_mod
use stdlib_logger
...
real, allocatable :: a(:)
...
type(logger_type) :: alogger
...
contains
...
subroutine example_sub( selection )
integer, intent(out) :: selection
integer :: stat
write(*,'(a)') "Enter an integer to select a widget"
read(*,'(i0)') selection
write( message, `(a, i0)' ) &
"The user selected ", selection
call alogger % log_debug( message, &
module = 'EXAMPLE_MOD', &
procedure = 'EXAMPLE_SUB' )
...
end subroutine example_sub
...
end module example_mod
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
用于发送消息的记录器 |
||
character(len=*), | intent(in) | :: | message |
要写入 log_unit 的字符串 |
||
character(len=*), | intent(in), | optional | :: | module |
包含 |
|
character(len=*), | intent(in), | optional | :: | procedure |
包含 |
将字符串 message
写入 self % log_units
,并可选地添加其他文本。(规范)
如果时间戳处于活动状态,则写入时间戳,如果存在,则随后写入 module
和 procedure
,然后以 'ERROR: ' 为前缀写入 message
,然后如果 stat
或 errmsg
存在,则写入它们。
module example_mod
use stdlib_logger
...
real, allocatable :: a(:)
...
type(logger_type) :: alogger
...
contains
...
subroutine example_sub( size )
integer, intent(in) :: size
character(128) :: errmsg, message
integer :: stat
allocate( a(size), stat=stat, errmsg=errmsg )
if ( stat /= 0 ) then
write( message, `(a, i0)' ) &
"Allocation of A failed with SIZE = ", size
alogger % call log_error( message, &
module = 'EXAMPLE_MOD', &
procedure = 'EXAMPLE_SUB', &
stat = stat, &
errmsg = errmsg )
end if
end subroutine example_sub
...
end module example_mod
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
用于记录消息的记录器 |
||
character(len=*), | intent(in) | :: | message |
要写入 log_unit 的字符串 |
||
character(len=*), | intent(in), | optional | :: | module |
包含 |
|
character(len=*), | intent(in), | optional | :: | procedure |
包含 |
|
integer, | intent(in), | optional | :: | stat |
Fortran 语句返回的 |
|
character(len=*), | intent(in), | optional | :: | errmsg |
Fortran 语句返回的 |
将字符串 message
写入 self % log_units
,并可选地添加其他文本。(规范)
如果时间戳处于活动状态,则写入时间戳,如果存在,则随后写入 module
和 procedure
,然后以 'INFO: ' 为前缀写入 message
。
module example_mod
use stdlib_logger
...
real, allocatable :: a(:)
...
type(logger_type) :: alogger
...
contains
...
subroutine example_sub( selection )
integer, intent(out) :: selection
integer :: stat
write(*,'(a)') "Enter an integer to select a widget"
read(*,'(i0)') selection
write( message, `(a, i0)' ) &
"The user selected ", selection
call alogger % log_information( message, &
module = 'EXAMPLE_MOD', &
procedure = 'EXAMPLE_SUB' )
...
end subroutine example_sub
...
end module example_mod
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
用于发送消息的记录器 |
||
character(len=*), | intent(in) | :: | message |
要写入 log_unit 的字符串 |
||
character(len=*), | intent(in), | optional | :: | module |
包含 |
|
character(len=*), | intent(in), | optional | :: | procedure |
包含 |
将字符串 message
写入 self % log_units
,并可选地添加其他文本。(规范)
如果时间戳处于活动状态,则写入时间戳,如果存在,则随后写入 module
和 procedure
,然后以 'I/O ERROR: ' 为前缀写入 message
,然后如果 iostat
或 iomsg
存在,则也写入它们。
program example
use stdlib_logger
...
character(*), parameter :: filename = 'dummy.txt'
integer :: iostat, lun
character(128) :: iomsg
character(*), parameter :: message = 'Failure in opening "dummy.txt".'
open( newunit=lun, file = filename, form='formatted', &
status='old', iostat=iostat, iomsg=iomsg )
if ( iostat /= 0 ) then
call global_logger % log_io_error( message, procedure = 'EXAMPLE', &
iostat=iostat, iomsg = iomsg )
error stop 'Error on opening ' // filename
end if
...
end program example
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
要接收消息的记录器变量 |
||
character(len=*), | intent(in) | :: | message |
要写入 LOG_UNIT 的字符串 |
||
character(len=*), | intent(in), | optional | :: | module |
包含 REPORT_ERROR 当前调用的模块的名称 |
|
character(len=*), | intent(in), | optional | :: | procedure |
包含 REPORT_ERROR 当前调用的过程的名称 |
|
integer, | intent(in), | optional | :: | iostat |
Fortran I/O 语句返回的 IOSTAT 说明符的值 |
|
character(len=*), | intent(in), | optional | :: | iomsg |
Fortran I/O 语句返回的 IOMSG 说明符的值 |
将字符串 message
写入 self % log_units
,并可选地添加其他文本。(规范)
如果时间戳处于活动状态,则写入时间戳,如果存在,则随后写入 module
和 procedure
,如果存在,则随后写入 prefix // ': '
,然后写入 message
。
module example_mod
use stdlib_logger
...
real, allocatable :: a(:)
...
contains
...
subroutine example_sub( selection )
integer, intent(out) :: selection
integer :: stat
write(*,'(a)') "Enter an integer to select a widget"
read(*,'(i0)') selection
write( message, `(a, i0)' ) &
"The user selected ", selection
call global_logger % log_message( message, &
module = 'example_mod', &
procedure = 'example_sub', &
prefix = 'info' )
end subroutine example_sub
...
end module example_mod
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
要接收消息的记录器变量 |
||
character(len=*), | intent(in) | :: | message |
要写入 log_unit 的字符串 |
||
character(len=*), | intent(in), | optional | :: | module |
包含 |
|
character(len=*), | intent(in), | optional | :: | procedure |
包含当前 |
|
character(len=*), | intent(in), | optional | :: | 前缀 |
作为 |
向 self % log_units
发送一条消息,描述在文本行中发现的错误。(规范)
如果时间戳处于活动状态,则首先写入时间戳。然后,如果 filename
或 line_number
或 column
存在,则写入它们。然后写入 line
。然后在 column
指示的列下,在 line
下方写入符号 caret
。然后写入 summary
。
program example
...
character(*), parameter :: filename = 'dummy.txt'
integer :: col_num, line_num, lun
character(128) :: line
character(*), parameter :: message = 'Bad text found.'
open( newunit=lun, file = filename, statu='old', form='formatted' )
line_num = 0
do
read( lun, fmt='(a)', end=900 ) line
line_num = line_num + 1
call check_line( line, status, col_num )
if ( status /= 0 )
call global_logger % log_text_error( line, col_num, message, &
filename, line_num )
error stop 'Error in reading ' // filename
end if
...
end do
900 继续 ... 程序示例结束
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
要接收消息的记录器变量 |
||
character(len=*), | intent(in) | :: | 行 |
发现错误的文本行。 |
||
integer, | intent(in) | :: | 列 |
LINE 中错误开始位置的基于一的列。 |
||
character(len=*), | intent(in) | :: | 摘要 |
错误的简要描述。 |
||
character(len=*), | intent(in), | optional | :: | filename |
如果存在,则为发现错误的文件名。 |
|
integer, | intent(in), | optional | :: | 行号 |
文件中 |
|
字符(len=1), | intent(in), | optional | :: | 脱字号 |
用于标记首次检测到错误的列的符号 |
|
integer, | intent(out), | optional | :: | stat |
整数标志,表示发生了错误。如果未发生错误,则值为 |
返回分配给 self % log_units
的单元数 (规范)
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
要查询的日志记录器主体 |
module example_mod
use stdlib_logger
...
type(logger_type) :: alogger
...
contains
...
subroutine example_sub(unit, ...)
integer, intent(in) :: unit
...
integer, allocatable :: log_units(:)
...
if ( alogger % log_units_assigned() == 0 ) then
call alogger % add_log_unit( unit )
end if
...
end subroutine example_sub
...
end module example_mod
将字符串 message
写入 self % log_units
,并可选地添加其他文本。(规范)
如果时间戳处于活动状态,则写入时间戳,然后写入 module
和 procedure
(如果存在),然后使用前缀 'WARN: ' 写入 message
。
module example_mod
use stdlib_logger
...
real, allocatable :: a(:)
...
type(logger_type) :: alogger
...
contains
...
subroutine example_sub( size, stat )
integer, intent(in) :: size
integer, intent(out) :: stat
allocate( a(size) )
if ( stat /= 0 ) then
write( message, `(a, i0)' ) &
"Allocation of A failed with SIZE = ", size
call alogger % log_warning( message, &
module = 'EXAMPLE_MOD', &
procedure = 'EXAMPLE_SUB' )
end if
end subroutine example_sub
...
end module example_mod
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
写入消息的日志记录器 |
||
character(len=*), | intent(in) | :: | message |
要写入 LOG_UNIT 的字符串 |
||
character(len=*), | intent(in), | optional | :: | module |
包含当前 |
|
character(len=*), | intent(in), | optional | :: | procedure |
包含当前 |
从 self % log_units 列表中删除 I/O 单元。如果 close_unit
存在且为 .true.
,则关闭相应的文件。如果 unit
不在 log_units
中,则不执行任何操作。如果 stat
存在,则默认情况下其值为 success
。如果关闭 unit
失败,则如果 stat
存在,则其值为 close_failure
,否则处理将停止并显示一条信息性消息。(规范)
类型 | 意图 | 可选 | 属性 | 名称 | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(inout) | :: | self |
要删除其单元的日志记录器变量 |
||
integer, | intent(in) | :: | unit |
要从 self 中删除的 I/O 单元 |
||
logical, | intent(in), | optional | :: | close_unit |
一个逻辑标志,用于在从 SELF 列表中删除单元时关闭它 |
|
integer, | intent(out), | optional | :: | stat |
错误状态,其值包括:* success - 未发现问题 * close_failure - 单元的 close 语句失败 示例
|
type :: logger_type !! version: experimental !! Public derived type ([Specification](../page/specs/stdlib_logger.html#the-derived-type-logger_type)) private logical :: add_blank_line = .false. logical :: indent_lines = .true. integer :: level = information_level integer, allocatable :: log_units(:) integer :: max_width = 0 logical :: time_stamp = .true. integer :: units = 0 contains private procedure, public, pass(self) :: add_log_file procedure, public, pass(self) :: add_log_unit procedure, public, pass(self) :: configuration procedure, public, pass(self) :: configure procedure, public, pass(self) :: log_debug procedure, public, pass(self) :: log_error procedure, public, pass(self) :: log_information procedure, public, pass(self) :: log_io_error procedure, public, pass(self) :: log_message procedure, public, pass(self) :: log_text_error procedure, public, pass(self) :: log_units_assigned procedure, public, pass(self) :: log_warning procedure, public, pass(self) :: remove_log_unit final :: final_logger end type logger_type