diff --git a/doc/specs/stdlib_logger.md b/doc/specs/stdlib_logger.md
index 9677b48ad..60a823406 100644
--- a/doc/specs/stdlib_logger.md
+++ b/doc/specs/stdlib_logger.md
@@ -8,19 +8,20 @@ title: logger
 ## Introduction
 
 This module defines a derived type, its methods, a variable, and
-constants to be used for the reporting of errors and other
-information. The derived type, `logger_type`, is to be used to define
-both global and local logger variables. The `logger_type` methods serve
-to configure the loggers and use the logger variables to report
-messages to a variable specific list of I/O units termed
-`log_units`. The variable, `global_logger`, of type `logger_type`, is
-intended to serve as the default global logger. The constants serve as
-error flags returned by the optional integer `stat` argument.
+constants to be used for the reporting of errors, displaying messages,
+and other information. The derived type, `logger_type`, is to be used
+to define both global and local logger variables. The `logger_type`
+methods serve to configure the loggers and use the logger variables to
+report messages to a variable specific list of I/O units termed
+`log_units`. The variable, `global_logger`, of type `logger_type`,
+is intended to serve as the default global logger. The constants serve
+as error flags returned by the optional integer `stat` argument.
 
 The logger variables have the option to:
 
 * change which units receive the log messages;
 * report which units receive the log messages;
+* select which types of messages are logged;
 * precede messages by a blank line;
 * precede messages by a time stamp of the form
   `yyyy-mm-dd hh:mm:ss.sss`;
@@ -64,6 +65,18 @@ Error Code             | Description
 `unopened_in_error`    | the unit was not opened
 `write_fault`          | one of the writes to `log_units` failed
 
+The module also defines eight distinct public integer constants for
+selecting the messages that are logged. These constants, termed
+severity levels, are (sorted following their increasing order of
+severity): `all_level`, `debug_level`, `information_level`,
+`warning_level`, `error_level`, `io_error_level`, `text_error_level`,
+and `none_level`.
+All log messages with a level (e.g., `debug_level`) lower than a
+specified severity level (e.g., `information_level`) will be ignored.
+The levels `error_level` and `io_error_level` have the same severity.
+The default severity level is `information_level`.
+
+
 ## The derived type: logger_type
 
 ### Status
@@ -81,14 +94,15 @@ significant events encountered during the execution of a program.
 
 ### Private attributes
 
-| Attribute        | Type          | Description                                     | Initial value |
-|------------------|---------------|-------------------------------------------------|--------------|
-| `add_blank_line` | Logical       | Flag to precede output with a blank line        | `.false.`    |
-| `indent_lines`   | Logical       | Flag to indent subsequent lines by four columns | `.true.`     |
-| `log_units`      | Integer array | List of I/O units used for output               | Unallocated  |
-| `max_width`      | Integer       | Maximum column width of output                  | 0            |
-| `time_stamp`     | Logical       | Flag to precede output by a time stamp          | `.true.`     |
-| `units`          | Integer       | Count of the number of active output units      | 0            |
+| Attribute        | Type          | Description                                     | Initial value       |
+|------------------|---------------|-------------------------------------------------|---------------------|
+| `add_blank_line` | Logical       | Flag to precede output with a blank line        | `.false.`           |
+| `indent_lines`   | Logical       | Flag to indent subsequent lines by four columns | `.true.`            |
+| `level`          | Integer       | Severity level                                  | `information_level` |
+| `log_units`      | Integer array | List of I/O units used for output               | Unallocated         |
+| `max_width`      | Integer       | Maximum column width of output                  | 0                   |
+| `time_stamp`     | Logical       | Flag to precede output by a time stamp          | `.true.`            |
+| `units`          | Integer       | Count of the number of active output units      | 0                   |
 
 ## The `stdlib_logger` variable
 
@@ -284,7 +298,7 @@ Reports the configuration of a logger.
 
 #### Syntax
 
-`call self % [[logger_type(type):configuration(bound)]]( [ add_blankline, indent, max_width, time_stamp, log_units ] )`
+`call self % [[logger_type(type):configuration(bound)]]( [ add_blankline, indent, level, max_width, time_stamp, log_units ] )`
 
 #### Class
 
