此模块定义了一个派生类型、其方法、一个变量和常量,用于报告错误、显示消息和其他信息。派生类型 logger_type
用于定义全局和局部日志记录器变量。logger_type
方法用于配置日志记录器,并使用日志记录器变量将消息报告到称为 log_units
的特定 I/O 单元列表。类型为 logger_type
的变量 global_logger
旨在用作默认全局日志记录器。常量用作某些模块过程可选整数 stat
参数返回的错误标志。
日志记录器变量可以选择
yyyy-mm-dd hh:mm:ss.sss
格式的时间戳;stat
和 errmsg
;iostat
和 iomsg
;'DEBUG: '
、'INFO: '
、'WARN: '
、'ERROR: '
或 'I/O ERROR: '
中的一个标记消息;虽然已尽一切努力使代码处理和异步 I/O 安全,但最好让每个进程写入其自己的专用日志文件。对于线程并行(例如,使用 OpenMP),建议将日志记录器调用放在保护区域(例如,在 OpenMP 临界区)中。
注意:类型为 logger_type
的日志记录器通常将其消息报告到称为 log_units
的内部列表中的 I/O 单元。但是,如果 log_units
为空,则消息将发送到内在模块 iso_fortran_env
的 output_unit
。
该模块定义了九个不同的公共整数常量,用于在某些模块过程的 stat
参数中报告错误。这些常量称为错误代码,如下所示
错误代码 | 描述 |
---|---|
success |
未检测到错误 |
close_failure |
I/O 单元的 close 语句失败 |
index_invalid_error |
给定 line 的 column 无效 |
non_sequential_error |
I/O 单元没有 SEQUENTIAL 访问权限 |
open_failure |
open 语句失败 |
read_only_error |
输出单元没有 'WRITE' 或 'READWRITE' 的 access 说明符 |
unformatted_in_error |
单元没有 'FORMATTED' 的 form |
unopened_in_error |
单元未打开 |
write_fault |
写入 log_units 的其中一个操作失败 |
该模块还定义了八个不同的公共整数常量,用于选择要记录的消息。这些常量称为严重性级别,分别为(按其严重性递增顺序排序):all_level
、debug_level
、information_level
、warning_level
、error_level
、io_error_level
、text_error_level
和 none_level
。所有级别(例如,debug_level
)低于指定严重性级别(例如,information_level
)的日志消息将被忽略。级别 error_level
和 io_error_level
具有相同的严重性。默认严重性级别为 information_level
。
实验性
用于定义“logger”变量,以用于报告程序执行期间遇到的重大事件。
type(
logger_type ) :: variable
属性 | 类型 | 描述 | 初始值 |
---|---|---|---|
add_blank_line |
逻辑 | 在输出前加上空行的标志 | .false. |
indent_lines |
逻辑 | 将后续行缩进四列的标志 | .true. |
level |
整数 | 严重性级别 | information_level |
log_units |
整数数组 | 用于输出的 I/O 单元列表 | 未分配 |
max_width |
整数 | 输出的最大列宽 | 0 |
time_stamp |
逻辑 | 在输出前加上时间戳的标志 | .true. |
units |
整数 | 活动输出单元的数量 | 0 |
该模块定义了一个公共变量 global_logger
,其类型为 logger_type
。顾名思义,global_logger
旨在用作整个应用程序的默认日志记录器。
该模块定义了十二个公共过程:一个函数和十一个子程序。这些方法是
方法 | 类 | 描述 |
---|---|---|
add_log_file |
子程序 | 使用 newunit 打开文件,并将结果单元添加到 log_units 列表 |
add_log_unit |
子程序 | 将现有单元添加到 log_units 列表 |
configuration |
子程序 | 报告日志记录配置的详细信息 |
configure |
子程序 | 配置日志记录过程的详细信息 |
log_debug |
子程序 | 发送以 'DEBUG: ' 开头的消息 |
log_error |
子程序 | 发送以 'ERROR: ' 开头的消息,后面可以选择跟上 stat 或 errmsg |
log_information |
子程序 | 发送以 'INFO: ' 开头的消息 |
log_io_error |
子程序 | 发送以 'I/O ERROR: ' 开头的消息,后面可以选择跟上 iostat 或 iomsg |
log_message |
子程序 | 发送消息 |
log_text_error |
子程序 | 发送一条描述在文本行中发现的错误的消息 |
log_units_assigned |
函数 | 返回 log_units 中活动 I/O 单元的数量 |
log_warning |
子程序 | 发送以 'WARN: ' 开头的消息 |
remove_log_unit |
子程序 | 从 log_units 数组中删除 unit 编号 |
add_log_file
- 打开文件并将它的单元添加到 self % log_units
实验性
使用 newunit
打开格式化的、顺序访问的输出文件 filename
,并将结果单元号添加到日志记录器的 log_units
数组中。
call self %
add_log_file ( filename [, unit, action, position, status, stat ] )
子程序
self
:应为 logger_type
类型的标量变量。它是一个 intent(inout)
参数。它应该是将文件添加到其 log_units
中的日志记录器。
filename
:应为标量默认字符表达式。它是一个 intent(in)
参数。它应该是要打开的文件的名称。
unit
(可选):应为标量默认整数变量。它是一个 intent(out)
参数。它将是 filename
的 open
语句的 newunit
说明符返回的单元号。
action
(可选):应为标量默认字符表达式。它是一个 intent(in)
参数。它应该是 open
语句的 action
说明符,并且必须具有 'WRITE'
或 'READWRITE'
之一的值。它的默认值为 'WRITE'
。
position
(可选):应为标量默认字符表达式。它是一个 intent(in)
参数。它应该是 open
语句的 position
说明符,并且必须具有 'ASIS'
、'REWIND'
或 'APPEND'
之一的值。它的默认值为 'REWIND'
。
status
(可选):应为标量默认字符表达式。它是一个 intent(in)
参数。它应该是 open
语句的 status
说明符,并且必须具有 'OLD'
、'NEW'
、'REPLACE'
或 'UNKNOWN'
之一的值。它的默认值为 'REPLACE'
。
stat
(可选):应为标量默认整型变量。它是intent(out)
参数。如果存在,则在返回时,如果可以打开filename
,则其值为success
;如果action
说明符为"READ"
,则其值为read_only_error
;如果无法打开filename
,则其值为open_failure
。如果不存在且无法打开filename
,则处理将停止,并以信息性消息作为停止代码。
program example_global_logger
use stdlib_logger, global => global_logger
implicit none
integer :: unit, stat
call global%add_log_file('error_log.txt', unit, &
position='asis', stat=stat)
if (stat /= success) then
error stop 'Unable to open "error_log.txt".'
end if
end program example_global_logger
add_log_unit
- 向数组self % log_units
添加一个单元实验性
将unit
添加到self % log_units
数组中。unit
应为已打开的、顺序的、格式化的文件的单元号,其action
说明符为'WRITE'
或'READWRITE'
。如果unit
不满足这些要求,则如果存在,stat
将不为success
,并且unit
不会添加到log_units
中。在这种情况下,如果stat
不存在,则导致处理停止,并以信息性字符串作为停止代码。
call self %
add_log_unit ( unit [, stat ] )
子程序。
self
:应为logger_type
类型的标量变量。它是intent(inout)
参数。它应为将输出定向到unit
的日志记录器。
unit
:应为标量默认整型表达式。它是intent(in)
参数。它应为已打开的、顺序的、格式化的文件的单元号,其action
说明符为'WRITE'
或'READWRITE'
。
stat
(可选):应为标量默认整型变量。它是intent(out)
参数。如果不存在且无法将unit
添加到self的log_units
中,则处理将停止,并以信息性消息作为停止代码。如果存在,则应具有模块错误代码之一的值,指示在unit
中发现的任何错误。代码为* success
- 未发现问题 * non_sequential_error
- unit
没有access
说明符'SEQUENTIAL'
* read_only_error
- unit
的action
说明符为'READ'
,而它需要'WRITE'
或'READWRITE'
说明符 * unformatted_in_error
- unit
没有form
说明符'FORMATTED'
* unopened_in_error
- unit
未打开
program example_add_log_unit
use stdlib_logger, only: global_logger, read_only_error
implicit none
character(256) :: iomsg
integer :: iostat, unit, stat
open (newunit=unit, file='error_log.txt', &
form='formatted', status='replace', &
position='rewind', &
action='write', iostat=iostat, iomsg=iomsg)
call global_logger%add_log_unit(unit, stat)
select case (stat)
case (read_only_error)
error stop 'Unable to write to "error_log.txt".'
end select
end program example_add_log_unit
configuration
- 报告日志记录器的配置实验性
报告日志记录器的配置。
call self %
configuration ( [ add_blankline, indent, level, max_width, time_stamp, log_units ] )
纯子程序
self
:应为logger_type
类型的标量表达式。它是intent(in)
参数。它应为要报告其配置的日志记录器。
add_blank_line
(可选):应为标量默认逻辑变量。它是intent(out)
参数。值为.true.
表示输出以空行开头,否则为.false.
。
indent
(可选):应为标量默认逻辑变量。它是intent(out)
参数。值为.true.
表示后续行缩进四个空格,否则为.false.
。
level
(可选):应为标量默认整型变量。它是intent(out)
参数。该值对应于忽略消息的严重性级别。
max_width
(可选):应为标量默认整型变量。它是intent(out)
参数。大于四的正值定义输出的最大宽度,否则没有最大宽度。
time_stamp
(可选):应为标量默认逻辑变量。它是intent(out)
参数。值为.true.
表示输出以'yyyy-mm-dd hh:mm:ss.sss'形式的时间戳开头,否则为.false.
。
log_units
(可选):应为类型为默认整型的秩一可分配数组变量。它是intent(out)
参数。返回时,它应为self
的log_units
数组的元素。如果self
的log_units
中没有元素,则返回一个零大小的数组。
module example_mod
use stdlib_logger
type(logger_type) :: logger
contains
subroutine example_sub(unit, ...)
integer, intent(in) :: unit
integer, allocatable :: log_units(:)
call logger % configuration( log_units=log_units )
if ( size(log_units) == 0 ) then
call add_logger_unit( unit )
end if
end subroutine example_sub
end module example_mod
configure
- 配置日志记录过程实验性
为self配置日志记录过程。
call self %
configure ( [ add_blank_line, indent, level, max_width, time_stamp ] )
纯子程序
self
:应为logger_type
类型的标量变量。它是intent(inout)
参数。它应为要配置的日志记录器。
add_blank_line
(可选):应为标量默认逻辑表达式。它是intent(in)
参数。设置为.true.
表示输出以空行开头,否则设置为.false.
。
indent
(可选):应为标量默认逻辑表达式。它是intent(in)
参数。设置为.true.
表示后续行缩进四个空格,设置为.false.
表示不缩进。
level
(可选):应为标量默认整型表达式。它是intent(in)
参数。设置忽略日志消息的严重性级别。
max_width
(可选):应为标量默认整型表达式。它是intent(in)
参数。设置为大于四的正值以定义输出的最大宽度,否则没有最大宽度。
time_stamp
(可选):应为标量默认逻辑表达式。它是intent(in)
参数。设置为.true.
表示输出以'yyyy-mm-dd hh:mm:ss.sss'形式的时间戳开头,否则设置为.false.
。
program example_configure
use stdlib_logger, only: global => global_logger
implicit none
call global%configure(indent=.false., max_width=72)
end program example_configure
log_debug
- 将字符串message
写入self % log_units
实验性
将字符串message
写入self % log_units
,并带可选的附加文本。
call self %
log_debug ( message [, module, procedure ] )
如果时间戳处于活动状态,则写入时间戳,如果存在,则随后写入module
和procedure
,然后以'DEBUG: '
为前缀写入message
。
如果self
的level
高于debug_level
,则忽略它。
子程序
self
:应为logger_type
类型的标量变量。它是intent(in)
参数。它是用于发送消息的日志记录器。
message
:应为标量默认字符表达式。它是intent(in)
参数。
message
可能包含嵌入的新行调用。module
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_information
调用的模块的名称。
procedure
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_information
调用的过程的名称。
module example_mod
use stdlib_logger
real, allocatable :: a(:)
type(logger_type) :: logger
contains
subroutine example_sub( selection )
integer, intent(out) :: selection
character(128) :: errmsg, message
integer :: stat
write(*,'(a)') "Enter an integer to select a widget"
read(*,'(i0)') selection
write( message, '(a, i0)' ) &
"The user selected ", selection
call logger % log_DEBUG( message, &
module = 'EXAMPLE_MOD', procedure = 'EXAMPLE_SUB' )
end subroutine example_sub
end module example_mod
log_error
- 将字符串message
写入self % log_units
实验性
将字符串message
写入self % log_units
,并带可选的附加文本。
call self %
log_error ( message [, module, procedure, stat, errmsg ] )
如果self
的时间戳处于活动状态,则首先写入时间戳,如果存在,则随后写入module
和procedure
,然后以'ERROR: '
为前缀写入message
,然后如果存在stat
或errmsg
,则写入它们。
如果self
的level
高于error_level
,则忽略它。
子程序
self
:应为logger_type
类型的标量变量。它是intent(in)
参数。它是用于发送消息的日志记录器。
message
:应为标量默认字符表达式。它是intent(in)
参数。
message
可能包含嵌入的新行调用。module
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_error
调用的模块的名称。
procedure
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_error
调用的过程的名称。
stat
(可选):应为标量默认整型表达式。它是intent(in)
参数。它应该是导致log_error
调用的子程序调用或内在语句的stat
说明符。
errmsg
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是导致log_error
调用的子程序调用或内在语句的errmsg
说明符。
module example_mod
use stdlib_logger
real, allocatable :: a(:)
type(logger_type) :: logger
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
call logger % log_error( message, &
module = 'EXAMPLE_MOD', &
procedure = 'EXAMPLE_SUB', &
stat = stat, &
errmsg = errmsg )
end if
end subroutine example_sub
end module example_mod
log_information
- 将字符串message
写入self % log_units
实验性
将字符串message
写入self % log_units
,并带可选的附加文本。
call self %
log_information ( message [, module, procedure ] )
如果时间戳处于活动状态,则写入时间戳,如果存在,则随后写入module
和procedure
,然后以'INFO: '
为前缀写入message
。
如果self
的level
高于information_level
,则忽略它。
子程序
self
:应为logger_type
类型的标量变量。它是intent(in)
参数。它是用于发送消息的日志记录器。
message
:应为标量默认字符表达式。它是intent(in)
参数。
message
可能包含嵌入的新行调用。module
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_information
调用的模块的名称。
procedure
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_information
调用的过程的名称。
module example_mod
use stdlib_logger
real, allocatable :: a(:)
type(logger_type) :: logger
contains
subroutine example_sub( selection )
integer, intent(out) :: selection
character(128) :: errmsg, message
integer :: stat
write(*,'(a)') "Enter an integer to select a widget"
read(*,'(i0)') selection
write( message, '(a, i0)' ) &
"The user selected ", selection
call logger % log_information( message, &
module = 'EXAMPLE_MOD', procedure = 'EXAMPLE_SUB' )
end subroutine example_sub
end module example_mod
log_io_error
- 将字符串message
写入self % log_units
实验性
将字符串message
写入self % log_units
,并带可选的附加文本。
如果时间戳处于活动状态,则首先写入时间戳。然后,如果存在module
或procedure
,则写入它们。然后以'I/O ERROR: '
为前缀写入message
。然后,如果存在iostat
或iomsg
,则写入它们。
如果self
的level
高于io_error_level
,则忽略它。
call self %
log_io_error ( message [, module, procedure, iostat, iomsg ] )
子程序
self
:应为logger_type
类型的标量变量。它是intent(in)
参数。它是用于发送消息的日志记录器。
message
:应为标量默认字符表达式。它是intent(in)
参数。
message
可能包含嵌入的新行调用。module
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_io_error
调用的模块的名称。
procedure
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_io_error
调用的过程的名称。
iostat
(可选):应为标量默认整型表达式。它是intent(in)
参数。它应该是导致log_io_error
调用的子程序调用或内在语句的iostat
说明符。
iomsg
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是导致log_io_error
调用的子程序调用或内在语句的iomsg
说明符。
program example_log_io_error
use stdlib_logger, global => global_logger
implicit none
character(*), parameter :: filename = 'nodummy.txt'
integer :: iostat, lun
character(128) :: iomsg
character(*), parameter :: message = &
'Failure in opening "nodummy.txt".'
open (newunit=lun, file=filename, form='formatted', &
status='old', iostat=iostat, iomsg=iomsg)
if (iostat /= 0) then
call global%log_io_error(message, &
procedure='EXAMPLE', &
iostat=iostat, &
iomsg=iomsg)
error stop 'Error on opening a file'
end if
end program example_log_io_error
log_message
- 将字符串message
写入self % log_units
实验性
将字符串message
写入self % log_units
,并带可选的附加文本。
如果时间戳处于活动状态,则写入时间戳,然后如果存在,则写入module
和procedure
,随后写入prefix \\ ': '
(如果存在),最后写入message
。
不会将严重性级别应用于log_message
。
call self %
log_message ( message [, module, procedure, prefix ] )
子程序
self
:应为logger_type
类型的标量变量。它是intent(in)
参数。它是用于发送消息的日志记录器。
message
:应为标量默认字符表达式。它是intent(in)
参数。
message
可能包含嵌入的新行调用。module
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_message
调用的模块的名称。
procedure
(可选):应为标量默认字符表达式。它是intent(in)
参数。它应该是包含log_message
调用的过程的名称。
prefix
(可选):应为标量默认字符表达式。它是intent(in)
参数。它将在message
前面加上附加的': '
。
module example_mod
use stdlib_logger
real, allocatable :: a(:)
type(logger_type) :: logger
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 logger % log_message( message, &
module = 'EXAMPLE_MOD', &
procedure = 'EXAMPLE_SUB', &
prefix = `INFO' )
end subroutine example_sub
end module example_mod
log_text_error
- 向self % log_units
发送一条描述错误的消息实验性
log_text_error
向self % log_units
发送一条描述在文本行中发现的错误的消息。
如果时间戳处于活动状态,则首先写入时间戳。然后,如果存在filename
或line_number
,则与column
一起写入它们。然后写入line
。然后在line
下方用column
指示的列写入插入符号'^'。然后在插入符号下方写入summary
。
如果self
的level
高于text_error_level
,则忽略它。
call self %
log_text_error ( line, column, summary [, filename, line_number, caret, stat ] )
子程序
self
:应为logger_type
类型的标量变量。它是intent(in)
参数。它是用于发送消息的日志记录器。
line
:应为标量默认字符表达式。它是一个intent(in)
参数。它应该是发现错误的行文本。
column
:应为标量默认整数表达式。它是一个intent(in)
参数。它应该是错误开始位置的基于一的列号。
summary
:应为标量默认字符表达式。它是一个intent(in)
参数。它应该是对line
中错误的描述。
filename
(可选):应为标量默认字符表达式。它是一个intent(in)
参数。它应该是文件名称(如果存在),其中包含line
。
line_number
(可选):应为标量默认整数表达式。它是一个intent(in)
参数。它应该是与line
关联的filename
中的行号。
caret
(可选):应为标量默认单字符表达式。它是一个intent(in)
参数。如果存在,它将在输出中放置在line
下方,以指示错误的起始位置。它的默认值为'^'。
stat
(可选):应为标量默认整数变量。它是一个intent(out)
参数。如果存在,如果未遇到错误,则其值为success
;如果column
小于1或大于len(line)+1
,则其值为index_invalid_error
;如果对任何log_units
的写入失败,则其值为write_fault
。如果stat
不存在且其值不为success
,则处理将以信息性停止代码停止。
program example_log_text_error
use stdlib_logger
implicit none
character(*), parameter :: filename = 'dummy.txt'
integer :: col_no, line_no, lun, status
character(128) :: line
character(*), parameter :: message = 'Bad text found.'
open (newunit=lun, file=filename, status='old', &
form='formatted')
line_no = 0
do
read (lun, fmt='(a)', end=900) line
line_no = line_no + 1
call check_line(line, status, col_no)
if (status /= 0) then
call global_logger%log_text_error(line, &
col_no, message, filename, line_no)
error stop 'Error in reading '//filename
end if
end do
900 continue
contains
subroutine check_line(line, status, col_no)
character(*), intent(in) :: line
integer, intent(inout) :: status
integer, intent(inout) :: col_no
! scan the line for forbidden characters
col_no = scan(line, ".$/")
! col_no > 0 means there is a forbidden character
status = col_no
end subroutine
end program example_log_text_error
log_units_assigned
- 返回活动I/O单元的数量实验性
返回self % log_units
中活动I/O单元的数量
result = self %
log_units_assigned ()
元素函数
self
:应为logger_type
类型的标量表达式。它是一个intent(in)
参数。它是查询其状态的日志记录器。
结果应为默认整数类型的标量。
结果是self % log_units
中I/O单元的数量。
module example_mod
use stdlib_logger
type(logger_type) :: logger
contains
subroutine example_sub(unit, ...)
integer, intent(in) :: unit
integer, allocatable :: log_units(:)
if ( logger % log_units_assigned() == 0 ) then
call logger % add_log_unit( unit )
end if
end subroutine example_sub
end module example_mod
log_warning
- 将字符串message
写入log_units
实验性
将字符串message
写入log_units
,并带有可选的附加文本。
如果时间戳处于活动状态,则写入时间戳,然后写入module
和procedure
(如果存在),然后以WARN: '
为前缀写入message
。
call self %
log_warning ( message [, module, procedure ] )
子程序
self
:应为logger_type
类型的标量变量。它是intent(in)
参数。它是用于发送消息的日志记录器。
message
:应为标量默认字符表达式。它是intent(in)
参数。
message
可能包含嵌入的新行调用。module
:(可选)应为标量默认字符表达式。它是一个intent(in)
参数。它应该是包含log_warning
调用的模块的名称。
procedure
:(可选)应为标量默认字符表达式。它是一个intent(in)
参数。它应该是包含log_warning
调用的过程的名称。
module example_mod
use stdlib_logger
real, allocatable :: a(:)
type(logger_type) :: logger
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 logger % log_warning( message, &
module = 'EXAMPLE_MOD', &
procedure = 'EXAMPLE_SUB' )
end if
end subroutine example_sub
end module example_mod
remove_log_unit
- 从self % log_units
中移除unit
实验性
从self % log_units
列表中移除unit
。如果close_unit
存在且为.true.
,则关闭相应的文件。如果unit
不在self % log_units
中,则不执行任何操作。
call self %
remove_log_unit ( unit [, close_unit, stat ] )
子程序
self
:应为logger_type
类型的标量变量。它是一个intent(inout)
参数。它是其log_units
需要修改的日志记录器。
unit
:应为标量默认整数表达式。它是一个intent(in)
参数。它应该是self % log_units
中I/Ounit
编号之一。如果不是,则不执行任何操作。
close_unit
(可选):应为标量默认逻辑表达式。它是一个intent(in)
参数。如果为.true
且unit
在self % log_units
中,则unit
将被关闭,否则I/O单元将不受影响。
stat
(可选):应为标量默认整数变量。它是一个intent(out)
参数。如果存在,其默认值为success
,但如果close_unit
存在且值为.true.
,并且unit
最初在log_units
中,并且关闭unit
失败,则其值为close_failure
。如果stat
不存在并且关闭unit
失败,则处理将以信息性停止代码停止。
module example_mod
use stdlib_logger, global => global_logger
contains
subroutine example_sub(unit, ...)
integer, intent(in) :: unit
call global % remove_log_unit( unit )
end subroutine example_sub
end module example_mod