Public derived type (Specification)
Finalizes the logger_type
entity self
by flushing the units
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(logger_type), | intent(in) | :: | self |
Opens a formatted sequential access output file, filename
using
newunit
and adds the resulting unit number to self
's log_units
array. action
, if present, is the action
specifier of the open
statement, and has the default value of "write"
. position
, if present,
is the position
specifier, and has the default value of "REWIND"
.
status
, if present, is the status
specifier of the open
statement,
and has the default value of "REPLACE"
. stat
, if present, has the value
success
if filename
could be opened, read_only_error
if action
is
"read"
, and open_failure
otherwise.
(Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(inout) | :: | self |
The logger variable to which the file is to be added |
||
character(len=*), | intent(in) | :: | filename |
The name of the file to be added to the logger |
||
integer, | intent(out), | optional | :: | unit |
The resulting I/O unit number |
|
character(len=*), | intent(in), | optional | :: | action |
The |
|
character(len=*), | intent(in), | optional | :: | position |
The |
|
character(len=*), | intent(in), | optional | :: | status |
The |
|
integer, | intent(out), | optional | :: | stat |
The error status on exit with the possible values
* Example
|
Adds unit
to the log file units in log_units
. unit
must be an open
file, of form
"formatted"
, with "sequential"
access
, and an action
of "write"
or "readwrite"
, otherwise either stat
, if present, has a
value other than success
and unit
is not entered into log_units
,
or, if stat
is not presecn, processing stops.
(Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(inout) | :: | self |
The logger variable to which the I/O unit is to be added |
||
integer, | intent(in) | :: | unit |
The input logical unit number |
||
integer, | intent(out), | optional | :: | stat |
An error code with the possible values
* Example
|
Reports the logging configuration of self
. The following attributes are
reported:
1. add_blank_line
is a logical flag with .true.
implying that output
starts with a blank line, and .false.
implying no blank line.
2. indent
is a logical flag with .true.
implying that subsequent columns
will be indented 4 spaces and .false.
implying no indentation.
3. level
is the lowest level for printing a message
4. max_width
is the maximum number of columns of output text with
max_width
== 0 => no bounds on output width.
5. time_stamp
is a logical flag with .true.
implying that the output
will have a time stamp, and .false.
implying that there will be no
time stamp.
6. log_units
is an array of the I/O unit numbers to which log output
will be written.
(Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger variable whose configuration is being reported |
||
logical, | intent(out), | optional | :: | add_blank_line |
A logical flag to add a preceding blank line |
|
logical, | intent(out), | optional | :: | indent |
A logical flag to indent subsequent lines |
|
integer, | intent(out), | optional | :: | level |
The minimum level for printing a message |
|
integer, | intent(out), | optional | :: | max_width |
The maximum number of columns for most outputs |
|
logical, | intent(out), | optional | :: | time_stamp |
A logical flag to add a time stamp |
|
integer, | intent(out), | optional, | allocatable | :: | log_units(:) |
The I/O units used in output Example
|
Configures the logging process for SELF. The following attributes are
configured:
1. add_blank_line
is a logical flag with .true.
implying that output
starts with a blank line, and .false.
implying no blank line.
add_blank_line
has a startup value of .false.
.
2. indent
is a logical flag with .true.
implying that subsequent lines
will be indented 4 spaces and .false.
implying no indentation. indent
has a startup value of .true.
.
3. level
is the lowest level for printing a message
4. max_width
is the maximum number of columns of output text with
max_width == 0
=> no bounds on output width. max_width
has a startup
value of 0.
5. time_stamp
is a logical flag with .true.
implying that the output
will have a time stamp, and .false.
implying that there will be no
time stamp. time_stamp
has a startup value of .true.
.
(Specification)
program main
use stdlib_logger
...
call global_logger % configure( indent=.false., max_width=72 )
...
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
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 |
Writes the string message
to self % log_units
with optional additional
text.
(Specification)
If time stamps are active, a time stamp is written, followed by
module
and procedure
if present, and then message
is
written with the prefix 'DEBUG: '.
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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger used to send the message |
||
character(len=*), | intent(in) | :: | message |
A string to be written to log_unit |
||
character(len=*), | intent(in), | optional | :: | module |
The name of the module containing the current invocation of |
|
character(len=*), | intent(in), | optional | :: | procedure |
The name of the procedure containing the current invocation of
|
Writes the string message
to self % log_units
with optional additional
text.
(Specification)
If time stamps are active, a time stamp is written, followed by
module
and procedure
if present, then message
is
written with the prefix 'ERROR: ', and then if stat
or errmsg
are present they are written.
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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger to be used in logging the message |
||
character(len=*), | intent(in) | :: | message |
A string to be written to log_unit |
||
character(len=*), | intent(in), | optional | :: | module |
The name of the module containing the current invocation of |
|
character(len=*), | intent(in), | optional | :: | procedure |
The name of the procedure containing the current invocation of |
|
integer, | intent(in), | optional | :: | stat |
The value of the |
|
character(len=*), | intent(in), | optional | :: | errmsg |
The value of the |
Writes the string message
to self % log_units
with optional additional
text.
(Specification)
If time stamps are active, a time stamp is written, followed by
module
and procedure
if present, and then message
is
written with the prefix 'INFO: '.
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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger used to send the message |
||
character(len=*), | intent(in) | :: | message |
A string to be written to log_unit |
||
character(len=*), | intent(in), | optional | :: | module |
The name of the module containing the current invocation of |
|
character(len=*), | intent(in), | optional | :: | procedure |
The name of the procedure containing the current invocation of
|
Writes the string message
to the self % log_units
with optional
additional text.
(Specification)
If time stamps are active, a time stamp is written, followed by
module
and procedure
if present, then message
is
written with a prefix 'I/O ERROR: ', and then if iostat
or iomsg
are present they are also written.
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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger variable to receivee the message |
||
character(len=*), | intent(in) | :: | message |
A string to be written to LOG_UNIT |
||
character(len=*), | intent(in), | optional | :: | module |
The name of the module containing the current invocation of REPORT_ERROR |
|
character(len=*), | intent(in), | optional | :: | procedure |
The name of the procedure containing the current invocation of REPORT_ERROR |
|
integer, | intent(in), | optional | :: | iostat |
The value of the IOSTAT specifier returned by a Fortran I/O statement |
|
character(len=*), | intent(in), | optional | :: | iomsg |
The value of the IOMSG specifier returned by a Fortran I/O statement |
Writes the string message
to the self % log_units
with optional
additional text.
(Specification)
If time stamps are active, a time stamp is written, followed by module
and procedure
if present, followed by prefix // ': '
if present,
and then 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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger variable to receive the message |
||
character(len=*), | intent(in) | :: | message |
A string to be written to log_unit |
||
character(len=*), | intent(in), | optional | :: | module |
The name of the module containing the current invocation of |
|
character(len=*), | intent(in), | optional | :: | procedure |
The name of the procedure containing the current invocation of |
|
character(len=*), | intent(in), | optional | :: | prefix |
To be prepended to message as |
Sends a message to self % log_units
describing an error found
in a line of text.
(Specification)
If time stamps are active first a time stamp is written. Then if
filename
or line_number
or column
are present they are written.
Then line
is written. Then the symbol caret
is written below line
at the column indicated by column
. Then summary
is written.
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 continue ... end program example
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger variable to receive the message |
||
character(len=*), | intent(in) | :: | line |
The line of text in which the error was found. |
||
integer, | intent(in) | :: | column |
The one's based column in LINE at which the error starts. |
||
character(len=*), | intent(in) | :: | summary |
A brief description of the error. |
||
character(len=*), | intent(in), | optional | :: | filename |
The name of the file, if any, in which the error was found. |
|
integer, | intent(in), | optional | :: | line_number |
The one's based line number in the file where |
|
character(len=1), | intent(in), | optional | :: | caret |
The symbol used to mark the column wher the error was first detected |
|
integer, | intent(out), | optional | :: | stat |
Integer flag that an error has occurred. Has the value |
Returns the number of units assigned to self % log_units
(Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger subject to the inquiry |
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
Writes the string message
to self % log_units
with optional additional
text.
(Specification)
If time stamps are active, a time stamp is written, followed by
module
and procedure
if present, then message
is
written with the prefix 'WARN: '.
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
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(in) | :: | self |
The logger to which the message is written |
||
character(len=*), | intent(in) | :: | message |
A string to be written to LOG_UNIT |
||
character(len=*), | intent(in), | optional | :: | module |
The name of the module containing the current invocation of |
|
character(len=*), | intent(in), | optional | :: | procedure |
The name of the procedure containing the current invocation of |
Remove the I/O unit from the self % log_units list. If close_unit
is
present and .true.
then the corresponding file is closed. If unit
is
not in log_units
then nothing is done. If stat
is present it, by
default, has the value success
. If closing the unit
fails, then if
stat
is present it has the value close_failure
, otherwise processing
stops with an informative message.
(Specification)
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(logger_type), | intent(inout) | :: | self |
The logger variable whose unit is to be removed |
||
integer, | intent(in) | :: | unit |
The I/O unit to be removed from self |
||
logical, | intent(in), | optional | :: | close_unit |
A logical flag to close the unit while removing it from the SELF list |
|
integer, | intent(out), | optional | :: | stat |
An error status with the values * success - no problems found * close_failure - the close statement for unit failed Example
|
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