@@ -303,6 +317,10 @@ Pure subroutine
   is an `intent(out)` argument. A value of `.true.` indents subsequent
   lines by four spaces, and `.false.` otherwise.
 
+`level` (optional): shall be a scalar default integer variable. It is an
+  `intent(out)` argument. The value corresponds to the severity level for
+  ignoring a message.
+
 `max_width` (optional): shall be a scalar default integer
   variable. It is an `intent(out)` argument. A positive value bigger
   than four defines the maximum width of the output, otherwise there
@@ -355,7 +373,7 @@ Configures the logging process for self.
 
 #### Syntax
 
-`call self % [[logger_type(type):configure(bound)]]( [ add_blank_line, indent, max_width, time_stamp ] )`
+`call self % [[logger_type(type):configure(bound)]]( [ add_blank_line, indent, level, max_width, time_stamp ] )`
 
 #### Class
 
@@ -375,6 +393,10 @@ Pure subroutine
   indent subsequent lines by four spaces, and to `.false.` to
   not indent.
 
+`level` (optional): shall be a scalar default integer expression. It is
+  an `intent(in)` argument. Set the severity level for ignoring a log
+  message.
+
 `max_width` (optional): shall be a scalar default integer
   expression. It is an `intent(in)` argument. Set to a positive value
   bigger than four to define the maximum width of the output,
@@ -416,6 +438,8 @@ 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: '`.
 
+It is ignored if the `level` of `self` is higher than `debug_level`.
+
 #### Class
 
 Subroutine
@@ -486,6 +510,8 @@ 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.
 
+It is ignored if the `level` of `self` is higher than `error_level`.
+
 #### Class
 
 Subroutine
@@ -569,6 +595,8 @@ 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: '`.
 
+It is ignored if the `level` of `self` is higher than `information_level`.
+
 #### Class
 
 Subroutine
@@ -637,6 +665,8 @@ written. Then `message` is written with the prefix
 `'I/O ERROR: '`. Then if `iostat` or `iomsg` are present they are
 written.
 
+It is ignored if the `level` of `self` is higher than `io_error_level`.
+
 #### Syntax
 
 `call self % [[logger_type(type):log_io_error(bound)]]( message [, module, procedure, iostat, iomsg ] )`
@@ -714,6 +744,8 @@ If time stamps are active, a time stamp is written,
 then `module` and `procedure` are written if present,
 followed by `prefix \\ ': '`, if present, and finally `message`.
 
+No severity level is applied to `log_message`.
+
 #### Syntax
 
 `call self % [[logger_type(type):log_message(bound)]]( message [, module, procedure, prefix ] )`
@@ -790,6 +822,8 @@ written with `column`. Then `line` is written. Then a caret, '^', is
 written below `line` at the column indicated by `column`. Then
 `summary` is written below the caret.
 
+It is ignored if the `level` of `self` is higher than `text_error_level`.
+
 #### Syntax
 
 `call self % [[logger_type(type):log_text_error(bound)]]( line, column, summary [, filename, line_number, caret, stat ] )`
diff --git a/src/stdlib_logger.f90 b/src/stdlib_logger.f90
index c0d02cf4c..70f83b94b 100644
--- a/src/stdlib_logger.f90
+++ b/src/stdlib_logger.f90
@@ -68,6 +68,28 @@ module stdlib_logger
         unopened_in_error = 7,    &
         write_failure = 8
 
+    integer, parameter, public ::      &
+        debug_level = 10,       &
+        information_level = 20, &
+        warning_level = 30,     &
+        error_level = 40,       &
+        io_error_level = 40,    &
+        text_error_level = 50,  &
+        all_level = -10 + min(  &
+            debug_level,        &
+            information_level,  &
+            warning_level,      &
+            error_level,        &
+            io_error_level,     &
+            text_error_level),  &
+        none_level = 10 + max(  &
+            debug_level,        &
+            information_level,  &
+            warning_level,      &
+            error_level,        &
+            io_error_level,     &
+            text_error_level)
+
     character(*), parameter :: module_name = 'stdlib_logger'
 
     type :: logger_type
@@ -78,6 +100,7 @@ module stdlib_logger
 
         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.
@@ -379,7 +402,7 @@ end subroutine validate_unit
     end subroutine add_log_unit
 
 
