Skip to content

Commit d0d927d

Browse files
authored
Merge pull request #256 from jvdp1/debug_logger
debug_logger: add log_debug to logger
2 parents c23a1c6 + 7941301 commit d0d927d

File tree

3 files changed

+146
-1
lines changed

3 files changed

+146
-1
lines changed

doc/specs/stdlib_logger.md

Lines changed: 71 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ The logger variables have the option to:
2929
that prompted the log message;
3030
* follow a message with the `iostat` and `iomsg` of the I/O error
3131
report that prompted the log message;
32-
* label a message with one of `'INFO: '`, `'WARN: '`,
32+
* label a message with one of `'DEBUG: '`, `'INFO: '`, `'WARN: '`,
3333
`'ERROR: '`, or `'I/O ERROR: '`;
3434
* indent subsequent lines of the messages; and
3535
* format the text to fit within a maximum column width.
@@ -110,6 +110,7 @@ Method | Class | Description
110110
[`add_log_unit`](./stdlib_logger.html#add_log_unit-add-a-unit-to-the-array-self-log_units) | Subroutine | Adds an existing unit to the `log_units` list
111111
[`configuration`](./stdlib_logger.html#configuration-report-a-loggers-configuration) | Subroutine | Reports the details of the logging configuration
112112
[`configure`](./stdlib_logger.html#configure-configure-the-logging-process) | Subroutine | Configures the details of the logging process
113+
[`log_debug`](./stdlib_logger.html#log_debug-writes-the-string-message-to-self-log_units) | Subroutine | Sends a message prepended by `'DEBUG: '`
113114
[`log_error`](./stdlib_logger.html#log_error-writes-the-string-message-to-self-log_units) | Subroutine | Sends a message prepended by `'ERROR: '` optionally followed by a `stat` or `errmsg`
114115
[`log_information`](./stdlib_logger.html#log_information-writes-the-string-message-to-self-log_units) | Subroutine | Sends a message prepended by `'INFO: '`
115116
[`log_io_error`](./stdlib_logger.html#log_io_error-write-the-string-message-to-self-log_units) | Subroutine | Sends a message prepended by `'I/O ERROR: '` optionally followed by an `iostat` or `iomsg`
@@ -395,6 +396,75 @@ program demo_configure
395396
end program demo_configure
396397
```
397398

399+
### `log_debug` - Writes the string `message` to `self % log_units`
400+
401+
#### Status
402+
403+
Experimental
404+
405+
#### Description
406+
407+
Writes the string `message` to `self % log_units` with optional additional text.
408+
409+
#### Syntax
410+
411+
`call self % [[logger_type(type):log_debug(bound)]]( message [, module, procedure ] )`
412+
413+
#### Behavior
414+
415+
If time stamps are active, a time stamp is written, followed
416+
by `module` and `procedure` if present, and then
417+
`message` is written with the prefix `'DEBUG: '`.
418+
419+
#### Class
420+
421+
Subroutine
422+
423+
#### Arguments
424+
425+
`self`: shall be a scalar variable of type `logger_type`. It is an
426+
`intent(in)` argument. It is the logger used to send the message.
427+
428+
`message`: shall be a scalar default character expression. It is an
429+
`intent(in)` argument.
430+
431+
* Note `message` may have embedded new_line calls.
432+
433+
`module` (optional): shall be a scalar default character
434+
expression. It is an `intent(in)` argument. It should be the name of
435+
the module containing the `log_information` call.
436+
437+
`procedure` (optional): shall be a scalar default character
438+
expression. It is an `intent(in)` argument. It should be the name of
439+
the procedure containing the `log_information` call.
440+
441+
#### Example
442+
443+
```fortran
444+
module example_mod
445+
use stdlib_logger
446+
447+
real, allocatable :: a(:)
448+
449+
type(logger_type) :: logger
450+
contains
451+
452+
subroutine example_sub( selection )
453+
integer, intent(out) :: selection
454+
character(128) :: errmsg, message
455+
integer :: stat
456+
write(*,'(a)') "Enter an integer to select a widget"
457+
read(*,'(i0)') selection
458+
write( message, '(a, i0)' ) &
459+
"The user selected ", selection
460+
call logger % log_DEBUG( message, &
461+
module = 'EXAMPLE_MOD', procedure = 'EXAMPLE_SUB' )
462+
463+
end subroutine example_sub
464+
465+
end module example_mod
466+
```
467+
398468
### `log_error` - Writes the string `message` to `self % log_units`
399469

400470
#### Status

src/stdlib_logger.f90

Lines changed: 59 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -91,6 +91,7 @@ module stdlib_logger
9191
procedure, public, pass(self) :: add_log_unit
9292
procedure, public, pass(self) :: configuration
9393
procedure, public, pass(self) :: configure
94+
procedure, public, pass(self) :: log_debug
9495
procedure, public, pass(self) :: log_error
9596
procedure, public, pass(self) :: log_information
9697
procedure, public, pass(self) :: log_io_error
@@ -757,6 +758,64 @@ subroutine handle_write_failure( unit, procedure_name, iostat, iomsg )
757758
end subroutine handle_write_failure
758759

759760

761+
subroutine log_debug( self, message, module, procedure )
762+
!! version: experimental
763+
764+
!! Writes the string `message` to `self % log_units` with optional additional
765+
!! text.
766+
!!([Specification](../page/specs/stdlib_logger.html#log_debug-writes-the-string-message-to-self-log_units))
767+
!!
768+
!!##### Behavior
769+
!!
770+
!! If time stamps are active, a time stamp is written, followed by
771+
!! `module` and `procedure` if present, and then `message` is
772+
!! written with the prefix 'DEBUG: '.
773+
!!
774+
!!##### Example
775+
!!
776+
!! module example_mod
777+
!! use stdlib_logger
778+
!! ...
779+
!! real, allocatable :: a(:)
780+
!! ...
781+
!! type(logger_type) :: alogger
782+
!! ...
783+
!! contains
784+
!! ...
785+
!! subroutine example_sub( selection )
786+
!! integer, intent(out) :: selection
787+
!! integer :: stat
788+
!! write(*,'(a)') "Enter an integer to select a widget"
789+
!! read(*,'(i0)') selection
790+
!! write( message, `(a, i0)' ) &
791+
!! "The user selected ", selection
792+
!! call alogger % log_debug( message, &
793+
!! module = 'EXAMPLE_MOD', &
794+
!! procedure = 'EXAMPLE_SUB' )
795+
!! ...
796+
!! end subroutine example_sub
797+
!! ...
798+
!! end module example_mod
799+
!!
800+
801+
class(logger_type), intent(in) :: self
802+
!! The logger used to send the message
803+
character(len=*), intent(in) :: message
804+
!! A string to be written to log_unit
805+
character(len=*), intent(in), optional :: module
806+
!! The name of the module contining the current invocation of `log_information`
807+
character(len=*), intent(in), optional :: procedure
808+
!! The name of the procedure contining the current invocation of
809+
!! `log_information`
810+
811+
call self % log_message( message, &
812+
module = module, &
813+
procedure = procedure, &
814+
prefix = 'DEBUG' )
815+
816+
end subroutine log_debug
817+
818+
760819
subroutine log_error( self, message, module, procedure, stat, errmsg )
761820
!! version: experimental
762821

src/tests/logger/test_stdlib_logger.f90

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -198,6 +198,22 @@ subroutine test_logging_configuration()
198198
module = 'N/A', &
199199
procedure = 'TEST_STDLIB_LOGGER' )
200200

201+
call global % log_debug( 'This message should be output ' // &
202+
'to OUTPUT_UNIT, unlimited in width, not preceded by ' // &
203+
'a blank line, then by a time stamp, then by MODULE % ' // &
204+
'PROCEDURE, be prefixed by DEBUG and be indented on ' // &
205+
'subsequent lines by 4 columns.', &
206+
module = 'N/A', &
207+
procedure = 'TEST_STDLIB_LOGGER' )
208+
209+
call global % log_debug( 'This message should be output ' // &
210+
'to OUTPUT_UNIT, unlimited in width, not preceded by ' // &
211+
'a blank line, then by a time stamp, then by MODULE % ' // &
212+
'PROCEDURE, be prefixed by DEBUG. ' // new_line('a') // &
213+
'This is a new line of the same log message.', &
214+
module = 'N/A', &
215+
procedure = 'TEST_STDLIB_LOGGER' )
216+
201217
call global % configure( add_blank_line=.true., indent=.false., &
202218
max_width=72, time_stamp=.false. )
203219

0 commit comments

Comments
 (0)