@@ -68,6 +68,28 @@ module stdlib_logger
6868 unopened_in_error = 7 , &
6969 write_failure = 8
7070
71+ integer , parameter , public :: &
72+ debug_level = 10 , &
73+ information_level = 20 , &
74+ warning_level = 30 , &
75+ error_level = 40 , &
76+ io_error_level = 40 , &
77+ text_error_level = 50 , &
78+ all_level = - 10 + min ( &
79+ debug_level, &
80+ information_level, &
81+ warning_level, &
82+ error_level, &
83+ io_error_level, &
84+ text_error_level), &
85+ none_level = 10 + max ( &
86+ debug_level, &
87+ information_level, &
88+ warning_level, &
89+ error_level, &
90+ io_error_level, &
91+ text_error_level)
92+
7193 character (* ), parameter :: module_name = ' stdlib_logger'
7294
7395 type :: logger_type
@@ -78,6 +100,7 @@ module stdlib_logger
78100
79101 logical :: add_blank_line = .false.
80102 logical :: indent_lines = .true.
103+ integer :: level = information_level
81104 integer , allocatable :: log_units(:)
82105 integer :: max_width = 0
83106 logical :: time_stamp = .true.
@@ -379,7 +402,7 @@ end subroutine validate_unit
379402 end subroutine add_log_unit
380403
381404
382- pure subroutine configuration ( self , add_blank_line , indent , &
405+ pure subroutine configuration ( self , add_blank_line , indent , level , &
383406 max_width , time_stamp , log_units )
384407! ! version: experimental
385408
@@ -389,12 +412,13 @@ pure subroutine configuration( self, add_blank_line, indent, &
389412! ! starts with a blank line, and `.false.` implying no blank line.
390413! ! 2. `indent` is a logical flag with `.true.` implying that subsequent columns
391414! ! will be indented 4 spaces and `.false.` implying no indentation.
392- ! ! 3. `max_width` is the maximum number of columns of output text with
415+ ! ! 3. `level` is the lowest level for printing a message
416+ ! ! 4. `max_width` is the maximum number of columns of output text with
393417! ! `max_width` == 0 => no bounds on output width.
394- ! ! 4 . `time_stamp` is a logical flag with `.true.` implying that the output
418+ ! ! 5 . `time_stamp` is a logical flag with `.true.` implying that the output
395419! ! will have a time stamp, and `.false.` implying that there will be no
396420! ! time stamp.
397- ! ! 5 . `log_units` is an array of the I/O unit numbers to which log output
421+ ! ! 6 . `log_units` is an array of the I/O unit numbers to which log output
398422! ! will be written.
399423! !([Specification](../page/specs/stdlib_logger.html#configuration-report-a-loggers-configuration))
400424
@@ -404,6 +428,8 @@ pure subroutine configuration( self, add_blank_line, indent, &
404428! ! A logical flag to add a preceding blank line
405429 logical , intent (out ), optional :: indent
406430! ! A logical flag to indent subsequent lines
431+ integer , intent (out ), optional :: level
432+ ! ! The minimum level for printing a message
407433 integer , intent (out ), optional :: max_width
408434! ! The maximum number of columns for most outputs
409435 logical , intent (out ), optional :: time_stamp
@@ -434,6 +460,7 @@ pure subroutine configuration( self, add_blank_line, indent, &
434460
435461 if ( present (add_blank_line) ) add_blank_line = self % add_blank_line
436462 if ( present (indent) ) indent = self % indent_lines
463+ if ( present (level) ) level = self % level
437464 if ( present (max_width) ) max_width = self % max_width
438465 if ( present (time_stamp) ) time_stamp = self % time_stamp
439466 if ( present (log_units) ) then
@@ -447,7 +474,7 @@ pure subroutine configuration( self, add_blank_line, indent, &
447474 end subroutine configuration
448475
449476
450- pure subroutine configure ( self , add_blank_line , indent , max_width , &
477+ pure subroutine configure ( self , add_blank_line , indent , level , max_width , &
451478 time_stamp )
452479! ! version: experimental
453480
@@ -459,10 +486,11 @@ pure subroutine configure( self, add_blank_line, indent, max_width, &
459486! ! 2. `indent` is a logical flag with `.true.` implying that subsequent lines
460487! ! will be indented 4 spaces and `.false.` implying no indentation. `indent`
461488! ! has a startup value of `.true.`.
462- ! ! 3. `max_width` is the maximum number of columns of output text with
489+ ! ! 3. `level` is the lowest level for printing a message
490+ ! ! 4. `max_width` is the maximum number of columns of output text with
463491! ! `max_width == 0` => no bounds on output width. `max_width` has a startup
464492! ! value of 0.
465- ! ! 4 . `time_stamp` is a logical flag with `.true.` implying that the output
493+ ! ! 5 . `time_stamp` is a logical flag with `.true.` implying that the output
466494! ! will have a time stamp, and `.false.` implying that there will be no
467495! ! time stamp. `time_stamp` has a startup value of `.true.`.
468496! !([Specification](../page/specs/stdlib_logger.html#configure-configure-the-logging-process))
@@ -477,10 +505,12 @@ pure subroutine configure( self, add_blank_line, indent, max_width, &
477505 class(logger_type), intent (inout ) :: self
478506 logical , intent (in ), optional :: add_blank_line
479507 logical , intent (in ), optional :: indent
508+ integer , intent (in ), optional :: level
480509 integer , intent (in ), optional :: max_width
481510 logical , intent (in ), optional :: time_stamp
482511
483512 if ( present (add_blank_line) ) self % add_blank_line = add_blank_line
513+ if ( present (level) ) self % level = level
484514 if ( present (indent) ) self % indent_lines = indent
485515 if ( present (max_width) ) then
486516 if ( max_width <= 4 ) then
@@ -803,11 +833,13 @@ subroutine log_debug( self, message, module, procedure )
803833 character (len=* ), intent (in ) :: message
804834! ! A string to be written to log_unit
805835 character (len=* ), intent (in ), optional :: module
806- ! ! The name of the module contining the current invocation of `log_information`
836+ ! ! The name of the module containing the current invocation of `log_information`
807837 character (len=* ), intent (in ), optional :: procedure
808- ! ! The name of the procedure contining the current invocation of
838+ ! ! The name of the procedure containing the current invocation of
809839! ! `log_information`
810840
841+ if ( self % level > debug_level ) return
842+
811843 call self % log_message( message, &
812844 module = module , &
813845 procedure = procedure , &
@@ -865,9 +897,9 @@ subroutine log_error( self, message, module, procedure, stat, errmsg )
865897 character (len=* ), intent (in ) :: message
866898! ! A string to be written to log_unit
867899 character (len=* ), intent (in ), optional :: module
868- ! ! The name of the module contining the current invocation of `log_error`
900+ ! ! The name of the module containing the current invocation of `log_error`
869901 character (len=* ), intent (in ), optional :: procedure
870- ! ! The name of the procedure contining the current invocation of `log_error`
902+ ! ! The name of the procedure containing the current invocation of `log_error`
871903 integer , intent (in ), optional :: stat
872904! ! The value of the `stat` specifier returned by a Fortran statement
873905 character (len=* ), intent (in ), optional :: errmsg
@@ -879,6 +911,8 @@ subroutine log_error( self, message, module, procedure, stat, errmsg )
879911 character (* ), parameter :: procedure_name = ' log_error'
880912 character (:), allocatable :: suffix
881913
914+ if ( self % level > error_level ) return
915+
882916 if ( present (stat) ) then
883917 write ( dummy, ' (a, i0)' , err= 999 , iostat= iostat, iomsg= iomsg ) &
884918 new_line(' a' ) // " With stat = " , stat
@@ -954,11 +988,13 @@ subroutine log_information( self, message, module, procedure )
954988 character (len=* ), intent (in ) :: message
955989! ! A string to be written to log_unit
956990 character (len=* ), intent (in ), optional :: module
957- ! ! The name of the module contining the current invocation of `log_information`
991+ ! ! The name of the module containing the current invocation of `log_information`
958992 character (len=* ), intent (in ), optional :: procedure
959- ! ! The name of the procedure contining the current invocation of
993+ ! ! The name of the procedure containing the current invocation of
960994! ! `log_information`
961995
996+ if ( self % level > information_level ) return
997+
962998 call self % log_message( message, &
963999 module = module , &
9641000 procedure = procedure , &
@@ -1007,9 +1043,9 @@ subroutine log_io_error( self, message, module, procedure, iostat, &
10071043 character (len=* ), intent (in ) :: message
10081044! ! A string to be written to LOG_UNIT
10091045 character (len=* ), intent (in ), optional :: module
1010- ! ! The name of the module contining the current invocation of REPORT_ERROR
1046+ ! ! The name of the module containing the current invocation of REPORT_ERROR
10111047 character (len=* ), intent (in ), optional :: procedure
1012- ! ! The name of the procedure contining the current invocation of REPORT_ERROR
1048+ ! ! The name of the procedure containing the current invocation of REPORT_ERROR
10131049 integer , intent (in ), optional :: iostat
10141050! ! The value of the IOSTAT specifier returned by a Fortran I/O statement
10151051 character (len=* ), intent (in ), optional :: iomsg
@@ -1021,6 +1057,8 @@ subroutine log_io_error( self, message, module, procedure, iostat, &
10211057 character (* ), parameter :: procedure_name = ' log_io_error'
10221058 character (:), allocatable :: suffix
10231059
1060+ if ( self % level > io_error_level ) return
1061+
10241062 if ( present (iostat) ) then
10251063 write ( dummy, ' (a, i0)' , err= 999 , iostat= iostat2, iomsg= iomsg2 ) &
10261064 new_line(' a' ) // " With iostat = " , iostat
@@ -1093,9 +1131,9 @@ subroutine log_message( self, message, module, procedure, prefix )
10931131 character (len=* ), intent (in ) :: message
10941132! ! A string to be written to log_unit
10951133 character (len=* ), intent (in ), optional :: module
1096- ! ! The name of the module contining the current invocation of `log_message`
1134+ ! ! The name of the module containing the current invocation of `log_message`
10971135 character (len=* ), intent (in ), optional :: procedure
1098- ! ! The name of the procedure contining the current invocation of `log_message`
1136+ ! ! The name of the procedure containing the current invocation of `log_message`
10991137 character (len=* ), intent (in ), optional :: prefix
11001138! ! To be prepended to message as `prefix // ': ' // message`.
11011139
@@ -1239,6 +1277,8 @@ subroutine log_text_error( self, line, column, summary, filename, &
12391277 character (* ), parameter :: procedure_name = ' LOG_TEXT_ERROR'
12401278 character (len= :), allocatable :: buffer
12411279
1280+ if ( self % level > text_error_level ) return
1281+
12421282 acaret = optval(caret, ' ^' )
12431283
12441284 if ( column < 0 .or. column > len ( line ) + 1 ) then
@@ -1428,9 +1468,11 @@ subroutine log_warning( self, message, module, procedure )
14281468 character (len=* ), intent (in ) :: message
14291469! ! A string to be written to LOG_UNIT
14301470 character (len=* ), intent (in ), optional :: module
1431- ! ! The name of the module contining the current invocation of `log_warning`
1471+ ! ! The name of the module containing the current invocation of `log_warning`
14321472 character (len=* ), intent (in ), optional :: procedure
1433- ! ! The name of the procedure contining the current invocation of `log_warning`
1473+ ! ! The name of the procedure containing the current invocation of `log_warning`
1474+
1475+ if ( self % level > warning_level ) return
14341476
14351477 call self % log_message( message, &
14361478 module = module , &
0 commit comments