-    pure subroutine configuration( self, add_blank_line, indent, &
+    pure subroutine configuration( self, add_blank_line, indent, level, &
         max_width, time_stamp, log_units )
 !! version: experimental
 
@@ -389,12 +412,13 @@ pure subroutine configuration( self, add_blank_line, indent, &
 !!    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. `max_width` is the maximum number of columns of output text with
+!! 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.
-!! 4. `time_stamp` is a logical flag with `.true.` implying that the output
+!! 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.
-!! 5. `log_units` is an array of the I/O unit numbers to which log output
+!! 6. `log_units` is an array of the I/O unit numbers to which log output
 !!    will be written.
 !!([Specification](../page/specs/stdlib_logger.html#configuration-report-a-loggers-configuration))
 
@@ -404,6 +428,8 @@ pure subroutine configuration( self, add_blank_line, indent, &
 !! 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
@@ -434,6 +460,7 @@ pure subroutine configuration( self, add_blank_line, indent, &
 
         if ( present(add_blank_line) ) add_blank_line = self % add_blank_line
         if ( present(indent) ) indent = self % indent_lines
+        if ( present(level) ) level = self % level
         if ( present(max_width) ) max_width = self % max_width
         if ( present(time_stamp) ) time_stamp = self % time_stamp
         if ( present(log_units) ) then
@@ -447,7 +474,7 @@ pure subroutine configuration( self, add_blank_line, indent, &
     end subroutine configuration
 
 
-    pure subroutine configure( self, add_blank_line, indent, max_width, &
+    pure subroutine configure( self, add_blank_line, indent, level, max_width, &
         time_stamp )
 !! version: experimental
 
@@ -459,10 +486,11 @@ pure subroutine configure( self, add_blank_line, indent, max_width, &
 !! 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. `max_width` is the maximum number of columns of output text with
+!! 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.
-!! 4. `time_stamp` is a logical flag with `.true.` implying that the output
+!! 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](../page/specs/stdlib_logger.html#configure-configure-the-logging-process))
@@ -477,10 +505,12 @@ pure subroutine configure( self, add_blank_line, indent, max_width, &
         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
 
         if ( present(add_blank_line) ) self % add_blank_line = add_blank_line
+        if ( present(level) ) self % level = level
         if ( present(indent) ) self % indent_lines = indent
         if ( present(max_width) ) then
             if ( max_width <= 4 ) then
@@ -803,11 +833,13 @@ subroutine log_debug( self, message, module, procedure )
         character(len=*), intent(in)            :: message
 !! A string to be written to log_unit
         character(len=*), intent(in), optional  :: module
-!! The name of the module contining the current invocation of `log_information`
+!! The name of the module containing the current invocation of `log_information`
         character(len=*), intent(in), optional  :: procedure
-!! The name of the procedure contining the current invocation of
+!! The name of the procedure containing the current invocation of
 !! `log_information`
 
+        if ( self % level > debug_level ) return
+
         call self % log_message( message,               &
                                  module = module,       &
                                  procedure = procedure, &
@@ -865,9 +897,9 @@ subroutine log_error( self, message, module, procedure, stat, errmsg )
         character(len=*), intent(in)            :: message
 !! A string to be written to log_unit
         character(len=*), intent(in), optional  :: module
-!! The name of the module contining the current invocation of `log_error`
+!! The name of the module containing the current invocation of `log_error`
         character(len=*), intent(in), optional  :: procedure
-!! The name of the procedure contining the current invocation of `log_error`
+!! The name of the procedure containing the current invocation of `log_error`
         integer, intent(in), optional           :: stat
 !! The value of the `stat` specifier returned by a Fortran statement
         character(len=*), intent(in), optional  :: errmsg
@@ -879,6 +911,8 @@ subroutine log_error( self, message, module, procedure, stat, errmsg )
         character(*), parameter :: procedure_name = 'log_error'
         character(:), allocatable :: suffix
 
+        if ( self % level > error_level ) return
+
         if ( present(stat) ) then
             write( dummy, '(a, i0)', err=999, iostat=iostat, iomsg=iomsg ) &
                 new_line('a') // "With stat = ", stat
@@ -954,11 +988,13 @@ subroutine log_information( self, message, module, procedure )
         character(len=*), intent(in)            :: message
 !! A string to be written to log_unit
         character(len=*), intent(in), optional  :: module
-!! The name of the module contining the current invocation of `log_information`
+!! The name of the module containing the current invocation of `log_information`
         character(len=*), intent(in), optional  :: procedure
-!! The name of the procedure contining the current invocation of
+!! The name of the procedure containing the current invocation of
 !! `log_information`
 
+        if ( self % level > information_level ) return
+
         call self % log_message( message,               &
                                  module = module,       &
                                  procedure = procedure, &
@@ -1007,9 +1043,9 @@ subroutine log_io_error( self, message, module, procedure, iostat, &
         character(len=*), intent(in)            :: message
 !! A string to be written to LOG_UNIT
         character(len=*), intent(in), optional  :: module
-!! The name of the module contining the current invocation of REPORT_ERROR
+!! The name of the module containing the current invocation of REPORT_ERROR
         character(len=*), intent(in), optional  :: procedure
-!! The name of the procedure contining the current invocation of REPORT_ERROR
+!! 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
@@ -1021,6 +1057,8 @@ subroutine log_io_error( self, message, module, procedure, iostat, &
         character(*), parameter :: procedure_name = 'log_io_error'
         character(:), allocatable :: suffix
 
+        if ( self % level > io_error_level ) return
+
         if ( present(iostat) ) then
             write( dummy, '(a, i0)', err=999, iostat=iostat2, iomsg=iomsg2 ) &
                 new_line('a') // "With iostat = ", iostat
@@ -1093,9 +1131,9 @@ subroutine log_message( self, message, module, procedure, prefix )
         character(len=*), intent(in)            :: message
 !! A string to be written to log_unit
         character(len=*), intent(in), optional  :: module
-!! The name of the module contining the current invocation of `log_message`
+!! The name of the module containing the current invocation of `log_message`
         character(len=*), intent(in), optional  :: procedure
-!! The name of the procedure contining the current invocation of `log_message`
+!! The name of the procedure containing the current invocation of `log_message`
         character(len=*), intent(in), optional  :: prefix
 !! To be prepended to message as `prefix // ': ' // message`.
 
@@ -1239,6 +1277,8 @@ subroutine log_text_error( self, line, column, summary, filename,  &
         character(*), parameter       :: procedure_name = 'LOG_TEXT_ERROR'
         character(len=:), allocatable :: buffer
 
+        if ( self % level > text_error_level ) return
+
         acaret = optval(caret, '^')
 
         if ( column < 0 .or. column > len( line ) + 1 ) then
@@ -1428,9 +1468,11 @@ subroutine log_warning( self, message, module, procedure )
         character(len=*), intent(in)            :: message
 !! A string to be written to LOG_UNIT
         character(len=*), intent(in), optional  :: module
-!! The name of the module contining the current invocation of `log_warning`
+!! The name of the module containing the current invocation of `log_warning`
         character(len=*), intent(in), optional  :: procedure
-!! The name of the procedure contining the current invocation of `log_warning`
+!! The name of the procedure containing the current invocation of `log_warning`
+
+        if ( self % level > warning_level ) return
 
         call self % log_message( message,               &
                                  module = module,       &
diff --git a/src/tests/logger/test_stdlib_logger.f90 b/src/tests/logger/test_stdlib_logger.f90
index ffb7d9305..649494819 100644
--- a/src/tests/logger/test_stdlib_logger.f90
+++ b/src/tests/logger/test_stdlib_logger.f90
@@ -12,7 +12,7 @@ program test_stdlib_logger
     implicit none
 
     integer, allocatable :: log_units(:)
-    integer              :: max_width, stat
+    integer              :: level, max_width, stat
     integer              :: unit1, unit2, unit3, unit4, unit5, unit6
     logical              :: add_blank_line, exist, indent, time_stamp
 
@@ -71,6 +71,7 @@ program test_stdlib_logger
                                   caret = '^',                              &
                                   stat = stat )
 
+    call test_level()
 
 contains
 
@@ -705,4 +706,138 @@ subroutine test_adding_log_units()
         return
     end subroutine test_adding_log_units
 
+    subroutine test_level()
+
+        print *, 'running test_level'
+
+        call global % configure( level = all_level )
+
+        call global % configuration( level = level )
+        if ( level == all_level ) then
+            write(*,*) 'LEVEL is all_level as expected.'
+
+        else
+            error stop 'LEVEL starts off as not equal to all_level ' //&
+            'contrary to expectations.'
+
+        end if
+
+        call global % log_message('This message should be always printed, &
+             & irrespective of the severity level')
+
+        call global % log_debug( 'This message should be printed')
+        call global % log_information( 'This message should be printed')
+        call global % log_warning( 'This message should be printed')
+        call global % log_error( 'This message should be printed')
+        call global % log_io_error( 'This message should be printed')
+
+        call global % configure( level = debug_level )
+
+        call global % configuration( level = level )
+        if ( level == debug_level ) then
+            write(*,*) 'LEVEL is debug_level as expected.'
+
+        else
+            error stop 'LEVEL starts off as not equal to debug_level ' //&
+            'contrary to expectations.'
+
+        end if
+
+        call global % log_message('This message should be always printed, &
+             & irrespective of the severity level')
+
+        call global % log_debug( 'This message should be printed')
+        call global % log_information( 'This message should be printed')
+        call global % log_warning( 'This message should be printed')
+        call global % log_error( 'This message should be printed')
+        call global % log_io_error( 'This message should be printed')
+
+        call global % configure( level = information_level )
+
+        call global % configuration( level = level )
+        if ( level == information_level ) then
+            write(*,*) 'LEVEL is information_level as expected.'
+
+        else
+            error stop 'LEVEL starts off as not equal to information_level ' //&
+            'contrary to expectations.'
+
+        end if
+
+        call global % log_message('This message should be always printed, &
+             & irrespective of the severity level')
+
+        call global % log_debug( 'This message should NOT be printed')
+        call global % log_information( 'This message should be printed')
+        call global % log_warning( 'This message should be printed')
+        call global % log_error( 'This message should be printed')
+        call global % log_io_error( 'This message should be printed')
+
+        call global % configure( level = warning_level )
+
+        call global % configuration( level = level )
+        if ( level == warning_level ) then
+            write(*,*) 'LEVEL is warning_level as expected.'
+
+        else
+            error stop 'LEVEL starts off as not equal to warning_level ' //&
+            'contrary to expectations.'
+
+        end if
+
+        call global % log_message('This message should be always printed, &
+             & irrespective of the severity level')
+
+        call global % log_debug( 'This message should NOT be printed')
+        call global % log_information( 'This message should NOT be printed')
+        call global % log_warning( 'This message should be printed')
+        call global % log_error( 'This message should be printed')
+        call global % log_io_error( 'This message should be printed')
+
+        call global % configure( level = error_level )
+
+        call global % configuration( level = level )
+        if ( level == error_level ) then
+            write(*,*) 'LEVEL is error_level as expected.'
+
+        else
+            error stop 'LEVEL starts off as not equal to error_level ' //&
+            'contrary to expectations.'
+
+        end if
+
+        call global % log_message('This message should be always printed, &
+             & irrespective of the severity level')
+
+        call global % log_debug( 'This message should NOT be printed')
+        call global % log_information( 'This message should NOT be printed')
+        call global % log_warning( 'This message should NOT be printed')
+        call global % log_error( 'This message should be printed')
+        call global % log_io_error( 'This message should be printed')
+
+        call global % configure( level = none_level )
+
+        call global % configuration( level = level )
+        if ( level == none_level ) then
+            write(*,*) 'LEVEL is none_level as expected.'
+
+        else
+            error stop 'LEVEL starts off as not equal to none_level ' //&
+            'contrary to expectations.'
+
+        end if
+
+        call global % log_message('This message should be always printed, &
+             & irrespective of the severity level')
+
+        call global % log_debug( 'This message should NOT be printed')
+        call global % log_information( 'This message should NOT be printed')
+        call global % log_warning( 'This message should NOT be printed')
+        call global % log_error( 'This message should NOT be printed')
+        call global % log_io_error( 'This message should NOT be printed')
+
+        print *, 'end of test_level'
+
+    end subroutine test_level
+
 end program test_stdlib_logger